module CLog4
    use CIActionReference
    implicit none    
    public    
        interface Log_4
            module procedure :: Log4Log1, Log4Log2, Log4Log3, Log4Log4, Log4Log5
        end interface
                
        procedure (ActionString), pointer :: Log4MsgPtr
        procedure (ActionStringInt), pointer :: Log4MsgIntPtr
        procedure (ActionStringFloat), pointer :: Log4MsgFloatPtr
        procedure (ActionStringDouble), pointer :: Log4MsgDoublePtr
        procedure (ActionStringBool), pointer :: Log4MsgBoolPtr
    contains 
    
    subroutine Log4Log1(message)
        implicit none
        character(len=*), intent(in) :: message
#ifdef Log4
        if(associated(Log4MsgPtr)) call Log4MsgPtr(message)
#endif
    end subroutine
    
    subroutine Log4Log2(message, value)
        implicit none
        character(len=*), intent(in) :: message
        integer, intent(in) :: value
#ifdef Log4
        if(associated(Log4MsgIntPtr)) call Log4MsgIntPtr(message, value)
#endif
    end subroutine
    
    subroutine Log4Log3(message, value)
        implicit none
        character(len=*), intent(in) :: message
        real, intent(in) :: value
#ifdef Log4
        if(associated(Log4MsgFloatPtr)) call Log4MsgFloatPtr(message, value)
#endif
    end subroutine
    
    subroutine Log4Log4(message, value)
        implicit none
        character(len=*), intent(in) :: message
        real(8), intent(in) :: value
#ifdef Log4
        if(associated(Log4MsgDoublePtr)) call Log4MsgDoublePtr(message, value)
#endif
    end subroutine
    
    subroutine Log4Log5(message, value)
        implicit none
        character(len=*), intent(in) :: message
        logical, intent(in) :: value
#ifdef Log4
        if(associated(Log4MsgBoolPtr)) call Log4MsgBoolPtr(message, value)
#endif
    end subroutine
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    subroutine SubscribeLog4Message(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4Message
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4Message' :: SubscribeLog4Message
        implicit none
        procedure (ActionString) :: a
        Log4MsgPtr => a
    end subroutine
    
    subroutine SubscribeLog4MsgInt(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4MsgInt
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4MsgInt' :: SubscribeLog4MsgInt
        implicit none
        procedure (ActionStringInt) :: a
        Log4MsgIntPtr => a
    end subroutine
    
    subroutine SubscribeLog4MsgFloat(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4MsgFloat
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4MsgFloat' :: SubscribeLog4MsgFloat
        implicit none
        procedure (ActionStringFloat) :: a
        Log4MsgFloatPtr => a
    end subroutine
    
    subroutine SubscribeLog4MsgDouble(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4MsgDouble
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4MsgDouble' :: SubscribeLog4MsgDouble
        implicit none
        procedure (ActionStringDouble) :: a
        Log4MsgDoublePtr => a
    end subroutine
    
    subroutine SubscribeLog4MsgBool(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4MsgBool
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4MsgBool' :: SubscribeLog4MsgBool
        implicit none
        procedure (ActionStringBool) :: a
        Log4MsgBoolPtr => a
    end subroutine
    
end module CLog4