Skip to content
Snippets Groups Projects
read_input_file.f90 82.9 KiB
Newer Older
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|
!                                                                              |
!              ||===\\                                                         | 
!              ||    \\                                                        |
!              ||     ||   //==\\   ||  ||   //==||  ||/==\\                   |
!              ||     ||  ||    ||  ||  ||  ||   ||  ||    ||                  |
!              ||    //   ||    ||  ||  ||  ||   ||  ||                        |
!              ||===//     \\==//    \\==\\  \\==\\  ||                        |
!                                                                              |
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|
!                                                                              |
!              READ_INPUT_FILE    Feb. 2007                                    |
!                                                                              |
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|

subroutine read_input_file (params,threadinfo,material0,mat,surface,boxes,     &
                           sections,cube_faces,nest,bcdef)         

!------------------------------------------------------------------------------|
!(((((((((((((((( Purpose of the routine  ))))))))))))))))))))))))))))))))))))))
!------------------------------------------------------------------------------|

! subroutine where default values for all input parameters other than the
! controlling parameters are defined
! it is also where the input file 'input.txt' is read and the corresponding
! parameters are set

! nstep is number of time steps
! ns is number of surface - read in read_controlling_parameters
! dt is time step length
!  (note that if dt is negative, it will be replaced by a dynamically
!   determined value derived from Courant's condition and Courant's
!   parameter called "courant")
! nmat is number of material - read in read_controlling_parameters
! material0 is material number for stuff above 1st surface
!   or reference material when there is no surface
! mat:material properties, including, density,viscosity and compressibility
!     penalty parameters; ms is dimensioned (0:nmat)
!     material 0 is void
! leveluniform_oct is level of uniform discretization (power of 2)
! levelmax_oct is maximum discretization level
! matrule is the flag that determines the rule used for assigning material
!    properties within the model volume
! levelcut is maximum level (within a leave) used to estimate integrals
!    in divfem approximation
! levelapprox is maximum level to use to estimate positive volume
!    beyond levelcut
! noctreemax is maximum size of octrees when they are created
! penalty is penalty parameters for linear constraints arising from
!    bad faces in octree discretization (should be large)
! tempscale is temperature scaling parameter
! strain_ratio is used for refinement (if=1 no refinement;
!    if=0 uniform refinement) down to levelmax_oct
! istrain_refine: two algortihms are allowed for the refinement based on the strain ratio
!    one is based on the maximum difference between any two components of velocity
!    inside an element (istrain_refine=0) the other is based on the norm of the
!    velocity gradient (istrain_refine=1). Default is istrain_refine=1
! courant is ratio of courant conditoin used for moving particles (<1)
! stretch is the maximum allowed increase in linear length between two initially
!    adjacent particles on any surface; when this stretch is achieved, a new
!    particle is inserted on the surface, half-way along the stretched edge
!    stretch is specific to each surface
! anglemax is the maximum allowed angle between two adjacent normals; when the
!    angle is reached, a new point is injected
!    anglemax is specific to each surface
!    default value is 1.d0
! surface are surface structure
!    for each surface, one needs to define a levelt, itype, material and fnme.
!    levelt is the initial level for the particles on the surface; to be accurate
!    and avoid wholes in the surface during definition of the lsf, one should use
!    levelt=levelmax_oct+1 for all surfaces as a minimum value; itype should be 1
!    for foldable surfaces or 0 for nonfoldable surfaces; material is the material
!    type refering to the table of material available (max nmat); fnme is the name
!    of the file containing the geometry of the particles defining the surface
! npmin is the minimum number of particles in the strain cloud per element
! npmax is the maximum number of particles in the strain cloud per element
!       at levelmax_oct level (smallest possible elements)
! nonlineariter is number of iterations in nonlinear analysis
!   if nonlineariter is 0 no nonlinear iterations are performed (linear analysis)
!   if nonlineariter is positive, nonlineariter is the number of iterations performed
!                         regardless of convergence of solution
!   if nonlineariter is negative, -nonlineariter is maximum number of iterations allowed
!                         to reach convergence as determined by tol
! tol is relative tolerance (duvw/uvw) to achieve convergence
! criterion is criterion used to define the octree in the vicinity of the
!    sufaces; criterion 1 corresponds to imposing that all leaves that contain at
!    least one particle of any surface is at levelmax_oct; criterion 2 corresponds
!    to imposing that discretization is proportional to the curvature of the
!    surface; curvature is calculated from the local divergence of the normals.
!    the criterion is specific to each surface (default is 2)
! anglemaxoctree is only defined for criterion 2; it is the maximum allowable angle
!    between two adjacent normals; if the angle is greater than anglemaxoctree, the local
!    octree leaves are forced to be at level levelmax_oct; otherwise they are
!    proportionally larger (smaller levels) (default is 10)
!    anglemaxoctree is specific to each surface
!   (be aware that these files are enormous...)
! niter_move is number of iterations used to move particles in an
!  implicit, mid-point algorithm
! restart is a restart flag; if irestart is not 0, the run will restart from
!    an output file given by restartfile and at step irestart+1 - read in
!    read_controlling_parameters
! ismooth is a flag to impose an additional level of smoothing after refinement
!    for the surfaces and strain rate. It ensures that no leaf is flanked by
!    other leaves diffeing by more than 1 level of refinement
!    If ismooth is 0, no smoothing is performed; if ismooth is set to 1, smoothing
!    is performed (default is 1)
! boxes is the set of nboxes box structures defined by the user where a set level
!    of discretization is imposed

