Simulation Core
25'ten fazla konu seçemezsiniz Konular bir harf veya rakamla başlamalı, kısa çizgiler ('-') içerebilir ve en fazla 35 karakter uzunluğunda olabilir.
 
 
 
 
 
 

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