|
- module CDrillingConsole
- use CDrillingConsoleVariables
- use CSimulationVariables
- use CLog4
- use CLog3
- implicit none
- public
- contains
-
- ! Input routines
- subroutine SetAssignmentSwitch(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetAssignmentSwitch
- !DEC$ ATTRIBUTES ALIAS: 'SetAssignmentSwitch' :: SetAssignmentSwitch
- implicit none
- integer, intent(in) :: v
- AssignmentSwitch = v
- #ifdef deb
- call Log_4( 'AssignmentSwitch=', AssignmentSwitch)
- #endif
- end subroutine
-
- subroutine SetEmergencySwitch(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetEmergencySwitch
- !DEC$ ATTRIBUTES ALIAS: 'SetEmergencySwitch' :: SetEmergencySwitch
- implicit none
- logical, intent(in) :: v
- EmergencySwitch = v
- #ifdef deb
- print*, 'EmergencySwitch=', EmergencySwitch
- #endif
- end subroutine
-
- subroutine SetRTTorqueLimitKnob(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetRTTorqueLimitKnob
- !DEC$ ATTRIBUTES ALIAS: 'SetRTTorqueLimitKnob' :: SetRTTorqueLimitKnob
- implicit none
- real*8, intent(in) :: v
- RTTorqueLimitKnob = v
- #ifdef deb
- print*, 'RTTorqueLimitKnob=', RTTorqueLimitKnob
- #endif
- end subroutine
-
- subroutine SetMP1CPSwitch(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetMP1CPSwitch
- !DEC$ ATTRIBUTES ALIAS: 'SetMP1CPSwitch' :: SetMP1CPSwitch
- implicit none
- integer, intent(in) :: v
-
- if(MP1CPSwitch == v) return
-
- if(SimulationState == SimulationState_Started) then
- MP1CPSwitchI = MP1CPSwitchI + 1
- if(MP1CPSwitchI >= 1) MP1CPSwitch = v
- if(MP1CPSwitchI >= 100) MP1CPSwitchI = 1
- !call Log_3( "MP1CPSwitchI=", MP1CPSwitchI)
- !call Log_3( "MP1CPSwitch=", MP1CPSwitch)
-
- !MP1CPSwitch = v
- endif
- ! if(SimulationState == SimulationState_Started) then
- ! !call Log_3( 'MP1CPSwitc(s)h=', MP1CPSwitch)
- ! if(MP1CPSwitchT /= v) then
- ! MP1CPSwitchT = v
- ! MP1CPSwitch = v
- !#ifdef deb
- ! !print*, 'MP1CPSwitch=', MP1CPSwitch
- ! !call Log_3( 'MP1CPSwitch=', MP1CPSwitch)
- !#endif
- ! endif
- ! else
- ! MP1CPSwitchT = v
- ! endif
- end subroutine
-
- subroutine SetMP1Throttle(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetMP1Throttle
- !DEC$ ATTRIBUTES ALIAS: 'SetMP1Throttle' :: SetMP1Throttle
- implicit none
- real*8, intent(in) :: v
- if(MP1Throttle == v) return
- if(SimulationState == SimulationState_Started) then
- if( abs(v - MP1Throttle) > 0.1) MP1ThrottleUpdate = .true.
- if(MP1ThrottleUpdate) MP1Throttle = v
-
- !call Log_3( 'v-mp1=', v)
- !call Log_3( 'MP1Throttle=', MP1Throttle)
- !call Log_3( 'MP1ThrottleUpdate=', MP1ThrottleUpdate)
-
- !MP1Throttle = v
- endif
- #ifdef deb
- print*, 'MP1Throttle=', MP1Throttle
- #endif
- end subroutine
-
- subroutine SetMP2Switch(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetMP2Switch
- !DEC$ ATTRIBUTES ALIAS: 'SetMP2Switch' :: SetMP2Switch
- implicit none
- logical, intent(in) :: v
- !call Log_3( 'v=', MP2SwitchT)
-
- if(MP2Switch == v) return
-
- if(SimulationState == SimulationState_Started) then
- MP2SwitchI = MP2SwitchI + 1
- if(MP2SwitchI >= 1) MP2Switch = v
- if(MP2SwitchI >= 100) MP2SwitchI = 1
- !call Log_3( "MP1CPSwitchI=", MP1CPSwitchI)
- !call Log_3( "MP2Switch=", MP2Switch)
-
- !MP2Switch = v
- endif
-
- ! if(SimulationState == SimulationState_Started) then
- ! !call Log_3( 'MP2Switch(s)=', MP2Switch)
- ! if(MP2SwitchT /= v) then
- ! MP2SwitchT = v
- ! MP2Switch = v
- !#ifdef deb
- ! !print*, 'MP2Switch=', MP2Switch
- ! !call Log_3( 'MP2Switch=', MP2Switch)
- !#endif
- ! endif
- ! else
- ! MP2SwitchT = v
- ! !call Log_3( 'MP2SwitchTMP2SwitchTMP2SwitchT=', MP2SwitchT)
- ! endif
- end subroutine
-
- subroutine SetMP2Throttle(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetMP2Throttle
- !DEC$ ATTRIBUTES ALIAS: 'SetMP2Throttle' :: SetMP2Throttle
- implicit none
- real*8, intent(in) :: v
- if(MP2Throttle == v) return
- if(SimulationState == SimulationState_Started) then
- if( abs(v - MP2Throttle) > 0.1) MP2ThrottleUpdate = .true.
- if(MP2ThrottleUpdate) MP2Throttle = v
-
- !call Log_3( 'v-mp2=', v)
- !call Log_3( 'MP2Throttle=', MP2Throttle)
- !call Log_3( 'MP2ThrottleUpdate=', MP2ThrottleUpdate)
-
- !MP2Throttle = v
- endif
- #ifdef deb
- print*, 'MP2Throttle=', MP2Throttle
- #endif
- end subroutine
-
- subroutine SetDWSwitch(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetDWSwitch
- !DEC$ ATTRIBUTES ALIAS: 'SetDWSwitch' :: SetDWSwitch
- implicit none
- integer, intent(in) :: v
- DWSwitch = v
- #ifdef deb
- print*, 'DWSwitch=', DWSwitch
- #endif
- end subroutine
-
- subroutine SetDWThrottle(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetDWThrottle
- !DEC$ ATTRIBUTES ALIAS: 'SetDWThrottle' :: SetDWThrottle
- implicit none
- real*8, intent(in) :: v
- DWThrottle = v
- #ifdef deb
- print*, 'DWThrottle=', DWThrottle
- #endif
- end subroutine
-
- subroutine SetRTSwitch(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetRTSwitch
- !DEC$ ATTRIBUTES ALIAS: 'SetRTSwitch' :: SetRTSwitch
- implicit none
- integer, intent(in) :: v
- RTSwitch = v
- #ifdef deb
- print*, 'RTSwitch=', RTSwitch
- #endif
- end subroutine
-
- subroutine SetRTThrottle(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetRTThrottle
- !DEC$ ATTRIBUTES ALIAS: 'SetRTThrottle' :: SetRTThrottle
- implicit none
- real*8, intent(in) :: v
- RTThrottle = v
- #ifdef deb
- print*, 'RTThrottle=', RTThrottle
- #endif
- end subroutine
-
- subroutine SetDWBreak(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetDWBreak
- !DEC$ ATTRIBUTES ALIAS: 'SetDWBreak' :: SetDWBreak
- implicit none
- real*8, intent(in) :: v
- !if(ForceBreak) return
- PreviousDWBreak = DWBreak
- DWBreak = v
- #ifdef deb
- print*, 'DWBreak=', DWBreak
- #endif
- end subroutine
-
- subroutine SetDWAcceleretor(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetDWAcceleretor
- !DEC$ ATTRIBUTES ALIAS: 'SetDWAcceleretor' :: SetDWAcceleretor
- implicit none
- real*8, intent(in) :: v
- DWAcceleretor = v
- #ifdef deb
- print*, 'DWAcceleretor=', DWAcceleretor
- #endif
- end subroutine
-
- subroutine SetDWTransmisionLever(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetDWTransmisionLever
- !DEC$ ATTRIBUTES ALIAS: 'SetDWTransmisionLever' :: SetDWTransmisionLever
- implicit none
- real*8, intent(in) :: v
- DWTransmisionLever = v
- #ifdef deb
- print*, 'DWTransmisionLever=', DWTransmisionLever
- #endif
- end subroutine
-
- subroutine SetDWPowerLever(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetDWPowerLever
- !DEC$ ATTRIBUTES ALIAS: 'SetDWPowerLever' :: SetDWPowerLever
- implicit none
- real*8, intent(in) :: v
- DWPowerLever = v
- #ifdef deb
- print*, 'DWPowerLever=', DWPowerLever
- #endif
- end subroutine
-
- subroutine SetTongLever(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetTongLever
- !DEC$ ATTRIBUTES ALIAS: 'SetTongLever' :: SetTongLever
- implicit none
- real*8, intent(in) :: v
- if (TongLever == v) return
- TongLever = v
-
- ! if(dint(TongLever) == 1.0) then
- ! call OnBreakoutLeverPress%RunAll()
- ! #ifdef deb
- ! print*, 'OnBreakoutLeverPress=', size(OnBreakoutLeverPress%Delegates)
- ! #endif
- ! endif
- ! if(dint(TongLever) == -1.0) then
- ! call OnMakeupLeverPress%RunAll()
-
- ! #ifdef deb
- ! print*, 'OnMakeupPress=', size(OnMakeupLeverPress%Delegates)
- ! #endif
- ! endif
- ! if(dint(TongLever) == 0.0) then
- ! call OnTongNeutralPress%RunAll()
- ! #ifdef deb
- ! print*, 'OnTongNeutralPress=', size(OnTongNeutralPress%Delegates)
- ! #endif
- ! endif
-
- #ifdef deb
- print*, 'TongLever=', TongLever
- #endif
- end subroutine
-
- subroutine SetRTTransmissionLever(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetRTTransmissionLever
- !DEC$ ATTRIBUTES ALIAS: 'SetRTTransmissionLever' :: SetRTTransmissionLever
- implicit none
- real*8, intent(in) :: v
- RTTransmissionLever = v
- #ifdef deb
- print*, 'RTTransmissionLever=', RTTransmissionLever
- #endif
- end subroutine
-
- subroutine SetDWClutchLever(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetDWClutchLever
- !DEC$ ATTRIBUTES ALIAS: 'SetDWClutchLever' :: SetDWClutchLever
- implicit none
- real*8, intent(in) :: v
- DWClutchLever = v
- #ifdef deb
- print*, 'DWClutchLever=', DWClutchLever
- #endif
- end subroutine
-
- subroutine SetEddyBreakLever(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetEddyBreakLever
- !DEC$ ATTRIBUTES ALIAS: 'SetEddyBreakLever' :: SetEddyBreakLever
- implicit none
- real*8, intent(in) :: v
- EddyBreakLever = v
- #ifdef deb
- print*, 'EddyBreakLever=', EddyBreakLever
- #endif
- end subroutine
-
- subroutine SetAutoDW(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetAutoDW
- !DEC$ ATTRIBUTES ALIAS: 'SetAutoDW' :: SetAutoDW
- implicit none
- logical, intent(in) :: v
- AutoDW = v
- #ifdef deb
- print*, 'AutoDW=', AutoDW
- #endif
- end subroutine
-
- subroutine SetGEN1(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetGEN1
- !DEC$ ATTRIBUTES ALIAS: 'SetGEN1' :: SetGEN1
- implicit none
- logical, intent(in) :: v
- GEN1 = v
- #ifdef deb
- print*, 'GEN1=', GEN1
- #endif
- end subroutine
-
- subroutine SetGEN2(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetGEN2
- !DEC$ ATTRIBUTES ALIAS: 'SetGEN2' :: SetGEN2
- implicit none
- logical, intent(in) :: v
- GEN2 = v
- #ifdef deb
- print*, 'GEN2=', GEN2
- #endif
- end subroutine
-
- subroutine SetGEN3(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetGEN3
- !DEC$ ATTRIBUTES ALIAS: 'SetGEN3' :: SetGEN3
- implicit none
- logical, intent(in) :: v
- GEN3 = v
- #ifdef deb
- print*, 'GEN3=', GEN3
- #endif
- end subroutine
-
- subroutine SetGEN4(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetGEN4
- !DEC$ ATTRIBUTES ALIAS: 'SetGEN4' :: SetGEN4
- implicit none
- logical, intent(in) :: v
- GEN4 = v
- #ifdef deb
- print*, 'GEN4=', GEN4
- #endif
- end subroutine
-
- ! subroutine SetInstallSafetyValve(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SetInstallSafetyValve
- ! !DEC$ ATTRIBUTES ALIAS: 'SetInstallSafetyValve' :: SetInstallSafetyValve
- ! implicit none
- ! logical, intent(in) :: v
- ! InstallSafetyValve = v
- !#ifdef deb
- ! print*, 'InstallSafetyValve=', InstallSafetyValve
- !#endif
- ! end subroutine
- !
- ! subroutine SetOpenSafetyValve(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SetOpenSafetyValve
- ! !DEC$ ATTRIBUTES ALIAS: 'SetOpenSafetyValve' :: SetOpenSafetyValve
- ! implicit none
- ! logical, intent(in) :: v
- ! OpenSafetyValve = v
- !#ifdef deb
- ! print*, 'OpenSafetyValve=', OpenSafetyValve
- !#endif
- ! end subroutine
- !
- ! subroutine SetRemoveSafetyValve(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SetRemoveSafetyValve
- ! !DEC$ ATTRIBUTES ALIAS: 'SetRemoveSafetyValve' :: SetRemoveSafetyValve
- ! implicit none
- ! logical, intent(in) :: v
- ! RemoveSafetyValve = v
- !#ifdef deb
- ! print*, 'RemoveSafetyValve=', RemoveSafetyValve
- !#endif
- ! end subroutine
- !
- ! subroutine SetCloseSafetyValve(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SetCloseSafetyValve
- ! !DEC$ ATTRIBUTES ALIAS: 'SetCloseSafetyValve' :: SetCloseSafetyValve
- ! implicit none
- ! logical, intent(in) :: v
- ! CloseSafetyValve = v
- !#ifdef deb
- ! print*, 'CloseSafetyValve=', CloseSafetyValve
- !#endif
- ! end subroutine
- !
- ! subroutine SetMakeJoint(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SetMakeJoint
- ! !DEC$ ATTRIBUTES ALIAS: 'SetMakeJoint' :: SetMakeJoint
- ! implicit none
- ! logical, intent(in) :: v
- ! MakeJoint = v
- !#ifdef deb
- ! print*, 'MakeJoint=', MakeJoint
- !#endif
- ! end subroutine
- !
- ! subroutine SetBreakJoint(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SetBreakJoint
- ! !DEC$ ATTRIBUTES ALIAS: 'SetBreakJoint' :: SetBreakJoint
- ! implicit none
- ! logical, intent(in) :: v
- ! BreakJoint = v
- !#ifdef deb
- ! print*, 'BreakJoint=', BreakJoint
- !#endif
- ! end subroutine
-
- subroutine SetOpenKellyCock(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetOpenKellyCock
- !DEC$ ATTRIBUTES ALIAS: 'SetOpenKellyCock' :: SetOpenKellyCock
- use CManifolds, OpenKellyCockSub => OpenKellyCock
- implicit none
- logical, intent(in) :: v
- if (OpenKellyCock == v) return
- OpenKellyCock = v
- ! if (v) call OnOpenKellyCockPress%RunAll()
- if(v .and. Permission_OpenKellyCock) call OpenKellyCockSub()
- #ifdef deb
- print*, 'OpenKellyCock=', OpenKellyCock
- #endif
- end subroutine
-
- subroutine SetCloseKellyCock(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetCloseKellyCock
- !DEC$ ATTRIBUTES ALIAS: 'SetCloseKellyCock' :: SetCloseKellyCock
- use CManifolds, CloseKellyCockSub => CloseKellyCock
- implicit none
- logical, intent(in) :: v
- if (CloseKellyCock == v) return
- CloseKellyCock = v
- ! if (v) call OnCloseKellyCockPress%RunAll()
- if(v .and. Permission_CloseKellyCock) call CloseKellyCockSub()
- #ifdef deb
- print*, 'CloseKellyCock=', CloseKellyCock
- #endif
- end subroutine
-
- subroutine SetOpenSafetyValve(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetOpenSafetyValve
- !DEC$ ATTRIBUTES ALIAS: 'SetOpenSafetyValve' :: SetOpenSafetyValve
- !use CManifolds, OpenSafetyValveSub => OpenSafetyValve
- implicit none
- logical, intent(in) :: v
- if (OpenSafetyValve == v) return
- OpenSafetyValve = v
- ! if (v) call OnOpenSafetyValvePress%RunAll()
- !if(v .and. Permission_OpenSafetyValve) call OpenSafetyValveSub()
- #ifdef deb
- print*, 'OpenSafetyValve=', OpenSafetyValve
- #endif
- end subroutine
-
- subroutine SetCloseSafetyValve(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetCloseSafetyValve
- !DEC$ ATTRIBUTES ALIAS: 'SetCloseSafetyValve' :: SetCloseSafetyValve
- !use CManifolds, CloseSafetyValveSub => CloseSafetyValve
- implicit none
- logical, intent(in) :: v
- if (CloseSafetyValve == v) return
- CloseSafetyValve = v
- ! if (v) call OnCloseSafetyValvePress%RunAll()
- !if(v .and. Permission_CloseSafetyValve) call CloseSafetyValveSub()
- #ifdef deb
- print*, 'CloseSafetyValve=', CloseSafetyValve
- #endif
- end subroutine
-
- subroutine SetIRSafetyValve(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetIRSafetyValve
- !DEC$ ATTRIBUTES ALIAS: 'SetIRSafetyValve' :: SetIRSafetyValve
- use CManifolds
- implicit none
- logical, intent(in) :: v
- logical :: prev
- if (IRSafetyValve == v) return
- prev = IRSafetyValve
- IRSafetyValve = v
- ! if (v) call OnIRSafetyValvePress%RunAll()
- !if(prev /= IRSafetyValve .and. v .and. Permission_IRSafetyValve) call ToggleSafetyValve()
- !if(prev /= IRSafetyValve .and. v) call ToggleSafetyValve()
- #ifdef deb
- print*, 'IRSafetyValve=', IRSafetyValve
- #endif
- end subroutine
-
- subroutine SetIRIBop(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetIRIBop
- !DEC$ ATTRIBUTES ALIAS: 'SetIRIBop' :: SetIRIBop
- use CManifolds
- implicit none
- logical, intent(in) :: v
- logical :: prev
- if (IRIBop == v) return
- prev = IRIBop
- IRIBop = v
- ! if (v) call OnIRIBopPress%RunAll()
- !if(prev /= IRIBop .and. v .and. Permission_IRIBop) call ToggleIBop()
- !if(prev /= IRIBop .and. v) call ToggleIBop()
- #ifdef deb
- print*, 'IRIBop=', IRIBop
- #endif
- end subroutine
-
-
-
- subroutine SetLatchPipe(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetLatchPipe
- !DEC$ ATTRIBUTES ALIAS: 'SetLatchPipe' :: SetLatchPipe
- implicit none
- logical, intent(in) :: v
- if (LatchPipe .eqv. v) return
- LatchPipe = v
- ! if (v) call OnLatchPipePress%RunAll()
- #ifdef deb
- print*, 'LatchPipe=', LatchPipe
- #endif
- end subroutine
-
- subroutine SetUnlatchPipe(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetUnlatchPipe
- !DEC$ ATTRIBUTES ALIAS: 'SetUnlatchPipe' :: SetUnlatchPipe
- implicit none
- logical, intent(in) :: v
- if (UnlatchPipe .eqv. v) return
- UnlatchPipe = v
- ! if (v) call OnUnlatchPipePress%RunAll()
- #ifdef deb
- print*, 'UnlatchPipe=', UnlatchPipe
- #endif
- end subroutine
-
- subroutine SetSwing(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetSwing
- !DEC$ ATTRIBUTES ALIAS: 'SetSwing' :: SetSwing
- implicit none
- logical, intent(in) :: v
- if (Swing .eqv. v) return
- Swing = v
- ! if (v) call OnSwingPress%RunAll()
- #ifdef deb
- print*, 'Swing=', Swing
- #endif
- end subroutine
-
- subroutine SetFillMouseHole(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetFillMouseHole
- !DEC$ ATTRIBUTES ALIAS: 'SetFillMouseHole' :: SetFillMouseHole
- implicit none
- logical, intent(in) :: v
- if (FillMouseHole .eqv. v) return
- FillMouseHole = v
- ! if (v) call OnFillMouseHolePress%RunAll()
- #ifdef deb
- print*, 'FillMouseHole=', FillMouseHole
- #endif
- end subroutine
-
- subroutine SetSlips(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetSlips
- !DEC$ ATTRIBUTES ALIAS: 'SetSlips' :: SetSlips
- implicit none
- logical, intent(in) :: v
- if (Slips .eqv. v) return
- Slips = v
- #ifdef deb
- print*, 'Slips=', Slips
- #endif
- ! if (v) call OnSlipsPress%RunAll()
- end subroutine
-
-
- subroutine SetBrakeLeverCoefficient(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetBrakeLeverCoefficient
- !DEC$ ATTRIBUTES ALIAS: 'SetBrakeLeverCoefficient' :: SetBrakeLeverCoefficient
- implicit none
- real, intent(in) :: v
- BrakeLeverCoefficient = v
- #ifdef deb
- print*, 'BrakeLeverCoefficient=', BrakeLeverCoefficient
- #endif
- end subroutine
-
- subroutine SetHideDrillingBrake(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetHideDrillingBrake
- !DEC$ ATTRIBUTES ALIAS: 'SetHideDrillingBrake' :: SetHideDrillingBrake
- implicit none
- logical, intent(in) :: v
- HideDrillingBrake = v
- #ifdef deb
- print*, 'HideDrillingBrake=', HideDrillingBrake
- #endif
- end subroutine
-
-
-
-
-
-
-
-
- subroutine SetParkingBrake(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetParkingBrake
- !DEC$ ATTRIBUTES ALIAS: 'SetParkingBrake' :: SetParkingBrake
- implicit none
- logical, intent(in) :: v
- ParkingBrakeBtn = v
- #ifdef deb
- print*, 'ParkingBrakeBtn=', ParkingBrakeBtn
- #endif
- end subroutine
-
-
-
-
-
-
-
-
-
-
-
-
- ! Output routines
-
- logical function GetParkingBrakeLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetParkingBrakeLed
- !DEC$ ATTRIBUTES ALIAS: 'GetParkingBrakeLed' :: GetParkingBrakeLed
- implicit none
- GetParkingBrakeLed = ParkingBrakeLed
- !GetParkingBrakeLed = .true.
- end function
-
-
- integer function GetGEN1LED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetGEN1LED
- !DEC$ ATTRIBUTES ALIAS: 'GetGEN1LED' :: GetGEN1LED
- implicit none
- GetGEN1LED = 1
- !GetGEN1LED = GEN1LED
- end function
-
- integer function GetGEN2LED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetGEN2LED
- !DEC$ ATTRIBUTES ALIAS: 'GetGEN2LED' :: GetGEN2LED
- implicit none
- GetGEN2LED = 1
- !GetGEN2LED = GEN2LED
- end function
-
- integer function GetGEN3LED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetGEN3LED
- !DEC$ ATTRIBUTES ALIAS: 'GetGEN3LED' :: GetGEN3LED
- implicit none
- GetGEN3LED = 1
- !GetGEN3LED = GEN3LED
- end function
-
- integer function GetGEN4LED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetGEN4LED
- !DEC$ ATTRIBUTES ALIAS: 'GetGEN4LED' :: GetGEN4LED
- implicit none
- GetGEN4LED = 1
- !GetGEN4LED = GEN4LED
- end function
-
- integer function GetSCR1LED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetSCR1LED
- !DEC$ ATTRIBUTES ALIAS: 'GetSCR1LED' :: GetSCR1LED
- implicit none
- GetSCR1LED = SCR1LED
- end function
-
- integer function GetSCR2LED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetSCR2LED
- !DEC$ ATTRIBUTES ALIAS: 'GetSCR2LED' :: GetSCR2LED
- implicit none
- GetSCR2LED = SCR2LED
- end function
-
- integer function GetSCR3LED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetSCR3LED
- !DEC$ ATTRIBUTES ALIAS: 'GetSCR3LED' :: GetSCR3LED
- implicit none
- GetSCR3LED = SCR3LED
- end function
-
- integer function GetSCR4LED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetSCR4LED
- !DEC$ ATTRIBUTES ALIAS: 'GetSCR4LED' :: GetSCR4LED
- implicit none
- GetSCR4LED = SCR4LED
- end function
-
- integer function GetMP1BLWR()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetMP1BLWR
- !DEC$ ATTRIBUTES ALIAS: 'GetMP1BLWR' :: GetMP1BLWR
- implicit none
- GetMP1BLWR = MP1BLWR
- end function
-
- integer function GetMP2BLWR()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetMP2BLWR
- !DEC$ ATTRIBUTES ALIAS: 'GetMP2BLWR' :: GetMP2BLWR
- implicit none
- GetMP2BLWR = MP2BLWR
- end function
-
- integer function GetDWBLWR()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetDWBLWR
- !DEC$ ATTRIBUTES ALIAS: 'GetDWBLWR' :: GetDWBLWR
- implicit none
- GetDWBLWR = DWBLWR
- end function
-
- integer function GetRTBLWR()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetRTBLWR
- !DEC$ ATTRIBUTES ALIAS: 'GetRTBLWR' :: GetRTBLWR
- implicit none
- GetRTBLWR = RTBLWR
- end function
-
- integer function GetPWRLIM()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetPWRLIM
- !DEC$ ATTRIBUTES ALIAS: 'GetPWRLIM' :: GetPWRLIM
- implicit none
- GetPWRLIM = PWRLIM
- end function
-
- real(8) function GetPWRLIMMTR()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetPWRLIMMTR
- !DEC$ ATTRIBUTES ALIAS: 'GetPWRLIMMTR' :: GetPWRLIMMTR
- implicit none
- GetPWRLIMMTR = PWRLIMMTR
- end function
-
- real(8) function GetRTTorqueLimitGauge()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetRTTorqueLimitGauge
- !DEC$ ATTRIBUTES ALIAS: 'GetRTTorqueLimitGauge' :: GetRTTorqueLimitGauge
- implicit none
- GetRTTorqueLimitGauge = RTTorqueLimitGauge
- end function
-
- integer function GetAutoDWLED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetAutoDWLED
- !DEC$ ATTRIBUTES ALIAS: 'GetAutoDWLED' :: GetAutoDWLED
- implicit none
- GetAutoDWLED = AutoDWLED
- end function
-
- integer function GetGEN1BTNLED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetGEN1BTNLED
- !DEC$ ATTRIBUTES ALIAS: 'GetGEN1BTNLED' :: GetGEN1BTNLED
- implicit none
- GetGEN1BTNLED = GEN1BTNLED
- end function
-
- integer function GetGEN2BTNLED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetGEN2BTNLED
- !DEC$ ATTRIBUTES ALIAS: 'GetGEN2BTNLED' :: GetGEN2BTNLED
- implicit none
- GetGEN2BTNLED = GEN2BTNLED
- end function
-
- integer function GetGEN3BTNLED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetGEN3BTNLED
- !DEC$ ATTRIBUTES ALIAS: 'GetGEN3BTNLED' :: GetGEN3BTNLED
- implicit none
- GetGEN3BTNLED = GEN3BTNLED
- end function
-
- integer function GetGEN4BTNLED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetGEN4BTNLED
- !DEC$ ATTRIBUTES ALIAS: 'GetGEN4BTNLED' :: GetGEN4BTNLED
- implicit none
- GetGEN4BTNLED = GEN4BTNLED
- end function
-
- integer function GetOpenKellyCockLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetOpenKellyCockLed
- !DEC$ ATTRIBUTES ALIAS: 'GetOpenKellyCockLed' :: GetOpenKellyCockLed
- implicit none
- GetOpenKellyCockLed = OpenKellyCockLed
- end function
-
- integer function GetCloseKellyCockLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetCloseKellyCockLed
- !DEC$ ATTRIBUTES ALIAS: 'GetCloseKellyCockLed' :: GetCloseKellyCockLed
- implicit none
- GetCloseKellyCockLed = CloseKellyCockLed
- end function
-
- integer function GetOpenSafetyValveLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetOpenSafetyValveLed
- !DEC$ ATTRIBUTES ALIAS: 'GetOpenSafetyValveLed' :: GetOpenSafetyValveLed
- implicit none
- GetOpenSafetyValveLed = OpenSafetyValveLed
- end function
-
- integer function GetCloseSafetyValveLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetCloseSafetyValveLed
- !DEC$ ATTRIBUTES ALIAS: 'GetCloseSafetyValveLed' :: GetCloseSafetyValveLed
- implicit none
- GetCloseSafetyValveLed = CloseSafetyValveLed
- end function
-
- integer function GetIRSafetyValveLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetIRSafetyValveLed
- !DEC$ ATTRIBUTES ALIAS: 'GetIRSafetyValveLed' :: GetIRSafetyValveLed
- implicit none
- GetIRSafetyValveLed = IRSafetyValveLed
- end function
-
- integer function GetIRIBopLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetIRIBopLed
- !DEC$ ATTRIBUTES ALIAS: 'GetIRIBopLed' :: GetIRIBopLed
- implicit none
- GetIRIBopLed = IRIBopLed
- end function
-
-
- integer function GetLatchPipeLED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetLatchPipeLED
- !DEC$ ATTRIBUTES ALIAS: 'GetLatchPipeLED' :: GetLatchPipeLED
- implicit none
- GetLatchPipeLED = LatchPipeLED
- end function
-
- integer function GetUnlatchPipeLED()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetUnlatchPipeLED
- !DEC$ ATTRIBUTES ALIAS: 'GetUnlatchPipeLED' :: GetUnlatchPipeLED
- implicit none
- GetUnlatchPipeLED = UnlatchPipeLED
- end function
-
- integer function GetSwingLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetSwingLed
- !DEC$ ATTRIBUTES ALIAS: 'GetSwingLed' :: GetSwingLed
- implicit none
- GetSwingLed = SwingLed
- end function
-
- integer function GetFillMouseHoleLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetFillMouseHoleLed
- !DEC$ ATTRIBUTES ALIAS: 'GetFillMouseHoleLed' :: GetFillMouseHoleLed
- implicit none
- GetFillMouseHoleLed = FillMouseHoleLed
- end function
-
- end module CDrillingConsole
|