!------------------------------------------------------------------------------|
!((((((((((((((((  declaration of the subroutine arguments  ))))))))))))))))))))
!------------------------------------------------------------------------------|

use definitions
type (parameters) params
type (thread) threadinfo
integer material0
type (material) mat(0:params%nmat)
type (sheet) surface(params%ns)
type (box) boxes(params%nboxes)
type (cross_section) sections(params%nsections)
type (face),dimension(6) :: cube_faces
type (nest_info) :: nest
type (bc_definition) :: bcdef

!------------------------------------------------------------------------------|
!(((((((((((((((( declaration of the subroutine internal variables )))))))))))))
!------------------------------------------------------------------------------|

Dave Whipp's avatar
Dave Whipp committed
character(len=72) :: shift
character(len=3)  :: cm
character(len=1)  :: answer
integer iran,doru
integer flag

!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|

call mpi_comm_size (mpi_comm_world,nproc,ierr)
call mpi_comm_rank (mpi_comm_world,iproc,ierr)
Dave Whipp's avatar
Dave Whipp committed
shift=' '

!==============================================================================
!==============================================================================

params%nstep=2
if (iproc==0) call scanfile (params%infile,'nstep',params%nstep,ires)
call mpi_bcast(params%nstep,1,mpi_integer,0,mpi_comm_world,ierr)

params%nstep_spinup=0
if (iproc==0) call scanfile (params%infile,'nstep_spinup',params%nstep_spinup,ires)
call mpi_bcast(params%nstep_spinup,1,mpi_integer,0,mpi_comm_world,ierr)

!=====[material properties]====================================================

material0=0
if (iproc==0) call scanfile (params%infile,'material0',material0,ires)
call mpi_bcast(material0,1,mpi_integer,0,mpi_comm_world,ierr)

params%bulkvisc=.false.
if (iproc==0) then
  call scanfile (params%infile,'bulkvisc',answer,ires)
  params%bulkvisc=(trim(answer)=='T')
endif
call mpi_bcast(params%bulkvisc,1,mpi_logical,0,mpi_comm_world,ierr)

params%init_e2d=.false.
if (iproc==0) then
  call scanfile (params%infile,'init_e2d',answer,ires)
  params%init_e2d=(trim(answer)=='T')
endif
call mpi_bcast(params%init_e2d,1,mpi_logical,0,mpi_comm_world,ierr)

params%e2d0=1.d0
if (iproc==0) call scanfile (params%infile,'e2d0',params%e2d0,ires)
call mpi_bcast(params%e2d0,1,mpi_double_precision,0,mpi_comm_world,ierr)

params%plastic_stress_min=-1.d0
if (iproc==0) call scanfile (params%infile,'plastic_stress_min',params%plastic_stress_min,ires)
call mpi_bcast(params%plastic_stress_min,1,mpi_double_precision,0,mpi_comm_world,ierr)
params%pressure0=0.d0
if (iproc==0) call scanfile (params%infile,'pressure0',params%pressure0,ires)
call mpi_bcast(params%pressure0,1,mpi_double_precision,0,mpi_comm_world,ierr)

do i=0,params%nmat
   write(cm,'(i3)') i
   il=1
   if (i.lt.100) il=2
   if (i.lt.10) il=3

   mat(i)%density=1.d0
   if (i.eq.0) mat(i)%density=0.d0
   if (iproc==0) call scanfile (params%infile,'density'//cm(il:3),mat(i)%density,ires)
   call mpi_bcast(mat(i)%density,1,mpi_double_precision,0,mpi_comm_world,ierr)
 
   mat(i)%viscosity=1.d0
   if (i.eq.0) mat(i)%viscosity=1.d-8
   if (iproc==0) call scanfile (params%infile,'viscosity'//cm(il:3),mat(i)%viscosity,ires)
   call mpi_bcast(mat(i)%viscosity,1,mpi_double_precision,0,mpi_comm_world,ierr)

   mat(i)%penalty=1.d8
   if (iproc==0) call scanfile (params%infile,'penalty'//cm(il:3),mat(i)%penalty,ires)
   call mpi_bcast(mat(i)%penalty,1,mpi_double_precision,0,mpi_comm_world,ierr)

   mat(i)%expon=1.d0
   if (iproc==0) call scanfile (params%infile,'expon'//cm(il:3),mat(i)%expon,ires)
   call mpi_bcast(mat(i)%expon,1,mpi_double_precision,0,mpi_comm_world,ierr)
   
   mat(i)%activationenergy=0.d0
   if (iproc==0) call scanfile (params%infile,'activationenergy'//cm(il:3),mat(i)%activationenergy,ires)
   call mpi_bcast(mat(i)%activationenergy,1,mpi_double_precision,0,mpi_comm_world,ierr)
   
   mat(i)%expansion=0.d0
   if (iproc==0) call scanfile (params%infile,'expansion'//cm(il:3),mat(i)%expansion,ires)
   call mpi_bcast(mat(i)%expansion,1,mpi_double_precision,0,mpi_comm_world,ierr)

   mat(i)%diffusivity=1.d0
   if (iproc==0) call scanfile (params%infile,'diffusivity'//cm(il:3),mat(i)%diffusivity,ires)
   call mpi_bcast(mat(i)%diffusivity,1,mpi_double_precision,0,mpi_comm_world,ierr)

   mat(i)%heat=0.d0
   if (iproc==0) call scanfile (params%infile,'heat'//cm(il:3),mat(i)%heat,ires)
   call mpi_bcast(mat(i)%heat,1,mpi_double_precision,0,mpi_comm_world,ierr)

   mat(i)%plasticity_type='No'
   if (iproc==0) call scanfile (params%infile,'plasticity_type'//cm(il:3),mat(i)%plasticity_type,ires)
   call mpi_bcast(mat(i)%plasticity_type,8,mpi_character,0,mpi_comm_world,ierr)

   mat(i)%plasticity_parameters=0.d0
   mat(i)%plasticity_parameters(5)=-1.d0
   if ( trim(mat(i)%plasticity_type).ne.'No') then
       if (iproc==0) call scanfile (params%infile,'plasticity_1st_param'//cm(il:3),mat(i)%plasticity_parameters(1),ires)
       if (iproc==0) call scanfile (params%infile,'plasticity_2nd_param'//cm(il:3),mat(i)%plasticity_parameters(2),ires)
       if (iproc==0) call scanfile (params%infile,'plasticity_3rd_param'//cm(il:3),mat(i)%plasticity_parameters(3),ires)
       if (iproc==0) call scanfile (params%infile,'plasticity_4th_param'//cm(il:3),mat(i)%plasticity_parameters(4),ires)
       if (iproc==0) call scanfile (params%infile,'plasticity_5th_param'//cm(il:3),mat(i)%plasticity_parameters(5),ires)
       if (iproc==0) call scanfile (params%infile,'plasticity_6th_param'//cm(il:3),mat(i)%plasticity_parameters(6),ires)
       if (iproc==0) call scanfile (params%infile,'plasticity_7th_param'//cm(il:3),mat(i)%plasticity_parameters(7),ires)
       if (iproc==0) call scanfile (params%infile,'plasticity_8th_param'//cm(il:3),mat(i)%plasticity_parameters(8),ires)
       if (iproc==0) call scanfile (params%infile,'plasticity_9th_param'//cm(il:3),mat(i)%plasticity_parameters(9),ires)
       call mpi_bcast(mat(i)%plasticity_parameters,9,mpi_double_precision,0,mpi_comm_world,ierr)
   endif

   mat(i)%mattrans=-1.d0
   if (iproc==0) call scanfile (params%infile,'mattrans_xmin'//cm(il:3),mat(i)%mattrans(1),ires)
   if (iproc==0) call scanfile (params%infile,'mattrans_xmax'//cm(il:3),mat(i)%mattrans(2),ires)
   if (iproc==0) call scanfile (params%infile,'mattrans_ymin'//cm(il:3),mat(i)%mattrans(3),ires)
   if (iproc==0) call scanfile (params%infile,'mattrans_ymax'//cm(il:3),mat(i)%mattrans(4),ires)
   if (iproc==0) call scanfile (params%infile,'mattrans_zmin'//cm(il:3),mat(i)%mattrans(5),ires)
   if (iproc==0) call scanfile (params%infile,'mattrans_zmax'//cm(il:3),mat(i)%mattrans(6),ires)
   call mpi_bcast(mat(i)%mattrans,6,mpi_double_precision,0,mpi_comm_world,ierr)
   
Dave Whipp's avatar
Dave Whipp committed
   mat(i)%transnum=i
Loading
Loading full blame...