Newer
Older
MODULE basic
! Basic module for time dependent problems
use prec_const, ONLY : xp
PRIVATE
! INPUT PARAMETERS
INTEGER, PUBLIC, PROTECTED :: nrun = 1 ! Number of time steps to run
real(xp), PUBLIC, PROTECTED :: tmax = 100000.0 ! Maximum simulation time
real(xp), PUBLIC, PROTECTED :: dt = 1.0 ! Time step
real(xp), PUBLIC, PROTECTED :: maxruntime = 1e9 ! Maximum simulation CPU time
INTEGER, PUBLIC, PROTECTED :: job2load = 99 ! jobnum of the checkpoint to load
INTEGER, PUBLIC, PROTECTED :: VERBOSE_LVL= 1 ! tune the amount of std out (0: only time and fluxes, 1: MPI distribution, 2: all stages of init)
! Auxiliary variables
real(xp), PUBLIC, PROTECTED :: time = 0 ! Current simulation time (Init from restart file)
INTEGER, PUBLIC, PROTECTED :: jobnum = 0 ! Job number
INTEGER, PUBLIC, PROTECTED :: step = 0 ! Calculation step of this run
INTEGER, PUBLIC, PROTECTED :: cstep = 0 ! Current step number (Init from restart file)
LOGICAL, PUBLIC :: nlend = .FALSE. ! Signal end of run
LOGICAL, PUBLIC :: crashed = .FALSE. ! Signal end of crashed run
INTEGER, PUBLIC :: iframe0d ! counting the number of times 0d datasets are outputed (for diagnose)
INTEGER, PUBLIC :: iframe1d ! counting the number of times 1d datasets are outputed (for diagnose)
INTEGER, PUBLIC :: iframe2d ! counting the number of times 2d datasets are outputed (for diagnose)
INTEGER, PUBLIC :: iframe3d ! counting the number of times 3d datasets are outputed (for diagnose)
INTEGER, PUBLIC :: iframe5d ! counting the number of times 5d datasets are outputed (for diagnose)
! input file name
CHARACTER(len=32), PUBLIC, PROTECTED :: input_file = "params.in"
INTEGER, PUBLIC, PROTECTED :: lu_in = 90 ! File duplicated from STDIN
INTEGER, PUBLIC, PROTECTED :: lu_stop = 91 ! stop file, see subroutine TESEND
! To measure computation time
real(xp) :: tstart !start of the chrono
real(xp) :: tstop !stop
real(xp) :: ttot !cumulative time
! Define the chronos for each relevant routines
type(chrono), PUBLIC, PROTECTED :: chrono_runt, chrono_mrhs, chrono_advf, chrono_pois, chrono_sapj,&
chrono_diag, chrono_chck, chrono_step, chrono_clos, chrono_ghst, chrono_coll, chrono_napj, &
chrono_grad, chrono_ExBs
#ifdef TEST_SVD
type(chrono), PUBLIC, PROTECTED :: chrono_CLA
! This sets if the outputs is done through a large gather or using parallelization from futils
! it is recommended to set it to .true.
LOGICAL, PUBLIC, PROTECTED :: GATHERV_OUTPUT = .true.
! Store as a parameter the path to the main directory of the code
! (the path to gyacomo dir is stored during the compilation)
#ifdef __GYACDIR__
CHARACTER(len=*), PUBLIC, PARAMETER :: maindir = __GYACDIR__
#else
CHARACTER(len=*), PUBLIC, PARAMETER :: maindir = ""
#endif
PUBLIC :: allocate_array, basic_outputinputs,basic_data, show_title,&
speak, str, increase_step, increase_cstep, increase_time, display_h_min_s,&
set_basic_cp, daytim, start_chrono, stop_chrono, change_dt, day_and_time_str
! Interface for allocating arrays, these routines allocate and initialize directly to zero
MODULE PROCEDURE allocate_array_xp1,allocate_array_xp2,allocate_array_xp3, &
allocate_array_xp4, allocate_array_xp5, allocate_array_xp6, allocate_array_xp7
MODULE PROCEDURE allocate_array_dc1,allocate_array_dc2,allocate_array_dc3, &
allocate_array_dc4, allocate_array_dc5, allocate_array_dc6, allocate_array_dc7
MODULE PROCEDURE allocate_array_i1,allocate_array_i2,allocate_array_i3,allocate_array_i4
MODULE PROCEDURE allocate_array_l1,allocate_array_l2,allocate_array_l3,allocate_array_l4
END INTERFACE allocate_array
INTERFACE str
MODULE PROCEDURE str_xp, str_int
END INTERFACE
CONTAINS
!================================================================================
SUBROUTINE basic_data
! Read basic data for input file
use prec_const
IMPLICIT NONE
NAMELIST /BASIC/ nrun, dt, tmax, maxruntime, job2load, VERBOSE_LVL

Antoine Cyril David Hoffmann
committed
CALL find_input_file
!Init chronometers
chrono_mrhs%ttot = 0
chrono_pois%ttot = 0
chrono_sapj%ttot = 0
chrono_napj%ttot = 0
chrono_grad%ttot = 0
chrono_advf%ttot = 0
chrono_ghst%ttot = 0
chrono_clos%ttot = 0
chrono_chck%ttot = 0
chrono_diag%ttot = 0
chrono_step%ttot = 0
#ifdef TEST_SVD
chrono_CLA%ttot = 0
#endif
SUBROUTINE basic_outputinputs(fid)
!
! Write the input parameters to the results_xx.h5 file
!
USE prec_const
USE futils, ONLY: attach, creatd
IMPLICIT NONE
INTEGER, INTENT(in) :: fid
CHARACTER(len=256) :: str
WRITE(str,'(a)') '/data/input/basic'
CALL creatd(fid, 0,(/0/),TRIM(str),'Basic Input')
CALL attach(fid, TRIM(str), "start_iframe0d", iframe0d)
CALL attach(fid, TRIM(str), "start_iframe2d", iframe2d)
CALL attach(fid, TRIM(str), "start_iframe3d", iframe3d)
CALL attach(fid, TRIM(str), "start_iframe5d", iframe5d)
CALL attach(fid, TRIM(str), "start_time", time)
CALL attach(fid, TRIM(str), "start_cstep", cstep-1)
CALL attach(fid, TRIM(str), "dt", dt)
CALL attach(fid, TRIM(str), "tmax", tmax)
CALL attach(fid, TRIM(str), "nrun", nrun)
CALL attach(fid, TRIM(str), "cpu_time", -1)
END SUBROUTINE basic_outputinputs
SUBROUTINE increase_step
IMPLICIT NONE
step = step + 1
END SUBROUTINE
SUBROUTINE increase_cstep
IMPLICIT NONE
cstep = cstep + 1
END SUBROUTINE
SUBROUTINE change_dt(new_dt)
IMPLICIT NONE
REAL(xp), INTENT(IN) :: new_dt
dt = new_dt
END SUBROUTINE
SUBROUTINE increase_time
IMPLICIT NONE
time = time + dt
END SUBROUTINE
SUBROUTINE set_basic_cp(cstep_cp,time_cp,jobnum_cp)
IMPLICIT NONE
REAL(xp), INTENT(IN) :: time_cp
INTEGER, INTENT(IN) :: cstep_cp, jobnum_cp
cstep = cstep_cp
time = time_cp
jobnum = jobnum_cp+1
END SUBROUTINE
!! Chrono handling
SUBROUTINE start_chrono(timer)
IMPLICIT NONE
type(chrono) :: timer
CALL cpu_time(timer%tstart)
END SUBROUTINE
SUBROUTINE stop_chrono(timer)
IMPLICIT NONE
type(chrono) :: timer
CALL cpu_time(timer%tstop)
timer%ttot = timer%ttot + (timer%tstop-timer%tstart)
END SUBROUTINE
!================================================================================
! routine to speak in the terminal according to the verbose level
! The larger the verbose level, the more std output
SUBROUTINE speak(message,priority)
USE parallel, ONLY: my_id
IMPLICIT NONE
! input variables
CHARACTER(len=*), INTENT(IN) :: message
INTEGER, INTENT(IN) :: priority
! local variables
CHARACTER(len=16) :: indent
INTEGER :: i_
indent = ''
DO i_ = 1,priority
indent = trim(indent)//'-'
ENDDO
IF (priority .LE. VERBOSE_LVL) THEN
IF(my_id .EQ. 0) write(*,*) trim(indent)//message
ENDIF
END SUBROUTINE
!================================================================================
Antoine Cyril David Hoffmann
committed
SUBROUTINE find_input_file
USE parallel, ONLY: my_id
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
CHARACTER(len=32) :: str_
INTEGER :: nargs, fileid, l, ierr
LOGICAL :: mlexist, file_found
Antoine Cyril David Hoffmann
committed
nargs = COMMAND_ARGUMENT_COUNT()
file_found = .false. ! to check if the input file was correctly set
! Input param, option 1: input file is defined with an index as command argument
IF((nargs .EQ. 1) .OR. (nargs .EQ. 4)) THEN
CALL GET_COMMAND_ARGUMENT(nargs, str_, l, ierr)
READ(str_(1:l),'(i3)') fileid
! Old verson with "fort_XX.90" format (for retro compatibility)
Antoine Cyril David Hoffmann
committed
WRITE(input_file,'(a,a1,i2.2,a3)') 'fort','_',fileid,'.90'
INQUIRE(file=input_file, exist=mlexist)
IF( mlexist ) THEN
CALL speak('Reading input '// input_file,1)
Antoine Cyril David Hoffmann
committed
OPEN(lu_in, file=input_file)
Antoine Cyril David Hoffmann
committed
ELSE
! new verson with "params_XX.in" format
WRITE(input_file,'(a,a1,i2.2,a3)') 'params','_',fileid,'.in'
INQUIRE(file=input_file, exist=mlexist)
IF( mlexist ) THEN
CALL speak('Reading input '// input_file,1)
OPEN(lu_in, file=input_file)
file_found = .true.
ENDIF
ENDIF
IF (.NOT. file_found) THEN
WRITE(*,*) 'Error stop: ' // input_file // ' not found.'
ERROR STOP
ENDIF
ELSE
! Input param, option 2: a fort.90 or parameter.in input file is present
INQUIRE(file='fort.90', exist=mlexist)
IF ( mlexist ) THEN
CALL speak('Reading default input file (fort.90)',1)
Antoine Cyril David Hoffmann
committed
OPEN(lu_in, file='fort.90')
Antoine Cyril David Hoffmann
committed
ENDIF
! Test a parameters.in input file
INQUIRE(file='params.in', exist=mlexist)
IF ( mlexist ) THEN
CALL speak('Reading default input file (params.in)',1)
OPEN(lu_in, file='params.in')
file_found = .true.
ENDIF
Antoine Cyril David Hoffmann
committed
ENDIF
IF(.NOT. file_found) ERROR STOP "Error stop: basic input file not found (a file named params.in or fort.90 must be present)"
Antoine Cyril David Hoffmann
committed
END SUBROUTINE find_input_file
!================================================================================
SUBROUTINE daytim(str)
! Print date and time
USE parallel, ONLY: my_id
CHARACTER(len=*) , INTENT(in) :: str
CHARACTER(len=16) :: d, t, dat, time
!________________________________________________________________________________
!
CALL DATE_AND_TIME(d,t)
dat=d(7:8) // '/' // d(5:6) // '/' // d(1:4)
time=t(1:2) // ':' // t(3:4) // ':' // t(5:10)
IF (my_id .EQ. 0) &
WRITE(*,'(a,1x,a,1x,a)') str, dat(1:10), time(1:12)
!================================================================================
CHARACTER(64) FUNCTION day_and_time_str()
! Print date and time
USE parallel, ONLY: my_id
use prec_const
IMPLICIT NONE
CHARACTER(len=16) :: d, t, dat, time
!________________________________________________________________________________
!
CALL DATE_AND_TIME(d,t)
dat=d(7:8) // '/' // d(5:6) // '/' // d(1:4)
time=t(1:2) // ':' // t(3:4) // ':' // t(5:10)
day_and_time_str = trim(dat(1:10)//' '//trim(time(1:12)))
RETURN
END
!================================================================================
USE parallel, ONLY: my_id
IMPLICIT NONE
real(xp) :: time
integer :: days, hours, mins, secs
days = FLOOR(time/24./3600.);
hours= FLOOR(time/3600.);
mins = FLOOR(time/60.);
secs = FLOOR(time);
IF ( days .GT. 0 ) THEN !display day h min s
hours = NINT((time/3600./24. - days) * 24)
mins = NINT((time/3600. - days*24. - hours) * 60)
secs = NINT((time/60. - days*24.*60 - hours*60 - mins) * 60)
IF (my_id .EQ. 0) WRITE(*,*) 'CPU Time = ', days, '[day]', hours, '[h]', mins, '[min]', secs, '[s]'
IF (my_id .EQ. 0) WRITE(*,*) '(',time,'[s])'
ELSEIF ( hours .GT. 0 ) THEN !display h min s
mins = NINT((time/3600. - hours) * 60)
secs = NINT((time/60. - hours*60 - mins) * 60)
IF (my_id .EQ. 0) WRITE(*,*) 'CPU Time = ', hours, '[h]', mins, '[min]', secs, '[s]'
IF (my_id .EQ. 0) WRITE(*,*) '(',time,'[s])'
ELSEIF ( mins .GT. 0 ) THEN !display min s
secs = NINT((time/60. - mins) * 60)
IF (my_id .EQ. 0) WRITE(*,*) 'CPU Time = ', mins, '[min]', secs, '[s]'
IF (my_id .EQ. 0) WRITE(*,*) '(',time,'[s])'
IF (my_id .EQ. 0) WRITE(*,*) 'CPU Time = ', FLOOR(time), '[s]'
!================================================================================
function str_xp(k) result( str_ )
! "Convert an integer to string."
REAL(xp), intent(in) :: k
character(len=10):: str_
write (str_, "(G10.2)") k
str_ = adjustl(str_)
end function str_xp
function str_int(k) result( str_ )
! "Convert an integer to string."
integer, intent(in) :: k
end function str_int
! To allocate arrays of doubles, integers, etc. at run time
SUBROUTINE allocate_array_xp1(a,is1,ie1)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
real(xp), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1
ALLOCATE(a(is1:ie1))
a=0.0_xp
END SUBROUTINE allocate_array_xp1
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_xp2(a,is1,ie1,is2,ie2)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
real(xp), DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2
a=0.0_xp
END SUBROUTINE allocate_array_xp2
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_xp3(a,is1,ie1,is2,ie2,is3,ie3)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
real(xp), DIMENSION(:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3))
a=0.0_xp
END SUBROUTINE allocate_array_xp3
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_xp4(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
real(xp), DIMENSION(:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4))
a=0.0_xp
END SUBROUTINE allocate_array_xp4
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_xp5(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
real(xp), DIMENSION(:,:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4,is5:ie5))
a=0.0_xp
END SUBROUTINE allocate_array_xp5
SUBROUTINE allocate_array_xp6(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5,is6,ie6)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
real(xp), DIMENSION(:,:,:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
Antoine Cyril David Hoffmann
committed
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5,is6,ie6
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4,is5:ie5,is6:ie6))
a=0.0_xp
END SUBROUTINE allocate_array_xp6
SUBROUTINE allocate_array_xp7(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5,is6,ie6,is7,ie7)
IMPLICIT NONE
REAL(xp), DIMENSION(:,:,:,:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5,is6,ie6,is7,ie7
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4,is5:ie5,is6:ie6,is7:ie7))
a=0.0_xp
END SUBROUTINE allocate_array_xp7
Antoine Cyril David Hoffmann
committed
!========================================
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
COMPLEX(xp), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1
ALLOCATE(a(is1:ie1))
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_dc2(a,is1,ie1,is2,ie2)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
COMPLEX(xp), DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_dc3(a,is1,ie1,is2,ie2,is3,ie3)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
COMPLEX(xp), DIMENSION(:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3))
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_dc4(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
COMPLEX(xp), DIMENSION(:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4))
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_dc5(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
COMPLEX(xp), DIMENSION(:,:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4,is5:ie5))
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_dc6(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5,is6,ie6)
IMPLICIT NONE
COMPLEX(xp), DIMENSION(:,:,:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
Antoine Cyril David Hoffmann
committed
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5,is6,ie6
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4,is5:ie5,is6:ie6))
Antoine Cyril David Hoffmann
committed
END SUBROUTINE allocate_array_dc6
SUBROUTINE allocate_array_dc7(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5,is6,ie6,is7,ie7)
IMPLICIT NONE
COMPLEX(xp), DIMENSION(:,:,:,:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4,is5,ie5,is6,ie6,is7,ie7
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4,is5:ie5,is6:ie6,is7:ie7))
END SUBROUTINE allocate_array_dc7
Antoine Cyril David Hoffmann
committed
!========================================
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
INTEGER, DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1
ALLOCATE(a(is1:ie1))
a=0
END SUBROUTINE allocate_array_i1
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_i2(a,is1,ie1,is2,ie2)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
INTEGER, DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2
ALLOCATE(a(is1:ie1,is2:ie2))
a=0
END SUBROUTINE allocate_array_i2
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_i3(a,is1,ie1,is2,ie2,is3,ie3)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
INTEGER, DIMENSION(:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3))
a=0
END SUBROUTINE allocate_array_i3
Antoine Cyril David Hoffmann
committed
SUBROUTINE allocate_array_i4(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4)
Antoine Cyril David Hoffmann
committed
IMPLICIT NONE
INTEGER, DIMENSION(:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4))
a=0
END SUBROUTINE allocate_array_i4
Antoine Cyril David Hoffmann
committed
!========================================
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
SUBROUTINE allocate_array_l1(a,is1,ie1)
IMPLICIT NONE
LOGICAL, DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1
ALLOCATE(a(is1:ie1))
a=.false.
END SUBROUTINE allocate_array_l1
SUBROUTINE allocate_array_l2(a,is1,ie1,is2,ie2)
IMPLICIT NONE
LOGICAL, DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2
ALLOCATE(a(is1:ie1,is2:ie2))
a=.false.
END SUBROUTINE allocate_array_l2
SUBROUTINE allocate_array_l3(a,is1,ie1,is2,ie2,is3,ie3)
IMPLICIT NONE
LOGICAL, DIMENSION(:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3))
a=.false.
END SUBROUTINE allocate_array_l3
SUBROUTINE allocate_array_l4(a,is1,ie1,is2,ie2,is3,ie3,is4,ie4)
IMPLICIT NONE
LOGICAL, DIMENSION(:,:,:,:), ALLOCATABLE, INTENT(INOUT) :: a
INTEGER, INTENT(IN) :: is1,ie1,is2,ie2,is3,ie3,is4,ie4
ALLOCATE(a(is1:ie1,is2:ie2,is3:ie3,is4:ie4))
a=.false.
END SUBROUTINE allocate_array_l4
SUBROUTINE show_title
USE parallel, ONLY: my_id
IMPLICIT NONE
INCLUDE 'srcinfo/srcinfo.h' ! for the code version
IF(my_id .EQ. 0) THEN
write(*,*) "=============================================="
write(*,*) " ______ "
write(*,*) " / ____/_ ______ __________ ____ ___ ____ "
write(*,*) " / / __/ / / / __ `/ ___/ __ \/ __ `__ \/ __ \"
write(*,*) "/ /_/ / /_/ / /_/ / /__/ /_/ / / / / / / /_/ /"
write(*,*) "\____/\__, /\__,_/\___/\____/_/ /_/ /_/\____/ "
write(*,*) " /____/ "
! Write the git version of the code
write(*,*) 'This is the GYACOMO code'
write(*,*) 'version: ', VERSION
write(*,*) "=============================================="
ENDIF
END SUBROUTINE show_title