Simulation Core
Nelze vybrat více než 25 témat Téma musí začínat písmenem nebo číslem, může obsahovat pomlčky („-“) a může být dlouhé až 35 znaků.

Simulator.f90 28 KiB

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