-
Dave Whipp authoredDave Whipp authored
module_definitions.f90 16.30 KiB
module definitions
!=====[EDGE]====================================================================
!this type is to store edges in a trianglulation
! it is used to update (in a generalized Delaunay sense)
! the triangulation of the 3D points on the surfaces
! for each edge:
! n1, n2 are the node numbers defining the edge
! t1, t2 are the triangle numbers on either side of the edge
! going from n1 to n2, t1 is to the left and t2 is to the right
! m1, m2 are the node numbers of the two other nodes making t1 and t2
type edge
integer n1,n2,m1,m2,t1,t2
end type edge
!=====[SHEET]===================================================================
! this type to store surfaces tracked by particles
! nsurface is number of particles
! x,y,z and xn,yn,zn are the coordinates and normals of the particles
! r,s are the 2D positions of the particles
! levelt is the resolution level (power of 2)
! itype is the type of surface (0 not foldable, 1 foldable)
! material is the material number
type sheet
integer nsurface,nt
double precision,dimension(:),pointer::r,s,x,y,z,xn,yn,zn,u,v,w
integer levelt,itype,material_main,material_spinup,material,surface_type
integer closed
double precision :: sp01,sp02,sp03,sp04,sp05,sp06,sp07,sp08,sp09,sp10,sp11
double precision :: sp12,sp13,sp14,activation_time
integer,dimension(:,:),pointer::icon
logical rand,fixed_surf_spinup,fixed_surf,surf_for_mat_props
integer leveloct
double precision :: stretch,anglemax,anglemaxoctree
integer :: criterion
integer spread_surface_points
end type sheet
!=====[OCTREEV]=================================================================
! octreev type to store velocity/temperature octree
! octree is octree
! noctree is onctree max size
! nnode is number of nodes on the octree
! nleaves is number of leaves in the octree
! x,y,z are the coordinates of the nodes
! unode,vnode,wnode are the velocity conponents at the nodes
! wiso is the velocity z-component due to isostasy
! temp is temperature at the nodes
! icon is connectivity array between nodes
type octreev
integer,dimension(:),pointer::octree
integer noctree,nnode,nleaves
double precision,dimension(:),pointer::x,y,z,temp
double precision,dimension(:),pointer::unode,vnode,wnode,wnodeiso
double precision,dimension(:),pointer::pressure,spressure
double precision,dimension(:),pointer::temporary_nodal_pressure
integer,dimension(:,:),pointer::icon
logical, dimension(:),pointer :: whole_leaf_in_fluid
end type octreev
!=====[OCTREELSF]===============================================================
! octreelsf type to store level set function
! octree is octree
! noctree is onctree max size
! nnode is number of nodes on the octree
! nleaves is number of leaves in the octree
! x,y,z are the coordinates of the nodes