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.
 
 
 
 
 
 

830 lines
29 KiB

  1. module Simulator
  2. use IFPORT
  3. use RedisInterface
  4. use Bop
  5. use PumpsMain
  6. use RopMain
  7. use RotaryTableMain
  8. use DrawworksMain
  9. use FluidFlowMain
  10. use TorqueDragMain
  11. use MudSystemMain
  12. use PipeRams1Main
  13. use PipeRams2Main
  14. use KillLineMain
  15. use ChokeLineMain
  16. use BlindRamsMain
  17. use AnnularMain
  18. use TopDriveMain
  19. use CManifolds
  20. use GeoMain
  21. use ChokeControlMain
  22. use COperationScenariosMain
  23. ! For Json read and write
  24. use CStringConfiguration
  25. use CFormation
  26. use CReservoir
  27. use CShoe
  28. use CAccumulator
  29. use CBopStack
  30. use CHoisting
  31. use CPower
  32. use CPumpsVariables
  33. use CRigSize
  34. use CCasingLinerChoke
  35. use CPathGeneration
  36. use CWellSurveyData
  37. use MudPropertiesModule
  38. use CBitProblems
  39. use CBopProblems
  40. use CChokeProblems
  41. use CDrillStemProblems
  42. use CGaugesProblems
  43. use CHoistingProblems
  44. use CKickProblems
  45. use CLostProblems
  46. use CMudTreatmentProblems
  47. use COtherProblems
  48. use CPumpProblems
  49. use CRotaryProblems
  50. use OperationScenariosModule
  51. use PermissionsModule
  52. use UnitySignalsModule
  53. use CBopControlPanel
  54. use CChokeControlPanel
  55. use CChokeManifold
  56. use CDataDisplayConsole
  57. use CDrillingConsole
  58. use CHook
  59. use CStandPipeManifold
  60. use CTopDrivePanel
  61. use DrillingWatchModule
  62. use CTanks
  63. use UnityModule
  64. implicit none
  65. type(json_core):: jsoncore
  66. integer :: simulationStatus,simulationSpeed,msPerStep,simulationEnd,simulationStep
  67. logical::Kelly_ConnectionNothing_in_progress=.false.
  68. character(len=:),allocatable::redisInput
  69. character(len=:),allocatable::redisOutput,operationScenarioEvent
  70. character(len=100)::simulationId
  71. enum, bind(c)
  72. enumerator :: PLAY = 1
  73. enumerator :: PAUSE = 2
  74. enumerator :: STOP = 3
  75. enumerator :: PLAY_TO_DETERMINED_TIME = 4
  76. end enum
  77. contains
  78. FUNCTION time_ms()
  79. INTEGER(8) :: time_ms
  80. integer,dimension(8)::timearray
  81. call date_and_time(values=timearray)
  82. time_ms = timearray(8)+timearray(7)*1000 + timearray(6)*60000 + timearray(5)*60000*600000 +timearray(4)*24*60000*60000
  83. RETURN
  84. END FUNCTION
  85. subroutine Simulate(redis_host,redis_port,redis_password, sim_id,stepTime,print_freq)
  86. character(len=*) :: redis_host,redis_password, sim_id
  87. integer::t0,t1,t2,t3,t_read=0,t_write=0,t_exec=0,i,status,redis_port,stepTime,print_freq
  88. integer(8),dimension(12)::t,t_modules
  89. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  90. simulationId = sim_id
  91. do i=1,size(t_modules)
  92. t_modules(i)=0
  93. end do
  94. ! call initSimulation(configFilename)
  95. call initConnection(redis_host,redis_port,redis_password, sim_id,status)
  96. if (status<0) then
  97. print *,"Can not init connection to redis."
  98. stop
  99. endif
  100. call read_configuration()
  101. ! call read_variables()
  102. print *,"connection initialized"
  103. call init_modules()
  104. print *,"modules initialized"
  105. ! call cpu_time(T1)
  106. simulationStep = 1
  107. !$omp parallel sections
  108. !$omp section
  109. call listenToChannel()
  110. !$omp section
  111. ! call sleepqq(100000)
  112. do while (.true.)
  113. if(mod(simulationStep,print_freq)==0) then
  114. print_log=.true.
  115. else
  116. print_log=.false.
  117. endif
  118. if(mod(simulationStep,10)==0) call publishMessageToChannel("ack")
  119. if(simulationStep>100) exit
  120. t0 = time_ms()
  121. if(print_log) print *,"simulationStep = ",simulationStep
  122. call read_variables()
  123. if(simulationStatus==PLAY_TO_DETERMINED_TIME .and. simulationStep>simulationEnd) exit
  124. if(simulationStatus==STOP) exit
  125. if(simulationStatus==PAUSE) then
  126. if(print_log) print *, "Paused"
  127. call sleepqq(stepTime)
  128. go to 211
  129. endif
  130. t1 = time_ms()
  131. t_read = t_read+t1-t0
  132. call logg(4,"read completed")
  133. !! Rafiee, nothing changed
  134. call BopStack_Step()
  135. t(1) = time_ms()
  136. t_modules(1) = t_modules(1)+t(1)-t1
  137. !! Tarmigh, now is rewritten
  138. call Pumps_MainSolver()
  139. t(2) = time_ms()
  140. t_modules(2) = t_modules(2)+t(2)-t(1)
  141. !call Pump2_Step()
  142. !! Rafiee
  143. call ChokeControl_Step()
  144. t(3) = time_ms()
  145. t_modules(3) = t_modules(3)+t(3)-t(2)
  146. !! Tarmigh, now is rewritten
  147. call RotaryTable_Step()
  148. t(4) = time_ms()
  149. t_modules(4) = t_modules(4)+t(4)-t(3)
  150. !! Tarmigh, now is rewritten
  151. call Drawworks_Step()
  152. t(5) = time_ms()
  153. t_modules(5) = t_modules(5)+t(5)-t(4)
  154. !! Rafiee
  155. call MudSystem_Step()
  156. !! Rafiee
  157. call PipeRams1_Step()
  158. call PipeRams2_Step()
  159. !! Rafiee
  160. call KillLine_Step()
  161. t(6) = time_ms()
  162. t_modules(6) = t_modules(6)+t(6)-t(5)
  163. !! Rafiee
  164. call ChokeLine_Step()
  165. t(7) = time_ms()
  166. t_modules(7) = t_modules(7)+t(7)-t(6)
  167. call BlindRams_Step()
  168. t(8) = time_ms()
  169. t_modules(8) = t_modules(8)+t(8)-t(7)
  170. call Annular_Step()
  171. t(9) = time_ms()
  172. t_modules(9) = t_modules(9)+t(9)-t(8)
  173. !!Tarmigh. Step must rewrittem
  174. call TopDrive_Step()
  175. t(10) = time_ms()
  176. t_modules(10) = t_modules(10)+t(10)-t(9)
  177. ! call Geo_Step()
  178. !!Ahmadi
  179. call PathFinding_Step()
  180. t(11) = time_ms()
  181. t_modules(11) = t_modules(11)+t(11)-t(10)
  182. !! Ahmadi
  183. call OperationScenarios_Step()
  184. !! Sheikh
  185. call FluidFlow_Step()
  186. !! Write variables to shared files
  187. t2 = time_ms()
  188. ! stepTime = t2-t1
  189. t_modules(12) = t_modules(12)+t2-t(11)
  190. t_exec = t_exec+t2-t1
  191. ! call date_and_time(values=timearray)
  192. ! t0 = time_ms()
  193. call write_variables()
  194. t3 = time_ms()
  195. if(t3-t0 < stepTime) then
  196. call sleepqq(stepTime-t3+t0)
  197. else
  198. print *,"Simulation step can not be complete in 100 ms. step time=",t3-t0
  199. endif
  200. t_write = t_write+t3-t2
  201. ! print *,"write completed"
  202. ! print *,"t=",t
  203. simulationStep = simulationStep + 1
  204. 211 end do
  205. !$omp end parallel sections
  206. ! call write_variables()
  207. ! call json%print(jsonroot,'test.json')
  208. ! call json%destroy(jsonroot)
  209. do i=1,size(t)
  210. print *,"t_modules(",i,")=",t_modules(i)
  211. end do
  212. print *,"Number of steps =",simulationStep-1
  213. print *,"Read Time (from redis) =",t_read
  214. print *,"Write Time (to redis)=",t_write
  215. print *,"Simulation Time =",t_exec
  216. print *,"Total Time =",t_read+t_write+t_exec
  217. end subroutine Simulate
  218. subroutine write_variables()
  219. ! use CAccumulator
  220. use json_module
  221. implicit none
  222. type(json_value),pointer :: jsonroot
  223. ! character(len=:),allocatable::redisInput
  224. character(len=10)::str
  225. call jsoncore%initialize()
  226. call jsoncore%create_object(jsonroot,'')
  227. ! print *,"status=",simulationStatus
  228. ! call json%add(jsonroot,'status',simulationStatus)
  229. ! call json%add(jsonroot,'speed',simulationSpeed)
  230. ! call json%add(jsonroot,'endstep',simulationEnd)
  231. call jsoncore%add(jsonroot,'step',simulationStep)
  232. ! call ConfigurationToJson(jsonroot)
  233. call WarningsToJson(jsonroot)
  234. ! call ProblemsToJson(jsonroot)
  235. call EquipmentsToJson(jsonroot)
  236. call StateToJson(jsonroot)
  237. call jsoncore%print_to_string(jsonroot,redisInput)
  238. if(log_level>4) then
  239. write(str, '(I0)') len(redisInput)
  240. print *,"Writing to redis:"//trim(str)
  241. endif
  242. call setData(redisInput)
  243. ! nullify(redisContent)
  244. ! deallocate(redisContent)
  245. ! call json%destroy(pval)
  246. call jsoncore%destroy(jsonroot)
  247. ! print *,"write ends"
  248. end subroutine
  249. subroutine read_configuration()
  250. type(json_value),pointer :: jsonroot,pval
  251. type(json_file) :: jsonfile
  252. type(json_core)::json
  253. integer::len
  254. ! character(len=:),allocatable::redisOutput
  255. ! call getData3(simulationId,redisOutput)
  256. call getData(redisOutput,len)
  257. ! print *,len(redisOutput)," bytes read from redis"
  258. open(1,file="redisContent.json",status="REPLACE")
  259. write(1,"(A)") redisOutput
  260. close(1)
  261. call jsonfile%initialize()
  262. call jsonfile%get_core(json)
  263. call jsonfile%deserialize(redisOutput(1:len))
  264. call jsonfile%json_file_get_root(jsonroot)
  265. ! call json%info(jsonvalue, n_children=n_children)
  266. ! print *,"n_children =",n_children
  267. call json%get(jsonroot,'status',pval)
  268. call json%get(pval,simulationStatus)
  269. call json%get(jsonroot,'speed',pval)
  270. call json%get(pval,simulationSpeed)
  271. if(simulationSpeed==0) simulationSpeed = 1
  272. msPerStep = 100/simulationSpeed
  273. call json%get(jsonroot,'endstep',pval)
  274. call json%get(pval,simulationEnd)
  275. call ConfigurationFromJson(jsonfile)
  276. call jsonfile%destroy()
  277. end subroutine
  278. subroutine read_variables()
  279. type(json_value),pointer :: jsonroot,pval
  280. type(json_file) :: jsonfile
  281. type(json_core)::json
  282. integer::stat,leng
  283. logical::found
  284. call getData(redisOutput,leng)
  285. ! open(1,file="redisContent.json",status="REPLACE")
  286. ! write(1,"(A)") redisOutput
  287. ! close(1)
  288. call jsonfile%initialize()
  289. call jsonfile%get_core(json)
  290. ! print *,"len_trim(redidOutput)=",len_trim(redisOutput)
  291. call jsonfile%deserialize(redisOutput(1:leng))
  292. call jsonfile%json_file_get_root(jsonroot)
  293. ! call json%info(jsonvalue, n_children=n_children)
  294. ! print *,"n_children =",n_children
  295. call json%get(jsonroot,'status',pval)
  296. call json%get(pval,stat)
  297. if (stat==0) then
  298. if(print_log) print *,"Status is oddly zero"
  299. return
  300. endif
  301. simulationStatus = stat
  302. ! call jsonfile%get('OperationScenarioEvent',operationScenarioEvent,found)
  303. ! if ( .not. found .and. print_log) print *,"Not found: operationScenarioEvent"
  304. call json%get(jsonroot,'speed',pval)
  305. call json%get(pval,simulationSpeed)
  306. if(simulationSpeed==0) simulationSpeed = 1
  307. msPerStep = 100/simulationSpeed
  308. call json%get(jsonroot,'endstep',pval)
  309. call json%get(pval,simulationEnd)
  310. ! call ProblemsFromJson(jsonfile)
  311. call EquipmentsFromJson(jsonfile)
  312. call UnitySignalsFromJson(jsonfile)
  313. call jsonfile%destroy()
  314. end subroutine
  315. subroutine init_modules
  316. print *,"initializing modules"
  317. !Tarmigh
  318. call Pumps_StartUp()
  319. print *,"pump1 initialized"
  320. !call Pump2_Init()
  321. call RotaryTable_Init()
  322. print *,"RT initialized"
  323. call Drawworks_Init()
  324. call TopDrive_Init()
  325. print *,"TD initialized"
  326. !Nothing in init (and step)
  327. ! call Rop_Init()
  328. ! call TorqueDrag_Init()
  329. ! call Geo_Step()
  330. !! Rafiee
  331. call BopStack_Init()
  332. call ChokeControl_Init()
  333. call MudSystem_Init()
  334. ! call PipeRams1_Init()
  335. ! call PipeRams2_Step()
  336. ! call KillLine_Step()
  337. ! call ChokeLine_Step()
  338. ! call BlindRams_Step()
  339. ! call Annular_Step()
  340. !! Sheikh
  341. call FluidFlow_Init()
  342. !! Ahmadi
  343. call PathFinding_Init()
  344. print *,"Modules are initialized"
  345. ! Calls OSInitialization and that sub only subscribes some notif
  346. ! call OperationScenarios_Init()
  347. end subroutine init_modules
  348. subroutine EquipmentsFromJson(jsonfile)
  349. type(json_value),pointer :: parent
  350. type(json_value),pointer :: p
  351. type(json_file)::jsonfile
  352. integer::n_children
  353. logical::is_found
  354. ! 1. get related root
  355. ! call jsonfile%json_file_get_root(parent)
  356. ! call jsoncore%get(parent,"Equipments",p)
  357. call jsonfile%get("Equipments",p,is_found)
  358. ! call jsoncore%info(p, n_children=n_children)
  359. ! print *,"number of Equipments =",n_children
  360. ! 2. add member of data type to new node
  361. call BopControlPanelFromJson(p)
  362. call ChokeControlPanelFromJson(jsonfile)
  363. call ChokeManifoldFromJson(p)
  364. call DataDisplayConsoleFromJson(p)
  365. call DrillingConsoleFromJson(jsonfile)
  366. call StandPipeManifoldFromJson(p)
  367. call TopDrivePanelFromJson(p)
  368. ! call DrillingWatchFromJson(p)
  369. call TankFromJson(p)
  370. call UnityInputsFromJson(jsonfile)
  371. ! call HookFromJson(p)
  372. call jsonfile%get('Equipments.HookHeight',data%State%Drawworks%Hook_Height_final,is_found)
  373. if ( .not. is_found ) call logg(4,"Not found: Equipments.HookHeight")
  374. if(print_log) print *,"HookHeight=",data%State%Drawworks%Hook_Height_final
  375. end subroutine
  376. subroutine EquipmentsToJson(parent)
  377. type(json_value),pointer :: parent
  378. type(json_value),pointer :: p
  379. ! 1. create new node
  380. call jsoncore%create_object(p,'Equipments')
  381. ! 2. add member of data type to new node
  382. call BopControlPanelToJson(p)
  383. call ChokeControlPanelToJson(p)
  384. call ChokeManifoldToJson(p)
  385. call DataDisplayConsoleToJson(p)
  386. call DrillingConsoleToJson(p)
  387. call StandPipeManifoldToJson(p)
  388. call TopDrivePanelToJson(p)
  389. call DrillingWatchToJson(p)
  390. ! call HookToJson(p)
  391. call jsoncore%add(p,"HookVelocity",data%State%Drawworks%HookLinearVelocity_final)
  392. ! 3. add new node to parent
  393. call jsoncore%add(parent,p)
  394. end subroutine
  395. ! subroutine ConfigurationToJson(parent)
  396. ! type(json_value),pointer :: parent
  397. ! type(json_value),pointer :: p
  398. ! ! 1. create new node
  399. ! call jsoncore%create_object(p,'Configuration')
  400. ! ! 2. add member of data type to new node
  401. ! call StringConfigurationToJson(p)
  402. ! call FormationToJson(p)
  403. ! call ReservoirToJson(p)
  404. ! call ShoeToJson(p)
  405. ! call AccumulatorToJson(p)
  406. ! call BopStackToJson(p)
  407. ! call HoistingToJson(p)
  408. ! call PowerToJson(p)
  409. ! call PumpsToJson(p)
  410. ! call RigSizeToJson(p)
  411. ! call CasingLinerChokeToJson(p)
  412. ! call PathGenerationToJson(p)
  413. ! ! call WellSurveyDataToJson(p)
  414. ! call MudPropertiesToJson(p)
  415. ! call UnityOutputsToJson(p)
  416. ! ! 3. add new node to parent
  417. ! call jsoncore%add(parent,p)
  418. ! end subroutine
  419. subroutine WarningsToJson(parent)
  420. type(json_value),pointer :: parent
  421. type(json_value),pointer :: p
  422. ! 1. create new node
  423. call jsoncore%create_object(p,'Warnings')
  424. ! 2. add member of data type to new node
  425. call jsoncore%add(p,"PumpWithKellyDisconnected",data%Warnings%PumpWithKellyDisconnected)
  426. call jsoncore%add(p,"PumpWithTopdriveDisconnected",data%Warnings%PumpWithTopdriveDisconnected)
  427. call jsoncore%add(p,"Pump1PopOffValveBlown",data%Warnings%Pump1PopOffValveBlown)
  428. call jsoncore%add(p,"Pump1Failure",data%Warnings%Pump1Failure)
  429. call jsoncore%add(p,"Pump2PopOffValveBlown",data%Warnings%Pump2PopOffValveBlown)
  430. call jsoncore%add(p,"Pump2Failure",data%Warnings%Pump2Failure)
  431. call jsoncore%add(p,"Pump3PopOffValveBlown",data%Warnings%Pump3PopOffValveBlown)
  432. call jsoncore%add(p,"Pump3Failure",data%Warnings%Pump3Failure)
  433. call jsoncore%add(p,"DrawworksGearsAbuse",data%Warnings%DrawworksGearsAbuse)
  434. call jsoncore%add(p,"RotaryGearsAbuse",data%Warnings%RotaryGearsAbuse)
  435. call jsoncore%add(p,"HoistLineBreak",data%Warnings%HoistLineBreak)
  436. call jsoncore%add(p,"PartedDrillString",data%Warnings%PartedDrillString)
  437. call jsoncore%add(p,"ActiveTankOverflow",data%Warnings%ActiveTankOverflow)
  438. call jsoncore%add(p,"ActiveTankUnderVolume",data%Warnings%ActiveTankUnderVolume)
  439. call jsoncore%add(p,"TripTankOverflow",data%Warnings%TripTankOverflow)
  440. call jsoncore%add(p,"DrillPipeTwistOff",data%Warnings%DrillPipeTwistOff)
  441. call jsoncore%add(p,"DrillPipeParted",data%Warnings%DrillPipeParted)
  442. call jsoncore%add(p,"TripWithSlipsSet",data%Warnings%TripWithSlipsSet)
  443. call jsoncore%add(p,"Blowout",data%Warnings%Blowout)
  444. call jsoncore%add(p,"UndergroundBlowout",data%Warnings%UndergroundBlowout)
  445. call jsoncore%add(p,"MaximumWellDepthExceeded",data%Warnings%MaximumWellDepthExceeded)
  446. call jsoncore%add(p,"CrownCollision",data%Warnings%CrownCollision)
  447. call jsoncore%add(p,"FloorCollision",data%Warnings%FloorCollision)
  448. call jsoncore%add(p,"TopdriveRotaryTableConfilict",data%Warnings%TopdriveRotaryTableConfilict)
  449. ! 3. add new node to parent
  450. call jsoncore%add(parent,p)
  451. end subroutine
  452. subroutine ProblemsToJson(parent)
  453. type(json_value),pointer :: parent
  454. type(json_value),pointer :: p
  455. ! 1. create new node
  456. call jsoncore%create_object(p,'Problems')
  457. ! 2. add member of data type to new node
  458. call BitProblemsToJson(p)
  459. call BopProblemsToJson(p)
  460. call ChokeProblemsToJson(p)
  461. call DrillStemProblemsToJson(p)
  462. call GaugesProblemsToJson(p)
  463. call HoistingProblemsToJson(p)
  464. call KickProblemsToJson(p)
  465. call LostProblemsToJson(p)
  466. call MudTreatmentProblemsToJson(p)
  467. call OtherProblemsToJson(p)
  468. call PumpProblemsToJson(p)
  469. call RotaryProblemsToJson(p)
  470. ! 3. add new node to parent
  471. call jsoncore%add(parent,p)
  472. end subroutine
  473. subroutine StateToJson(parent)
  474. type(json_value),pointer :: parent
  475. type(json_value),pointer :: p
  476. ! 1. create new node
  477. call jsoncore%create_object(p,'State')
  478. call ManifoldToJson(p)
  479. ! call OperationScenarioToJson(p)
  480. call notificationsToJson(p)
  481. ! call permissionsToJson(p)
  482. ! call unitySignalsToJson(p)
  483. ! call StudentStationToJson(p)
  484. ! call BopStackInputToJson(p)
  485. ! call BopStackAccToJson(p)
  486. ! call RamLineToJson(p)
  487. ! call AnnularComputationalToJson(p)
  488. ! call AnnularToJson(p)
  489. ! call PipeRam1ToJson(p)
  490. ! call ShearRamToJson(p)
  491. ! call PipeRam2ToJson(p)
  492. ! call ChokeLineToJson(p)
  493. ! call KillLineToJson(p)
  494. ! call PumpsToJson(p)
  495. ! call RAMToJson(p)
  496. ! call RAMSToJson(p)
  497. ! call ChokeToJson(p)
  498. ! call AirDrivenPumpToJson(p)
  499. ! call AirPumpLineToJson(p)
  500. ! call CHOOKEToJson(p)
  501. ! call DrawworksToJson(p)
  502. ! call MudSystemToJson(p)
  503. ! call MUDToJson(p)
  504. ! call MPumpsToJson(p)
  505. ! call PUMPToJson(p)
  506. ! call RTableToJson(p)
  507. ! call TDSToJson(p)
  508. ! call GasType(3)ToJson(p)
  509. ! call PressureDisplayToJson(p)
  510. ! call FricPressDropToJson(p)
  511. ! call ROP_SpecToJson(p)
  512. ! call ROP_BitToJson(p)
  513. ! call TDGeoToJson(p)
  514. ! call F_String(:)ToJson(p)
  515. ! call F_CountsToJson(p)
  516. ! call F_Interval(:)ToJson(p)
  517. ! call OD_Annulus(4)ToJson(p)
  518. ! call TD_DrillStemToJson(p)
  519. ! call TD_DrillStemsToJson(p)
  520. ! call TD_StringToJson(p)
  521. ! call TD_CountToJson(p)
  522. ! call G_StringElementToJson(p)
  523. ! call TD_VolToJson(p)
  524. ! call TD_GeneralToJson(p)
  525. ! call TD_BOPToJson(p)
  526. ! call TD_BOPElement(4)ToJson(p)
  527. ! call TD_StConnToJson(p)
  528. ! call TD_LoadToJson(p)
  529. ! call TD_WellElToJson(p)
  530. ! call TD_CasingToJson(p)
  531. ! call TD_LinerToJson(p)
  532. ! call TD_OpenHoleToJson(p)
  533. ! call TD_ROPHoleToJson(p)
  534. ! call TD_WellGeneralToJson(p)
  535. ! call TD_WellGeo(:)ToJson(p)
  536. ! 2. add member of data type to new node
  537. ! 3. add new node to parent
  538. call jsoncore%add(parent,p)
  539. end subroutine
  540. !use this as a template
  541. subroutine notificationsToJson(parent)
  542. type(json_value),pointer :: parent
  543. type(json_value),pointer :: p
  544. ! 1. create new node
  545. call jsoncore%create_object(p,'Notifications')
  546. ! 2. add member of data type to new node
  547. ! 3. add new node to parent
  548. call jsoncore%add(parent,p)
  549. end subroutine
  550. subroutine ConfigurationFromJson(jsonfile)
  551. type(json_file)::jsonfile
  552. type(json_value),pointer :: parent
  553. type(json_value),pointer :: p
  554. ! 1. get related root
  555. call jsonfile%json_file_get_root(parent)
  556. call jsoncore%get(parent,"Configuration",p)
  557. call StringConfigurationFromJson(p)
  558. call FormationFromJson(p)
  559. call ReservoirFromJson(p)
  560. call ShoeFromJson(p)
  561. call AccumulatorFromJson(p)
  562. call BopStackFromJson(p)
  563. call HoistingFromJson(p)
  564. call PowerFromJson(p)
  565. call PumpsFromJson(p)
  566. call RigSizeFromJson(p)
  567. call CasingLinerChokeFromJson(p)
  568. call PathGenerationFromJson(p)
  569. call MudPropertiesFromJson(p)
  570. ! 3. add new node to parent
  571. ! nullify(parent)
  572. end subroutine
  573. subroutine WarningsFromJson(parent)
  574. type(json_value),pointer :: parent
  575. type(json_value),pointer :: p
  576. type(json_value),pointer :: pval
  577. ! 1. get node
  578. call jsoncore%get(parent,'Warnings',p)
  579. ! ! 2. add member of data type to new node
  580. call jsoncore%get(p,'PumpWithKellyDisconnected',pval)
  581. call jsoncore%get(pval,data%Warnings%PumpWithKellyDisconnected)
  582. call jsoncore%get(p,'PumpWithTopdriveDisconnected',pval)
  583. call jsoncore%get(pval,data%Warnings%PumpWithTopdriveDisconnected)
  584. call jsoncore%get(p,'Pump1PopOffValveBlown',pval)
  585. call jsoncore%get(pval,data%Warnings%Pump1PopOffValveBlown)
  586. call jsoncore%get(p,'Pump1Failure',pval)
  587. call jsoncore%get(pval,data%Warnings%Pump1Failure)
  588. call jsoncore%get(p,'Pump2PopOffValveBlown',pval)
  589. call jsoncore%get(pval,data%Warnings%Pump2PopOffValveBlown)
  590. call jsoncore%get(p,'Pump2Failure',pval)
  591. call jsoncore%get(pval,data%Warnings%Pump2Failure)
  592. call jsoncore%get(p,'Pump3PopOffValveBlown',pval)
  593. call jsoncore%get(pval,data%Warnings%Pump3PopOffValveBlown)
  594. call jsoncore%get(p,'Pump3Failure',pval)
  595. call jsoncore%get(pval,data%Warnings%Pump3Failure)
  596. call jsoncore%get(p,'DrawworksGearsAbuse',pval)
  597. call jsoncore%get(pval,data%Warnings%DrawworksGearsAbuse)
  598. call jsoncore%get(p,'RotaryGearsAbuse',pval)
  599. call jsoncore%get(pval,data%Warnings%RotaryGearsAbuse)
  600. call jsoncore%get(p,'HoistLineBreak',pval)
  601. call jsoncore%get(pval,data%Warnings%HoistLineBreak)
  602. call jsoncore%get(p,'PartedDrillString',pval)
  603. call jsoncore%get(pval,data%Warnings%PartedDrillString)
  604. call jsoncore%get(p,'ActiveTankOverflow',pval)
  605. call jsoncore%get(pval,data%Warnings%ActiveTankOverflow)
  606. call jsoncore%get(p,'ActiveTankUnderVolume',pval)
  607. call jsoncore%get(pval,data%Warnings%ActiveTankUnderVolume)
  608. call jsoncore%get(p,'TripTankOverflow',pval)
  609. call jsoncore%get(pval,data%Warnings%TripTankOverflow)
  610. call jsoncore%get(p,'DrillPipeTwistOff',pval)
  611. call jsoncore%get(pval,data%Warnings%DrillPipeTwistOff)
  612. call jsoncore%get(p,'DrillPipeParted',pval)
  613. call jsoncore%get(pval,data%Warnings%DrillPipeParted)
  614. call jsoncore%get(p,'TripWithSlipsSet',pval)
  615. call jsoncore%get(pval,data%Warnings%TripWithSlipsSet)
  616. call jsoncore%get(p,'Blowout',pval)
  617. call jsoncore%get(pval,data%Warnings%Blowout)
  618. call jsoncore%get(p,'UndergroundBlowout',pval)
  619. call jsoncore%get(pval,data%Warnings%UndergroundBlowout)
  620. call jsoncore%get(p,'MaximumWellDepthExceeded',pval)
  621. call jsoncore%get(pval,data%Warnings%MaximumWellDepthExceeded)
  622. call jsoncore%get(p,'CrownCollision',pval)
  623. call jsoncore%get(pval,data%Warnings%CrownCollision)
  624. call jsoncore%get(p,'FloorCollision',pval)
  625. call jsoncore%get(pval,data%Warnings%FloorCollision)
  626. call jsoncore%get(p,'TopdriveRotaryTableConfilict',pval)
  627. call jsoncore%get(pval,data%Warnings%TopdriveRotaryTableConfilict)
  628. end subroutine
  629. subroutine ProblemsFromJson(jsonfile)
  630. type(json_value),pointer :: parent
  631. type(json_value),pointer :: p
  632. type(json_file)::jsonfile
  633. call jsonfile%json_file_get_root(parent)
  634. call jsoncore%get(parent,'Warnings',p)
  635. call BitProblemsToJson(p)
  636. call BopProblemsFromJson(p)
  637. call ChokeProblemsFromJson(p)
  638. call DrillStemProblemsFromJson(p)
  639. call GaugesProblemsFromJson(p)
  640. call HoistingProblemsFromJson(p)
  641. call KickProblemsFromJson(p)
  642. call LostProblemsFromJson(p)
  643. call MudTreatmentProblemsFromJson(p)
  644. call OtherProblemsFromJson(p)
  645. call PumpProblemsFromJson(p)
  646. call RotaryProblemsFromJson(p)
  647. end subroutine
  648. subroutine StateFromJson(parent)
  649. type(json_value),pointer :: parent
  650. type(json_value),pointer :: p
  651. ! 1. create new node
  652. ! call json%create_object(p,'State')
  653. ! ! call OperationScenarioFromJson(p)
  654. ! call notificationsFromJson(p)
  655. ! call permissionsFromJson(p)
  656. ! call unitySignalsFromJson(p)
  657. ! call StudentStationFromJson(p)
  658. ! call BopStackInputFromJson(p)
  659. ! call BopStackAccFromJson(p)
  660. ! call RamLineFromJson(p)
  661. ! call AnnularComputationalFromJson(p)
  662. ! call AnnularFromJson(p)
  663. ! call PipeRam1FromJson(p)
  664. ! call ShearRamFromJson(p)
  665. ! call PipeRam2FromJson(p)
  666. ! call ChokeLineFromJson(p)
  667. ! call KillLineFromJson(p)
  668. ! call PumpsFromJson(p)
  669. ! call RAMFromJson(p)
  670. ! call RAMSFromJson(p)
  671. ! call ChokeFromJson(p)
  672. ! call AirDrivenPumpFromJson(p)
  673. ! call AirPumpLineFromJson(p)
  674. ! call CHOOKEFromJson(p)
  675. ! call DrawworksFromJson(p)
  676. ! call MudSystemFromJson(p)
  677. ! call MUDFromJson(p)
  678. ! call MPumpsFromJson(p)
  679. ! call PUMPFromJson(p)
  680. ! call RTableFromJson(p)
  681. ! call TDSFromJson(p)
  682. ! call GasType(3)FromJson(p)
  683. ! call PressureDisplayFromJson(p)
  684. ! call FricPressDropFromJson(p)
  685. ! call ROP_SpecFromJson(p)
  686. ! call ROP_BitFromJson(p)
  687. ! call TDGeoFromJson(p)
  688. ! call F_String(:)FromJson(p)
  689. ! call F_CountsFromJson(p)
  690. ! call F_Interval(:)FromJson(p)
  691. ! call OD_Annulus(4)FromJson(p)
  692. ! call TD_DrillStemFromJson(p)
  693. ! call TD_DrillStemsFromJson(p)
  694. ! call TD_StringFromJson(p)
  695. ! call TD_CountFromJson(p)
  696. ! call G_StringElementFromJson(p)
  697. ! call TD_VolFromJson(p)
  698. ! call TD_GeneralFromJson(p)
  699. ! call TD_BOPFromJson(p)
  700. ! call TD_BOPElement(4)FromJson(p)
  701. ! call TD_StConnFromJson(p)
  702. ! call TD_LoadFromJson(p)
  703. ! call TD_WellElFromJson(p)
  704. ! call TD_CasingFromJson(p)
  705. ! call TD_LinerFromJson(p)
  706. ! call TD_OpenHoleFromJson(p)
  707. ! call TD_ROPHoleFromJson(p)
  708. ! call TD_WellGeneralFromJson(p)
  709. ! call TD_WellGeo(:)FromJson(p)
  710. ! 2. add member of data type to new node
  711. ! 3. add new node to parent
  712. ! call jsoncore%add(parent,p)
  713. end subroutine
  714. !use this as a template
  715. subroutine notificationsFromJson(parent)
  716. type(json_value),pointer :: parent
  717. !
  718. ! type(json_value),pointer :: p
  719. ! 1. create new node
  720. ! call json%create_object(p,'Notifications')
  721. ! ! 2. add member of data type to new node
  722. ! ! 3. add new node to parent
  723. ! call json%add(parent,p)
  724. end subroutine
  725. ! subroutine fireOperationScenarioEvent()
  726. ! print *,"fireOperationScenarioEvent starts"
  727. ! if(operationScenarioEvent=='Kelly_ConnectionNothing'.and. .not. Kelly_ConnectionNothing_in_progress) then
  728. ! Kelly_ConnectionNothing_in_progress = .true.
  729. ! print *, "Starting Kelly_ConnectionNothing"
  730. ! call Kelly_ConnectionNothing()
  731. ! print *, "Kelly_ConnectionNothing ends."
  732. ! Kelly_ConnectionNothing_in_progress = .false.
  733. ! endif
  734. ! end subroutine
  735. end module Simulator