Simulation Core
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 
 
 

283 lines
9.6 KiB

  1. subroutine Drawworks_Solver
  2. Use CUnityInputs
  3. Use UnitySignalVariables
  4. Use Drawworks_VARIABLES
  5. Use CKellyConnectionEnumVariables
  6. Use CElevatorConnectionEnumVariables
  7. Use CTdsConnectionModesEnumVariables
  8. Use CTdsElevatorModesEnumVariables
  9. Use COperationScenariosVariables
  10. IMPLICIT NONE
  11. Integer :: j
  12. Integer :: CrownCollision_Status , FloorCollision_Status , CrownWarning_Status , FloorWarning_Status
  13. !>>>>>>>>>>>>>>>>>>>> Speed <<<<<<<<<<<<<<<<<<<<<<<<
  14. Drawworks%N_Throtle = Drawworks%Throttle ![rpm]
  15. !Drawworks%N_Accelarator = (Drawworks%Acceleretor/100.d0)*965.d0 ![rpm]
  16. !IF (Drawworks%N_Throtle>Drawworks%N_Accelarator) THEN
  17. Drawworks%N_new = Drawworks%N_Throtle
  18. !ELSE
  19. ! Drawworks%N_new = Drawworks%N_Accelarator
  20. !END IF
  21. !========================== Drawworks Rate limit ==========================
  22. if (((Drawworks%N_new-Drawworks%N_old)/Drawworks%time_step)>Drawworks%RateChange) then
  23. Drawworks%Speed =(Drawworks%RateChange*Drawworks%time_step)+Drawworks%N_old ![rpm]
  24. else if (((Drawworks%N_old-Drawworks%N_new)/Drawworks%time_step)>Drawworks%RateChange) then
  25. Drawworks%Speed = (-Drawworks%RateChange*Drawworks%time_step)+Drawworks%N_old
  26. else
  27. Drawworks%Speed = Drawworks%N_new
  28. end if
  29. !=======================================================================
  30. !========================== Speed Correction ==========================
  31. !===> SLIPS SET , No Motion
  32. if ( Drawworks%DriveType==1 .and. Get_Slips() == SLIPS_SET_END .and. Get_KellyConnection() == KELLY_CONNECTION_STRING ) then
  33. Drawworks%Speed = 0.d0
  34. end if
  35. if ( Drawworks%DriveType==0 .and. Get_Slips() == SLIPS_SET_END .and. (Get_TdsConnectionModes()==TDS_CONNECTION_SPINE .or. Get_TdsConnectionModes()==TDS_CONNECTION_STRING) ) then
  36. Drawworks%Speed = 0.d0
  37. end if
  38. !===> Closed BOP Rams , No Motion
  39. if ( Drawworks%ShearBopSituation==1 .and. (any(Drawworks%DrillModeCond==(/3,10,19,20,24/))) ) then
  40. Drawworks%Speed = 0.d0
  41. end if
  42. !=======================================================================
  43. Call Drawworks_Direction
  44. !====================================================
  45. ! Collision & Warning
  46. !====================================================
  47. if ( Drawworks%CrownCollision == .false. ) then
  48. CrownCollision_Status = 0
  49. end if
  50. if ( Drawworks%FloorCollision == .false. ) then
  51. FloorCollision_Status = 0
  52. end if
  53. !====================================================
  54. ! Crown Collision (Max_Hook_Height)
  55. !====================================================
  56. if ( ((3.280839895d0*Drawworks%Hook_Height)>=Drawworks%max_Hook_Height) .and. (any(Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then
  57. if ( CrownCollision_Status==0 .and. Drawworks%motion==1 ) then
  58. CrownCollision_Status = 1
  59. Drawworks%CrownCollision = .true.
  60. Drawworks%SoundCrownCollision = .true.
  61. else
  62. Drawworks%SoundCrownCollision = .false.
  63. end if
  64. if ( Drawworks%motion==-1 .and. Drawworks%CrownCollision==.false. ) then
  65. Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft]
  66. else
  67. Call DWFixModeMotion
  68. end if
  69. return
  70. end if
  71. !====================================================
  72. ! Floor Collision (Min_Hook_Height)
  73. !====================================================
  74. if ( ((3.280839895*Drawworks%Hook_Height)<=Drawworks%min_Hook_Height) .and. (any(Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then
  75. if ( FloorCollision_Status==0 .and. Drawworks%motion==-1 ) then
  76. FloorCollision_Status = 1
  77. Drawworks%FloorCollision = .true.
  78. Drawworks%SoundFloorCollision = .true.
  79. else
  80. Drawworks%SoundFloorCollision = .false.
  81. end if
  82. if ( Drawworks%motion==1 .and. Drawworks%FloorCollision==.false. ) then
  83. Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft]
  84. else
  85. Call DWFixModeMotion
  86. end if
  87. return
  88. end if
  89. !====================================================
  90. ! Crown Warning
  91. !====================================================
  92. if ( ((3.280839895*Drawworks%Hook_Height)>=Drawworks%max_Hook_Height) .and. (any(Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then
  93. if ( Drawworks%motion==-1 ) then
  94. Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft]
  95. else
  96. Call DWFixModeMotion
  97. end if
  98. return
  99. end if
  100. !====================================================
  101. ! Floor Warning
  102. !====================================================
  103. if ( ((3.280839895*Drawworks%Hook_Height)<=Drawworks%min_Hook_Height) .and. (any(Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then
  104. if ( Drawworks%motion==1 ) then
  105. Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft]
  106. else
  107. Call DWFixModeMotion
  108. end if
  109. return
  110. end if
  111. !====================================================
  112. ! ELEVATOR CONNECTION STRING (SLIPS SET , No Motion)
  113. !====================================================
  114. if ( Drawworks%DriveType==1 .and. Get_Slips() == SLIPS_SET_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and. Drawworks%motion/=-1 ) then
  115. Call DWFixModeMotion
  116. return
  117. end if
  118. if ( Drawworks%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
  119. Call DWFixModeMotion
  120. return
  121. end if
  122. !====================================================
  123. ! RAM & ToolJoint Collision (Top of RAM)
  124. !====================================================
  125. Do j = 2,4 !startup problem ???????
  126. if ( Drawworks%TDBOPElementNo(j)/=0 ) then
  127. if ( ((Drawworks%TDBOPHeight(j)-Drawworks%TDBOPThickness)<=(Drawworks%TDDrillStemsTopDepth(Drawworks%TDBOPElementNo(j))+Drawworks%TDDrillStemsToolJointRange(Drawworks%TDBOPElementNo(j)))) .and. ((Drawworks%TDBOPHeight(j)-Drawworks%TDBOPThickness)>Drawworks%TDDrillStemsTopDepth(Drawworks%TDBOPElementNo(j))) .and. (Drawworks%TDBOPRamDiam(j)<(2.d0*12.d0*Drawworks%TDDrillStemsRtoolJoint(Drawworks%TDBOPElementNo(j)))) ) then
  128. if ( Drawworks%motion==1 ) then
  129. Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft]
  130. else
  131. Call DWFixModeMotion
  132. end if
  133. return
  134. end if
  135. end if
  136. End Do
  137. !====================================================
  138. ! RAM & ToolJoint Collision (Bottom of RAM)
  139. !====================================================
  140. Do j = 2,4
  141. if ( Drawworks%TDBOPElementNo(j)/=0 ) then
  142. if ( ((Drawworks%TDBOPHeight(j)+Drawworks%TDBOPThickness)>=(Drawworks%TDDrillStemsDownDepth(Drawworks%TDBOPElementNo(j))-Drawworks%TDDrillStemsToolJointRange(Drawworks%TDBOPElementNo(j)))) .and. ((Drawworks%TDBOPHeight(j)+Drawworks%TDBOPThickness)<Drawworks%TDDrillStemsDownDepth(Drawworks%TDBOPElementNo(j))) .and. (Drawworks%TDBOPRamDiam(j)<(2.d0*12.d0*Drawworks%TDDrillStemsRtoolJoint(Drawworks%TDBOPElementNo(j)))) ) then
  143. if ( Drawworks%motion==-1 ) then
  144. Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft]
  145. else
  146. Call DWFixModeMotion
  147. end if
  148. return
  149. end if
  150. end if
  151. End Do
  152. !====================================================
  153. ! TopDrive (TdsStemIn)
  154. !====================================================
  155. if ( (Drawworks%DriveType==0) .and. (Get_TdsStemIn()) .and. Get_Slips() == SLIPS_SET_END ) then
  156. if ( Drawworks%motion==1 ) then
  157. Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft]
  158. else
  159. Call DWFixModeMotion
  160. end if
  161. return
  162. end if
  163. !=====> BottomHole ROP Condition
  164. if ( (int(Drawworks%TDDrillStemBottom*10000.d0)>=(int((Drawworks%TDWellTotalLength+Drawworks%TDDlMax)*10000.d0))) .and. (Drawworks%motion==-1 .or. Drawworks%motion==0) ) then
  165. if ( Drawworks%StringIsBottomOfWell==0 ) then
  166. Drawworks%Hook_Height_final = Drawworks%Hook_Height_final+(Drawworks%TDDrillStemBottom-(Drawworks%TDWellTotalLength+Drawworks%TDDlMax))
  167. Drawworks%StringIsBottomOfWell = 1
  168. end if
  169. Call DWFixModeMotion
  170. return
  171. else
  172. Drawworks%StringIsBottomOfWell = 0
  173. end if
  174. Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft]
  175. Drawworks%HookHeight_graph_output = 0.1189d0*((3.280839895d0*Drawworks%Hook_Height)-28.d0)-2.6d0 ![ft]
  176. end subroutine Drawworks_Solver