|
- module SoftwareInputsVariables
- ! use CVoidEventHandlerCollection
- type:: SoftwareInputsType
- real :: HookHeight = 0
- ! type(VoidEventHandlerCollection) :: OnHookHeightChange
- real :: IbopHeight = 0
- ! type(VoidEventHandlerCollection) :: OnIbopHeightChange
- real :: NearFloorConnection = 0
- ! type(VoidEventHandlerCollection) :: OnNearFloorConnectionChange
- real :: SafetyValveHeight = 0
- ! type(VoidEventHandlerCollection) :: OnSafetyValveHeightChange
- logical :: SlackOff = .false.
- ! type(VoidEventHandlerCollection) :: OnSlackOffChange
- integer :: StandRack = 0
- ! type(VoidEventHandlerCollection) :: OnStandRackChanged
- real :: StringPressure = 0
- ! type(VoidEventHandlerCollection) :: OnStringPressureChange
- real :: TdsStemJointHeight = 0
- ! type(VoidEventHandlerCollection) :: OnTdsStemJointHeightChange
- logical :: ZeroStringSpeed = .false.
- ! type(VoidEventHandlerCollection) :: OnZeroStringSpeedChange
- end type SoftwareInputsType
- type(SoftwareInputsType):: softwareInputs
-
- contains
-
- subroutine Set_ZeroStringSpeed(v)
- implicit none
- logical , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%ZeroStringSpeed == v) return
- #endif
- softwareInputs%ZeroStringSpeed = v
- #ifdef deb
- print*, 'ZeroStringSpeed=', softwareInputs%ZeroStringSpeed
- #endif
- ! call softwareInputs%OnZeroStringSpeedChange%RunAll()
- end subroutine
-
- logical function Get_ZeroStringSpeed()
- implicit none
- Get_ZeroStringSpeed = softwareInputs%ZeroStringSpeed
- !Get_ZeroStringSpeed = .true.
- end function
-
- subroutine Set_TdsStemJointHeight(v)
- implicit none
- real , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%TdsStemJointHeight == v) return
- #endif
- softwareInputs%TdsStemJointHeight = v
- #ifdef deb
- print*, 'TdsStemJointHeight=', softwareInputs%TdsStemJointHeight
- #endif
- ! call softwareInputs%OnTdsStemJointHeightChange%RunAll()
- end subroutine
-
- real function Get_TdsStemJointHeight()
- implicit none
- Get_TdsStemJointHeight = softwareInputs%TdsStemJointHeight
- end function
-
-
- subroutine Set_StringPressure(v)
- implicit none
- real , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%StringPressure == v) return
- #endif
- softwareInputs%StringPressure = v
- #ifdef deb
- print*, 'StringPressure=', softwareInputs%StringPressure
- #endif
- ! call softwareInputs%OnStringPressureChange%RunAll()
- end subroutine
-
- real function Get_StringPressure()
- implicit none
- Get_StringPressure = softwareInputs%StringPressure
- end function
-
- subroutine Set_StandRack(v)
- implicit none
- integer , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%StandRack == v) return
- #endif
- softwareInputs%StandRack = v
- #ifdef deb
- print*, 'StandRack=', softwareInputs%StandRack
- #endif
- ! call softwareInputs%OnStandRackChanged%RunAll()
- end subroutine
-
- integer function Get_StandRack()
- implicit none
- Get_StandRack = softwareInputs%StandRack
- end function
-
- subroutine Set_SlackOff(v)
- implicit none
- logical , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%SlackOff == v) return
- #endif
- softwareInputs%SlackOff = v
- #ifdef deb
- print*, 'SlackOff=', softwareInputs%SlackOff
- #endif
- ! call softwareInputs%OnSlackOffChange%RunAll()
- end subroutine
-
- logical function Get_SlackOff()
- implicit none
- Get_SlackOff = softwareInputs%SlackOff
- end function
-
- subroutine Set_SafetyValveHeight(v)
- implicit none
- real , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%SafetyValveHeight == v) return
- #endif
- softwareInputs%SafetyValveHeight = v
- #ifdef deb
- print*, 'SafetyValveHeight=', softwareInputs%SafetyValveHeight
- #endif
- ! call softwareInputs%OnSafetyValveHeightChange%RunAll()
- end subroutine
-
- real function Get_SafetyValveHeight()
- implicit none
- Get_SafetyValveHeight = softwareInputs%SafetyValveHeight
- !Get_SafetyValveHeight = 23
- end function
-
-
- subroutine Set_NearFloorConnection(v)
- implicit none
- real , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%NearFloorConnection == v) return
- #endif
- softwareInputs%NearFloorConnection = v
- #ifdef deb
- print*, 'NearFloorConnection=', softwareInputs%NearFloorConnection
- #endif
- ! call softwareInputs%OnNearFloorConnectionChange%RunAll()
- end subroutine
-
- real function Get_NearFloorConnection()
- implicit none
- Get_NearFloorConnection = softwareInputs%NearFloorConnection
- !Get_NearFloorConnection = 4
- end function
-
- subroutine Set_IbopHeight(v)
- implicit none
- real , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%IbopHeight == v) return
- #endif
- softwareInputs%IbopHeight = v
- #ifdef deb
- print*, 'IbopHeight=', softwareInputs%IbopHeight
- #endif
- ! call softwareInputs%OnIbopHeightChange%RunAll()
- end subroutine
-
- real function Get_IbopHeight()
- implicit none
- Get_IbopHeight = softwareInputs%IbopHeight
- !Get_IbopHeight = 23.0
- end function
-
- subroutine Set_HookHeight(v)
- implicit none
- real , intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(softwareInputs%HookHeight == v) return
- #endif
- softwareInputs%HookHeight = v
- #ifdef deb
- print*, 'HookHeight=', softwareInputs%HookHeight
- #endif
- ! call softwareInputs%OnHookHeightChange%RunAll()
- end subroutine
-
- real function Get_HookHeight()
- implicit none
- Get_HookHeight = softwareInputs%HookHeight
- end function
-
- end module
|