|
- module DrawworksMain
- implicit none
- public
- contains
-
- subroutine Drawworks_Setup()
- use CSimulationVariables
- implicit none
- call OnSimulationInitialization%Add(Drawworks_Init)
- call OnSimulationStop%Add(Drawworks_Init)
- call OnDrawworksStep%Add(Drawworks_Step)
- call OnDrawworksOutput%Add(Drawworks_Output)
- call OnDrawworksMain%Add(DrawworksMainBody)
- end subroutine
-
- subroutine Drawworks_Init
- implicit none
- end subroutine Drawworks_Init
-
- subroutine Drawworks_Step
- implicit none
- end subroutine Drawworks_Step
-
- subroutine Drawworks_Output
- implicit none
- end subroutine Drawworks_Output
-
- subroutine DrawworksMainBody
-
- use CDrillingConsoleVariables
- use CDataDisplayConsoleVariables
- use CHoistingVariables
- use CSimulationVariables
- use Drawworks_VARIABLES
- use CHookVariables
- use CWarningsVariables
- use CSounds
-
-
- implicit none
-
- integer,dimension(8) :: DW_START_TIME, DW_END_TIME
- INTEGER :: DW_SolDuration
-
-
-
-
- Call Drawworks_StartUp
- loopdrawsim : do
-
- CALL DATE_AND_TIME(values=DW_START_TIME)
- if (IsPortable) then
- Drawworks%AssignmentSwitch = 1
- else
- Drawworks%AssignmentSwitch = AssignmentSwitch
- end if
- if((any(Drawworks%AssignmentSwitch==(/1,2,3,4,5,7,8,9,10,11/))) .and. (DWSwitch==-1) .and. (DWThrottle==0.)) then
-
-
- Drawworks%SoundBlower = .true.
- Call SetSoundBlowerDW(Drawworks%SoundBlower)
- DWBLWR = 1
-
- loopDrawworks1 : do
-
- CALL DATE_AND_TIME(values=DW_START_TIME)
- if (IsPortable) then
- Drawworks%AssignmentSwitch = 1
- else
- Drawworks%AssignmentSwitch = AssignmentSwitch
- end if
- if(any(Drawworks%AssignmentSwitch==(/1,2,5,7,8,9,10,11/))) then
- Drawworks%NumberOfTracMotor = 2.0d0
- else if (any(Drawworks%AssignmentSwitch==(/3,4/))) then
- Drawworks%NumberOfTracMotor = 1.0d0
- end if
-
- Call Drawworks_Solver
- DW_TDHookHeight = Drawworks%Hook_Height_final
- if ( Drawworks%motion==+1 ) then
- Drawworks%SoundRev = 0 ![rpm] , Integer
- Call SetSoundDwRev( Drawworks%SoundRev )
- Drawworks%SoundFw = INT(Drawworks%w_drum) ![rpm] , Integer
- Call SetSoundDwFw(Drawworks%SoundFw)
- Call DWBrakeSound
- else
- Drawworks%SoundFw = 0 ![rpm] , Integer
- Call SetSoundDwFw(Drawworks%SoundFw)
- Drawworks%SoundRev = INT(Drawworks%w_drum) ![rpm] , Integer
- Call SetSoundDwRev( Drawworks%SoundRev )
- Call DWBrakeSound
- end if
- DW_OldTransMode = DWTransmisionLever
-
- if (IsPortable) then
- Drawworks%AssignmentSwitch = 1
- else
- Drawworks%AssignmentSwitch = AssignmentSwitch
- end if
- if ((any(Drawworks%AssignmentSwitch==(/6,12/))) .or. (any(DWSwitch==(/0,1/))) .or. (IsStopped == .true.)) then
- Drawworks%SoundBlower = .false.
- Call SetSoundBlowerDW(Drawworks%SoundBlower)
- DWBLWR = 0
- !Call Drawworks_Solver_FreeTractionMotor
- exit loopDrawworks1
- end if
-
- CALL DATE_AND_TIME(values=DW_END_TIME)
- DW_SolDuration = 100-(DW_END_TIME(5)*3600000+DW_END_TIME(6)*60000+DW_END_TIME(7)*1000+DW_END_TIME(8)-DW_START_TIME(5)*3600000-DW_START_TIME(6)*60000-DW_START_TIME(7)*1000-DW_START_TIME(8))
- if(DW_SolDuration > 0.0d0) then
- CALL sleepqq(DW_SolDuration)
- end if
-
- end do loopDrawworks1
-
-
- else
-
-
- if (IsPortable) then
- Drawworks%AssignmentSwitch = 1
- else
- Drawworks%AssignmentSwitch = AssignmentSwitch
- end if
- if((any(Drawworks%AssignmentSwitch==(/1,2,3,4,5,7,8,9,10,11/))) .and. (DWSwitch==-1)) then
- Drawworks%SoundBlower = .true.
- Call SetSoundBlowerDW(Drawworks%SoundBlower)
- DWBLWR = 1
- else
- Drawworks%SoundBlower = .false.
- Call SetSoundBlowerDW(Drawworks%SoundBlower)
- DWBLWR = 0
- end if
-
- Call Drawworks_Solver_FreeTractionMotor
- DW_TDHookHeight = Drawworks%Hook_Height_final
- if ( Drawworks%motion==+1 ) then
- Drawworks%SoundRev = 0 ![rpm] , Integer
- Call SetSoundDwRev( Drawworks%SoundRev )
- Drawworks%SoundFw = INT(Drawworks%w_drum) ![rpm] , Integer
- Call SetSoundDwFw(Drawworks%SoundFw)
- Call DWBrakeSound
- else
- Drawworks%SoundFw = 0 ![rpm] , Integer
- Call SetSoundDwFw(Drawworks%SoundFw)
- Drawworks%SoundRev = INT(Drawworks%w_drum) ![rpm] , Integer
- Call SetSoundDwRev( Drawworks%SoundRev )
- Call DWBrakeSound
- end if
- DW_OldTransMode = DWTransmisionLever
-
-
- end if
-
- if (IsStopped == .true.) then
- exit loopdrawsim
- end if
-
-
- CALL DATE_AND_TIME(values=DW_END_TIME)
- DW_SolDuration = 100-(DW_END_TIME(5)*3600000+DW_END_TIME(6)*60000+DW_END_TIME(7)*1000+DW_END_TIME(8)-DW_START_TIME(5)*3600000-DW_START_TIME(6)*60000-DW_START_TIME(7)*1000-DW_START_TIME(8))
- !print*, 'time=', DW_SolDuration
- if(DW_SolDuration > 0.0d0) then
- CALL sleepqq(DW_SolDuration)
- end if
-
- end do loopdrawsim
-
- end subroutine DrawworksMainBody
-
- end module DrawworksMain
|