Newer
Older
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,surface_type
double precision :: sp01,sp02,sp03,sp04,sp05,sp06,sp07,sp08,sp09,sp10,sp11
double precision :: sp12,activation_time
integer,dimension(:,:),pointer::icon
logical rand
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
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
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
! lsf is level set fuction values at the nodes
! icon is connectivity array between nodes
type octreelsf
integer,dimension(:),pointer::octree
integer noctree,nnode,nleaves
double precision,dimension(:),pointer::x,y,z,lsf
integer,dimension(:,:),pointer::icon
end type octreelsf
!=====[OCTREESOLVE]=============================================================
! same as octreelsf except that this type can store nlsf lsfs
! total accuulated strain interpolated from a 3D cloud
! nodal velocities u,v,w, interpolated from octreev
! temperature velocities temp
! and bad faces
type octreesolve
integer,dimension(:),pointer::octree,kfix,kfixt
integer noctree,nnode,nleaves,nlsf,nface
double precision,dimension(:),pointer::x,y,z
double precision,dimension(:),pointer::strain,pressure,spressure
double precision,dimension(:),pointer::crit
double precision,dimension(:),pointer::e2d
double precision,dimension(:),pointer::e3d
double precision,dimension(:),pointer::lode
double precision,dimension(:),pointer::u,v,w,wiso,temp
double precision,dimension(:,:),pointer::lsf
double precision,dimension(:),pointer::eviscosity,q,dilatr
integer,dimension(:,:),pointer::icon,iface
logical,dimension(:),pointer::is_plastic
integer,dimension(:),pointer :: matnum
end type octreesolve
!=====[MATERIAL]================================================================
! type material to define different materials
! density is product of density by g
! viscosity is viscosity
! expon is the stress exponent in the expression for the viscosity
! activationenergy is the activation energy
! expansion is the coefficient of thermal expansion (note that the temperature is first multiplied by the
! temperature scale before it is multiplied by the expansion coefficient)
! penalty is incompressibility penalty factor
! plasticity_type is the type of plasticity (vM for von Mises)
! plasticity_parameters are the nine plasticity parameters
type material
character(len=8) plasticity_type
Dave Whipp
committed
double precision :: plasticity_parameters(9)
double precision :: density,viscosity,penalty,expon,activationenergy
double precision :: diffusivity,heat,expansion,ztrans
integer :: transnum
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
end type material
!=====[VOID]====================================================================
! type void to store information on node, leaves and faces that are in the void
! node=1 for nodes that are conpletely in the void (they are taken out of the equation set)
! leaf=1 for leaves that are completely in the void
! face=1 for faces that are completely in the void
! nnode is the number of nodes to be solved for (number of nodes not in the void)
! nleaves is the number of active leaves
! nface is the number of active faces
! rtf (restricted to full) is an array that provides the connectivity
! between the restricted and full
! node numbers (j=rtf(i) where i is restricted node number (1 to vo%nnode)
! and j is full node number (1 to nnode))
! ftr (full to restricted) is the complement
! influid is true for nodes that are in the fluid
type void
integer,dimension(:),pointer::node,leaf,face,ftr,rtf
logical,dimension(:),pointer::influid
integer nnode,nleaves,nface
end type void
!=====[CLOUD]===================================================================
! type cloud is to store volumetric cloud of points
! it is very simple and made of
! np : number of particles!
! x,y,z : location
! x0, y0, z0: original particle position (used to calculate F: deformation gradient
! and from it the total strain)
! strain: accumulated strain
type cloud
integer np,ntag
double precision,dimension(:),pointer::x,y,z,x0,y0,z0,strain,lsf0,temp,press
integer,dimension(:),pointer::tag
end type cloud
!=====[TOPOLOGY]================================================================
! type topology is used to store the matrix topology for the solver
type topology
integer nheight,nheightmax
integer,dimension(:),pointer::icol
end type topology
!=====[BOX]=====================================================================
! type box is used to store the geometrical information about a general box
! that is used to refine an octree in an arbitrary manner
type box
double precision x0,y0,z0,x1,y1,z1
integer level
end type box
!=====[FACE]====================================================================
! type face is used to store the refinement informations on a given face of the cube
type face
integer level
double precision t,b,l,r
end type
!=====[CROSS_SECTION]===========================================================
! this type is used to store all the parameters related to the cross sections
! the 'flag' parameters toggle on/off the associated ield cross section
! scale is the global scale of the output postscript
! xyz =1,2,3 corresponding to a cross section at constant x,y, or z (resp.)
type cross_section
integer xyz
double precision slice,scale
logical flag_spress,flag_press,flag_e2d,flag_e3d,flag_crit,flag_grid,flag_lsf
logical flag_u,flag_v,flag_w,flag_uvw,flag_q,flag_vfield,flag_strain
logical flag_colour,flag_lode,flag_mu,flag_plastic,flag_velvect,flag_temp
character(len=3) colormap
integer ncolours
end type
!=====[PARAMETERS]==============================================================
! this contains all sorts of parameters used in the code, such as flags,
! convergence parameters, octree levels, ... pretty much all parameters
! that are read in the input file.
! isobc is a boolean value used to turn on/off the use of the modified isostasy
! boundary conditions (dwhipp 12/09)
type parameters
logical compute_qpgram
logical normaladvect
logical excl_vol
logical doDoRuRe
logical ref_on_faces
logical visualise_matrix
logical renumber_nodes
logical erosion
logical adaptive_tol
logical calculate_temp
logical isostasy
logical flexure
logical bulkvisc
logical init_e2d
logical ismooth
logical nest
integer levelcut
integer levelapprox
integer nstep
integer noctreemax
integer levelmax_oct
integer leveluniform_oct
integer smoothing_type
integer debug
integer npmin,npmax
integer irestart
integer refine_criterion
integer niter_move
integer griditer
integer nonlinear_iterations
integer mpe
integer nmat
integer nboxes
integer nb_iter_nl_min
integer nsections
integer ns
integer initial_refine_level
integer baselevelx0
integer baselevelx1
integer baselevely0
integer baselevely1
integer,dimension(:),pointer::materialn
double precision ztemp
double precision dt
double precision refine_ratio
double precision courant
double precision octree_refine_ratio
double precision distance_exponent
double precision tol
double precision penalty
double precision tempscale
double precision zerosion
double precision viscositymin,viscositymax
double precision velocity_scale,length_scale
double precision diffusion_erosion
double precision fluvial_erosion
double precision elastic_plate_thickness
double precision density_difference
Dave Whipp
committed
double precision vex
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
character*128 restartfile
character*40 infile
end type
!=====[INTERFACE SCANFILE]======================================================
! following is a general interface to read stuff from a file
interface scanfile
subroutine iscanfile (fnme,text,res,ires)
character*(*) fnme,text
integer,intent(out)::res
integer,intent(out)::ires
end subroutine iscanfile
subroutine dscanfile (fnme,text,res,ires)
character*(*) fnme,text
double precision,intent(out)::res
integer,intent(out)::ires
end subroutine dscanfile
subroutine cscanfile (fnme,text,res,ires)
character*(*) fnme,text
character*(*),intent(out)::res
integer,intent(out)::ires
end subroutine cscanfile
end interface
!=====[INTERFACE QSORT]=========================================================
! following is a general interface to sort an array of numbers
interface qsort
Douglas Guptill
committed
subroutine iqsort (array,n,perm)
integer,intent(in) :: n
Douglas Guptill
committed
integer,dimension(n),intent(inout)::array
integer,dimension(n),intent(inout)::perm
Douglas Guptill
committed
subroutine rqsort (array,n,perm)
integer,intent(in) :: n
Douglas Guptill
committed
real,dimension(n),intent(inout)::array
integer,dimension(n),intent(inout)::perm
Douglas Guptill
committed
subroutine dpqsort (array,n,perm)
integer,intent(in) :: n
Douglas Guptill
committed
real*8,dimension(n),intent(inout)::array
integer,dimension(n),intent(inout)::perm
Douglas Guptill
committed
subroutine iqsort_s (array,n)
integer,intent(in) :: n
Douglas Guptill
committed
integer,dimension(n),intent(inout)::array
Douglas Guptill
committed
subroutine rqsort_s (array,n)
integer,intent(in) :: n
Douglas Guptill
committed
real,dimension(n),intent(inout)::array
Douglas Guptill
committed
! subroutine dpqsort_s (array,n)
! integer,intent(in) :: n
! real*8,dimension(n),intent(inout)::array
! end subroutine dpqsort_s
!=====[ZISODISP]================================================================
! type ziso is used to store the isostatic deflection of the basal boundary
! due to isostasy
type ziso
double precision,dimension(:,:),pointer::zisodisp,zisoinc
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
!=====[BC_DEFINITION]===========================================================
! type bc_definition is used to store values related to the applied boundary
! conditions, including the velocity values and certain geometric parameters
type bc_definition
character(len=3) :: bcorder
double precision,dimension(:,:),pointer :: zisodisp,zisoinc
double precision :: ux0,ux1,vx0,vx1,wx0,wx1,uy0,uy1,vy0,vy1,wy0,wy1
double precision :: uz0,uz1,vz0,vz1,wz0,wz1
logical :: fixux0,fixux1,fixvx0,fixvx1,fixwx0,fixwx1
logical :: fixuy0,fixuy1,fixvy0,fixvy1,fixwy0,fixwy1
logical :: fixuz0,fixuz1,fixvz0,fixvz1,fixwz0,fixwz1
end type bc_definition
!=====[NEST_INFO]===============================================================
! type nest_info is used to store information related to the LS model and
! embedded SS nest
!
! sselem[x,y,z]: ratio of ss element size to ls element size (should be 0-1)
! [x,y,z]minls: location of (0,0,0) in the SS model within the LS model
type nest_info
double precision :: sselemx,sselemy,sselemz,xminls,yminls,zminls
end type nest_info
end module definitions