New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
in_out_manager.F90 in trunk/NEMO/OPA_SRC/IOM – NEMO

source: trunk/NEMO/OPA_SRC/IOM/in_out_manager.F90 @ 1579

Last change on this file since 1579 was 1579, checked in by smasson, 15 years ago

avoid write in numout before definition of lwp, see ticket:237

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 10.8 KB
RevLine 
[544]1MODULE in_out_manager   
2   !!======================================================================
3   !!                       ***  MODULE  in_out_manager  ***
4   !! Ocean physics:  vertical mixing coefficient compute from the tke
5   !!                 turbulent closure parameterization
6   !!=====================================================================
[1056]7   !! History :   1.0  !  2002-06  (G. Madec)  original code
8   !!             2.0  !  2006-07  (S. Masson)  iom, add ctl_stop, ctl_warn
9   !!             3.0  !  2008-06  (G. Madec)  add ctmp4 to ctmp10
[544]10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   ctl_stop   : update momentum and tracer Kz from a tke scheme
14   !!   ctl_warn   : initialization, namelist read, and parameters control
[1056]15   !!   getunit    : give the index of an unused logical unit
[544]16   !!----------------------------------------------------------------------
[1056]17   USE par_kind        ! kind definition
18   USE par_oce         ! ocean parameter
19   USE lib_print       ! formated print library
[544]20
21   IMPLICIT NONE
22   PUBLIC
23
24   !!----------------------------------------------------------------------
25   !!                   namrun namelist parameters
26   !!----------------------------------------------------------------------
[1229]27   CHARACTER(len=16)  ::   cexper        = "exp0"      !: experiment name used for output filename
28   CHARACTER(len=32)  ::   cn_ocerst_in  = "restart"   !: suffix of ocean restart name (input)
29   CHARACTER(len=32)  ::   cn_ocerst_out = "restart"   !: suffix of ocean restart name (output)
30   LOGICAL            ::   ln_rstart     = .FALSE.     !: start from (F) rest or (T) a restart file
31   INTEGER            ::   no            = 0           !: job number
32   INTEGER            ::   nrstdt        = 0           !: control of the time step (0, 1 or 2)
33   INTEGER            ::   nn_rstssh     = 0           !: hand made initilization of ssh or not (1/0)
34   INTEGER            ::   nit000        = 1           !: index of the first time step
35   INTEGER            ::   nitend        = 10          !: index of the last time step
36   INTEGER            ::   ndate0        = 961115      !: initial calendar date aammjj
37   INTEGER            ::   nleapy        = 0           !: Leap year calendar flag (0/1 or 30)
38   INTEGER            ::   ninist        = 0           !: initial state output flag (0/1)
39   LOGICAL            ::   ln_dimgnnn    = .FALSE.     !: type of dimgout. (F): 1 file for all proc
40                                                       !:                  (T): 1 file per proc
[1312]41   LOGICAL            ::   ln_mskland    = .FALSE.     !: mask land points in NetCDF outputs (costly: + ~15%)
[1488]42   LOGICAL            ::   ln_clobber    = .FALSE.     !: clobber (overwrite) an existing file
43   INTEGER            ::   nn_chunksz    = 0           !: chunksize (bytes) for NetCDF file (working only with iom_nf90 routines)
[544]44   !!----------------------------------------------------------------------
[557]45   !! was in restart but moved here because of the OFF line... better solution should be found...
46   !!----------------------------------------------------------------------
47   INTEGER            ::   nitrst                 !: time step at which restart file should be written
48   !!----------------------------------------------------------------------
[544]49   !!                    output monitoring
50   !!----------------------------------------------------------------------
[556]51   LOGICAL            ::   ln_ctl     = .FALSE.   !: run control for debugging
[547]52   INTEGER            ::   nstock     =   10      !: restart file frequency
[544]53   INTEGER            ::   nprint     =    0      !: level of print (0 no print)
[547]54   INTEGER            ::   nwrite     =   10      !: restart file frequency
[544]55   INTEGER            ::   nictls     =    0      !: Start i indice for the SUM control
56   INTEGER            ::   nictle     =    0      !: End   i indice for the SUM control
57   INTEGER            ::   njctls     =    0      !: Start j indice for the SUM control
58   INTEGER            ::   njctle     =    0      !: End   j indice for the SUM control
59   INTEGER            ::   isplt      =    1      !: number of processors following i
60   INTEGER            ::   jsplt      =    1      !: number of processors following j
61   INTEGER            ::   ijsplt     =    1      !: nb of local domain = nb of processors
[556]62   INTEGER            ::   nbench     =    0      !: benchmark parameter (0/1)
63   INTEGER            ::   nbit_cmp   =    0      !: bit reproducibility  (0/1)
[544]64   !!----------------------------------------------------------------------
65   !!                        logical units
66   !!----------------------------------------------------------------------
[624]67   INTEGER            ::   numstp                 !: logical unit for time step
[1579]68   INTEGER            ::   numout     =    6      !: logical unit for output print
[624]69   INTEGER            ::   numnam                 !: logical unit for namelist
70   INTEGER            ::   numnam_ice             !: logical unit for ice namelist
71   INTEGER            ::   numevo_ice             !: logical unit for ice variables (temp. evolution)
72   INTEGER            ::   numsol                 !: logical unit for solver statistics
73   INTEGER            ::   numwri                 !: logical unit for output write
74   INTEGER            ::   numgap                 !: logical unit for differences diagnostic
75   INTEGER            ::   numbol                 !: logical unit for "bol" diagnostics
76   INTEGER            ::   numptr                 !: logical unit for Poleward TRansports
77   INTEGER            ::   numflo                 !: logical unit for drifting floats
[544]78
79   !!----------------------------------------------------------------------
80   !!                          Run control 
81   !!----------------------------------------------------------------------
[631]82
[544]83   INTEGER            ::   nstop = 0                !: error flag (=number of reason for a premature stop run)
84   INTEGER            ::   nwarn = 0                !: warning flag (=number of warning found during the run)
[1056]85   CHARACTER(len=200) ::   ctmp1, ctmp2, ctmp3      !: temporary characters 1 to 3
86   CHARACTER(len=200) ::   ctmp4, ctmp5, ctmp6      !: temporary characters 4 to 6
87   CHARACTER(len=200) ::   ctmp7, ctmp8, ctmp9      !: temporary characters 7 to 9
88   CHARACTER(len=200) ::   ctmp10                   !: temporary character 10
[544]89   CHARACTER (len=64) ::   cform_err = "(/,' ===>>> : E R R O R',     /,'         ===========',/)"       !:
90   CHARACTER (len=64) ::   cform_war = "(/,' ===>>> : W A R N I N G', /,'         ===============',/)"   !:
[1579]91   LOGICAL            ::   lwp      = .FALSE.       !: boolean : true on the 1st processor only
[544]92   LOGICAL            ::   lsp_area = .TRUE.        !: to make a control print over a specific area
93   !!----------------------------------------------------------------------
[1056]94   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
[1146]95   !! $Id$
[544]96   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
97   !!----------------------------------------------------------------------
98
99CONTAINS
100
101   SUBROUTINE ctl_stop( cd1, cd2, cd3, cd4, cd5,   &
102      &                 cd6, cd7, cd8, cd9, cd10 )
[1056]103      !!----------------------------------------------------------------------
[544]104      !!                  ***  ROUTINE  stop_opa  ***
105      !!
[1056]106      !! ** Purpose :   print in ocean.outpput file a error message and
107      !!                increment the error number (nstop) by one.
108      !!----------------------------------------------------------------------
[544]109      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5
110      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10
[1056]111      !!----------------------------------------------------------------------
[544]112      !
113      nstop = nstop + 1 
114      IF(lwp) THEN
115         WRITE(numout,"(/,' ===>>> : E R R O R',     /,'         ===========',/)") 
116         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1
117         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2
118         IF( PRESENT(cd3 ) ) WRITE(numout,*) cd3
119         IF( PRESENT(cd4 ) ) WRITE(numout,*) cd4
120         IF( PRESENT(cd5 ) ) WRITE(numout,*) cd5
121         IF( PRESENT(cd6 ) ) WRITE(numout,*) cd6
122         IF( PRESENT(cd7 ) ) WRITE(numout,*) cd7
123         IF( PRESENT(cd8 ) ) WRITE(numout,*) cd8
124         IF( PRESENT(cd9 ) ) WRITE(numout,*) cd9
125         IF( PRESENT(cd10) ) WRITE(numout,*) cd10
126      ENDIF
127      CALL FLUSH(numout)
128      !
129   END SUBROUTINE ctl_stop
130
131
132   SUBROUTINE ctl_warn( cd1, cd2, cd3, cd4, cd5,   &
133      &                 cd6, cd7, cd8, cd9, cd10 )
[1056]134      !!----------------------------------------------------------------------
[544]135      !!                  ***  ROUTINE  stop_warn  ***
136      !!
[1056]137      !! ** Purpose :   print in ocean.outpput file a error message and
138      !!                increment the warning number (nwarn) by one.
139      !!----------------------------------------------------------------------
[544]140      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5
141      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10
[1056]142      !!----------------------------------------------------------------------
[544]143      !
144      nwarn = nwarn + 1 
145      IF(lwp) THEN
146         WRITE(numout,"(/,' ===>>> : W A R N I N G', /,'         ===============',/)") 
147         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1
148         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2
149         IF( PRESENT(cd3 ) ) WRITE(numout,*) cd3
150         IF( PRESENT(cd4 ) ) WRITE(numout,*) cd4
151         IF( PRESENT(cd5 ) ) WRITE(numout,*) cd5
152         IF( PRESENT(cd6 ) ) WRITE(numout,*) cd6
153         IF( PRESENT(cd7 ) ) WRITE(numout,*) cd7
154         IF( PRESENT(cd8 ) ) WRITE(numout,*) cd8
155         IF( PRESENT(cd9 ) ) WRITE(numout,*) cd9
156         IF( PRESENT(cd10) ) WRITE(numout,*) cd10
157      ENDIF
158      CALL FLUSH(numout)
159      !
160   END SUBROUTINE ctl_warn
161
162
163   FUNCTION getunit()
[1056]164      !!----------------------------------------------------------------------
165      !!                  ***  FUNCTION  getunit  ***
166      !!
167      !! ** Purpose :   return the index of an unused logical unit
168      !!----------------------------------------------------------------------
169      INTEGER :: getunit
170      LOGICAL :: llopn 
171      !!----------------------------------------------------------------------
172      !
173      getunit = 15   ! choose a unit that is big enough then it is not already used in NEMO
174      llopn = .TRUE.
175      DO WHILE( (getunit < 998) .AND. llopn )
176         getunit = getunit + 1
177         INQUIRE( unit = getunit, opened = llopn )
178      END DO
179      IF( (getunit == 999) .AND. llopn ) THEN
180         CALL ctl_stop( 'getunit: All logical units until 999 are used...' )
181         getunit = -1
182      ENDIF
183      !
[544]184   END FUNCTION getunit
185
186   !!=====================================================================
187END MODULE in_out_manager
Note: See TracBrowser for help on using the repository browser.