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.
 
 
 
 
 
 

380 lines
13 KiB

  1. subroutine Drawworks_Solver
  2. Use CDrillingConsoleVariables
  3. Use CDataDisplayConsoleVariables
  4. Use CHoistingVariables
  5. Use CUnityInputs
  6. Use Drawworks_VARIABLES
  7. Use CHookVariables
  8. Use CWarningsVariables
  9. Use COperationConditionEnumVariables
  10. Use CSlipsEnumVariables
  11. Use COperationScenariosVariables, only: Get_ElevatorConnection
  12. Use CElevatorConnectionEnumVariables
  13. Use CTdsConnectionModesEnumVariables
  14. Use CTdsElevatorModesEnumVariables
  15. Use TD_DrillStemComponents
  16. Use TD_WellGeometry
  17. Use CWarningsVariables
  18. Use TD_GeneralData
  19. Use CSounds
  20. IMPLICIT NONE
  21. Integer :: j
  22. Integer :: CrownCollision_Status , FloorCollision_Status , CrownWarning_Status , FloorWarning_Status
  23. real :: time
  24. !>>>>>>>>>>>>>>>>>>>> N_Ref <<<<<<<<<<<<<<<<<<<<<<<<
  25. Drawworks%N_Throtle = DrillingConsole%DWThrottle ![rpm]
  26. Drawworks%N_Accelarator = (DrillingConsole%DWAcceleretor/100.0)*965.0 ![rpm]
  27. !print* , 'Drawworks%N_Throtle=' , Drawworks%N_Throtle
  28. !print* , 'DWAcceleretor=' , DWAcceleretor
  29. !print* , 'Drawworks%N_Accelarator=' , Drawworks%N_Accelarator
  30. IF (Drawworks%N_Throtle>Drawworks%N_Accelarator) THEN
  31. Drawworks%N_new = Drawworks%N_Throtle
  32. !print* , 'Drawworks%N_Throtle'
  33. ELSE
  34. Drawworks%N_new = Drawworks%N_Accelarator
  35. !print* , 'Drawworks%N_Accelarator'
  36. END IF
  37. if (((Drawworks%N_new-Drawworks%N_old)/Drawworks%time_step)>193.) then
  38. Drawworks%N_ref = (193.*Drawworks%time_step)+Drawworks%N_old
  39. else if (((Drawworks%N_old-Drawworks%N_new)/Drawworks%time_step)>193.) then
  40. Drawworks%N_ref = (-193.*Drawworks%time_step)+Drawworks%N_old
  41. else
  42. Drawworks%N_ref = Drawworks%N_new
  43. end if
  44. Drawworks%N_old = Drawworks%N_ref
  45. !print* , 'Drawworks%N_ref=' , Drawworks%N_ref
  46. Call Drawworks_INPUTS
  47. ! Drawworks Malfunction ----> Drive Motor Failure
  48. Call DWMalfunction_MotorFailure
  49. !=====> Drawworks Gears Abuse
  50. if ( DW_OldTransMode==0 .and. Drawworks%TransMode/=0 .and. Drawworks%w_drum/=0. .and. Drawworks%ClutchMode/=0 ) then
  51. Call Activate_DrawworksGearsAbuse()
  52. Drawworks%SoundGearCrash = .true.
  53. Call SetSoundDwGearCrash(Drawworks%SoundGearCrash)
  54. Drawworks%ManualBreak = 100.
  55. !Drawworks%N_ref = 0.
  56. Call DWFixModeMotion
  57. Drawworks%SoundRev = INT(Drawworks%w_drum) ![rpm] , Integer
  58. Call SetSoundDwRev( Drawworks%SoundRev )
  59. return
  60. else
  61. Drawworks%SoundGearCrash = .false.
  62. Call SetSoundDwGearCrash(Drawworks%SoundGearCrash)
  63. end if
  64. if ( DrawworksGearsAbuse==1 ) then
  65. return
  66. end if
  67. Call Drawworks_Direction
  68. !====================================================
  69. ! Collision & Warning
  70. !====================================================
  71. if ( CrownCollision == .false. ) then
  72. CrownCollision_Status = 0
  73. end if
  74. if ( FloorCollision == .false. ) then
  75. FloorCollision_Status = 0
  76. end if
  77. !if ( CrownWarning == .false. ) then
  78. ! CrownWarning_Status = 0
  79. !end if
  80. !if ( FloorWarning == .false. ) then
  81. ! FloorWarning_Status = 0
  82. !end if
  83. !====================================================
  84. ! Crown Collision (Max_Hook_Height)
  85. !====================================================
  86. if ( ((3.280839895*Drawworks%Hook_Height)>=Drawworks%max_Hook_Height) .and. (any(DW_DrillModeCond==(/3,4,7,10,11,12,14/))) ) then
  87. if ( CrownCollision_Status==0 .and. Drawworks%motion==1 ) then
  88. Call Activate_CrownCollision()
  89. CrownCollision_Status = 1
  90. Drawworks%SoundCrownCollision = .true.
  91. Call SetSoundCrownCollision(Drawworks%SoundCrownCollision)
  92. else
  93. Drawworks%SoundCrownCollision = .false.
  94. Call SetSoundCrownCollision(Drawworks%SoundCrownCollision)
  95. end if
  96. do While ( CrownCollision==1 )
  97. Call DWFixModeMotion
  98. end do
  99. if ( Drawworks%motion==-1 ) then
  100. Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft]
  101. Call Set_HookHeight(real(Drawworks%Hook_Height_final))
  102. else
  103. Call DWFixModeMotion
  104. end if
  105. return
  106. end if
  107. !====================================================
  108. ! Floor Collision (Min_Hook_Height)
  109. !====================================================
  110. if ( ((3.280839895*Drawworks%Hook_Height)<=Drawworks%min_Hook_Height) .and. (any(DW_DrillModeCond==(/3,4,7,10,11,12,14/))) ) then
  111. if ( FloorCollision_Status==0 .and. Drawworks%motion==-1 ) then
  112. Call Activate_FloorCollision()
  113. Drawworks%SoundFloorCollision = .true.
  114. Call SetSoundFloorCollision(Drawworks%SoundFloorCollision)
  115. FloorCollision_Status = 1
  116. else
  117. Drawworks%SoundFloorCollision = .false.
  118. Call SetSoundFloorCollision(Drawworks%SoundFloorCollision)
  119. end if
  120. Do While ( FloorCollision ==1 )
  121. Call DWFixModeMotion
  122. End Do
  123. if ( Drawworks%motion==1 ) then
  124. Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft]
  125. Call Set_HookHeight(real(Drawworks%Hook_Height_final))
  126. else
  127. Call DWFixModeMotion
  128. end if
  129. return
  130. end if
  131. !====================================================
  132. ! Crown Warning
  133. !====================================================
  134. if ( ((3.280839895*Drawworks%Hook_Height)>=Drawworks%max_Hook_Height) .and. (any(DW_DrillModeCond==(/1,2,5,6,8,9,13/))) ) then
  135. !if ( crownwarning_Status==0 .and. Drawworks%motion==1 ) then ??????????
  136. ! Call Activate_crownwarning() ??????????
  137. !Drawworks%SoundCrownCollision = .true.
  138. !Call SetSoundCrownCollision(Drawworks%SoundCrownCollision)
  139. ! CrownWarning_Status = 1 ??????????
  140. !else
  141. ! Drawworks%SoundCrownCollision = .false.
  142. !Call SetSoundCrownCollision(Drawworks%SoundCrownCollision)
  143. !end if ??????????
  144. if ( Drawworks%motion==-1 ) then
  145. Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft]
  146. Call Set_HookHeight(real(Drawworks%Hook_Height_final))
  147. else
  148. Call DWFixModeMotion
  149. end if
  150. return
  151. end if
  152. !====================================================
  153. ! Floor Warning
  154. !====================================================
  155. if ( ((3.280839895*Drawworks%Hook_Height)<=Drawworks%min_Hook_Height) .and. (any(DW_DrillModeCond==(/1,2,5,6,8,9,13/))) ) then
  156. !if ( floorwarning_Status==0 .and. Drawworks%motion==-1 ) then ??????????
  157. ! Call Activate_floorwarning() ??????????
  158. !Drawworks%SoundCrownCollision = .true.
  159. !Call SetSoundCrownCollision(Drawworks%SoundCrownCollision)
  160. ! floorwarning_Status = 1 ??????????
  161. !else
  162. !Drawworks%SoundCrownCollision = .false.
  163. !Call SetSoundCrownCollision(Drawworks%SoundCrownCollision)
  164. !end if ??????????
  165. if ( Drawworks%motion==1 ) then
  166. Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft]
  167. Call Set_HookHeight(real(Drawworks%Hook_Height_final))
  168. else
  169. Call DWFixModeMotion
  170. end if
  171. return
  172. end if
  173. !====================================================
  174. ! ELEVATOR CONNECTION STRING (SLIPS SET , No Motion)
  175. !====================================================
  176. if ( Hoisting%DriveType==1 .and. Get_Slips() == SLIPS_SET_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and. Drawworks%motion/=-1 ) then
  177. !if ( Drawworks%motion/=-1 ) then
  178. Call DWFixModeMotion
  179. return
  180. !end if
  181. end if
  182. if ( Hoisting%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
  183. !if ( Drawworks%motion/=-1 ) then
  184. Call DWFixModeMotion
  185. return
  186. !end if
  187. end if
  188. !====================================================
  189. ! RAM & ToolJoint Collision (Top of RAM)
  190. !====================================================
  191. Do j = 2,4 !startup problem ???????
  192. if ( TD_BOPElementNo(j)/=0 ) then
  193. 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
  194. if ( Drawworks%motion==1 ) then
  195. Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft]
  196. Call Set_HookHeight(real(Drawworks%Hook_Height_final))
  197. else
  198. Call DWFixModeMotion
  199. end if
  200. return
  201. end if
  202. end if
  203. End Do
  204. !====================================================
  205. ! RAM & ToolJoint Collision (Bottom of RAM)
  206. !====================================================
  207. Do j = 2,4
  208. if ( TD_BOPElementNo(j)/=0 ) then
  209. if ( ((TD_BOPHeight(j)+TD_BOPThickness)>=(TD_DrillStems(TD_BOPElementNo(j))%DownDepth-TD_DrillStems(TD_BOPElementNo(j))%ToolJointRange)) .and. ((TD_BOPHeight(j)+TD_BOPThickness)<TD_DrillStems(TD_BOPElementNo(j))%DownDepth) .and. (TD_BOPRamDiam(j)<(2.d0*12.d0*TD_DrillStems(TD_BOPElementNo(j))%RtoolJoint)) ) then
  210. if ( Drawworks%motion==-1 ) then
  211. Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft]
  212. Call Set_HookHeight(real(Drawworks%Hook_Height_final))
  213. else
  214. Call DWFixModeMotion
  215. end if
  216. return
  217. end if
  218. end if
  219. End Do
  220. !====================================================
  221. ! TopDrive (TdsStemIn)
  222. !====================================================
  223. if ( (Hoisting%DriveType==0) .and. (Get_TdsStemIn()) .and. Get_Slips() == SLIPS_SET_END ) then
  224. if ( Drawworks%motion==1 ) then
  225. Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft]
  226. Call Set_HookHeight(real(Drawworks%Hook_Height_final))
  227. else
  228. Call DWFixModeMotion
  229. end if
  230. return
  231. end if
  232. !print* , 'Drawworks%Hook_Height_final15=' , Drawworks%Hook_Height_final , TD_DrillStemBottom , int(TD_DrillStemBottom*1000.d0) , int((TD_WellTotalLength+TD_DlMax)*1000.d0) , (TD_WellTotalLength+TD_DlMax) , Drawworks%motion , StringIsBottomOfWell
  233. !=====> BottomHole ROP Condition
  234. if ( (int(TD_DrillStemBottom*10000.d0)>=(int((TD_WellTotalLength+TD_DlMax)*10000.d0))) .and. (Drawworks%motion==-1 .or. Drawworks%motion==0) ) then
  235. !print* , 'Drawworks%Hook_Height_final10=' , Drawworks%Hook_Height_final , TD_DrillStemBottom , (TD_WellTotalLength+TD_DlMax)
  236. if ( StringIsBottomOfWell==0 ) then
  237. Drawworks%Hook_Height_final = Drawworks%Hook_Height_final+(TD_DrillStemBottom-(TD_WellTotalLength+TD_DlMax))
  238. StringIsBottomOfWell = 1
  239. !print* , 'Drawworks%Hook_Height_final11=' , Drawworks%Hook_Height_final , TD_DrillStemBottom , (TD_WellTotalLength+TD_DlMax)
  240. end if
  241. Call DWFixModeMotion
  242. !print* , 'Drawworks%Hook_Height_final12=' , Drawworks%Hook_Height_final
  243. !print* , 'bef return1'
  244. return
  245. !print* , 'aft return1'
  246. else
  247. StringIsBottomOfWell = 0
  248. end if
  249. Drawworks%Hook_Height_final = 3.280839895*Drawworks%Hook_Height ![ft]
  250. call Set_HookHeight(real(Drawworks%Hook_Height_final))
  251. Drawworks%HookHeight_graph_output = 0.1189*((3.280839895*Drawworks%Hook_Height)-28.0)-2.6 ![ft]
  252. !print*, 'Drawworks%motion=' , Drawworks%motion
  253. !print*, 'Drawworks%Hook_Height_final=' , Drawworks%Hook_Height_final
  254. !print*, 'Drawworks%ia_new=' , Drawworks%ia_new
  255. !print*, 'Drawworks%ia_ref=' , Drawworks%ia_ref
  256. !print*, 'Drawworks%dia=' , Drawworks%dia
  257. !print*, 'Drawworks%dw=' , Drawworks%dw
  258. !print*, 'Drawworks%w_new=' , Drawworks%w_new
  259. end subroutine Drawworks_Solver