subroutine Rtable_MainSolver use CDataDisplayConsoleVariables use CDrillingConsoleVariables ! use CSimulationVariables use RTable_VARIABLES use CDrillWatchVariables use CWarningsVariables use CSounds IMPLICIT NONE ! if (IsPortable) then ! RTable%AssignmentSwitch = 1 ! else RTable%AssignmentSwitch = DrillingConsole%AssignmentSwitch ! end if if (DrillingConsole%RTThrottle<=0.e0) then RTable%K_throttle = 1 end if if ( (any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (DrillingConsole%RTSwitch == -1) ) then !.and. (IsStopped == .false.) ) then RTable%SoundBlower = .true. Call SetSoundBlowerRT(RTable%SoundBlower) DrillingConsole%RTBLWR = 1 IF ( DrillingConsole%RTTransmissionLever /=0 .and. RotaryGearsAbuse==0 ) THEN !be in clutch mode ?????? RTable%N_new = DrillingConsole%RTThrottle !===> Rotary Table Malfunction ----> Drive Motor Failure call RTMalfunction_MotorFailure if (((RTable%N_new-RTable%N_old)/RTable%time_step)>193.) then RTable%N_ref = (193.*RTable%time_step)+RTable%N_old else if (((RTable%N_old-RTable%N_new)/RTable%time_step)>193.) then RTable%N_ref = (-193.*RTable%time_step)+RTable%N_old else RTable%N_ref = RTable%N_new end if CALL RTable_INPUTS CALL RTable_Solver RT_RPMUnityOutput = DataDisplayConsole%RotaryRPMGauge RTable%N_old = RTable%N_ref Else IF ( DrillingConsole%RTTransmissionLever==0) THEN !be in brake mode ?????? Call RTable_OffMode RT_RPMUnityOutput = DataDisplayConsole%RotaryRPMGauge End IF RT_OldTransMode = DrillingConsole%RTTransmissionLever else if ( (any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (DrillingConsole%RTSwitch == 1) .and. (RTable%K_throttle==1) ) then !.and. (IsStopped == .false.) ) then RTable%SoundBlower = .true. Call SetSoundBlowerRT(RTable%SoundBlower) DrillingConsole%RTBLWR = 1 IF ( DrillingConsole%RTTransmissionLever /=0 .and. RotaryGearsAbuse==0 ) THEN !be in clutch mode ?????? RTable%N_new = DrillingConsole%RTThrottle !===> Rotary Table Malfunction ----> Drive Motor Failure call RTMalfunction_MotorFailure if (((RTable%N_new-RTable%N_old)/RTable%time_step)>193.) then RTable%N_ref = (193.*RTable%time_step)+RTable%N_old else if (((RTable%N_old-RTable%N_new)/RTable%time_step)>193.) then RTable%N_ref = (-193.*RTable%time_step)+RTable%N_old else RTable%N_ref = RTable%N_new end if CALL RTable_INPUTS CALL RTable_Solver RT_RPMUnityOutput = -DataDisplayConsole%RotaryRPMGauge RTable%N_old = RTable%N_ref Else IF ( DrillingConsole%RTTransmissionLever==0) THEN !be in brake mode ?????? Call RTable_OffMode RT_RPMUnityOutput = -DataDisplayConsole%RotaryRPMGauge End IF RT_OldTransMode = DrillingConsole%RTTransmissionLever else if((any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (DrillingConsole%RTSwitch /= 0) ) then !.and. (IsStopped == .false.) ) then RTable%SoundBlower = .true. Call SetSoundBlowerRT(RTable%SoundBlower) DrillingConsole%RTBLWR = 1 else RTable%SoundBlower = .false. Call SetSoundBlowerRT(RTable%SoundBlower) DrillingConsole%RTBLWR = 0 end if Call RTable_OffMode RT_RPMUnityOutput = DataDisplayConsole%RotaryRPMGauge RT_OldTransMode = DrillingConsole%RTTransmissionLever RTable%K_throttle = 0 end if END subroutine Rtable_MainSolver