module CLog5
    use CIActionReference
    implicit none    
    public    
        interface Log_5
            module procedure :: Log5Log1, Log5Log2, Log5Log3, Log5Log4, Log5Log5
        end interface
                
        procedure (ActionString), pointer :: Log5MsgPtr
        procedure (ActionStringInt), pointer :: Log5MsgIntPtr
        procedure (ActionStringFloat), pointer :: Log5MsgFloatPtr
        procedure (ActionStringDouble), pointer :: Log5MsgDoublePtr
        procedure (ActionStringBool), pointer :: Log5MsgBoolPtr
    contains 
    
    subroutine Log5Log1(message)
        implicit none
        character(len=*), intent(in) :: message
#ifdef Log5
        if(associated(Log5MsgPtr)) call Log5MsgPtr(message)
#endif
    end subroutine
    
    subroutine Log5Log2(message, value)
        implicit none
        character(len=*), intent(in) :: message
        integer, intent(in) :: value
#ifdef Log5
        if(associated(Log5MsgIntPtr)) call Log5MsgIntPtr(message, value)
#endif
    end subroutine
    
    subroutine Log5Log3(message, value)
        implicit none
        character(len=*), intent(in) :: message
        real, intent(in) :: value
#ifdef Log5
        if(associated(Log5MsgFloatPtr)) call Log5MsgFloatPtr(message, value)
#endif
    end subroutine
    
    subroutine Log5Log4(message, value)
        implicit none
        character(len=*), intent(in) :: message
        real(8), intent(in) :: value
#ifdef Log5
        if(associated(Log5MsgDoublePtr)) call Log5MsgDoublePtr(message, value)
#endif
    end subroutine
    
    subroutine Log5Log5(message, value)
        implicit none
        character(len=*), intent(in) :: message
        logical, intent(in) :: value
#ifdef Log5
        if(associated(Log5MsgBoolPtr)) call Log5MsgBoolPtr(message, value)
#endif
    end subroutine
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    subroutine SubscribeLog5Message(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5Message
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5Message' :: SubscribeLog5Message
        implicit none
        procedure (ActionString) :: a
        Log5MsgPtr => a
    end subroutine
    
    subroutine SubscribeLog5MsgInt(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5MsgInt
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5MsgInt' :: SubscribeLog5MsgInt
        implicit none
        procedure (ActionStringInt) :: a
        Log5MsgIntPtr => a
    end subroutine
    
    subroutine SubscribeLog5MsgFloat(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5MsgFloat
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5MsgFloat' :: SubscribeLog5MsgFloat
        implicit none
        procedure (ActionStringFloat) :: a
        Log5MsgFloatPtr => a
    end subroutine
    
    subroutine SubscribeLog5MsgDouble(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5MsgDouble
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5MsgDouble' :: SubscribeLog5MsgDouble
        implicit none
        procedure (ActionStringDouble) :: a
        Log5MsgDoublePtr => a
    end subroutine
    
    subroutine SubscribeLog5MsgBool(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5MsgBool
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5MsgBool' :: SubscribeLog5MsgBool
        implicit none
        procedure (ActionStringBool) :: a
        Log5MsgBoolPtr => a
    end subroutine
    
end module CLog5