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.
 
 
 
 
 
 

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