Skip to content
Snippets Groups Projects
read_controlling_parameters.f90 4.45 KiB
Newer Older
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|
!                                                                              |
!              ||===\\                                                         | 
!              ||    \\                                                        |
!              ||     ||   //==\\   ||  ||   //==||  ||/==\\                   |
!              ||     ||  ||    ||  ||  ||  ||   ||  ||    ||                  |
!              ||    //   ||    ||  ||  ||  ||   ||  ||                        |
!              ||===//     \\==//    \\==\\  \\==\\  ||                        |
!                                                                              |
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|
!                                                                              |
!             READ_CONTROLLING_PARAMETERS     Apr. 2006                        |
!                                                                              |
!------------------------------------------------------------------------------|
!------------------------------------------------------------------------------|

subroutine read_controlling_parameters (params,threadinfo)

!------------------------------------------------------------------------------|
!(((((((((((((((( Purpose of the routine  ))))))))))))))))))))))))))))))))))))))
!------------------------------------------------------------------------------|
! subroutine to read the main controlling parameters
! ns number of surfaces in the problem
! nmat is number of material property arrays
! 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
! nboxes is the number of user supplied pre-refined boxes
! doDoRuRe is a flag that triggers the output of various statistics

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

use definitions

implicit none
type(parameters) params
type (thread) threadinfo
integer ires
integer iproc,nproc,ierr
character(len=1) :: answer

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

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

call mpi_comm_size (mpi_comm_world,nproc,ierr)
call mpi_comm_rank (mpi_comm_world,iproc,ierr)

if (iproc.eq.0) call scanfile (params%infile,'irestart',params%irestart,ires)
call mpi_bcast(params%irestart,1,mpi_integer,0,mpi_comm_world,ierr)
write(threadinfo%Logunit,*) 'irestart',params%irestart

if (iproc.eq.0) call scanfile (params%infile,'restartfile',params%restartfile,ires)

if (iproc.eq.0) call scanfile (params%infile,'ns',params%ns,ires)
call mpi_bcast(params%ns,1,mpi_integer,0,mpi_comm_world,ierr)
write(threadinfo%Logunit,*) 'ns',params%ns

if (iproc.eq.0) call scanfile (params%infile,'nmat',params%nmat,ires)
call mpi_bcast(params%nmat,1,mpi_integer,0,mpi_comm_world,ierr)
write(threadinfo%Logunit,*) 'nmat',params%nmat

if (iproc.eq.0) call scanfile (params%infile,'nboxes',params%nboxes,ires)
call mpi_bcast(params%nboxes,1,mpi_integer,0,mpi_comm_world,ierr)
write(threadinfo%Logunit,*) 'nboxes',params%nboxes

if (iproc.eq.0) call scanfile (params%infile,'nsections',params%nsections,ires)
call mpi_bcast(params%nsections,1,mpi_integer,0,mpi_comm_world,ierr)
write(threadinfo%Logunit,*) 'nsections',params%nsections

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


if (iproc.eq.0) call system ('rm fort.8')

return
end subroutine


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