123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109 |
- interface
- subroutine Createtree_(tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- type(c_ptr), intent(out) :: tree_ctx
- end subroutine
- subroutine DeleteTree(tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine GetTree(node_coord, parent_lst, child_lst, node_depth, node_ghost, node_leaf, Nnodes, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- type(c_ptr), intent(out) :: node_coord ! real*8, dimension(Nnode*3)
- type(c_ptr), intent(out) :: parent_lst ! integer*4, dimension(Nnode)
- type(c_ptr), intent(out) :: child_lst ! integer*4, dimension(Nnode*8)
- type(c_ptr), intent(out) :: node_depth ! integer*1, dimension(Nnode)
- type(c_ptr), intent(out) :: node_ghost ! integer*1, dimension(Nnode)
- type(c_ptr), intent(out) :: node_leaf ! integer*1, dimension(Nnode)
- integer*4 , intent(out) :: Nnodes
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine UpdateRefinement(pt_coord, Npt, max_pts, level_restrict, periodic, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- real*8 , intent(in) :: pt_coord(*)
- integer*4 , intent(in) :: Npt
- integer*4 , intent(in) :: max_pts
- logical , intent(in) :: level_restrict
- logical , intent(in) :: periodic
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine AddData(data_name, node_data, Ndata, cnt, Ncnt, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- character , intent(in) :: data_name(*)
- real*8 , intent(in) :: node_data(*)
- integer*4 , intent(in) :: Ndata
- integer*4 , intent(in) :: cnt(*)
- integer*4 , intent(in) :: Ncnt
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine GetData(node_data, Ndata, cnt, Ncnt, data_name, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- type(c_ptr), intent(out) :: node_data ! real*8 , dimension(Ndata)
- integer*4 , intent(out) :: Ndata
- type(c_ptr), intent(out) :: cnt ! integer*4, dimension(Ncnt)
- integer*4 , intent(out) :: Ncnt
- character , intent(in) :: data_name(*)
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine DeleteData(data_name, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- character , intent(in) :: data_name(*)
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine WriteTreeVTK(fname, show_ghost, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- character , intent(in) :: fname(*)
- logical , intent(in) :: show_ghost
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine AddParticles(pt_name, coord, Npt, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- character , intent(in) :: pt_name
- real*8 , intent(in) :: coord(*)
- integer*4 , intent(in) :: Npt
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine AddParticleData(data_name, pt_name, pt_data, Ndata, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- character , intent(in) :: data_name(*)
- character , intent(in) :: pt_name(*)
- real*8 , intent(in) :: pt_data(*)
- integer*4 , intent(in) :: Ndata
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine GetParticleData(pt_data, N, data_name, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- type(c_ptr), intent(out) :: pt_data ! real*8, dimension(N)
- integer*4 , intent(out) :: N
- character , intent(in) :: data_name(*)
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine DeleteParticleData(data_name, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- character , intent(in) :: data_name
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- subroutine WriteParticleVTK(fname, data_name, show_ghost, tree_ctx)
- use, intrinsic :: ISO_C_BINDING
- character , intent(in) :: fname(*)
- character , intent(in) :: data_name(*)
- logical , intent(in) :: show_ghost
- type(c_ptr), intent(in) :: tree_ctx
- end subroutine
- end interface
|