module CLog1
    use CIActionReference
    implicit none    
    public    
        interface Log_1
            module procedure :: Log1Log1, Log1Log2, Log1Log3, Log1Log4, Log1Log5
        end interface
                
        procedure (ActionString), pointer :: Log1MsgPtr
        procedure (ActionStringInt), pointer :: Log1MsgIntPtr
        procedure (ActionStringFloat), pointer :: Log1MsgFloatPtr
        procedure (ActionStringDouble), pointer :: Log1MsgDoublePtr
        procedure (ActionStringBool), pointer :: Log1MsgBoolPtr
    contains 
    
    subroutine Log1Log1(message)
        implicit none
        character(len=*), intent(in) :: message
#ifdef Log1
        if(associated(Log1MsgPtr)) call Log1MsgPtr(message)
#endif
    end subroutine
    
    subroutine Log1Log2(message, value)
        implicit none
        character(len=*), intent(in) :: message
        integer, intent(in) :: value
#ifdef Log1
        if(associated(Log1MsgIntPtr)) call Log1MsgIntPtr(message, value)
#endif
    end subroutine
    
    subroutine Log1Log3(message, value)
        implicit none
        character(len=*), intent(in) :: message
        real, intent(in) :: value
#ifdef Log1
        if(associated(Log1MsgFloatPtr)) call Log1MsgFloatPtr(message, value)
#endif
    end subroutine
    
    subroutine Log1Log4(message, value)
        implicit none
        character(len=*), intent(in) :: message
        real(8), intent(in) :: value
#ifdef Log1
        if(associated(Log1MsgDoublePtr)) call Log1MsgDoublePtr(message, value)
#endif
    end subroutine
    
    subroutine Log1Log5(message, value)
        implicit none
        character(len=*), intent(in) :: message
        logical, intent(in) :: value
#ifdef Log1
        if(associated(Log1MsgBoolPtr)) call Log1MsgBoolPtr(message, value)
#endif
    end subroutine
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    subroutine SubscribeLog1Message(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1Message
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1Message' :: SubscribeLog1Message
        implicit none
        procedure (ActionString) :: a
        Log1MsgPtr => a
    end subroutine
    
    subroutine SubscribeLog1MsgInt(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1MsgInt
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1MsgInt' :: SubscribeLog1MsgInt
        implicit none
        procedure (ActionStringInt) :: a
        Log1MsgIntPtr => a
    end subroutine
    
    subroutine SubscribeLog1MsgFloat(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1MsgFloat
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1MsgFloat' :: SubscribeLog1MsgFloat
        implicit none
        procedure (ActionStringFloat) :: a
        Log1MsgFloatPtr => a
    end subroutine
    
    subroutine SubscribeLog1MsgDouble(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1MsgDouble
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1MsgDouble' :: SubscribeLog1MsgDouble
        implicit none
        procedure (ActionStringDouble) :: a
        Log1MsgDoublePtr => a
    end subroutine
    
    subroutine SubscribeLog1MsgBool(a) 
    !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1MsgBool
    !DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1MsgBool' :: SubscribeLog1MsgBool
        implicit none
        procedure (ActionStringBool) :: a
        Log1MsgBoolPtr => a
    end subroutine
    
end module CLog1