|
- module CFormation
- use CFormationVariables
- use SimulationVariables
- use json_module
- implicit none
-
- contains
-
- subroutine FormationFromJson(parent)
- use json_module,IK =>json_ik
- type(json_value),pointer :: parent
- type(json_core) :: json
- type(json_value),pointer :: p,pitem,pval
- logical::is_found
- integer::i,n_children
- CHARACTER(KIND=JSON_CK, LEN=:), ALLOCATABLE :: val
-
-
- call json%get(parent,'Formation',p)
-
- call json%info(p, n_children=n_children)
- data%Configuration%Formation%Count = n_children
- if (.not. allocated(data%Configuration%Formation%Formations) .or. size(data%Configuration%Formation%Formations)/=n_children) then
- ALLOCATE(data%Configuration%Formation%Formations(n_children))
- endif
- data%Configuration%Formation%Count = n_children
- do i=1,n_children
- call json%get_child(p, i, pitem, found=is_found)
-
- call json%get(pitem,'Top',pval)
- call json%get(pval,data%Configuration%Formation%Formations(i)%Top)
- call json%get(pitem,'Thickness',pval)
- call json%get(pval,data%Configuration%Formation%Formations(i)%Thickness)
- call json%get(pitem,'Drillablity',pval)
- call json%get(pval,data%Configuration%Formation%Formations(i)%Drillablity)
- call json%get(pitem,'Abrasiveness',pval)
- call json%get(pval,data%Configuration%Formation%Formations(i)%Abrasiveness)
- call json%get(pitem,'ThresholdWeight',pval)
- call json%get(pval,data%Configuration%Formation%Formations(i)%ThresholdWeight)
- call json%get(pitem,'PorePressureGradient',pval)
- call json%get(pval,data%Configuration%Formation%Formations(i)%PorePressureGradient)
- end do
- end subroutine
-
- subroutine FormationToJson(parent)
-
- type(json_value),pointer :: parent
- type(json_core) :: json
- type(json_value),pointer :: p,pform
- integer :: i,n
-
- ! 1. create new node
- call json%create_array(p,'Formations')
- n= data%Configuration%Formation%Count
- do i=1,n
- call json%create_object(pform,'')
- call json%add(pform,"Abrasiveness",data%Configuration%Formation%Formations(i)%Abrasiveness)
- call json%add(pform,"Drillablity",data%Configuration%Formation%Formations(i)%Drillablity)
- call json%add(pform,"PorePressureGradient",data%Configuration%Formation%Formations(i)%PorePressureGradient)
- call json%add(pform,"Thickness",data%Configuration%Formation%Formations(i)%Thickness)
- call json%add(pform,"ThresholdWeight",data%Configuration%Formation%Formations(i)%ThresholdWeight)
- call json%add(pform,"Top",data%Configuration%Formation%Formations(i)%Top)
- call json%add(p,pform)
- end do
-
- call json%add(parent,p)
- end subroutine
-
- end module CFormation
|