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

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

!------------------------------------------------------------------------------|
!(((((((((((((((( 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

!------------------------------------------------------------------------------|
!(((((((((((((((( 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)

!=====[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)

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)%ztrans=-1.d0
   if (iproc==0) call scanfile (params%infile,'ztrans'//cm(il:3),mat(i)%ztrans,ires)
   call mpi_bcast(mat(i)%ztrans,1,mpi_double_precision,0,mpi_comm_world,ierr)

   mat(i)%transnum=1
   if (iproc==0) call scanfile (params%infile,'transnum'//cm(il:3),mat(i)%transnum,ires)
   call mpi_bcast(mat(i)%transnum,1,mpi_integer,0,mpi_comm_world,ierr)
enddo

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

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

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

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

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

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

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

params%levelapprox=3
if (iproc.eq.0) call scanfile (params%infile,'levelapprox',params%levelapprox,ires)
call mpi_bcast(params%levelapprox,1,mpi_integer,0,mpi_comm_world,ierr)

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

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

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

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

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

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

!=====[surface properties]=====================================================
do i=1,params%ns
   write(cm,'(i3)') i
   il=1
   if (i.lt.100) il=2
   if (il.lt.10) il=3
   
   surface(i)%itype=1
   if (iproc==0) call scanfile (params%infile,'itype'//cm(il:3),surface(i)%itype,ires)
   call mpi_bcast(surface(i)%itype,1,mpi_integer,0,mpi_comm_world,ierr)
   
   surface(i)%material=1
   if (iproc==0) call scanfile (params%infile,'material'//cm(il:3),surface(i)%material,ires)
   call mpi_bcast(surface(i)%material,1,mpi_integer,0,mpi_comm_world,ierr)

   surface(i)%rand=.false.
   if (iproc==0) then
      call scanfile (params%infile,'rand'//cm(il:3),answer,ires)
      surface(i)%rand=(trim(answer)=='T')
   end if
   call mpi_bcast(surface(i)%rand,1,mpi_logical,0,mpi_comm_world,ierr)
   
   surface(i)%levelt=params%levelmax_oct+1
   if (iproc==0) call scanfile (params%infile,'levelt'//cm(il:3),surface(i)%levelt,ires)
   call mpi_bcast(surface(i)%levelt,1,mpi_integer,0,mpi_comm_world,ierr)
   
   surface(i)%stretch=1.5d0
   if (iproc==0) call scanfile (params%infile,'stretch'//cm(il:3),surface(i)%stretch,ires)
   call mpi_bcast(surface(i)%stretch,1,mpi_double_precision,0,mpi_comm_world,ierr)

   surface(i)%criterion=1
   if (iproc==0) call scanfile (params%infile,'criterion'//cm(il:3),surface(i)%criterion,ires)
   call mpi_bcast(surface(i)%criterion,1,mpi_integer,0,mpi_comm_world,ierr)

   surface(i)%anglemax=1.d0
   if (iproc==0) call scanfile (params%infile,'anglemax'//cm(il:3),surface(i)%anglemax,ires)
   surface(i)%anglemax=surface(i)%anglemax*pi/180.d0
   call mpi_bcast(surface(i)%anglemax,1,mpi_double_precision,0,mpi_comm_world,ierr)

   surface(i)%anglemaxoctree=1.d0
   if (iproc==0) call scanfile (params%infile,'anglemaxoctree'//cm(il:3),surface(i)%anglemaxoctree,ires)
   surface(i)%anglemaxoctree=surface(i)%anglemaxoctree*pi/180.d0
   call mpi_bcast(surface(i)%anglemaxoctree,1,mpi_double_precision,0,mpi_comm_world,ierr)

   surface(i)%spread_surface_points=0
   if (iproc==0) call scanfile (params%infile,'spread_surface_points'//cm(il:3),surface(i)%spread_surface_points,ires)
   call mpi_bcast(surface(i)%spread_surface_points,1,mpi_integer,0,mpi_comm_world,ierr)

   if (iproc==0) call scanfile (params%infile,'surface_type_'//cm(il:3),surface(i)%surface_type,ires)
   call mpi_bcast(surface(i)%surface_type,1,mpi_integer,0,mpi_comm_world,ierr)
 
   if (iproc==0) call scanfile (params%infile,'surface_param_01_'//cm(il:3),surface(i)%sp01,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_02_'//cm(il:3),surface(i)%sp02,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_03_'//cm(il:3),surface(i)%sp03,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_04_'//cm(il:3),surface(i)%sp04,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_05_'//cm(il:3),surface(i)%sp05,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_06_'//cm(il:3),surface(i)%sp06,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_07_'//cm(il:3),surface(i)%sp07,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_08_'//cm(il:3),surface(i)%sp08,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_09_'//cm(il:3),surface(i)%sp09,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_10_'//cm(il:3),surface(i)%sp10,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_11_'//cm(il:3),surface(i)%sp11,ires)
   if (iproc==0) call scanfile (params%infile,'surface_param_12_'//cm(il:3),surface(i)%sp12,ires)
   
   call mpi_bcast(surface(i)%sp01,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp02,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp03,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp04,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp05,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp06,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp07,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp08,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp09,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp10,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp11,1,mpi_double_precision,0,mpi_comm_world,ierr)
   call mpi_bcast(surface(i)%sp12,1,mpi_double_precision,0,mpi_comm_world,ierr)

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

   surface(i)%leveloct=6
   if (iproc==0) call scanfile (params%infile,'leveloct'//cm(il:3),surface(i)%leveloct,ires)
   call mpi_bcast(surface(i)%leveloct,1,mpi_integer,0,mpi_comm_world,ierr)
enddo

!=====[face refinement parameters]=============================================

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

do i=1,6
   write(cm,'(i3)') i

   if (iproc==0) call scanfile (params%infile,'level_face'//cm(3:3),cube_faces(i)%level,ires)
   call mpi_bcast(cube_faces(i)%level,1,mpi_integer,0,mpi_comm_world,ierr)

   if (iproc==0) call scanfile (params%infile,'l'//cm(3:3),cube_faces(i)%l,ires)
   call mpi_bcast(cube_faces(i)%l,1,mpi_double_precision,0,mpi_comm_world,ierr)

   if (iproc==0) call scanfile (params%infile,'r'//cm(3:3),cube_faces(i)%r,ires)
   call mpi_bcast(cube_faces(i)%r,1,mpi_double_precision,0,mpi_comm_world,ierr)

   if (iproc==0) call scanfile (params%infile,'b'//cm(3:3),cube_faces(i)%b,ires)
   call mpi_bcast(cube_faces(i)%b,1,mpi_double_precision,0,mpi_comm_world,ierr)

   if (iproc==0) call scanfile (params%infile,'t'//cm(3:3),cube_faces(i)%t,ires)
   call mpi_bcast(cube_faces(i)%t,1,mpi_double_precision,0,mpi_comm_world,ierr)
end do

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

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

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

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

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

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

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

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

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

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

!=====[boundary conditions]=====================================================

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

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

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

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

params%tol=1.d-3
if (iproc==0) call scanfile (params%infile,'tol',params%tol,ires)
call mpi_bcast(params%tol,1,mpi_double_precision,0,mpi_comm_world,ierr)

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

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

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

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

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

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

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

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

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

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

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

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

   boxes(i)%level=1
   if (iproc==0) call scanfile (params%infile,'box'//cm(il:3)//'level',boxes(i)%level,ires)
   call mpi_bcast(boxes(i)%level,1,mpi_integer,0,mpi_comm_world,ierr)
enddo

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

   sections(i)%xyz=0
   if (iproc==0) call scanfile (params%infile,'xyz_'//cm(il:3),sections(i)%xyz,ires)

   if (iproc==0) call scanfile (params%infile,'slice_'//cm(il:3),sections(i)%slice,ires)
!   if (sections(i)%slice<0.d0 .or. sections(i)%slice>1.d0) call stop_run ('pb with slice value')

   sections(i)%flag_press = .false. 
   if (iproc==0) then
      call scanfile (params%infile,'flag_press_'//cm(il:3),answer,ires)
      sections(i)%flag_press=(trim(answer)=='T')
   end if

   sections(i)%flag_spress = .false. 
   if (iproc==0) then
      call scanfile (params%infile,'flag_spress_'//cm(il:3),answer,ires)
      sections(i)%flag_spress=(trim(answer)=='T')
   end if

   sections(i)%flag_e2d   = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_e2d_'//cm(il:3),answer,ires)
      sections(i)%flag_e2d=(trim(answer)=='T')
   end if

   sections(i)%flag_e3d   = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_e3d_'//cm(il:3),answer,ires)
      sections(i)%flag_e3d=(trim(answer)=='T')
   end if

   sections(i)%flag_strain   = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_strain_'//cm(il:3),answer,ires)
      sections(i)%flag_strain=(trim(answer)=='T')
   end if

   sections(i)%flag_crit  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_crit_'//cm(il:3),answer,ires)
      sections(i)%flag_crit=(trim(answer)=='T')
   end if

   sections(i)%flag_grid  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_grid_'//cm(il:3),answer,ires)
      sections(i)%flag_grid=(trim(answer)=='T')
   end if

   sections(i)%flag_u  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_u_'//cm(il:3),answer,ires)
      sections(i)%flag_u=(trim(answer)=='T')
   end if
 
   sections(i)%flag_v  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_v_'//cm(il:3),answer,ires)
      sections(i)%flag_v=(trim(answer)=='T')
   end if

   sections(i)%flag_w  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_w_'//cm(il:3),answer,ires)
      sections(i)%flag_w=(trim(answer)=='T')
   end if

   sections(i)%flag_uvw  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_uvw_'//cm(il:3),answer,ires)
      sections(i)%flag_uvw=(trim(answer)=='T')
   end if

   sections(i)%flag_colour  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_colour_'//cm(il:3),answer,ires)
      sections(i)%flag_colour=(trim(answer)=='T')
   end if

   sections(i)%flag_mu  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_mu_'//cm(il:3),answer,ires)
      sections(i)%flag_mu=(trim(answer)=='T')
   end if

   sections(i)%flag_plastic  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_plastic_'//cm(il:3),answer,ires)
      sections(i)%flag_plastic=(trim(answer)=='T')
   end if

   sections(i)%flag_q  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_q_'//cm(il:3),answer,ires)
      sections(i)%flag_q=(trim(answer)=='T')
   end if

   sections(i)%flag_lode  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_lode_'//cm(il:3),answer,ires)
      sections(i)%flag_lode=(trim(answer)=='T')
   end if

   sections(i)%flag_vfield  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_vfield_'//cm(il:3),answer,ires)
      sections(i)%flag_vfield=(trim(answer)=='T')
   end if

   sections(i)%flag_lsf  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_lsf_'//cm(il:3),answer,ires)
      sections(i)%flag_lsf=(trim(answer)=='T')
   end if

   sections(i)%flag_temp  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_temp_'//cm(il:3),answer,ires)
      sections(i)%flag_temp=(trim(answer)=='T')
   end if

   sections(i)%flag_velvect  = .false.
   if (iproc==0) then
      call scanfile (params%infile,'flag_velvect_'//cm(il:3),answer,ires)
      sections(i)%flag_velvect=(trim(answer)=='T')
   end if

   sections(i)%scale=100.d0
   if (iproc==0) call scanfile (params%infile,'scale_'//cm(il:3),sections(i)%scale,ires)

   if (iproc==0) call scanfile (params%infile,'colormap_'//cm(il:3),sections(i)%colormap,ires)

   if (iproc==0) call scanfile (params%infile,'ncolours_'//cm(il:3),sections(i)%ncolours,ires)
end do

!=====[erosion parameters]=====================================================
params%erosion=.false.
if (iproc==0) then
   call scanfile (params%infile,'erosion',answer,ires)
   params%erosion=(trim(answer)=='T')
end if
call mpi_bcast(params%erosion,1,mpi_logical,0,mpi_comm_world,ierr)

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

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

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

params%fluvial_erosion=2.d-1
if (iproc==0) call scanfile (params%infile,'fluvial_erosion',params%fluvial_erosion,ires)
call mpi_bcast(params%fluvial_erosion,1,mpi_double_precision,0,mpi_comm_world,ierr)

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

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

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

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

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

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

!=====[flexure parameters]=====================================================
params%isostasy=.false.
if (iproc.eq.0) then
   call scanfile (params%infile,'isostasy',answer,ires)
   params%isostasy=(trim(answer)=='T')
endif
Douglas Guptill's avatar
Douglas Guptill committed
call mpi_bcast(params%isostasy,1,mpi_logical,0,mpi_comm_world,ierr)

params%flexure=.false.
if (iproc.eq.0) then
   call scanfile (params%infile,'flexure',answer,ires)
   params%flexure=(trim(answer)=='T')
endif
Douglas Guptill's avatar
Douglas Guptill committed
call mpi_bcast(params%flexure,1,mpi_logical,0,mpi_comm_world,ierr)
Dave Whipp's avatar
Dave Whipp committed
params%isobc=.false. 
if (iproc==0) then 
   call scanfile (params%infile,'isobc',answer,ires)  
   params%isobc=(trim(answer)=='T') 
end if 
call mpi_bcast(params%isobc,1,mpi_logical,0,mpi_comm_world,ierr) 

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

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

!=====[nest parameters]========================================================
params%nest=.false.
if (iproc==0) then
   call scanfile (params%infile,'nest',answer,ires)  
   params%nest=(trim(answer)=='T') 
end if 
call mpi_bcast(params%nest,1,mpi_logical,0,mpi_comm_world,ierr) 

if (params%nest) then
Dave Whipp's avatar
Dave Whipp committed
   nest%lsoutfile='OUT/time_0001.bin'
   if (iproc.eq.0) call scanfile (params%infile,'lsoutfile',nest%lsoutfile,ires)
   call mpi_bcast(nest%lsoutfile,128,mpi_character,0,mpi_comm_world,ierr)

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

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

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

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

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

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

! Defined, but not broadcast or read from input file
!params%distance_exponent=-log(2.d0)/log(cos(params%anglemax))
params%distance_exponent=1.d0
! Input values are now written to stdout or log files here
if (params%debug.gt.0 .and. iproc.eq.0) then
  write(*,'(a)')         shift//'Input file values: '
Dave Whipp's avatar
Dave Whipp committed
  write(*,'(a,i4)')    shift//'nstep ',params%nstep
  write(*,'(a,i4)')    shift//'material0 ',material0
Dave Whipp's avatar
Dave Whipp committed
  write(*,'(a,l1)')    shift//'bulkvisc ',params%bulkvisc
Dave Whipp's avatar
Dave Whipp committed
  write(*,'(a,l1)')    shift//'init_e2d ',params%init_e2d
  write(*,'(a,e11.4)') shift//'e2d0 ',params%e2d0
    write(*,'(a,i4,a)')  shift//'--- Properties for material ',i,' ---'
Dave Whipp's avatar
Dave Whipp committed
    write(*,'(a,e11.4)') shift//'density ',mat(i)%density
    write(*,'(a,e11.4)') shift//'viscosity ',mat(i)%viscosity
    write(*,'(a,e11.4)') shift//'penalty ',mat(i)%penalty
    write(*,'(a,e11.4)') shift//'expon ',mat(i)%expon
    write(*,'(a,e11.4)') shift//'activationenergy ',mat(i)%activationenergy
    write(*,'(a,e11.4)') shift//'expansion ',mat(i)%expansion
    write(*,'(a,e11.4)') shift//'diffusivity ',mat(i)%diffusivity
    write(*,'(a,e11.4)') shift//'heat ',mat(i)%heat
    write(*,'(a,a8)')    shift//'plasticity_type ',mat(i)%plasticity_type
    if (trim(mat(i)%plasticity_type).ne.'No') then
      write(*,'(a,i4)') shift//'Plasticity parameters for material ',i
      do j=1,9
Dave Whipp's avatar
Dave Whipp committed
        write(*,'(a,i1,a2,e11.4)') shift//'plasticity parameter ',j,': ',mat(i)%plasticity_parameters(j)
Dave Whipp's avatar
Dave Whipp committed
    write(*,'(a,e11.4)') shift//'ztrans mat ',mat(i)%ztrans
    write(*,'(a,i4)')    shift//'transnum mat ',mat(i)%transnum
Dave Whipp's avatar
Dave Whipp committed
  write(*,'(a,e11.4)') shift//'viscositymin ',params%viscositymin
  write(*,'(a,e11.4)') shift//'viscositymax ',params%viscositymax
  write(*,'(a,e11.4)') shift//'vex ',params%vex
  write(*,'(a,i4)')    shift//'leveluniform_oct ',params%leveluniform_oct
  write(*,'(a,i4)')    shift//'levelmax_oct ',params%levelmax_oct
  write(*,'(a,i4)')    shift//'matrule ',params%matrule
  write(*,'(a,i4)')    shift//'levelcut ',params%levelcut
  write(*,'(a,i4)')    shift//'levelapprox ',params%levelapprox
  write(*,'(a,l1)')    shift//'calculate_temp ',params%calculate_temp
  write(*,'(a,e11.4)') shift//'ztemp ',params%ztemp
  write(*,'(a,i4)')    shift//'smoothing_type ',params%smoothing_type
  write(*,'(a,l1)')    shift//'normaladvect ',params%normaladvect
  write(*,'(a,l1)')    shift//'excl_vol ',params%excl_vol
  write(*,'(a,l1)')    shift//'adaptive_tol ',params%adaptive_tol
    write(*,'(a,i4,a)')       shift//'--- Properties for surface ',i,' ---'
    write(*,'(a,i4,a,i4)')    shift//'surface ',i,' itype ',surface(i)%itype
    write(*,'(a,i4,a,i4)')    shift//'surface ',i,' material ',surface(i)%material
    write(*,'(a,i4,a,l1)')    shift//'surface ',i,' rand ',surface(i)%rand
    write(*,'(a,i4,a,i4)')    shift//'surface ',i,' levelt ',surface(i)%levelt
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' stretch ',surface(i)%stretch
    write(*,'(a,i4,a,i4)')    shift//'surface ',i,' criterion ',surface(i)%criterion
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' anglemax ',surface(i)%anglemax
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' anglemaxoctree ',surface(i)%anglemaxoctree
    write(*,'(a,i4,a,i4)')    shift//'surface ',i,' spread_surface_points ',surface(i)%spread_surface_points
    write(*,'(a,i4,a,i4)')    shift//'surface ',i,' type ',surface(i)%surface_type
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp01 ',surface(i)%sp01
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp02 ',surface(i)%sp02
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp03 ',surface(i)%sp03
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp04 ',surface(i)%sp04
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp05 ',surface(i)%sp05
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp06 ',surface(i)%sp06
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp07 ',surface(i)%sp07
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp08 ',surface(i)%sp08
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp09 ',surface(i)%sp09
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp10 ',surface(i)%sp10
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp11 ',surface(i)%sp11
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' sp12 ',surface(i)%sp12
    write(*,'(a,i4,a,e11.4)') shift//'surface ',i,' activation_time ',surface(i)%activation_time
    write(*,'(a,i4,a,i4)')    shift//'surface ',i,' leveloct ',surface(i)%leveloct
Dave Whipp's avatar
Dave Whipp committed
  write(*,'(a,l1)') shift//'ref_on_faces ',params%ref_on_faces
      write(*,'(a,i1,a)')  shift//'--- Refinement values for face ',i,' ---'
Dave Whipp's avatar
Dave Whipp committed
      write(*,'(a,i4)')    shift//'cube_faces level ',cube_faces(i)%level
      write(*,'(a,e11.4)') shift//'cube_faces l ',cube_faces(i)%l
      write(*,'(a,e11.4)') shift//'cube_faces r ',cube_faces(i)%r
      write(*,'(a,e11.4)') shift//'cube_faces b ',cube_faces(i)%b
      write(*,'(a,e11.4)') shift//'cube_faces t ',cube_faces(i)%t
  write(*,'(a,i12)') shift//'noctreemax ',params%noctreemax
Dave Whipp's avatar
Dave Whipp committed
  write(*,'(a,i4)') shift//'nonlinear_iterations ',params%nonlinear_iterations
  write(*,'(a,i4)') shift//'initial_refine_level ',params%initial_refine_level
  write(*,'(a,e11.4)') shift//'dt ',params%dt
  write(*,'(a,l1)') shift//'damp_surface ',params%damp_surface
Dave Whipp's avatar
Dave Whipp committed
  write(*,'(a,e11.4)') shift//'penalty ',params%penalty
  write(*,'(a,e11.4)') shift//'tempscale ',params%tempscale
  write(*,'(a,e11.4)') shift//'refine_ratio ',params%refine_ratio
  write(*,'(a,i4)') shift//'refine_criterion ',params%refine_criterion
  write(*,'(a,e11.4)') shift//'octree_refine_ratio ',params%octree_refine_ratio
  write(*,'(a,e11.4)') shift//'courant ',params%courant
  write(*,'(a,l1)') shift//'invariants_2d ',params%invariants_2d
  write(*,'(a,i4)') shift//'npmin ',params%npmin
  write(*,'(a,i4)') shift//'npmax ',params%npmax
  write(*,'(a,i4)') shift//'griditer ',params%griditer
  write(*,'(a,e11.4)') shift//'tol ',params%tol
  write(*,'(a,i4)') shift//'niter_move ',params%niter_move
  write(*,'(a,l1)') shift//'ismooth ',params%ismooth
  write(*,'(a,i4)') shift//'nb_iter_nl_min ',params%nb_iter_nl_min
  write(*,'(a,l1)') shift//'visualise_matrix ',params%visualise_matrix
  write(*,'(a,l1)') shift//'renumber_nodes ',params%renumber_nodes
  if (params%nboxes.gt.0) then
    do i=1,params%nboxes
      write(*,'(a,i3,a)')  shift//'--- Input values for box ',i,' ---'
Dave Whipp's avatar
Dave Whipp committed
      write(*,'(a,e11.4)') shift//'box x0 ',boxes(i)%x0
      write(*,'(a,e11.4)') shift//'box x1 ',boxes(i)%x1
      write(*,'(a,e11.4)') shift//'box y0 ',boxes(i)%y0
      write(*,'(a,e11.4)') shift//'box y1 ',boxes(i)%y1
      write(*,'(a,e11.4)') shift//'box z0 ',boxes(i)%z0
      write(*,'(a,e11.4)') shift//'box z1 ',boxes(i)%z1
      write(*,'(a,i4)')    shift//'box level ',boxes(i)%level
    enddo
  endif
  if (params%nsections.gt.0) then
    do i=1,params%nsections
      write(*,'(a,i3,a)')  shift//'--- Input values for section ',i,' ---'    
Dave Whipp's avatar
Dave Whipp committed
      write(*,'(a,i4)')    shift//'section xyz ',sections(i)%xyz
      write(*,'(a,e11.4)') shift//'section slice ',sections(i)%slice
      write(*,'(a,l1)')    shift//'section flag press ',sections(i)%flag_press
      write(*,'(a,l1)')    shift//'section flag spress ',sections(i)%flag_spress
      write(*,'(a,l1)')    shift//'section flag e2d ',sections(i)%flag_e2d
      write(*,'(a,l1)')    shift//'section flag e3d ',sections(i)%flag_e3d
      write(*,'(a,l1)')    shift//'section flag strain ',sections(i)%flag_strain
      write(*,'(a,l1)')    shift//'section flag crit ',sections(i)%flag_crit
      write(*,'(a,l1)')    shift//'section flag grid ',sections(i)%flag_grid
      write(*,'(a,l1)')    shift//'section flag u ',sections(i)%flag_u
      write(*,'(a,l1)')    shift//'section flag v ',sections(i)%flag_v  
      write(*,'(a,l1)')    shift//'section flag w ',sections(i)%flag_w 
      write(*,'(a,l1)')    shift//'section flag uvw ',sections(i)%flag_uvw
      write(*,'(a,l1)')    shift//'section flag colour ',sections(i)%flag_colour
      write(*,'(a,l1)')    shift//'section flag mu ',sections(i)%flag_mu
      write(*,'(a,l1)')    shift//'section flag plastic ',sections(i)%flag_plastic
      write(*,'(a,l1)')    shift//'section flag q ',sections(i)%flag_q
      write(*,'(a,l1)')    shift//'section flag lode ',sections(i)%flag_lode
      write(*,'(a,l1)')    shift//'section flag vfield ',sections(i)%flag_vfield
      write(*,'(a,l1)')    shift//'section flag lsf ',sections(i)%flag_lsf
      write(*,'(a,i3)')    shift//'section flag temp ',sections(i)%flag_temp
      write(*,'(a,l1)')    shift//'section flag velvect ',sections(i)%flag_velvect
      write(*,'(a,e11.4)') shift//'section scale ',sections(i)%scale
      write(*,'(a,a3)')    shift//'section colormap ',sections(i)%colormap