@@ -5,3 +5,5 @@ | |||
/.vs/SimulationCore2/FileContentIndex | |||
/.vs/SimulationCore2/v17 | |||
/.vs | |||
/x64 | |||
*.rar |
@@ -29,7 +29,7 @@ module PumpsMain | |||
end subroutine | |||
subroutine Pump1_Init | |||
implicit none | |||
Call Pump_StartUp | |||
end subroutine Pump1_Init | |||
subroutine Pump1_Step | |||
@@ -51,7 +51,6 @@ module PumpsMain | |||
integer,dimension(8) :: MP_START_TIME, MP_END_TIME | |||
INTEGER :: MP_SolDuration | |||
Call Pump_StartUp | |||
loop1 : do | |||
@@ -13,7 +13,7 @@ subroutine RTable_OffMode | |||
!================================================================== | |||
! Rate limit for off Mode | |||
Do while (((RTable%N_old-0.0d0)/RTable%time_step)>386.0d0) | |||
if (((RTable%N_old-0.0d0)/RTable%time_step)>386.0d0) then | |||
RTable%N_ref = (-386.0d0*RTable%time_step)+RTable%N_old | |||
!else | |||
! RTable%N_ref=0.0d0 | |||
@@ -31,51 +31,41 @@ subroutine RTable_OffMode | |||
Call SetSoundRtGearCrash(RTable%SoundGearCrash) | |||
end if | |||
RT_OldTransMode = RTTransmissionLever | |||
if (IsPortable) then | |||
RTable%AssignmentSwitch = 1 | |||
else | |||
RTable%AssignmentSwitch = AssignmentSwitch | |||
end if | |||
if ((any(RTable%AssignmentSwitch==(/6,7,12/))) .or. (RTSwitch==0) .or. (IsStopped == .true.)) then | |||
RTBLWR = 0 | |||
end if | |||
Call sleepqq (80) !????????????????? | |||
End Do | |||
!================================================================== | |||
else | |||
RTable%N_ref = 0. | |||
RTable%N_new = 0. | |||
RTable%N_old = 0. | |||
RTable%N_ref = 0. | |||
RTable%N_new = 0. | |||
RTable%N_old = 0. | |||
RTable%ia = 0. | |||
RTable%ia_old = 0. | |||
RTable%ia_new = 0. | |||
RTable%x = 0. | |||
RTable%x_old = 0. | |||
RTable%x_new = 0. | |||
RTable%y = 0. | |||
RTable%y_old = 0. | |||
RTable%y_new = 0. | |||
RTable%w = 0. | |||
RTable%w_old = 0. | |||
RTable%w_new = 0. | |||
RTable%Speed = 0. | |||
RT_wOld = 0. | |||
Call Set_RotaryRPMGauge(sngl(1-RTable%RpmGaugeMalf)*real(RTable%Speed,8)) | |||
RTable%SoundRPM = INT(RTable%Speed) | |||
Call SetSoundRT( RTable%SoundRPM ) | |||
!RotaryRPMGauge=RTable%Speed | |||
!RPM=RotaryRPMGauge | |||
RTable%Output_Current = 0. | |||
RotaryTorqueGauge = ( ((RTable%J_coef+RTable%String_JCoef)*(((RTable%w_new/RTable%Conv_Ratio)-RT_wOld)/RTable%time_step))+(RTable%String_Torque) )*0.73756215 ![N.m]*0.73756215 = [ft.lbf] | |||
RTable%Torque = ( ((RTable%J_coef+RTable%String_JCoef)*(((RTable%w_new/RTable%Conv_Ratio)-RT_wOld)/RTable%time_step))+(RTable%String_Torque) )*0.73756215 ![N.m]*0.73756215 = [ft.lbf] | |||
Call Set_RotaryTorque(sngl(1-RTable%TorqueGaugeMalf)*real(RTable%Torque,8)) | |||
!RotaryTorqueGauge=(RTable%String_Torque)/12. | |||
RTable%ia = 0. | |||
RTable%ia_old = 0. | |||
RTable%ia_new = 0. | |||
RTable%x = 0. | |||
RTable%x_old = 0. | |||
RTable%x_new = 0. | |||
RTable%y = 0. | |||
RTable%y_old = 0. | |||
RTable%y_new = 0. | |||
RTable%w = 0. | |||
RTable%w_old = 0. | |||
RTable%w_new = 0. | |||
RTable%Speed = 0. | |||
RT_wOld = 0. | |||
Call Set_RotaryRPMGauge(sngl(1-RTable%RpmGaugeMalf)*real(RTable%Speed,8)) | |||
RTable%SoundRPM = INT(RTable%Speed) | |||
Call SetSoundRT( RTable%SoundRPM ) | |||
!RotaryRPMGauge=RTable%Speed | |||
!RPM=RotaryRPMGauge | |||
RTable%Output_Current = 0. | |||
RotaryTorqueGauge = ( ((RTable%J_coef+RTable%String_JCoef)*(((RTable%w_new/RTable%Conv_Ratio)-RT_wOld)/RTable%time_step))+(RTable%String_Torque) )*0.73756215 ![N.m]*0.73756215 = [ft.lbf] | |||
RTable%Torque = ( ((RTable%J_coef+RTable%String_JCoef)*(((RTable%w_new/RTable%Conv_Ratio)-RT_wOld)/RTable%time_step))+(RTable%String_Torque) )*0.73756215 ![N.m]*0.73756215 = [ft.lbf] | |||
Call Set_RotaryTorque(sngl(1-RTable%TorqueGaugeMalf)*real(RTable%Torque,8)) | |||
!RotaryTorqueGauge=(RTable%String_Torque)/12. | |||
end if | |||
end subroutine RTable_OffMode |
@@ -9,23 +9,24 @@ subroutine RTable_StartUp | |||
!RTable%=0. | |||
RTable%Inertia_Moment = 23.261341 ! 23.261341 [kg.m^2] = 552 [lb.ft^2] | |||
RTable%J_coef = RTable%Inertia_Moment+(1.*(RTable%Inertia_Moment)) ! [kg.m^2]??????????? | |||
RTable%String_JCoef = 0. !??????????????? | |||
RTable%Mech_Efficiency = 0.930 | |||
RTable%ConstLoad = 2000. ![lb.in] | |||
RTable%ConstLoad = 0.112984829*RTable%ConstLoad ![N.m] | |||
RTable%Torque = 0.0 | |||
RTable%Inertia_Moment = 23.261341e0 ! 23.261341 [kg.m^2] = 552 [lb.ft^2] | |||
RTable%J_coef = RTable%Inertia_Moment+(1.e0*(RTable%Inertia_Moment)) ! [kg.m^2]??????????? | |||
RTable%String_JCoef = 0.e0 !??????????????? | |||
RTable%Mech_Efficiency = 0.93e0 | |||
!RTable%ConstLoad = 2000.e0 ![lb.in] | |||
!RTable%ConstLoad = 0.112984829e0*RTable%ConstLoad ![N.m] | |||
RTable%Torque = 0.0e0 | |||
RTable%High_Conv_Ratio = 4.8250 | |||
RTable%Low_Conv_Ratio = 7.310 | |||
RTable%High_Conv_Ratio = 4.825e0 | |||
RTable%Low_Conv_Ratio = 7.31e0 | |||
RTable%Conv_Ratio = RTable%Low_Conv_Ratio | |||
RTable%time_step = .10 | |||
RTable%time_step = 0.1e0 | |||
RTable%w = 0.0 | |||
RTable%w_new = 0.0 | |||
RTable%w = 0.e0 | |||
RTable%w_new = 0.e0 | |||
RTable%K_throttle = 0 | |||
@@ -17,7 +17,7 @@ MODULE RTable_VARIABLES | |||
TYPE, PUBLIC :: RTable_Var | |||
!***** RTable_VARIABLES ************************* | |||
INTEGER :: j , AssignmentSwitch | |||
INTEGER :: j , AssignmentSwitch , K_throttle | |||
INTEGER :: MotorFaileMalf , OverideTorqueLimitMalf , RpmGaugeMalf , TorqueGaugeMalf , TorqueLimitGaugeMalf | |||
REAL :: Horsepower, Speed, Output_Current, Inertia_Moment, Mech_Efficiency, Torque | |||
@@ -3,31 +3,30 @@ module RotaryTableMain | |||
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_Setup() | |||
!use CSimulationVariables | |||
!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 | |||
Call RTable_StartUp | |||
end subroutine RotaryTable_Init | |||
subroutine RotaryTable_Step | |||
subroutine RotaryTable_Step | |||
implicit none | |||
Call Rtable_MainSolver | |||
end subroutine RotaryTable_Step | |||
subroutine RotaryTable_Output | |||
implicit none | |||
end subroutine RotaryTable_Output | |||
subroutine RotaryTableMainBody | |||
use CDataDisplayConsoleVariables | |||
use CDrillingConsoleVariables | |||
use CSimulationVariables | |||
@@ -44,161 +43,27 @@ module RotaryTableMain | |||
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 | |||
CALL DATE_AND_TIME(values=RT_START_TIME) | |||
Call Rtable_MainSolver | |||
end do loopRtableswitchREV | |||
else | |||
if (IsPortable) then | |||
RTable%AssignmentSwitch = 1 | |||
else | |||
RTable%AssignmentSwitch = AssignmentSwitch | |||
if (IsStopped == .true.) then | |||
exit loopRtablestart | |||
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 | |||
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)) | |||
if(RT_SolDuration > 0.0) then | |||
CALL sleepqq(RT_SolDuration) | |||
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 |
@@ -0,0 +1,107 @@ | |||
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 = AssignmentSwitch | |||
end if | |||
if (RTThrottle<=0.e0) then | |||
RTable%K_throttle = 1 | |||
end if | |||
if ( (any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (RTSwitch == -1) .and. (IsStopped == .false.) ) then | |||
RTable%SoundBlower = .true. | |||
Call SetSoundBlowerRT(RTable%SoundBlower) | |||
RTBLWR = 1 | |||
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 | |||
else if ( (any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (RTSwitch == 1) .and. (RTable%K_throttle==1) .and. (IsStopped == .false.) ) then | |||
RTable%SoundBlower = .true. | |||
Call SetSoundBlowerRT(RTable%SoundBlower) | |||
RTBLWR = 1 | |||
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 | |||
else | |||
if((any(RTable%AssignmentSwitch==(/1,2,3,4,5,8,9,10,11/))) .and. (RTSwitch /= 0) .and. (IsStopped == .false.) ) 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 | |||
RT_OldTransMode = RTTransmissionLever | |||
RTable%K_throttle = 0 | |||
end if | |||
END subroutine Rtable_MainSolver |
@@ -4,13 +4,14 @@ module TopDriveMain | |||
public | |||
contains | |||
subroutine TopDrive_Setup() | |||
use CSimulationVariables | |||
implicit none | |||
call OnSimulationStop%Add(TopDrive_Stop) | |||
call OnTopDriveStart%Add(TopDrive_Start) | |||
call OnTopDriveStep%Add(TopDrive_Step) | |||
call OnTopDriveMain%Add(TopDriveMainBody) | |||
subroutine TopDrive_Init() | |||
!use CSimulationVariables | |||
!implicit none | |||
!call OnSimulationStop%Add(TopDrive_Stop) | |||
!call OnTopDriveStart%Add(TopDrive_Start) | |||
!call OnTopDriveStep%Add(TopDrive_Step) | |||
!call OnTopDriveMain%Add(TopDriveMainBody) | |||
Call TopDrive_StartUp | |||
end subroutine | |||
subroutine TopDrive_Stop | |||
@@ -26,15 +27,11 @@ module TopDriveMain | |||
subroutine TopDrive_Step | |||
implicit none | |||
call Log_4('TopDrive_Step') | |||
end subroutine TopDrive_Step | |||
Call Rtable_MainSolver | |||
end subroutine TopDrive_Step | |||
subroutine TopDriveMainBody | |||
!use CDataDisplayConsoleVariables | |||
!use CDrillingConsoleVariables | |||
use CSimulationVariables | |||
use TopDrive_VARIABLES | |||
use CDrillWatchVariables | |||
@@ -50,125 +47,24 @@ module TopDriveMain | |||
call Log_4('TopDriveMainBody') | |||
Call TopDrive_StartUp | |||
loopTopDrivestart : do | |||
call sleepqq(10) | |||
!if ( (TopDriveTdsPowerState==-1) .and. (RpmKnob==0.) ) then !FWD | |||
if ( (TopDriveTdsPowerState==-1) ) then !FWD | |||
TDS%SoundBlower = .true. | |||
!Call SetSoundBlowerRT(TDS%SoundBlower) | |||
TopDriveTdsPowerLed = 1 | |||
loopTopDriveswitchFWD: do | |||
CALL DATE_AND_TIME(values=TDS_START_TIME) | |||
!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 | |||
!print*, 'TDSN=', RpmKnob , TDS%N_new | |||
!===> 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 | |||
if ( (TopDriveTdsPowerState/=-1) .or. (IsStopped == .true.) ) then | |||
TDS%SoundBlower = .false. | |||
!Call SetSoundBlowerRT(TDS%SoundBlower) | |||
TopDriveTdsPowerLed = 0 | |||
Call TopDrive_OffMode | |||
exit loopTopDriveswitchFWD | |||
end if | |||
CALL DATE_AND_TIME(values=TDS_END_TIME) | |||
TDS_SolDuration = 100-(TDS_END_TIME(5)*3600000+TDS_END_TIME(6)*60000+TDS_END_TIME(7)*1000+TDS_END_TIME(8)-TDS_START_TIME(5)*3600000-TDS_START_TIME(6)*60000-TDS_START_TIME(7)*1000-TDS_START_TIME(8)) | |||
!print*, 'TDStime=', TDS_SolDuration | |||
if(TDS_SolDuration > 0.0) then | |||
CALL sleepqq(TDS_SolDuration) | |||
end if | |||
end do loopTopDriveswitchFWD | |||
!else if ( (TopDriveTdsPowerState==1) .and. (RpmKnob==0.) ) then !REV | |||
else if ( (TopDriveTdsPowerState==1) ) then !REV | |||
TDS%SoundBlower = .true. | |||
!Call SetSoundBlowerRT(TDS%SoundBlower) | |||
TopDriveTdsPowerLed = 1 | |||
loopTopDrivestart : do | |||
loopTopDriveswitchREV: do | |||
CALL DATE_AND_TIME(values=TDS_START_TIME) | |||
CALL DATE_AND_TIME(values=TDS_START_TIME) | |||
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 | |||
if ( (TopDriveTdsPowerState/=1) .or. (IsStopped == .true.) ) then | |||
TDS%SoundBlower = .false. | |||
!Call SetSoundBlowerRT(TDS%SoundBlower) | |||
TopDriveTdsPowerLed = 0 | |||
Call TopDrive_OffMode | |||
exit loopTopDriveswitchREV | |||
end if | |||
CALL DATE_AND_TIME(values=TDS_END_TIME) | |||
TDS_SolDuration = 100-(TDS_END_TIME(5)*3600000+TDS_END_TIME(6)*60000+TDS_END_TIME(7)*1000+TDS_END_TIME(8)-TDS_START_TIME(5)*3600000-TDS_START_TIME(6)*60000-TDS_START_TIME(7)*1000-TDS_START_TIME(8)) | |||
!print*, 'TDStime=', TDS_SolDuration | |||
if(TDS_SolDuration > 0.0) then | |||
CALL sleepqq(TDS_SolDuration) | |||
end if | |||
Call TopDrive_MainSolver | |||
end do loopTopDriveswitchREV | |||
else | |||
if( TopDriveTdsPowerState /= 0 ) then | |||
TDS%SoundBlower = .true. | |||
!Call SetSoundBlowerRT(TDS%SoundBlower) | |||
TopDriveTdsPowerLed = 1 | |||
else | |||
TDS%SoundBlower = .false. | |||
!Call SetSoundBlowerRT(TDS%SoundBlower) | |||
TopDriveTdsPowerLed = 0 | |||
if (IsStopped == .true.) then | |||
exit loopTopDrivestart | |||
end if | |||
Call TopDrive_OffMode | |||
!exit loopTopDriveswitchFWD | |||
end if | |||
CALL DATE_AND_TIME(values=TDS_END_TIME) | |||
TDS_SolDuration = 100-(TDS_END_TIME(5)*3600000+TDS_END_TIME(6)*60000+TDS_END_TIME(7)*1000+TDS_END_TIME(8)-TDS_START_TIME(5)*3600000-TDS_START_TIME(6)*60000-TDS_START_TIME(7)*1000-TDS_START_TIME(8)) | |||
!print*, 'TDStime=', TDS_SolDuration | |||
if(TDS_SolDuration > 0.0) then | |||
CALL sleepqq(TDS_SolDuration) | |||
end if | |||
if (IsStopped == .true.) then | |||
exit loopTopDrivestart | |||
end if | |||
end do loopTopDrivestart | |||
@@ -0,0 +1,88 @@ | |||
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 |
@@ -14,7 +14,7 @@ subroutine TopDrive_OffMode | |||
!================================================================== | |||
! Rate limit for off Mode | |||
Do while ( ((TDS%N_old-0.0d0)/TDS%time_step)>386.0d0 ) | |||
if ( ((TDS%N_old-0.0d0)/TDS%time_step)>386.0d0 ) then | |||
TDS%N_ref = (-386.0d0*TDS%time_step)+TDS%N_old | |||
!else | |||
! TDS%N_ref=0.0d0 | |||
@@ -32,49 +32,44 @@ subroutine TopDrive_OffMode | |||
! Call SetSoundRtGearCrash(TDS%SoundGearCrash) | |||
!end if | |||
!TDS_OldTransMode = RTTransmissionLever | |||
if ( (TopDriveTdsPowerState==0) .or. (IsStopped == .true.) ) then | |||
TopDriveTdsPowerLed = 0 | |||
end if | |||
Call sleepqq (80) !????????????????? | |||
End Do | |||
!================================================================== | |||
else | |||
TDS%N_ref = 0. | |||
TDS%N_new = 0. | |||
TDS%N_old = 0. | |||
TDS%N_ref = 0. | |||
TDS%N_new = 0. | |||
TDS%N_old = 0. | |||
TDS%ia = 0. | |||
TDS%ia_old = 0. | |||
TDS%ia_new = 0. | |||
TDS%x = 0. | |||
TDS%x_old = 0. | |||
TDS%x_new = 0. | |||
TDS%y = 0. | |||
TDS%y_old = 0. | |||
TDS%y_new = 0. | |||
TDS%w = 0. | |||
TDS%w_old = 0. | |||
TDS%w_new = 0. | |||
TDS%Speed = 0. | |||
TDS_wOld = 0. | |||
TDS%ia = 0. | |||
TDS%ia_old = 0. | |||
TDS%ia_new = 0. | |||
TDS%x = 0. | |||
TDS%x_old = 0. | |||
TDS%x_new = 0. | |||
TDS%y = 0. | |||
TDS%y_old = 0. | |||
TDS%y_new = 0. | |||
TDS%w = 0. | |||
TDS%w_old = 0. | |||
TDS%w_new = 0. | |||
TDS%Speed = 0. | |||
TDS_wOld = 0. | |||
TopDriveOperationFaultLed = 0 | |||
TDS%Speed = 0.d0 !Speed [RPM] | |||
TopDriveRpmGauge = TDS%Speed | |||
TD_RPMUnityOutput = -TopDriveRpmGauge | |||
TDS%SoundRPM = 0 | |||
!Call SetSound( TDS%SoundRPM ) | |||
TDS%Torque = 0.d0 ![ft.lbf] | |||
TopDriveTorqueGauge = 0.d0 ![ft.lbf] | |||
TDS_OldPowerMode = 1 | |||
TDS_OldPowerMode = 0 | |||
TopDriveOperationFaultLed = 0 | |||
TDS%Speed = 0.d0 !Speed [RPM] | |||
TopDriveRpmGauge = TDS%Speed | |||
TD_RPMUnityOutput = -TopDriveRpmGauge | |||
TDS%SoundRPM = 0 | |||
!Call SetSound( TDS%SoundRPM ) | |||
TDS%Torque = 0.d0 ![ft.lbf] | |||
TopDriveTorqueGauge = 0.d0 ![ft.lbf] | |||
TDS_OldPowerMode = 1 | |||
TDS_OldPowerMode = 0 | |||
End if | |||
end subroutine |
@@ -397,6 +397,7 @@ | |||
<File RelativePath=".\Equipments\RotaryTable\RotaryTableMain.f90"/> | |||
<File RelativePath=".\Equipments\RotaryTable\RTable_diff_eqs.f90"/> | |||
<File RelativePath=".\Equipments\RotaryTable\RTable_INPUTS.f90"/> | |||
<File RelativePath=".\Equipments\RotaryTable\Rtable_MainSolver.f90"/> | |||
<File RelativePath=".\Equipments\RotaryTable\RTable_OffMode.f90"/> | |||
<File RelativePath=".\Equipments\RotaryTable\RTable_Solver.f90"/> | |||
<File RelativePath=".\Equipments\RotaryTable\RTable_StartUp.f90"/> | |||
@@ -407,6 +408,7 @@ | |||
<Filter Name="TopDrive"> | |||
<File RelativePath=".\Equipments\TopDrive\TopDrive_diff_eqs.f90"/> | |||
<File RelativePath=".\Equipments\TopDrive\TopDrive_INPUTS.f90"/> | |||
<File RelativePath=".\Equipments\TopDrive\TopDrive_MainSolver.f90"/> | |||
<File RelativePath=".\Equipments\TopDrive\TopDrive_Malfunction_MotorFailure.f90"/> | |||
<File RelativePath=".\Equipments\TopDrive\TopDrive_OffMode.f90"/> | |||
<File RelativePath=".\Equipments\TopDrive\TopDrive_Solver.f90"/> | |||