|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632 |
- module CUnityInputs
- use CVoidEventHandlerCollection
- implicit none
-
- logical :: ElevatorConnectionPossible
- logical :: JointConnectionPossible
- logical :: IsKellyBushingSetInTable
- logical :: ElevatorPickup
- logical :: NearFloorPosition
- logical :: SingleSetInMouseHole
- !logical :: SwingCenter
- !logical :: MakeupTong
- !logical :: BreakupTong
- !logical :: SlipsSet
- !logical :: SlipsUnSet
- !logical :: Latch
- !logical :: Unlatch
- !logical :: OutOfMouseHole
- !real(8) :: NewHookHeight
- logical :: TdsConnectionPossible
- logical :: TdsStemIn
-
-
- private :: ElevatorConnectionPossible
- private :: JointConnectionPossible
- private :: IsKellyBushingSetInTable
- private :: ElevatorPickup
- private :: NearFloorPosition
- private :: singleSetInMouseHole
- !private :: SwingCenter
- !private :: MakeupTong
- !private :: BreakupTong
- !private :: SlipsSet
- !private :: SlipsUnSet
- !private :: Latch
- !private :: Unlatch
- !private :: OutOfMouseHole
- !private :: NewHookHeight
- private :: TdsConnectionPossible
- private :: TdsStemIn
-
- public
-
- type(VoidEventHandlerCollection) :: OnElevatorConnectionPossibleChange
- type(VoidEventHandlerCollection) :: OnJointConnectionPossibleChange
- type(VoidEventHandlerCollection) :: OnIsKellyBushingSetInTableChange
- type(VoidEventHandlerCollection) :: OnElevatorPickupChange
- type(VoidEventHandlerCollection) :: OnNearFloorPositionChange
- type(VoidEventHandlerCollection) :: OnSingleSetInMouseHoleChange
- !type(VoidEventHandlerCollection) :: OnSwingCenterChange
- !type(VoidEventHandlerCollection) :: OnNewHookHeightChange
-
- !type(VoidEventHandlerCollection) :: OnMakeupTongChange
- !type(VoidEventHandlerCollection) :: OnBreakupTongChange
- !type(VoidEventHandlerCollection) :: OnSlipsSetChange
- !type(VoidEventHandlerCollection) :: OnSlipsUnSetChange
- !type(VoidEventHandlerCollection) :: OnLatchChange
- !type(VoidEventHandlerCollection) :: OnUnlatchChange
- !type(VoidEventHandlerCollection) :: OnOutOfMouseHoleChange
-
- type(VoidEventHandlerCollection) :: OnTdsConnectionPossibleChange
- type(VoidEventHandlerCollection) :: OnTdsStemInChange
-
- contains
-
- ! Input routines
-
-
- subroutine Set_OutOfMouseHole(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_OutOfMouseHole
- !DEC$ ATTRIBUTES ALIAS: 'Set_OutOfMouseHole' :: Set_OutOfMouseHole
- implicit none
- logical, intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(OutOfMouseHole == v) return
- !#endif
- ! OutOfMouseHole = v
- ! call OnOutOfMouseHoleChange%RunAll()
- !#ifdef deb
- ! print*, 'OutOfMouseHole=', OutOfMouseHole
- !#endif
- end subroutine
-
- !logical function Get_OutOfMouseHole()
- ! implicit none
- ! Get_OutOfMouseHole = OutOfMouseHole
- !end function
-
-
-
-
-
-
-
-
-
-
-
-
- subroutine Set_Unlatch(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_Unlatch
- !DEC$ ATTRIBUTES ALIAS: 'Set_Unlatch' :: Set_Unlatch
- implicit none
- logical, intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(Unlatch == v) return
- !#endif
- ! Unlatch = v
- ! call OnUnlatchChange%RunAll()
- !#ifdef deb
- ! print*, 'Unlatch=', Unlatch
- !#endif
- end subroutine
-
- !logical function Get_Unlatch()
- ! implicit none
- ! Get_Unlatch = Unlatch
- !end function
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- subroutine Set_Latch(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_Latch
- !DEC$ ATTRIBUTES ALIAS: 'Set_Latch' :: Set_Latch
- implicit none
- logical, intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(Latch == v) return
- !#endif
- ! Latch = v
- ! call OnLatchChange%RunAll()
- !#ifdef deb
- ! print*, 'Latch=', Latch
- !#endif
- end subroutine
-
- !logical function Get_Latch()
- ! implicit none
- ! Get_Latch = Latch
- !end function
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- subroutine Set_SlipsUnSet(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_SlipsUnSet
- !DEC$ ATTRIBUTES ALIAS: 'Set_SlipsUnSet' :: Set_SlipsUnSet
- implicit none
- logical, intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(SlipsUnSet == v) return
- !#endif
- ! SlipsUnSet = v
- ! call OnSlipsUnSetChange%RunAll()
- !#ifdef deb
- ! print*, 'SlipsUnSet=', SlipsUnSet
- !#endif
- end subroutine
-
- !logical function Get_SlipsUnSet()
- ! implicit none
- ! Get_SlipsUnSet = SlipsUnSet
- !end function
-
-
-
-
-
-
-
-
-
-
-
-
-
- subroutine Set_SlipsSet(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_SlipsSet
- !DEC$ ATTRIBUTES ALIAS: 'Set_SlipsSet' :: Set_SlipsSet
- implicit none
- logical, intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(SlipsSet == v) return
- !#endif
- ! SlipsSet = v
- ! call OnSlipsSetChange%RunAll()
- !#ifdef deb
- ! print*, 'SlipsSet=', SlipsSet
- !#endif
- end subroutine
-
- !logical function Get_SlipsSet()
- ! implicit none
- ! Get_SlipsSet = SlipsSet
- !end function
-
-
-
-
-
-
-
-
-
-
-
- subroutine Set_BreakupTong(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_BreakupTong
- !DEC$ ATTRIBUTES ALIAS: 'Set_BreakupTong' :: Set_BreakupTong
- implicit none
- logical, intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(BreakupTong == v) return
- !#endif
- ! BreakupTong = v
- ! call OnBreakupTongChange%RunAll()
- !#ifdef deb
- ! print*, 'BreakupTong=', BreakupTong
- !#endif
- end subroutine
-
- !logical function Get_BreakupTong()
- ! implicit none
- ! Get_BreakupTong = BreakupTong
- !end function
-
-
-
-
-
-
-
-
-
- subroutine Set_MakeupTong(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_MakeupTong
- !DEC$ ATTRIBUTES ALIAS: 'Set_MakeupTong' :: Set_MakeupTong
- implicit none
- logical, intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(MakeupTong == v) return
- !#endif
- ! MakeupTong = v
- ! call OnMakeupTongChange%RunAll()
- !#ifdef deb
- ! print*, 'MakeupTong=', MakeupTong
- !#endif
- end subroutine
-
- !logical function Get_MakeupTong()
- ! implicit none
- ! Get_MakeupTong = MakeupTong
- !end function
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- subroutine Set_NewHookHeight(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_NewHookHeight
- !DEC$ ATTRIBUTES ALIAS: 'Set_NewHookHeight' :: Set_NewHookHeight
- implicit none
- real(8), intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(NewHookHeight == v) return
- !#endif
- ! NewHookHeight = v
- ! call OnNewHookHeightChange%RunAll()
- !#ifdef deb
- ! print*, 'NewHookHeight=', NewHookHeight
- !#endif
- end subroutine
-
- !real(8) function Get_NewHookHeight()
- ! implicit none
- ! Get_NewHookHeight = NewHookHeight
- !end function
-
-
-
-
-
-
-
-
-
- subroutine Set_ElevatorConnectionPossible(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_ElevatorConnectionPossible
- !DEC$ ATTRIBUTES ALIAS: 'Set_ElevatorConnectionPossible' :: Set_ElevatorConnectionPossible
- implicit none
- logical, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(ElevatorConnectionPossible == v) return
- #endif
- ElevatorConnectionPossible = v
- call OnElevatorConnectionPossibleChange%RunAll()
- #ifdef deb
- print*, 'ElevatorConnectionPossible=', ElevatorConnectionPossible
- #endif
- end subroutine
-
- logical function Get_ElevatorConnectionPossible()
- implicit none
- Get_ElevatorConnectionPossible = ElevatorConnectionPossible
- end function
-
- logical function Get_ElevatorConnectionPossible_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_ElevatorConnectionPossible_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_ElevatorConnectionPossible_WN' :: Get_ElevatorConnectionPossible_WN
- implicit none
- Get_ElevatorConnectionPossible_WN = ElevatorConnectionPossible
- !Get_ElevatorConnectionPossible_WN = .true.
- end function
-
-
-
-
-
-
-
-
- subroutine Set_JointConnectionPossible(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_JointConnectionPossible
- !DEC$ ATTRIBUTES ALIAS: 'Set_JointConnectionPossible' :: Set_JointConnectionPossible
- implicit none
- logical, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(JointConnectionPossible == v) return
- #endif
- JointConnectionPossible = v
- call OnJointConnectionPossibleChange%RunAll()
- #ifdef deb
- print*, 'JointConnectionPossible=', JointConnectionPossible
- #endif
- end subroutine
-
- logical function Get_JointConnectionPossible()
- implicit none
- Get_JointConnectionPossible = JointConnectionPossible
- end function
-
-
- logical function Get_JointConnectionPossible_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_JointConnectionPossible_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_JointConnectionPossible_WN' :: Get_JointConnectionPossible_WN
- implicit none
- Get_JointConnectionPossible_WN = JointConnectionPossible
- end function
-
-
-
-
-
- subroutine Set_IsKellyBushingSetInTable(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_IsKellyBushingSetInTable
- !DEC$ ATTRIBUTES ALIAS: 'Set_IsKellyBushingSetInTable' :: Set_IsKellyBushingSetInTable
- implicit none
- logical, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(IsKellyBushingSetInTable == v) return
- #endif
- IsKellyBushingSetInTable = v
- call OnIsKellyBushingSetInTableChange%RunAll()
- #ifdef deb
- print*, 'IsKellyBushingSetInTable=', IsKellyBushingSetInTable
- #endif
- end subroutine
-
- logical function Get_IsKellyBushingSetInTable()
- implicit none
- Get_IsKellyBushingSetInTable = IsKellyBushingSetInTable
- end function
-
- logical function Get_IsKellyBushingSetInTable_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_IsKellyBushingSetInTable_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_IsKellyBushingSetInTable_WN' :: Get_IsKellyBushingSetInTable_WN
- implicit none
- Get_IsKellyBushingSetInTable_WN = IsKellyBushingSetInTable
- end function
-
-
-
-
-
-
-
- subroutine Set_ElevatorPickup(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_ElevatorPickup
- !DEC$ ATTRIBUTES ALIAS: 'Set_ElevatorPickup' :: Set_ElevatorPickup
- implicit none
- logical, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(ElevatorPickup == v) return
- #endif
- ElevatorPickup = v
- call OnElevatorPickupChange%RunAll()
- #ifdef deb
- print*, 'ElevatorPickup =', ElevatorPickup
- #endif
- end subroutine
-
- logical function Get_ElevatorPickup()
- implicit none
- Get_ElevatorPickup = ElevatorPickup
- end function
-
-
- logical function Get_ElevatorPickup_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_ElevatorPickup_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_ElevatorPickup_WN' :: Get_ElevatorPickup_WN
- implicit none
- Get_ElevatorPickup_WN = ElevatorPickup
- end function
-
-
-
-
-
-
-
- subroutine Set_NearFloorPosition(v)
- implicit none
- logical, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(NearFloorPosition == v) return
- #endif
- NearFloorPosition = v
- call OnNearFloorPositionChange%RunAll()
- #ifdef deb
- print*, 'NearFloorPosition =', NearFloorPosition
- #endif
- end subroutine
-
- subroutine Set_NearFloorPosition_WN(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_NearFloorPosition_WN
- !DEC$ ATTRIBUTES ALIAS: 'Set_NearFloorPosition_WN' :: Set_NearFloorPosition_WN
- implicit none
- logical, intent(in) :: v
- call Set_NearFloorPosition(v)
- end subroutine
-
- logical function Get_NearFloorPosition()
- implicit none
- Get_NearFloorPosition = NearFloorPosition
- end function
-
-
- logical function Get_NearFloorPosition_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_NearFloorPosition_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_NearFloorPosition_WN' :: Get_NearFloorPosition_WN
- implicit none
- Get_NearFloorPosition_WN = NearFloorPosition
- end function
-
-
-
-
-
-
-
-
-
- subroutine Set_SingleSetInMouseHole(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_SingleSetInMouseHole
- !DEC$ ATTRIBUTES ALIAS: 'Set_SingleSetInMouseHole' :: Set_SingleSetInMouseHole
- implicit none
- logical, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(SingleSetInMouseHole == v) return
- #endif
- SingleSetInMouseHole = v
- call OnSingleSetInMouseHoleChange%RunAll()
- #ifdef deb
- print*, 'singleSetInMouseHole=', SingleSetInMouseHole
- #endif
- end subroutine
-
- logical function Get_SingleSetInMouseHole()
- implicit none
- Get_SingleSetInMouseHole = SingleSetInMouseHole
- end function
-
-
- logical function Get_SingleSetInMouseHole_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_SingleSetInMouseHole_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_SingleSetInMouseHole_WN' :: Get_SingleSetInMouseHole_WN
- implicit none
- Get_SingleSetInMouseHole_WN = SingleSetInMouseHole
- end function
-
-
-
-
-
-
-
-
- subroutine Set_SwingCenter(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_SwingCenter
- !DEC$ ATTRIBUTES ALIAS: 'Set_SwingCenter' :: Set_SwingCenter
- !USE CSwingEnum
- implicit none
- logical, intent(in) :: v
- !#ifdef ExcludeExtraChanges
- ! if(SwingCenter == v) return
- !#endif
- ! SwingCenter = v
- ! call OnSwingCenterChange%RunAll()
- ! !if(SwingCenter .and. Get_Swing() /= SWING_WELL ) call Set_Swing(SWING_WELL)
- !#ifdef deb
- ! print*, 'SwingCenter=', SwingCenter
- !#endif
- end subroutine
-
- !logical function Get_SwingCenter()
- ! implicit none
- ! Get_SwingCenter = SwingCenter
- !end function
-
-
-
-
-
-
-
-
-
-
-
-
- !top drive
- subroutine Set_TdsConnectionPossible(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_TdsConnectionPossible
- !DEC$ ATTRIBUTES ALIAS: 'Set_TdsConnectionPossible' :: Set_TdsConnectionPossible
- implicit none
- logical, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(TdsConnectionPossible == v) return
- #endif
- TdsConnectionPossible = v
- call OnTdsConnectionPossibleChange%RunAll()
- #ifdef deb
- print*, 'TdsConnectionPossible=', TdsConnectionPossible
- #endif
- end subroutine
-
- logical function Get_TdsConnectionPossible()
- implicit none
- Get_TdsConnectionPossible = TdsConnectionPossible
- end function
-
- logical function Get_TdsConnectionPossible_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_TdsConnectionPossible_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_TdsConnectionPossible_WN' :: Get_TdsConnectionPossible_WN
- implicit none
- Get_TdsConnectionPossible_WN = TdsConnectionPossible
- !Get_TdsConnectionPossible_WN = .true.
- end function
-
-
-
- subroutine Set_TdsStemIn(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: Set_TdsStemIn
- !DEC$ ATTRIBUTES ALIAS: 'Set_TdsStemIn' :: Set_TdsStemIn
- implicit none
- logical, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(TdsStemIn == v) return
- #endif
- TdsStemIn = v
- call OnTdsStemInChange%RunAll()
- #ifdef deb
- print*, 'TdsStemIn=', TdsStemIn
- #endif
- end subroutine
-
- logical function Get_TdsStemIn()
- implicit none
- Get_TdsStemIn = TdsStemIn
- end function
-
- logical function Get_TdsStemIn_WN()
- !DEC$ ATTRIBUTES DLLEXPORT :: Get_TdsStemIn_WN
- !DEC$ ATTRIBUTES ALIAS: 'Get_TdsStemIn_WN' :: Get_TdsStemIn_WN
- implicit none
- Get_TdsStemIn_WN = TdsStemIn
- !Get_TdsStemIn_WN = .true.
- end function
-
-
-
-
- end module CUnityInputs
|