read_sphincs_id_parameters Subroutine

public subroutine read_sphincs_id_parameters()

Read the parameters to steer SPHINCS_ID

FT


Arguments

None

Called by

proc~~read_sphincs_id_parameters~~CalledByGraph proc~read_sphincs_id_parameters read_sphincs_id_parameters program~convergence_test convergence_test program~convergence_test->proc~read_sphincs_id_parameters program~sphincs_id sphincs_id program~sphincs_id->proc~read_sphincs_id_parameters

Contents


Variables

Type Visibility Attributes Name Initial
character(len=100), public :: msg
character(len=:), public, ALLOCATABLE :: sphincs_id_parameters_namefile
integer, public :: stat
integer, public, parameter :: unit_parameters = 17

Source Code

  SUBROUTINE read_sphincs_id_parameters()

    !***********************************************
    !
    !# Read the parameters to steer SPHINCS_ID
    !
    !  FT
    !
    !***********************************************

    IMPLICIT NONE

    INTEGER:: stat
    INTEGER, PARAMETER:: unit_parameters= 17

    CHARACTER(LEN=:), ALLOCATABLE:: sphincs_id_parameters_namefile
    CHARACTER(LEN=100):: msg

    ! Namelist containing parameters read from sphincs_id_parameters.par
    ! by the SUBROUTINE read_sphincs_id_parameters of this PROGRAM
    NAMELIST /sphincs_id_parameters/ &
              n_id, common_path, filenames, &
              common_eos_path, use_eos_from_id, eos_filenames, &
              placer, export_bin, export_form, export_form_xy, &
              export_form_x, export_constraints_xy, &
              export_constraints_x, compute_constraints, &
              export_constraints, export_constraints_details, &
              constraints_step, compute_parts_constraints, &
              numerator_ratio_dx, denominator_ratio_dx, ref_lev, &
              one_lapse, zero_shift, show_progress, &
              run_sph, run_spacetime, sph_path, spacetime_path, &
              estimate_length_scale

    use_eos_from_id= .TRUE.

    sphincs_id_parameters_namefile= 'sphincs_id_parameters.dat'

    INQUIRE( FILE= sphincs_id_parameters_namefile, EXIST= file_exists )
    IF( file_exists )THEN

      OPEN( unit_parameters, FILE= sphincs_id_parameters_namefile, &
            STATUS= 'OLD' )

    ELSE

      PRINT*
      PRINT*,'** ERROR: ', sphincs_id_parameters_namefile, " file not found!"
      PRINT*
      STOP

    ENDIF

    READ( UNIT= unit_parameters, NML= sphincs_id_parameters, IOSTAT= stat, &
          IOMSG= msg )

    IF( stat /= 0 )THEN
      PRINT *, "** ERROR: Error in reading ", sphincs_id_parameters_namefile, &
               ". The IOSTAT variable is ", stat, &
               "The error message is", msg
      STOP
    ENDIF

    CLOSE( UNIT= unit_parameters )

    DO itr= 1, max_length, 1
      IF( TRIM(filenames(itr)).NE."0" )THEN
        cnt= cnt + 1
      ENDIF
    ENDDO
    IF( cnt.NE.n_id )THEN
      PRINT *, "** ERROR! The number of file names is", cnt, &
               "and n_id=", n_id, ". The two should be the same."
      PRINT *
      STOP
    ENDIF

   !DO itr= 1, n_id, 1
   !  DO itr2= 1, max_n_parts, 1
   !    IF( placer( itr, itr2 ) == test_int )THEN
   !      PRINT *
   !      PRINT *, "** ERROR! The array placer does not have ", &
   !               "enough components to specify all the desired ", &
   !               "particle distributions. Specify the ", &
   !               "components in file sphincs_id_particles.par"
   !      PRINT *
   !      STOP
   !    ENDIF
   !  ENDDO
   !ENDDO

  END SUBROUTINE read_sphincs_id_parameters