Skip to content
Snippets Groups Projects
Commit 90665b46 authored by Antoine Cyril David Hoffmann's avatar Antoine Cyril David Hoffmann
Browse files

inputfile+jobid e.g. fort_00.90. the id is set as first or third arg

parent b266f63f
No related branches found
No related tags found
No related merge requests found
...@@ -58,7 +58,6 @@ MODULE basic ...@@ -58,7 +58,6 @@ MODULE basic
END INTERFACE allocate_array END INTERFACE allocate_array
CONTAINS CONTAINS
!================================================================================ !================================================================================
SUBROUTINE basic_data SUBROUTINE basic_data
! Read basic data for input file ! Read basic data for input file
...@@ -66,6 +65,8 @@ CONTAINS ...@@ -66,6 +65,8 @@ CONTAINS
use prec_const use prec_const
IMPLICIT NONE IMPLICIT NONE
CALL find_input_file
NAMELIST /BASIC/ nrun, dt, tmax, maxruntime NAMELIST /BASIC/ nrun, dt, tmax, maxruntime
READ(lu_in,basic) READ(lu_in,basic)
...@@ -76,6 +77,28 @@ CONTAINS ...@@ -76,6 +77,28 @@ CONTAINS
END SUBROUTINE basic_data END SUBROUTINE basic_data
!================================================================================ !================================================================================
SUBROUTINE find_input_file
IMPLICIT NONE
CHARACTER(len=32) :: str, input_file
INTEGER :: nargs, fileid, l
LOGICAL :: mlexist
nargs = COMMAND_ARGUMENT_COUNT()
IF((nargs .EQ. 1) .OR. (nargs .EQ. 3)) THEN
CALL GET_COMMAND_ARGUMENT(nargs, str, l, ierr)
READ(str(1:l),'(i3)') fileid
WRITE(input_file,'(a,a1,i2.2,a3)') 'fort','_',fileid,'.90'
INQUIRE(file=input_file, exist=mlexist)
IF( mlexist ) THEN
IF(my_id.EQ.0) write(*,*) 'Reading input ', input_file,'...'
OPEN(lu_in, file=input_file)
ELSE
IF(my_id.EQ.0) write(*,*) 'Reading input fort.90...'
OPEN(lu_in, file='fort.90')
ENDIF
ENDIF
END SUBROUTINE find_input_file
!================================================================================
SUBROUTINE daytim(str) SUBROUTINE daytim(str)
! Print date and time ! Print date and time
......
...@@ -19,13 +19,9 @@ SUBROUTINE ppinit ...@@ -19,13 +19,9 @@ SUBROUTINE ppinit
CALL MPI_COMM_SIZE (MPI_COMM_WORLD, num_procs, ierr) CALL MPI_COMM_SIZE (MPI_COMM_WORLD, num_procs, ierr)
nargs = COMMAND_ARGUMENT_COUNT() nargs = COMMAND_ARGUMENT_COUNT()
IF( nargs .NE. 0 .AND. nargs .NE. ndims ) THEN
IF(my_id .EQ. 0) WRITE(*, '(a,i4,a)') 'Number of arguments not equal to NDIMS =', ndims, '!'
CALL MPI_ABORT(MPI_COMM_WORLD, -1, ierr)
END IF
! !
IF( nargs .NE. 0 ) THEN IF( nargs .GT. 1 ) THEN
DO i=1,nargs DO i=1,ndims
CALL GET_COMMAND_ARGUMENT(i, str, l, ierr) CALL GET_COMMAND_ARGUMENT(i, str, l, ierr)
READ(str(1:l),'(i3)') dims(i) READ(str(1:l),'(i3)') dims(i)
END DO END DO
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment