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.
 
 
 
 
 
 

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