|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204 |
- module RotaryTableMain
- implicit none
- public
- contains
-
- ! subroutine RotaryTable_Setup()
- ! use CSimulationVariables
- ! implicit none
- ! call OnSimulationInitialization%Add(RotaryTable_Init)
- ! call OnSimulationStop%Add(RotaryTable_Init)
- ! call OnRotaryTableStep%Add(RotaryTable_Step)
- ! call OnRotaryTableOutput%Add(RotaryTable_Output)
- ! call OnRotaryTableMain%Add(RotaryTableMainBody)
- ! end subroutine
-
- subroutine RotaryTable_Init
- implicit none
- end subroutine RotaryTable_Init
-
- subroutine RotaryTable_Step
- implicit none
- end subroutine RotaryTable_Step
-
- subroutine RotaryTable_Output
- implicit none
- end subroutine RotaryTable_Output
-
-
- subroutine RotaryTableMainBody
-
- use CDataDisplayConsoleVariables
- use CDrillingConsoleVariables
- use CSimulationVariables
- use RTable_VARIABLES
- use CDrillWatchVariables
- use CWarningsVariables
- use CSounds
-
- implicit none
-
- integer,dimension(8) :: RT_START_TIME, RT_END_TIME
- INTEGER :: RT_SolDuration
-
-
- Call RTable_StartUp
- loopRtablestart : do
-
- call sleepqq(10)
-
- if (IsPortable) then
- RTable%AssignmentSwitch = 1
- else
- RTable%AssignmentSwitch = AssignmentSwitch
- end if
- if ( (any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (RTSwitch == -1) ) then
-
- RTable%SoundBlower = .true.
- Call SetSoundBlowerRT(RTable%SoundBlower)
- RTBLWR = 1
-
- loopRtableswitch: do
-
- CALL DATE_AND_TIME(values=RT_START_TIME)
-
- IF ( RTTransmissionLever /=0 .and. RotaryGearsAbuse==0 ) THEN !be in clutch mode ??????
- RTable%N_new = 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 = RotaryRPMGauge
- RTable%N_old = RTable%N_ref
- Else IF ( RTTransmissionLever==0) THEN !be in brake mode ??????
- Call RTable_OffMode
- RT_RPMUnityOutput = RotaryRPMGauge
- End IF
- RT_OldTransMode = RTTransmissionLever
-
- CALL DATE_AND_TIME(values=RT_END_TIME)
- RT_SolDuration = 100-(RT_END_TIME(5)*3600000+RT_END_TIME(6)*60000+RT_END_TIME(7)*1000+RT_END_TIME(8)-RT_START_TIME(5)*3600000-RT_START_TIME(6)*60000-RT_START_TIME(7)*1000-RT_START_TIME(8))
- !print*, 'RTtime=', RT_SolDuration
- if(RT_SolDuration > 0.0) then
- CALL sleepqq(RT_SolDuration)
- end if
-
- if (IsPortable) then
- RTable%AssignmentSwitch = 1
- else
- RTable%AssignmentSwitch = AssignmentSwitch
- end if
- if ((any(RTable%AssignmentSwitch==(/6,7,12/))) .or. (RTSwitch/=-1) .or. (IsStopped == .true.)) then
- RTable%SoundBlower = .false.
- Call SetSoundBlowerRT(RTable%SoundBlower)
- RTBLWR = 0
- Call RTable_OffMode
- RT_RPMUnityOutput = RotaryRPMGauge
- exit loopRtableswitch
- end if
-
- end do loopRtableswitch
-
-
-
- else if ( (any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (RTSwitch == 1) .and. (RTThrottle==0.) ) then
-
- RTable%SoundBlower = .true.
- Call SetSoundBlowerRT(RTable%SoundBlower)
- RTBLWR = 1
-
- loopRtableswitchREV: do
-
- CALL DATE_AND_TIME(values=RT_START_TIME)
-
- IF ( RTTransmissionLever /=0 .and. RotaryGearsAbuse==0 ) THEN !be in clutch mode ??????
- RTable%N_new = 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 = -RotaryRPMGauge
- RTable%N_old = RTable%N_ref
- Else IF ( RTTransmissionLever==0) THEN !be in brake mode ??????
- Call RTable_OffMode
- RT_RPMUnityOutput = -RotaryRPMGauge
- End IF
- RT_OldTransMode = RTTransmissionLever
-
- CALL DATE_AND_TIME(values=RT_END_TIME)
- RT_SolDuration = 100-(RT_END_TIME(5)*3600000+RT_END_TIME(6)*60000+RT_END_TIME(7)*1000+RT_END_TIME(8)-RT_START_TIME(5)*3600000-RT_START_TIME(6)*60000-RT_START_TIME(7)*1000-RT_START_TIME(8))
- !print*, 'RTtime=', RT_SolDuration
- if(RT_SolDuration > 0.0) then
- CALL sleepqq(RT_SolDuration)
- end if
-
- if (IsPortable) then
- RTable%AssignmentSwitch = 1
- else
- RTable%AssignmentSwitch = AssignmentSwitch
- end if
- if ((any(RTable%AssignmentSwitch==(/6,7,12/))) .or. (RTSwitch/=1) .or. (IsStopped == .true.)) then
- RTable%SoundBlower = .false.
- Call SetSoundBlowerRT(RTable%SoundBlower)
- RTBLWR = 0
- Call RTable_OffMode
- RT_RPMUnityOutput = -RotaryRPMGauge
- exit loopRtableswitchREV
- end if
-
- end do loopRtableswitchREV
-
-
- else
-
-
- if (IsPortable) then
- RTable%AssignmentSwitch = 1
- else
- RTable%AssignmentSwitch = AssignmentSwitch
- end if
- if((any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (RTSwitch /= 0)) then
- RTable%SoundBlower = .true.
- Call SetSoundBlowerRT(RTable%SoundBlower)
- RTBLWR = 1
- else
- RTable%SoundBlower = .false.
- Call SetSoundBlowerRT(RTable%SoundBlower)
- RTBLWR = 0
- end if
- Call RTable_OffMode
- RT_RPMUnityOutput = RotaryRPMGauge
- !exit loopRtableswitch
- RT_OldTransMode = RTTransmissionLever
-
-
- end if
-
- if (IsStopped == .true.) then
- exit loopRtablestart
- end if
-
- end do loopRtablestart
-
-
- end subroutine RotaryTableMainBody
-
- end module RotaryTableMain
|