You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
|
- subroutine TopDrive_MainSolver
-
- !use CDataDisplayConsoleVariables
- !use CDrillingConsoleVariables
- use CSimulationVariables
- use TopDrive_VARIABLES
- use CDrillWatchVariables
- use CWarningsVariables
- use CSounds
- use CTopDrivePanelVariables
-
- IMPLICIT NONE
-
-
- !if ( (TopDriveTdsPowerState==-1) .and. (RpmKnob==0.) ) then !FWD
- if ( (TopDriveTdsPowerState==-1) .and. (IsStopped == .false.) ) then !FWD
-
-
- TDS%SoundBlower = .true.
- !Call SetSoundBlowerRT(TDS%SoundBlower)
- TopDriveTdsPowerLed = 1
-
-
- !IF ( RTTransmissionLever /=0 .and. RotaryGearsAbuse==0 ) THEN !be in clutch mode ????
- TDS%N_new = (RpmKnob/250.d0)*965.d0 ! 0<RpmKnob<250 , 0<TDS%N_ref(truction motor)<965
-
- !===> Top Drive Malfunction ----> Drive Motor Failure
- call TopDrive_Malfunction_MotorFailure
-
- if (((TDS%N_new-TDS%N_old)/TDS%time_step)>193.) then
- TDS%N_ref = (193.*TDS%time_step)+TDS%N_old
- else if (((TDS%N_old-TDS%N_new)/TDS%time_step)>193.) then
- TDS%N_ref = (-193.*TDS%time_step)+TDS%N_old
- else
- TDS%N_ref = TDS%N_new
- end if
- CALL TopDrive_INPUTS
- CALL TopDrive_Solver
- TDS%N_old = TDS%N_ref
-
-
- !else if ( (TopDriveTdsPowerState==1) .and. (RpmKnob==0.) ) then !REV
- else if ( (TopDriveTdsPowerState==1) .and. (IsStopped == .false.) ) then !REV
-
-
- TDS%SoundBlower = .true.
- !Call SetSoundBlowerRT(TDS%SoundBlower)
- TopDriveTdsPowerLed = 1
-
-
- TDS%N_new = (RpmKnob/250.d0)*965.d0
-
- !===> Top Drive Malfunction ----> Drive Motor Failure
- call TopDrive_Malfunction_MotorFailure
-
- if (((TDS%N_new-TDS%N_old)/TDS%time_step)>193.) then
- TDS%N_ref = (193.*TDS%time_step)+TDS%N_old
- else if (((TDS%N_old-TDS%N_new)/TDS%time_step)>193.) then
- TDS%N_ref = (-193.*TDS%time_step)+TDS%N_old
- else
- TDS%N_ref = TDS%N_new
- end if
- CALL TopDrive_INPUTS
- CALL TopDrive_Solver
- TDS%N_old = TDS%N_ref
-
-
- else
-
-
- if( (TopDriveTdsPowerState /= 0) .and. (IsStopped == .false.) ) then
- TDS%SoundBlower = .true.
- !Call SetSoundBlowerRT(TDS%SoundBlower)
- TopDriveTdsPowerLed = 1
- else
- TDS%SoundBlower = .false.
- !Call SetSoundBlowerRT(TDS%SoundBlower)
- TopDriveTdsPowerLed = 0
- end if
- Call TopDrive_OffMode
-
-
- end if
-
-
-
-
- end subroutine TopDrive_MainSolver
|