subroutine Drawworks_Solver Use CDrillingConsoleVariables Use CDataDisplayConsoleVariables Use CHoistingVariables Use CUnityInputs Use Drawworks_VARIABLES Use CHookVariables Use CWarningsVariables Use COperationConditionEnumVariables Use CSlipsEnumVariables Use CElevatorConnectionEnumVariables Use CTdsConnectionModesEnumVariables Use CTdsElevatorModesEnumVariables Use TD_DrillStemComponents Use TD_WellGeometry Use CWarningsVariables Use TD_GeneralData Use CSounds IMPLICIT NONE Integer :: j Integer :: CrownCollision_Status , FloorCollision_Status , CrownWarning_Status , FloorWarning_Status real :: time !>>>>>>>>>>>>>>>>>>>> N_Ref <<<<<<<<<<<<<<<<<<<<<<<< Drawworks%N_Throtle = DWThrottle ![rpm] Drawworks%N_Accelarator = (DWAcceleretor/100.0)*965.0 ![rpm] !print* , 'Drawworks%N_Throtle=' , Drawworks%N_Throtle !print* , 'DWAcceleretor=' , DWAcceleretor !print* , 'Drawworks%N_Accelarator=' , Drawworks%N_Accelarator IF (Drawworks%N_Throtle>Drawworks%N_Accelarator) THEN Drawworks%N_new = Drawworks%N_Throtle !print* , 'Drawworks%N_Throtle' ELSE Drawworks%N_new = Drawworks%N_Accelarator !print* , 'Drawworks%N_Accelarator' END IF if (((Drawworks%N_new-Drawworks%N_old)/Drawworks%time_step)>193.) then Drawworks%N_ref = (193.*Drawworks%time_step)+Drawworks%N_old else if (((Drawworks%N_old-Drawworks%N_new)/Drawworks%time_step)>193.) then Drawworks%N_ref = (-193.*Drawworks%time_step)+Drawworks%N_old else Drawworks%N_ref = Drawworks%N_new end if Drawworks%N_old = Drawworks%N_ref !print* , 'Drawworks%N_ref=' , Drawworks%N_ref Call Drawworks_INPUTS ! Drawworks Malfunction ----> Drive Motor Failure Call DWMalfunction_MotorFailure !=====> Drawworks Gears Abuse if ( DW_OldTransMode==0 .and. Drawworks%TransMode/=0 .and. Drawworks%w_drum/=0. .and. Drawworks%ClutchMode/=0 ) then Call Activate_DrawworksGearsAbuse() Drawworks%SoundGearCrash = .true. Call SetSoundDwGearCrash(Drawworks%SoundGearCrash) Drawworks%ManualBreak = 100. !Drawworks%N_ref = 0. Call DWFixModeMotion Drawworks%SoundRev = INT(Drawworks%w_drum) ![rpm] , Integer Call SetSoundDwRev( Drawworks%SoundRev ) return else Drawworks%SoundGearCrash = .false. Call SetSoundDwGearCrash(Drawworks%SoundGearCrash) end if if ( DrawworksGearsAbuse==1 ) then return end if Call Drawworks_Direction !==================================================== ! Collision & Warning !==================================================== if ( CrownCollision == .false. ) then CrownCollision_Status = 0 end if if ( FloorCollision == .false. ) then FloorCollision_Status = 0 end if !if ( CrownWarning == .false. ) then ! CrownWarning_Status = 0 !end if !if ( FloorWarning == .false. ) then ! FloorWarning_Status = 0 !end if !==================================================== ! Crown Collision (Max_Hook_Height) !==================================================== if ( ((3.280839895*Drawworks%Hook_Height)>=Drawworks%max_Hook_Height) .and. (any(DW_DrillModeCond==(/3,4,7,10,11,12,14/))) ) then if ( CrownCollision_Status==0 .and. Drawworks%motion==1 ) then Call Activate_CrownCollision() CrownCollision_Status = 1 Drawworks%SoundCrownCollision = .true. Call SetSoundCrownCollision(Drawworks%SoundCrownCollision) else Drawworks%SoundCrownCollision = .false. Call SetSoundCrownCollision(Drawworks%SoundCrownCollision) end if do While ( CrownCollision==1 ) Call DWFixModeMotion end do if ( Drawworks%motion==-1 ) then Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft] Call Set_HookHeight(real(Drawworks%Hook_Height_final)) else Call DWFixModeMotion end if return end if !==================================================== ! Floor Collision (Min_Hook_Height) !==================================================== if ( ((3.280839895*Drawworks%Hook_Height)<=Drawworks%min_Hook_Height) .and. (any(DW_DrillModeCond==(/3,4,7,10,11,12,14/))) ) then if ( FloorCollision_Status==0 .and. Drawworks%motion==-1 ) then Call Activate_FloorCollision() Drawworks%SoundFloorCollision = .true. Call SetSoundFloorCollision(Drawworks%SoundFloorCollision) FloorCollision_Status = 1 else Drawworks%SoundFloorCollision = .false. Call SetSoundFloorCollision(Drawworks%SoundFloorCollision) end if Do While ( FloorCollision ==1 ) Call DWFixModeMotion End Do if ( Drawworks%motion==1 ) then Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft] Call Set_HookHeight(real(Drawworks%Hook_Height_final)) else Call DWFixModeMotion end if return end if !==================================================== ! Crown Warning !==================================================== if ( ((3.280839895*Drawworks%Hook_Height)>=Drawworks%max_Hook_Height) .and. (any(DW_DrillModeCond==(/1,2,5,6,8,9,13/))) ) then !if ( crownwarning_Status==0 .and. Drawworks%motion==1 ) then ?????????? ! Call Activate_crownwarning() ?????????? !Drawworks%SoundCrownCollision = .true. !Call SetSoundCrownCollision(Drawworks%SoundCrownCollision) ! CrownWarning_Status = 1 ?????????? !else ! Drawworks%SoundCrownCollision = .false. !Call SetSoundCrownCollision(Drawworks%SoundCrownCollision) !end if ?????????? if ( Drawworks%motion==-1 ) then Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft] Call Set_HookHeight(real(Drawworks%Hook_Height_final)) else Call DWFixModeMotion end if return end if !==================================================== ! Floor Warning !==================================================== if ( ((3.280839895*Drawworks%Hook_Height)<=Drawworks%min_Hook_Height) .and. (any(DW_DrillModeCond==(/1,2,5,6,8,9,13/))) ) then !if ( floorwarning_Status==0 .and. Drawworks%motion==-1 ) then ?????????? ! Call Activate_floorwarning() ?????????? !Drawworks%SoundCrownCollision = .true. !Call SetSoundCrownCollision(Drawworks%SoundCrownCollision) ! floorwarning_Status = 1 ?????????? !else !Drawworks%SoundCrownCollision = .false. !Call SetSoundCrownCollision(Drawworks%SoundCrownCollision) !end if ?????????? if ( Drawworks%motion==1 ) then Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft] Call Set_HookHeight(real(Drawworks%Hook_Height_final)) else Call DWFixModeMotion end if return end if !==================================================== ! ELEVATOR CONNECTION STRING (SLIPS SET , No Motion) !==================================================== if ( DriveType==1 .and. Get_Slips() == SLIPS_SET_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and. Drawworks%motion/=-1 ) then !if ( Drawworks%motion/=-1 ) then Call DWFixModeMotion return !end if end if if ( DriveType==0 .and. Get_Slips() == SLIPS_SET_END .and. (Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_STRING) .and. Drawworks%motion/=-1 ) then !if ( Drawworks%motion/=-1 ) then Call DWFixModeMotion return !end if end if !==================================================== ! RAM & ToolJoint Collision (Top of RAM) !==================================================== Do j = 2,4 !startup problem ??????? if ( TD_BOPElementNo(j)/=0 ) then if ( ((TD_BOPHeight(j)-TD_BOPThickness)<=(TD_DrillStems(TD_BOPElementNo(j))%TopDepth+TD_DrillStems(TD_BOPElementNo(j))%ToolJointRange)) .and. ((TD_BOPHeight(j)-TD_BOPThickness)>TD_DrillStems(TD_BOPElementNo(j))%TopDepth) .and. (TD_BOPRamDiam(j)<(2.d0*12.d0*TD_DrillStems(TD_BOPElementNo(j))%RtoolJoint)) ) then if ( Drawworks%motion==1 ) then Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft] Call Set_HookHeight(real(Drawworks%Hook_Height_final)) else Call DWFixModeMotion end if return end if end if End Do !==================================================== ! RAM & ToolJoint Collision (Bottom of RAM) !==================================================== Do j = 2,4 if ( TD_BOPElementNo(j)/=0 ) then if ( ((TD_BOPHeight(j)+TD_BOPThickness)>=(TD_DrillStems(TD_BOPElementNo(j))%DownDepth-TD_DrillStems(TD_BOPElementNo(j))%ToolJointRange)) .and. ((TD_BOPHeight(j)+TD_BOPThickness)