MODULE in_out_manager !!====================================================================== !! *** MODULE in_out_manager *** !! Ocean physics: vertical mixing coefficient compute from the tke !! turbulent closure parameterization !!===================================================================== !! History : 1.0 ! 2002-06 (G. Madec) original code !! 2.0 ! 2006-07 (S. Masson) iom, add ctl_stop, ctl_warn !! 3.0 ! 2008-06 (G. Madec) add ctmp4 to ctmp10 !! 3.2 ! 2009-08 (S. MAsson) add new ctl_opn !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! ctl_stop : update momentum and tracer Kz from a tke scheme !! ctl_warn : initialization, namelist read, and parameters control !! getunit : give the index of an unused logical unit !!---------------------------------------------------------------------- USE par_kind ! kind definition USE par_oce ! ocean parameter USE lib_print ! formated print library #if defined key_agrif USE Agrif_Util #endif IMPLICIT NONE PUBLIC !!---------------------------------------------------------------------- !! namrun namelist parameters !!---------------------------------------------------------------------- CHARACTER(len=16) :: cn_exp = "exp0" !: experiment name used for output filename CHARACTER(len=32) :: cn_ocerst_in = "restart" !: suffix of ocean restart name (input) CHARACTER(len=32) :: cn_ocerst_out = "restart" !: suffix of ocean restart name (output) LOGICAL :: ln_rstart = .FALSE. !: start from (F) rest or (T) a restart file INTEGER :: nn_no = 0 !: job number INTEGER :: nn_rstctl = 0 !: control of the time step (0, 1 or 2) INTEGER :: nn_rstssh = 0 !: hand made initilization of ssh or not (1/0) INTEGER :: nn_it000 = 1 !: index of the first time step INTEGER :: nn_itend = 10 !: index of the last time step INTEGER :: nn_date0 = 961115 !: initial calendar date aammjj INTEGER :: nn_leapy = 0 !: Leap year calendar flag (0/1 or 30) INTEGER :: nn_istate = 0 !: initial state output flag (0/1) INTEGER :: nn_write = 10 !: model standard output frequency INTEGER :: nn_stock = 10 !: restart file frequency LOGICAL :: ln_dimgnnn = .FALSE. !: type of dimgout. (F): 1 file for all proc !: (T): 1 file per proc LOGICAL :: ln_mskland = .FALSE. !: mask land points in NetCDF outputs (costly: + ~15%) LOGICAL :: ln_clobber = .FALSE. !: clobber (overwrite) an existing file INTEGER :: nn_chunksz = 0 !: chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) !! conversion of DOCTOR norm namelist name into model name !! (this should disappear in a near futur) CHARACTER(len=16) :: cexper !: experiment name used for output filename INTEGER :: no !: job number INTEGER :: nrstdt !: control of the time step (0, 1 or 2) INTEGER :: nit000 !: index of the first time step INTEGER :: nitend !: index of the last time step INTEGER :: ndate0 !: initial calendar date aammjj INTEGER :: nleapy !: Leap year calendar flag (0/1 or 30) INTEGER :: ninist !: initial state output flag (0/1) INTEGER :: nwrite !: model standard output frequency INTEGER :: nstock !: restart file frequency !!---------------------------------------------------------------------- !! was in restart but moved here because of the OFF line... better solution should be found... !!---------------------------------------------------------------------- INTEGER :: nitrst !: time step at which restart file should be written !!---------------------------------------------------------------------- !! output monitoring !!---------------------------------------------------------------------- LOGICAL :: ln_ctl = .FALSE. !: run control for debugging INTEGER :: nn_print = 0 !: level of print (0 no print) INTEGER :: nn_ictls = 0 !: Start i indice for the SUM control INTEGER :: nn_ictle = 0 !: End i indice for the SUM control INTEGER :: nn_jctls = 0 !: Start j indice for the SUM control INTEGER :: nn_jctle = 0 !: End j indice for the SUM control INTEGER :: nn_isplt = 1 !: number of processors following i INTEGER :: nn_jsplt = 1 !: number of processors following j INTEGER :: nn_bench = 0 !: benchmark parameter (0/1) INTEGER :: nn_bit_cmp = 0 !: bit reproducibility (0/1) ! !: OLD namelist names INTEGER :: nprint, nictls, nictle, njctls, njctle, isplt, jsplt, nbench, nbit_cmp INTEGER :: ijsplt = 1 !: nb of local domain = nb of processors !!---------------------------------------------------------------------- !! logical units !!---------------------------------------------------------------------- INTEGER :: numstp !: logical unit for time step INTEGER :: numout = 6 !: logical unit for output print INTEGER :: numnam !: logical unit for namelist INTEGER :: numnam_ice !: logical unit for ice namelist INTEGER :: numevo_ice !: logical unit for ice variables (temp. evolution) INTEGER :: numsol !: logical unit for solver statistics INTEGER :: numwri !: logical unit for output write INTEGER :: numgap !: logical unit for differences diagnostic INTEGER :: numbol !: logical unit for "bol" diagnostics INTEGER :: numptr !: logical unit for Poleward TRansports INTEGER :: numflo !: logical unit for drifting floats !!---------------------------------------------------------------------- !! Run control !!---------------------------------------------------------------------- INTEGER :: nstop = 0 !: error flag (=number of reason for a premature stop run) INTEGER :: nwarn = 0 !: warning flag (=number of warning found during the run) CHARACTER(len=200) :: ctmp1, ctmp2, ctmp3 !: temporary characters 1 to 3 CHARACTER(len=200) :: ctmp4, ctmp5, ctmp6 !: temporary characters 4 to 6 CHARACTER(len=200) :: ctmp7, ctmp8, ctmp9 !: temporary characters 7 to 9 CHARACTER(len=200) :: ctmp10 !: temporary character 10 CHARACTER (len=64) :: cform_err = "(/,' ===>>> : E R R O R', /,' ===========',/)" !: CHARACTER (len=64) :: cform_war = "(/,' ===>>> : W A R N I N G', /,' ===============',/)" !: LOGICAL :: lwp = .FALSE. !: boolean : true on the 1st processor only LOGICAL :: lsp_area = .TRUE. !: to make a control print over a specific area !!---------------------------------------------------------------------- !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008) !! $Id$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE ctl_stop( cd1, cd2, cd3, cd4, cd5, & & cd6, cd7, cd8, cd9, cd10 ) !!---------------------------------------------------------------------- !! *** ROUTINE stop_opa *** !! !! ** Purpose : print in ocean.outpput file a error message and !! increment the error number (nstop) by one. !!---------------------------------------------------------------------- CHARACTER(len=*), INTENT(in), OPTIONAL :: cd1, cd2, cd3, cd4, cd5 CHARACTER(len=*), INTENT(in), OPTIONAL :: cd6, cd7, cd8, cd9, cd10 !!---------------------------------------------------------------------- ! nstop = nstop + 1 IF(lwp) THEN WRITE(numout,"(/,' ===>>> : E R R O R', /,' ===========',/)") IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1 IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2 IF( PRESENT(cd3 ) ) WRITE(numout,*) cd3 IF( PRESENT(cd4 ) ) WRITE(numout,*) cd4 IF( PRESENT(cd5 ) ) WRITE(numout,*) cd5 IF( PRESENT(cd6 ) ) WRITE(numout,*) cd6 IF( PRESENT(cd7 ) ) WRITE(numout,*) cd7 IF( PRESENT(cd8 ) ) WRITE(numout,*) cd8 IF( PRESENT(cd9 ) ) WRITE(numout,*) cd9 IF( PRESENT(cd10) ) WRITE(numout,*) cd10 ENDIF CALL FLUSH(numout) ! END SUBROUTINE ctl_stop SUBROUTINE ctl_warn( cd1, cd2, cd3, cd4, cd5, & & cd6, cd7, cd8, cd9, cd10 ) !!---------------------------------------------------------------------- !! *** ROUTINE stop_warn *** !! !! ** Purpose : print in ocean.outpput file a error message and !! increment the warning number (nwarn) by one. !!---------------------------------------------------------------------- CHARACTER(len=*), INTENT(in), OPTIONAL :: cd1, cd2, cd3, cd4, cd5 CHARACTER(len=*), INTENT(in), OPTIONAL :: cd6, cd7, cd8, cd9, cd10 !!---------------------------------------------------------------------- ! nwarn = nwarn + 1 IF(lwp) THEN WRITE(numout,"(/,' ===>>> : W A R N I N G', /,' ===============',/)") IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1 IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2 IF( PRESENT(cd3 ) ) WRITE(numout,*) cd3 IF( PRESENT(cd4 ) ) WRITE(numout,*) cd4 IF( PRESENT(cd5 ) ) WRITE(numout,*) cd5 IF( PRESENT(cd6 ) ) WRITE(numout,*) cd6 IF( PRESENT(cd7 ) ) WRITE(numout,*) cd7 IF( PRESENT(cd8 ) ) WRITE(numout,*) cd8 IF( PRESENT(cd9 ) ) WRITE(numout,*) cd9 IF( PRESENT(cd10) ) WRITE(numout,*) cd10 ENDIF CALL FLUSH(numout) ! END SUBROUTINE ctl_warn SUBROUTINE ctl_opn ( knum, cdfile, cdstat, cdform, cdacce, klengh, kout, ldwp, karea ) !!---------------------------------------------------------------------- !! *** ROUTINE ctl_opn *** !! !! ** Purpose : Open file and check if required file is available. !! !! ** Method : Fortan open !! !! History : !! ! 1995-12 (G. Madec) Original code !! 8.5 ! 2002-06 (G. Madec) F90: Free form and module !!---------------------------------------------------------------------- INTEGER , INTENT( out) :: knum ! logical unit to open CHARACTER(len=*) , INTENT(in ) :: cdfile ! file name to open CHARACTER(len=*) , INTENT(in ) :: cdstat ! disposition specifier CHARACTER(len=*) , INTENT(in ) :: cdform ! formatting specifier CHARACTER(len=*) , INTENT(in ) :: cdacce ! access specifier INTEGER , INTENT(in ) :: klengh ! record length INTEGER , INTENT(in ) :: kout ! number of logical units for write LOGICAL , INTENT(in ) :: ldwp ! boolean term for print INTEGER, OPTIONAL, INTENT(in ) :: karea ! proc number !! CHARACTER(len=80) :: clfile INTEGER :: iost ! adapt filename ! ---------------- clfile = TRIM(cdfile) IF( PRESENT( karea ) ) THEN IF( karea > 1 ) WRITE(clfile, "(a,'_',i4.4)") TRIM(clfile), karea-1 ENDIF #if defined key_agrif IF( .NOT. Agrif_Root() ) clfile = TRIM(Agrif_CFixed())//'_'//TRIM(clfile) knum=Agrif_Get_Unit() #else knum=getunit() #endif iost=0 IF( cdacce(1:6) == 'DIRECT' ) THEN OPEN( UNIT=knum, FILE=clfile, FORM=cdform, ACCESS=cdacce, STATUS=cdstat, RECL=klengh, ERR=100, IOSTAT=iost ) ELSE OPEN( UNIT=knum, FILE=clfile, FORM=cdform, ACCESS=cdacce, STATUS=cdstat , ERR=100, IOSTAT=iost ) ENDIF IF( iost == 0 ) THEN IF(ldwp) THEN WRITE(kout,*) ' file : ', clfile,' open ok' WRITE(kout,*) ' unit = ', knum WRITE(kout,*) ' status = ', cdstat WRITE(kout,*) ' form = ', cdform WRITE(kout,*) ' access = ', cdacce WRITE(kout,*) ENDIF ENDIF 100 CONTINUE IF( iost /= 0 ) THEN IF(ldwp) THEN WRITE(kout,*) WRITE(kout,*) ' ===>>>> : bad opening file: ', clfile WRITE(kout,*) ' ======= === ' WRITE(kout,*) ' unit = ', knum WRITE(kout,*) ' status = ', cdstat WRITE(kout,*) ' form = ', cdform WRITE(kout,*) ' access = ', cdacce WRITE(kout,*) ' iostat = ', iost WRITE(kout,*) ' we stop. verify the file ' WRITE(kout,*) ENDIF STOP 'ctl_opn bad opening' ENDIF END SUBROUTINE ctl_opn FUNCTION getunit() !!---------------------------------------------------------------------- !! *** FUNCTION getunit *** !! !! ** Purpose : return the index of an unused logical unit !!---------------------------------------------------------------------- INTEGER :: getunit LOGICAL :: llopn !!---------------------------------------------------------------------- ! getunit = 15 ! choose a unit that is big enough then it is not already used in NEMO llopn = .TRUE. DO WHILE( (getunit < 998) .AND. llopn ) getunit = getunit + 1 INQUIRE( unit = getunit, opened = llopn ) END DO IF( (getunit == 999) .AND. llopn ) THEN CALL ctl_stop( 'getunit: All logical units until 999 are used...' ) getunit = -1 ENDIF ! END FUNCTION getunit !!===================================================================== END MODULE in_out_manager