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 @ 557

Last change on this file since 557 was 557, checked in by opalod, 18 years ago

nemo_v1_bugfix_069: SM+CT+CE: bugfix of mld restart + OFF line compatibiblity

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.4 KB
Line 
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   !!=====================================================================
7   !! History :   8.5  !  02-06  (G. Madec)  original code
8   !!             9.0  !  06-07  (S. Masson)  iom, add ctl_stop, ctl_warn
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   ctl_stop   : update momentum and tracer Kz from a tke scheme
13   !!   ctl_warn   : initialization, namelist read, and parameters control
14   !!----------------------------------------------------------------------
15   USE par_kind
16   USE par_oce
17   USE lib_print         ! formated print library
18
19   IMPLICIT NONE
20   PUBLIC
21
22   !!----------------------------------------------------------------------
23   !!                   namrun namelist parameters
24   !!----------------------------------------------------------------------
25   CHARACTER (len=16) ::   cexper     = "exp0"    !: experiment name used for output filename
26   LOGICAL            ::   ln_rstart  = .FALSE.   !: start from (F) rest or (T) a restart file
27   INTEGER            ::   no         = 0         !: job number
28   INTEGER            ::   nrstdt     = 0         !: control of the time step (0, 1 or 2)
29   INTEGER            ::   nit000     = 1         !: index of the first time step
30   INTEGER            ::   nitend     = 10        !: index of the last time step
31   INTEGER            ::   ndate0     = 961115    !: initial calendar date aammjj
32   INTEGER            ::   nleapy     = 0         !: Leap year calendar flag (0/1 or 30)
33   INTEGER            ::   ninist     = 0         !: initial state output flag (0/1)
34   !!----------------------------------------------------------------------
35   !! was in restart but moved here because of the OFF line... better solution should be found...
36   !!----------------------------------------------------------------------
37   INTEGER            ::   nitrst                 !: time step at which restart file should be written
38   !!----------------------------------------------------------------------
39   !!                    output monitoring
40   !!----------------------------------------------------------------------
41   LOGICAL            ::   ln_ctl     = .FALSE.   !: run control for debugging
42   INTEGER            ::   nstock     =   10      !: restart file frequency
43   INTEGER            ::   nprint     =    0      !: level of print (0 no print)
44   INTEGER            ::   nwrite     =   10      !: restart file frequency
45   INTEGER            ::   nictls     =    0      !: Start i indice for the SUM control
46   INTEGER            ::   nictle     =    0      !: End   i indice for the SUM control
47   INTEGER            ::   njctls     =    0      !: Start j indice for the SUM control
48   INTEGER            ::   njctle     =    0      !: End   j indice for the SUM control
49   INTEGER            ::   isplt      =    1      !: number of processors following i
50   INTEGER            ::   jsplt      =    1      !: number of processors following j
51   INTEGER            ::   ijsplt     =    1      !: nb of local domain = nb of processors
52   INTEGER            ::   nbench     =    0      !: benchmark parameter (0/1)
53   INTEGER            ::   nbit_cmp   =    0      !: bit reproducibility  (0/1)
54   !!----------------------------------------------------------------------
55   !!                        logical units
56   !!----------------------------------------------------------------------
57   INTEGER            ::   numstp     =  1        !: logical unit for time step
58   INTEGER            ::   numout     =  2        !: logical unit for output print
59   INTEGER            ::   numnam     =  3        !: logical unit for namelist
60   INTEGER            ::   numnam_ice =  4        !: logical unit for ice namelist
61   INTEGER            ::   numevo_ice = 17        !: logical unit for ice variables (temp. evolution)
62   INTEGER            ::   numsol     = 25        !: logical unit for solver statistics
63   INTEGER            ::   numwri     = 40        !: logical unit for output write
64   INTEGER            ::   numisp     = 41        !: logical unit for island statistics
65   INTEGER            ::   numgap     = 45        !: logical unit for differences diagnostic
66   INTEGER            ::   numbol     = 67        !: logical unit for "bol" diagnostics
67   INTEGER            ::   numptr     = 68        !: logical unit for Poleward TRansports
68   INTEGER            ::   numflo     = 69        !: logical unit for drifting floats
69
70   !!----------------------------------------------------------------------
71   !!                          Run control 
72   !!----------------------------------------------------------------------
73   
74   INTEGER            ::   nstop = 0                !: error flag (=number of reason for a premature stop run)
75   INTEGER            ::   nwarn = 0                !: warning flag (=number of warning found during the run)
76   CHARACTER(LEN=100) ::   ctmp1, ctmp2, ctmp3      !: temporary character
77   CHARACTER (len=64) ::   cform_err = "(/,' ===>>> : E R R O R',     /,'         ===========',/)"       !:
78   CHARACTER (len=64) ::   cform_war = "(/,' ===>>> : W A R N I N G', /,'         ===============',/)"   !:
79   LOGICAL            ::   lwp                      !: boolean : true on the 1st processor only
80   LOGICAL            ::   lsp_area = .TRUE.        !: to make a control print over a specific area
81   !!----------------------------------------------------------------------
82   !!  OPA 9.0 , LOCEAN-IPSL (2005)
83   !! $Header$
84   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
85   !!----------------------------------------------------------------------
86
87CONTAINS
88
89   SUBROUTINE ctl_stop( cd1, cd2, cd3, cd4, cd5,   &
90      &                 cd6, cd7, cd8, cd9, cd10 )
91      !!-----------------------------------------------------------------------
92      !!                  ***  ROUTINE  stop_opa  ***
93      !!
94      !! ** Purpose : ??? blah blah....
95      !!-----------------------------------------------------------------------
96      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5
97      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10
98      !!-----------------------------------------------------------------------
99      !
100      nstop = nstop + 1 
101      IF(lwp) THEN
102         WRITE(numout,"(/,' ===>>> : E R R O R',     /,'         ===========',/)") 
103         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1
104         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2
105         IF( PRESENT(cd3 ) ) WRITE(numout,*) cd3
106         IF( PRESENT(cd4 ) ) WRITE(numout,*) cd4
107         IF( PRESENT(cd5 ) ) WRITE(numout,*) cd5
108         IF( PRESENT(cd6 ) ) WRITE(numout,*) cd6
109         IF( PRESENT(cd7 ) ) WRITE(numout,*) cd7
110         IF( PRESENT(cd8 ) ) WRITE(numout,*) cd8
111         IF( PRESENT(cd9 ) ) WRITE(numout,*) cd9
112         IF( PRESENT(cd10) ) WRITE(numout,*) cd10
113      ENDIF
114      CALL FLUSH(numout)
115      !
116   END SUBROUTINE ctl_stop
117
118
119   SUBROUTINE ctl_warn( cd1, cd2, cd3, cd4, cd5,   &
120      &                 cd6, cd7, cd8, cd9, cd10 )
121      !!-----------------------------------------------------------------------
122      !!                  ***  ROUTINE  stop_warn  ***
123      !!
124      !! ** Purpose : ???  blah blah....
125      !!-----------------------------------------------------------------------
126      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5
127      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10
128      !!-----------------------------------------------------------------------
129      !
130      nwarn = nwarn + 1 
131      IF(lwp) THEN
132         WRITE(numout,"(/,' ===>>> : W A R N I N G', /,'         ===============',/)") 
133         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1
134         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2
135         IF( PRESENT(cd3 ) ) WRITE(numout,*) cd3
136         IF( PRESENT(cd4 ) ) WRITE(numout,*) cd4
137         IF( PRESENT(cd5 ) ) WRITE(numout,*) cd5
138         IF( PRESENT(cd6 ) ) WRITE(numout,*) cd6
139         IF( PRESENT(cd7 ) ) WRITE(numout,*) cd7
140         IF( PRESENT(cd8 ) ) WRITE(numout,*) cd8
141         IF( PRESENT(cd9 ) ) WRITE(numout,*) cd9
142         IF( PRESENT(cd10) ) WRITE(numout,*) cd10
143      ENDIF
144      CALL FLUSH(numout)
145      !
146   END SUBROUTINE ctl_warn
147
148
149   FUNCTION getunit()
150     !!-----------------------------------------------------------------------
151     !!                  ***  FUNCTION  getunit  ***
152     !!
153     !! ** Purpose : ???  blah blah....
154     !!-----------------------------------------------------------------------
155     INTEGER :: getunit
156     LOGICAL :: llopn 
157     !---------------------------------------------------------------------
158     getunit = 50   ! choose a unit that is big enough then it is
159                    !  not already used in OPA
160     llopn = .TRUE.
161     DO WHILE( (getunit < 998) .AND. llopn )
162        getunit = getunit + 1
163        INQUIRE( unit = getunit, opened = llopn )
164     END DO
165     IF( (getunit == 999) .AND. llopn ) THEN
166        CALL ctl_stop( 'getunit: All logical units until 999 are used...' )
167        getunit = -1
168     ENDIF
169     
170   END FUNCTION getunit
171
172   !!=====================================================================
173END MODULE in_out_manager
Note: See TracBrowser for help on using the repository browser.