module CLog3
    use CIActionReference
    implicit none    
    public    
        interface Log_3
            module procedure :: Log3Log1, Log3Log2, Log3Log3, Log3Log4, Log3Log5
        end interface
                
        procedure (ActionString), pointer :: Log3MsgPtr
        procedure (ActionStringInt), pointer :: Log3MsgIntPtr
        procedure (ActionStringFloat), pointer :: Log3MsgFloatPtr
        procedure (ActionStringDouble), pointer :: Log3MsgDoublePtr
        procedure (ActionStringBool), pointer :: Log3MsgBoolPtr
    contains 
    
    subroutine Log3Log1(message)
        implicit none
        character(len=*), intent(in) :: message
#ifdef Log3
        if(associated(Log3MsgPtr)) call Log3MsgPtr(message)
#endif
    end subroutine
    
    subroutine Log3Log2(message, value)
        implicit none
        character(len=*), intent(in) :: message
        integer, intent(in) :: value
#ifdef Log3
        if(associated(Log3MsgIntPtr)) call Log3MsgIntPtr(message, value)
#endif
    end subroutine
    
    subroutine Log3Log3(message, value)
        implicit none
        character(len=*), intent(in) :: message
        real, intent(in) :: value
#ifdef Log3
        if(associated(Log3MsgFloatPtr)) call Log3MsgFloatPtr(message, value)
#endif
    end subroutine
    
    subroutine Log3Log4(message, value)
        implicit none
        character(len=*), intent(in) :: message
        real(8), intent(in) :: value
#ifdef Log3
        if(associated(Log3MsgDoublePtr)) call Log3MsgDoublePtr(message, value)
#endif
    end subroutine
    
    subroutine Log3Log5(message, value)
        implicit none
        character(len=*), intent(in) :: message
        logical, intent(in) :: value
#ifdef Log3
        if(associated(Log3MsgBoolPtr)) call Log3MsgBoolPtr(message, value)
#endif
    end subroutine
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    subroutine SubscribeLog3Message(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3Message
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3Message' :: SubscribeLog3Message
        implicit none
        procedure (ActionString) :: a
        Log3MsgPtr => a
    end subroutine
    
    subroutine SubscribeLog3MsgInt(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3MsgInt
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3MsgInt' :: SubscribeLog3MsgInt
        implicit none
        procedure (ActionStringInt) :: a
        Log3MsgIntPtr => a
    end subroutine
    
    subroutine SubscribeLog3MsgFloat(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3MsgFloat
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3MsgFloat' :: SubscribeLog3MsgFloat
        implicit none
        procedure (ActionStringFloat) :: a
        Log3MsgFloatPtr => a
    end subroutine
    
    subroutine SubscribeLog3MsgDouble(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3MsgDouble
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3MsgDouble' :: SubscribeLog3MsgDouble
        implicit none
        procedure (ActionStringDouble) :: a
        Log3MsgDoublePtr => a
    end subroutine
    
    subroutine SubscribeLog3MsgBool(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3MsgBool
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3MsgBool' :: SubscribeLog3MsgBool
        implicit none
        procedure (ActionStringBool) :: a
        Log3MsgBoolPtr => a
    end subroutine
    
end module CLog3