|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211 |
- module CTopDrivePanel
- use CTopDrivePanelVariables
- use CLog3
- implicit none
- public
- contains
-
- ! Input routines
- subroutine SetTopDriveTdsPowerState(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveTdsPowerState
- !DEC$ ATTRIBUTES ALIAS: 'SetTopDriveTdsPowerState' :: SetTopDriveTdsPowerState
- implicit none
- integer, intent(in) :: v
- TopDriveTdsPowerState = v
- #ifdef deb
- call Log_3( 'TopDriveTdsPowerState=', TopDriveTdsPowerState)
- #endif
- end subroutine
-
- subroutine SetTopDriveTorqueWrench(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveTorqueWrench
- !DEC$ ATTRIBUTES ALIAS: 'SetTopDriveTorqueWrench' :: SetTopDriveTorqueWrench
- implicit none
- logical, intent(in) :: v
- TopDriveTorqueWrench = v
- #ifdef deb
- call Log_3( 'TopDriveTorqueWrench=', TopDriveTorqueWrench)
- #endif
- end subroutine
-
- subroutine SetTopDriveDrillTorqueState(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveDrillTorqueState
- !DEC$ ATTRIBUTES ALIAS: 'SetTopDriveDrillTorqueState' :: SetTopDriveDrillTorqueState
- implicit none
- integer, intent(in) :: v
- TopDriveDrillTorqueState = v
- #ifdef deb
- call Log_3( 'TopDriveDrillTorqueState=', TopDriveDrillTorqueState)
- #endif
- end subroutine
-
- subroutine SetTopDriveLinkTiltState(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveLinkTiltState
- !DEC$ ATTRIBUTES ALIAS: 'SetTopDriveLinkTiltState' :: SetTopDriveLinkTiltState
- implicit none
- integer, intent(in) :: v
- TopDriveLinkTiltState = v
- #ifdef deb
- call Log_3( 'TopDriveLinkTiltState=', TopDriveLinkTiltState)
- #endif
- end subroutine
-
- subroutine SetTopDriveIbop(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveIbop
- !DEC$ ATTRIBUTES ALIAS: 'SetTopDriveIbop' :: SetTopDriveIbop
- implicit none
- logical, intent(in) :: v
- TopDriveIbop = v
- #ifdef deb
- call Log_3( 'TopDriveIbop=', TopDriveIbop)
- #endif
- end subroutine
-
- subroutine SetTopDriveTorqueLimitKnob(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveTorqueLimitKnob
- !DEC$ ATTRIBUTES ALIAS: 'SetTopDriveTorqueLimitKnob' :: SetTopDriveTorqueLimitKnob
- use CSimulationVariables, only: IsPortable
- use CDrillingConsoleVariables, only: RTSwitch, RTTorqueLimitKnob
- use CWarningsVariables, only: Activate_TopdriveRotaryTableConfilict
- use CScaleRange
- implicit none
- real, intent(in) :: v
- if (IsPortable) then
- if(TopDriveTdsPowerState /= 0 .and. RTSwitch /= 0) call Activate_TopdriveRotaryTableConfilict()
- if(TopDriveTdsPowerState /= 0 .and. RTSwitch == 0) then
- RTTorqueLimitKnob = 0
- TopDriveTorqueLimitKnob = v
- #ifdef deb
- call Log_3( 'RTTorqueLimitKnob=', RTTorqueLimitKnob )
- call Log_3( 'TopDriveTorqueLimitKnob=', TopDriveTorqueLimitKnob )
- #endif
- endif
- if(TopDriveTdsPowerState == 0 .and. RTSwitch /= 0) then
- TopDriveTorqueLimitKnob = 0
- RTTorqueLimitKnob = real(ScaleRange(v, 0.0, 10.0, 0.0, 6000.0), 8)
- #ifdef deb
- call Log_3( 'RTTorqueLimitKnob=', RTTorqueLimitKnob )
- call Log_3( 'TopDriveTorqueLimitKnob=', TopDriveTorqueLimitKnob )
- #endif
- endif
- else
- TopDriveTorqueLimitKnob = v
- #ifdef deb
- call Log_3( 'TopDriveTorqueLimitKnob=', TopDriveTorqueLimitKnob)
- #endif
- endif
-
- end subroutine
-
- subroutine SetRpmKnob(v)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetRpmKnob
- !DEC$ ATTRIBUTES ALIAS: 'SetRpmKnob' :: SetRpmKnob
- use CSimulationVariables, only: IsPortable
- use CDrillingConsoleVariables, only: RTSwitch, RTThrottle
- use CWarningsVariables, only: Activate_TopdriveRotaryTableConfilict
- use CScaleRange
- implicit none
- real, intent(in) :: v
- if (IsPortable) then
- if(TopDriveTdsPowerState /= 0 .and. RTSwitch /= 0) call Activate_TopdriveRotaryTableConfilict()
- if(TopDriveTdsPowerState /= 0 .and. RTSwitch == 0) then
- RTThrottle = 0
- RpmKnob = v
- #ifdef deb
- call Log_3( 'RTThrottle=', RTThrottle )
- call Log_3( 'RpmKnob=', RpmKnob )
- #endif
- endif
- if(TopDriveTdsPowerState == 0 .and. RTSwitch /= 0) then
- RpmKnob = 0
- RTThrottle = real(ScaleRange(v, 0.0, 965.0, 0.0, 250.0), 8)
- #ifdef deb
- call Log_3( 'RpmKnob=', RpmKnob )
- call Log_3( 'RTThrottle=', RTThrottle )
- #endif
- endif
- else
- RpmKnob = v
- endif
-
-
-
- if (IsPortable) then
- !
- else
- RpmKnob = v
- #ifdef deb
- call Log_3( 'RpmKnob=', RpmKnob )
- #endif
- endif
-
- end subroutine
-
-
- ! Output routines
- integer function GetTopDriveOperationFaultLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveOperationFaultLed
- !DEC$ ATTRIBUTES ALIAS: 'GetTopDriveOperationFaultLed' :: GetTopDriveOperationFaultLed
- implicit none
- GetTopDriveOperationFaultLed = TopDriveOperationFaultLed
- !GetTopDriveOperationFaultLed = 1
- end function
-
- integer function GetTopDriveTdsPowerLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveTdsPowerLed
- !DEC$ ATTRIBUTES ALIAS: 'GetTopDriveTdsPowerLed' :: GetTopDriveTdsPowerLed
- implicit none
- GetTopDriveTdsPowerLed = TopDriveTdsPowerLed
- !GetTopDriveTdsPowerLed = 1
- end function
-
- integer function GetTopDriveTorqueWrenchLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveTorqueWrenchLed
- !DEC$ ATTRIBUTES ALIAS: 'GetTopDriveTorqueWrenchLed' :: GetTopDriveTorqueWrenchLed
- implicit none
- GetTopDriveTorqueWrenchLed = TopDriveTorqueWrenchLed
- !GetTopDriveTorqueWrenchLed = 1
- end function
-
- integer function GetTopDriveLinkTiltLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveLinkTiltLed
- !DEC$ ATTRIBUTES ALIAS: 'GetTopDriveLinkTiltLed' :: GetTopDriveLinkTiltLed
- implicit none
- GetTopDriveLinkTiltLed = TopDriveLinkTiltLed
- !GetTopDriveLinkTiltLed = 1
- end function
-
- integer function GetTopDriveIbopLed()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveIbopLed
- !DEC$ ATTRIBUTES ALIAS: 'GetTopDriveIbopLed' :: GetTopDriveIbopLed
- implicit none
- GetTopDriveIbopLed = TopDriveIbopLed
- !GetTopDriveIbopLed = 1
- end function
-
- real function GetTopDriveTorqueGauge()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveTorqueGauge
- !DEC$ ATTRIBUTES ALIAS: 'GetTopDriveTorqueGauge' :: GetTopDriveTorqueGauge
- implicit none
- GetTopDriveTorqueGauge = TopDriveTorqueGauge
- !GetTopDriveTorqueGauge = 340
- end function
-
- real function GetTopDriveTorqueLimitGauge()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveTorqueLimitGauge
- !DEC$ ATTRIBUTES ALIAS: 'GetTopDriveTorqueLimitGauge' :: GetTopDriveTorqueLimitGauge
- implicit none
- GetTopDriveTorqueLimitGauge = TopDriveTorqueLimitGauge
- !GetTopDriveTorqueLimitGauge = 442
- end function
-
- real function GetTopDriveRpmGauge()
- !DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveRpmGauge
- !DEC$ ATTRIBUTES ALIAS: 'GetTopDriveRpmGauge' :: GetTopDriveRpmGauge
- implicit none
- GetTopDriveRpmGauge = TopDriveRpmGauge
- !GetTopDriveRpmGauge = 67
- end function
-
-
- end module CTopDrivePanel
|