|
- module CSlipsEnumVariables
- use CVoidEventHandlerCollection
- implicit none
- integer :: Slips = 0
- integer :: Slips_S = 0
-
- public
-
- type(VoidEventHandlerCollection) :: OnSlipsChange
-
- enum, bind(c)
- enumerator SLIPS_NEUTRAL
- enumerator SLIPS_SET_BEGIN
- enumerator SLIPS_SET_END
- enumerator SLIPS_UNSET_BEGIN
- enumerator SLIPS_UNSET_END
- end enum
-
- private :: Slips
-
- contains
-
- subroutine Set_Slips(v)
- implicit none
- integer , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(Slips == v) return
- #endif
- Slips = v
- #ifdef deb
- print*, 'Slips=', Slips
- #endif
- call OnSlipsChange%RunAll()
- end subroutine
-
- integer function Get_Slips()
- implicit none
- Get_Slips = Slips
- end function
-
-
-
- subroutine Set_Slips_WN(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_Slips_WN
- !DEC$ ATTRIBUTES ALIAS: 'Set_Slips_WN' :: Set_Slips_WN
- implicit none
- integer , intent(in) :: v
- !call Set_Slips(v)
- Slips_S = v
- end subroutine
-
- integer function Get_Slips_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_Slips_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_Slips_WN' :: Get_Slips_WN
- implicit none
- Get_Slips_WN = Slips
- end function
-
-
-
- subroutine SlipsSetEnd()
- !DEC$ ATTRIBUTES DLLEXPORT :: SlipsSetEnd
- !DEC$ ATTRIBUTES ALIAS: 'SlipsSetEnd' :: SlipsSetEnd
- implicit none
- !if(Slips /= SLIPS_SET_END) Slips = SLIPS_SET_END
- call Set_Slips(SLIPS_SET_END)
- #ifdef deb
- print*, 'SlipsSetEnd'
- #endif
- end subroutine
-
- subroutine SlipsUnsetEnd()
- !DEC$ ATTRIBUTES DLLEXPORT :: SlipsUnsetEnd
- !DEC$ ATTRIBUTES ALIAS: 'SlipsUnsetEnd' :: SlipsUnsetEnd
- implicit none
- !if(Slips /= SLIPS_UNSET_END) Slips = SLIPS_UNSET_END
- call Set_Slips(SLIPS_UNSET_END)
- #ifdef deb
- print*, 'SlipsUnsetEnd'
- #endif
- end subroutine
-
-
-
-
-
-
-
-
-
-
-
-
- logical function Get_SlipsUnset()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_SlipsUnset
- !DEC$ ATTRIBUTES ALIAS: 'Get_SlipsUnset' :: Get_SlipsUnset
- implicit none
- Get_SlipsUnset = .false. ! Slips == SLIPS_UNSET
- end function
-
- logical function Get_SlipsSet()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_SlipsSet
- !DEC$ ATTRIBUTES ALIAS: 'Get_SlipsSet' :: Get_SlipsSet
- implicit none
- Get_SlipsSet = .false. ! Slips == SLIPS_SET
- end function
-
- end module CSlipsEnumVariables
|