|
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768 |
- module CKellyConnectionEnumVariables
- use CVoidEventHandlerCollection
- implicit none
- type::KellyConnectionEnumType
- integer :: KellyConnection = 0
- type(VoidEventHandlerCollection) :: OnKellyConnectionChange
- end type KellyConnectionEnumType
- type(KellyConnectionEnumType)::KellyConnectionEnum
- ! public
-
-
- enum, bind(c)
- enumerator KELLY_CONNECTION_NOTHING
- enumerator KELLY_CONNECTION_STRING
- enumerator KELLY_CONNECTION_SINGLE
- end enum
-
- ! private :: OperationScenario%KellyConnection
- contains
-
- subroutine Set_KellyConnection(v)
- use CManifolds, Only: KellyConnected, KellyDisconnected
- implicit none
- integer , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(KellyConnectionEnum%KellyConnection == v) return
- #endif
-
- KellyConnectionEnum%KellyConnection = v
-
- if(KellyConnectionEnum%KellyConnection /= KELLY_CONNECTION_STRING) then
- call KellyDisconnected()
- else
- call KellyConnected()
- endif
-
- #ifdef deb
- print*, 'KellyConnectionEnum%KellyConnection=', KellyConnectionEnum%KellyConnection
- #endif
- call KellyConnectionEnum%OnKellyConnectionChange%RunAll()
- end subroutine
-
- integer function Get_KellyConnection()
- implicit none
- Get_KellyConnection = KellyConnectionEnum%KellyConnection
- end function
-
-
-
-
-
-
- ! subroutine Set_KellyConnection_WN(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: Set_KellyConnection_WN
- ! !DEC$ ATTRIBUTES ALIAS: 'Set_KellyConnection_WN' :: Set_KellyConnection_WN
- ! implicit none
- ! integer , intent(in) :: v
- ! call Set_KellyConnection(v)
- ! end subroutine
-
- ! integer function Get_KellyConnection_WN()
- ! !DEC$ ATTRIBUTES DLLEXPORT :: Get_KellyConnection_WN
- ! !DEC$ ATTRIBUTES ALIAS: 'Get_KellyConnection_WN' :: Get_KellyConnection_WN
- ! implicit none
- ! Get_KellyConnection_WN = OperationScenario%KellyConnection
- ! end function
-
- end module CKellyConnectionEnumVariables
|