Skip to content
Snippets Groups Projects
read_controlling_parameters.f90 6.93 KiB
Newer Older
  • Learn to ignore specific revisions
  • !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    !                                                                              |
    !              ||===\\                                                         | 
    !              ||    \\                                                        |
    !              ||     ||   //==\\   ||  ||   //==||  ||/==\\                   |
    !              ||     ||  ||    ||  ||  ||  ||   ||  ||    ||                  |
    !              ||    //   ||    ||  ||  ||  ||   ||  ||                        |
    !              ||===//     \\==//    \\==\\  \\==\\  ||                        |
    !                                                                              |
    !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    !                                                                              |
    !             READ_CONTROLLING_PARAMETERS     Apr. 2006                        |
    !                                                                              |
    !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    
    
    subroutine read_controlling_parameters (params,threadinfo,incase)
    
    
    !------------------------------------------------------------------------------|
    !(((((((((((((((( Purpose of the routine  ))))))))))))))))))))))))))))))))))))))
    !------------------------------------------------------------------------------|
    ! subroutine to read the main controlling parameters
    
    ! debug is the debug level (0=no debug output, 1=debug output to screen, 2=
    !   debug output to files in the DEBUG subdirectory - these files can be large!
    ! 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
    
    ! ns number of surfaces in the problem
    ! nmat is number of material property arrays
    ! nboxes is the number of user supplied pre-refined boxes
    
    ! nsections is the number of user-supplied cross-section locations for output
    
    ! 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
    
    
    !------------------------------------------------------------------------------|
    !(((((((((((((((( declaration of the subroutine internal variables )))))))))))))
    !------------------------------------------------------------------------------|
    
    integer ires
    integer iproc,nproc,ierr
    character(len=1)  :: answer
    character(len=3)  :: ciproc
    character(len=72) :: shift
    
    
    !------------------------------------------------------------------------------|
    !------------------------------------------------------------------------------|
    
    call mpi_comm_size (mpi_comm_world,nproc,ierr)
    call mpi_comm_rank (mpi_comm_world,iproc,ierr)
    
    
    shift=' '
    
    select case(trim(incase))
    
    case ('debug')
      params%debug=0
      if (iproc.eq.0) call scanfile (params%infile,'debug',params%debug,ires)
      call mpi_bcast(params%debug,1,mpi_integer,0,mpi_comm_world,ierr)
    
      ! Input values are now written to stdout or log files here
      if (params%debug.gt.0 .and. iproc.eq.0) then
    
        write(*,'(a)')      shift//'--------------------------------------------------------------------------------'
        write(*,'(a)')      shift//'--- INPUT FILE VALUES ---'
        write(*,'(a)')      shift//'--------------------------------------------------------------------------------'
        write(*,'(a)')      shift//'--- CONTROLLING PARAMETERS ---'
    
    Dave Whipp's avatar
    Dave Whipp committed
        write(*,'(a,i3)') shift//'debug',params%debug
    
      endif
    
    case ('main')
      params%irestart=0
      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)
    
      params%restartfile='OUT/xxxxxx.bin'
      if (iproc.eq.0) call scanfile (params%infile,'restartfile',params%restartfile,ires)
      call mpi_bcast(params%restartfile,128,mpi_character,0,mpi_comm_world,ierr)
    
      params%ns=1
      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)
    
      params%nmat=1
      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)
    
      params%nboxes=0
      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)
    
      params%nsections=0
      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)
    
      params%doDoRuRe=.false.
      if (iproc==0) then
         call scanfile (params%infile,'doDoRuRe',answer,ires)
         params%doDoRuRe=(trim(answer)=='T')
      endif
      call mpi_bcast(params%doDoRuRe,1,mpi_logical,0,mpi_comm_world,ierr)
    
      ! Input values are now written to stdout or log files here
      if (params%debug.gt.0 .and. iproc.eq.0) then
    
        write(*,'(a,l1)') shift//'doDoRuRe ',params%doDoRuRe
        write(*,'(a)')    shift//'--- RESTART ---'
    
    Dave Whipp's avatar
    Dave Whipp committed
        write(*,'(a,l1)') shift//'irestart ',params%irestart
        write(*,'(a,a)')  shift//'restartfile ',trim(params%restartfile)
    
        write(*,'(a)')    shift//'--- # OF SURFACES, MATERIALS, BOXES, SECTIONS ---'
    
    Dave Whipp's avatar
    Dave Whipp committed
        write(*,'(a,i3)') shift//'ns ',params%ns
        write(*,'(a,i3)') shift//'nmat ',params%nmat
        write(*,'(a,i3)') shift//'nboxes ',params%nboxes
        write(*,'(a,i3)') shift//'nsections ',params%nsections
    
        write(threadinfo%Logunit,'(a)') '--------------------------------------------------------------------------------'
        write(threadinfo%Logunit,'(a)') '--- INPUT FILE VALUES ---'
        write(threadinfo%Logunit,'(a)') '--------------------------------------------------------------------------------'
        write(threadinfo%Logunit,'(a)') '--- CONTROLLING PARAMETERS ---'
        write(threadinfo%Logunit,'(a16,l1)') 'doDoRuRe ',params%doDoRuRe
        write(threadinfo%Logunit,'(a)')      '--- RESTART ---'
    
    Dave Whipp's avatar
    Dave Whipp committed
        write(threadinfo%Logunit,'(a16,l1)') 'irestart ',params%irestart
        write(threadinfo%Logunit,'(a16,a)')  'restartfile ',trim(params%restartfile)
    
        write(threadinfo%Logunit,'(a)')      '--- # OF SURFACES, MATERIALS, BOXES, SECTIONS ---'
    
    Dave Whipp's avatar
    Dave Whipp committed
        write(threadinfo%Logunit,'(a16,i3)') 'ns ',params%ns
        write(threadinfo%Logunit,'(a16,i3)') 'nmat ',params%nmat
        write(threadinfo%Logunit,'(a16,i3)') 'nboxes ',params%nboxes
        write(threadinfo%Logunit,'(a16,i3)') 'nsections ',params%nsections
    
    Dave Whipp's avatar
    Dave Whipp committed
    !if (iproc.eq.0) call system ('rm fort.8')