|
- module CPathGeneration
- use SimulationVariables !@
- use json_module
- implicit none
- public
- contains
-
- subroutine PathGenerationToJson(parent)
-
- type(json_value),pointer :: parent
- type(json_core) :: json
- type(json_value),pointer :: ppath,pitems,pdp,p
- integer::i
-
- ! 1. create new node
- call json%create_object(ppath,'Path')
-
- call json%create_array(pitems,'Items')
- do i=1,data%Configuration%Path%ItemCount
- call json%create_object(p,'')
- call json%add(p,"HoleType",data%Configuration%Path%items(i)%HoleType)
- call json%add(p,"Angle",data%Configuration%Path%items(i)%Angle)
- call json%add(p,"Length",data%Configuration%Path%items(i)%Length)
- call json%add(p,"FinalAngle",data%Configuration%Path%items(i)%FinalAngle)
- call json%add(p,"TotalLength",data%Configuration%Path%items(i)%TotalLength)
- call json%add(p,"MeasuredDepth",data%Configuration%Path%items(i)%MeasuredDepth)
- call json%add(p,"TotalVerticalDepth",data%Configuration%Path%items(i)%TotalVerticalDepth)
- call json%add(pitems,p)
- end do
-
- call json%create_array(pdp,'DataPoints')
- do i=1,data%Configuration%Path%DataPointsCount
- call json%create_object(p,'')
- call json%add(p,"X",data%Configuration%Path%DataPoints(i)%X)
- call json%add(p,"Y",data%Configuration%Path%DataPoints(i)%Y)
- call json%add(pdp,p)
- end do
-
- ! 3. add new node to parent
- call json%add(ppath,pitems)
- call json%add(ppath,pdp)
- call json%add(parent,ppath)
- end subroutine
-
- subroutine PathGenerationFromJson(parent)
- use json_module,IK =>json_ik
- type(json_value),pointer :: parent
- type(json_core) :: json
- type(json_value),pointer :: p,pitems,pitem,pval,pbit,dpoints,dpoint
- logical::is_found
- type(CStringItem) :: item
- integer::i,n_children
- CHARACTER(KIND=JSON_CK, LEN=:), ALLOCATABLE :: val
-
- call json%get(parent,'Path',p)
- call json%get(p,'Items',pitems)
- call json%info(pitems, n_children=n_children)
-
- if (.not. allocated(data%Configuration%Path%Items) .or. size(data%Configuration%Configuration%Path%Items)/=n_children) then
- ALLOCATE(data%Configuration%Configuration%Path%Items(n_children))
- endif
- do i=1,n_children
- call json%get_child(pitems, i, pitem, found=is_found)
- call json%get(pitem,"HoleType",pval)
- call json%get(pval,data%Configuration%Path%Items(i)%HoleType)
- call json%get(pitem,"Angle",pval)
- call json%get(pval,data%Configuration%Path%Items(i)%Angle)
- call json%get(pitem,"Length",pval)
- call json%get(pval,data%Configuration%Path%Items(i)%Length)
- call json%get(pitem,"FinalAngle",pval)
- call json%get(pval,data%Configuration%Path%Items(i)%FinalAngle)
- call json%get(pitem,"TotalLength",pval)
- call json%get(pval,data%Configuration%Path%Items(i)%TotalLength)
- call json%get(pitem,"MeasuredDepth",pval)
- call json%get(pval,data%Configuration%Path%Items(i)%MeasuredDepth)
- call json%get(pitem,"TotalVerticalDepth",pval)
- call json%get(pval,data%Configuration%Path%Items(i)%TotalVerticalDepth)
- end do
-
- call json%get(p,'DataPoints',dpoints)
- call json%info(dpoints, n_children=n_children)
-
- if (.not. allocated(data%Configuration%Path%DataPoints) .or. size(data%Configuration%Configuration%Path%DataPoints)/=n_children) then
- ALLOCATE(data%Configuration%Configuration%Path%DataPoints(n_children))
- endif
- do i=1,n_children
- call json%get_child(dpoints, i, dpoint, found=is_found)
- call json%get(dpoint,"X",pval)
- call json%get(pval,data%Configuration%Path%DataPoints(i)%X)
- call json%get(dpoint,"Y",pval)
- call json%get(pval,data%Configuration%Path%DataPoints(i)%Y)
- end do
-
-
- end subroutine
- end module CPathGeneration
|