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.
dianam.F90 in trunk/NEMO/OPA_SRC/DIA – NEMO

source: trunk/NEMO/OPA_SRC/DIA/dianam.F90 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.6 KB
Line 
1MODULE dianam
2   !!======================================================================
3   !!                       ***  MODULE  dianam  ***
4   !! Ocean diagnostics:  Builds output file name
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   dia_nam       : Builds output file name
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE dom_oce         ! ocean space and time domain
12   USE phycst          ! physical constants
13   USE in_out_manager  ! I/O manager
14   USE daymod          ! calendar
15
16   IMPLICIT NONE
17   PRIVATE
18
19   !! * Routine accessibility
20   PUBLIC dia_nam   ! routine called by step.F90
21   !!----------------------------------------------------------------------
22   !!   OPA 9.0 , LOCEAN-IPSL (2005)
23   !! $Header$
24   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
25   !!----------------------------------------------------------------------
26
27CONTAINS
28
29   SUBROUTINE dia_nam( cdfnam, kfreq, cdsuff )
30      !!---------------------------------------------------------------------
31      !!                  ***  ROUTINE dia_nam  ***
32      !!                   
33      !! ** Purpose :   Builds output file name
34      !!
35      !! ** Method  :   File name is a function of date and output frequency
36      !!      cdfnam=<cexper>_<clave>_<idtbeg>_<idtend>_grid_<cdsuff>
37      !!      <clave> = averaging frequency (DA, MO, etc...)
38      !!      <idtbeg>,<idtend> date of beginning and end of run
39      !!
40      !! History :
41      !!        !  99-02  (E. Guilyardi)  Creation for 30 days/month
42      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
43      !!----------------------------------------------------------------------
44      !! * Arguments
45      CHARACTER (len=*), INTENT( out ) ::   cdfnam   ! file name
46      CHARACTER (len=*), INTENT( in  ) ::   cdsuff   ! ???
47      INTEGER,           INTENT( in  ) ::   kfreq    ! ???
48
49      !! * Local declarations
50      CHARACTER (len=2) ::   clave
51      CHARACTER (len=5) ::   clout
52      INTEGER :: jt                       ! dummy loop indices
53      INTEGER :: ig, ijjmm, iout          ! temporary integers
54      INTEGER :: iyear1, imonth1, iday1   !    "          "
55      INTEGER :: iyear2, imonth2, iday2   !    "          "
56      REAL(wp) ::  z5j, znbsec, zdate1, zdate2, zdrun, zdt   ! temporary scalars
57      !!----------------------------------------------------------------------
58
59      IF(lwp) WRITE(numout,*)
60      IF(lwp) WRITE(numout,*) ' dia_nam: building output file name'
61      IF(lwp) WRITE(numout,*) ' ~~~~~~~'
62      IF(lwp) WRITE(numout,*)
63
64      ! 0. Initialisation
65      ! -----------------
66
67      cdfnam = ''
68
69      !    number of seconds of the run
70
71      z5j = 5*rjjss
72      zdt = rdt
73      IF( nacc == 1 ) zdt = rdtmin
74      zdrun = FLOAT( nitend - nit000 ) * zdt
75
76      !  date of beginning of run
77
78      iyear1  = ndastp/10000
79      imonth1 = ndastp/100 - iyear1*100
80      iday1   = ndastp - imonth1*100 - iyear1*10000
81      IF( nleapy == 1) THEN
82         ijjmm=0
83         IF( MOD( iyear1, 4 ) == 0 ) THEN
84            DO jt = 1, imonth1-1
85               ijjmm = ijjmm + nbiss(jt)
86            END DO
87         ELSE
88            DO jt = 1, imonth1-1
89               ijjmm = ijjmm + nobis(jt)
90            END DO
91         ENDIF
92         ijjmm = ijjmm + (iyear1-1)/4
93         zdate1 = ( (iyear1-1)*365 + ijjmm +iday1-1 ) * rjjss   
94      ELSE IF( nleapy == 0 ) THEN
95         ijjmm = 0
96         DO jt = 1, imonth1-1
97            ijjmm = ijjmm + nobis(jt)
98         END DO
99         zdate1 = ( (iyear1-1)*raajj + ijjmm + iday1-1)* rjjss
100      ELSE
101         zdate1 = ( (iyear1-1)*nleapy*raamo + (imonth1-1)*nleapy + iday1-1)* rjjss
102      ENDIF
103
104      !  date of end of run (= date of beginning of next run)
105
106      zdate2 = zdate1 + zdrun
107      IF( nleapy == 1 ) THEN
108         iyear2 = zdate2/(365.25*rjjss)+1
109         ijjmm = INT(zdate2/rjjss)-365*(iyear2-1)-(iyear2-1)/4
110         IF( ijjmm < 0 ) THEN
111            iyear2 = iyear2-1
112            ijjmm = zdate2/rjjss-365.*(iyear2-1)-(iyear2-1)/4
113         ENDIF
114         IF( MOD( iyear2, 4 ) == 0 ) THEN
115            DO jt = 1, 12
116               ijjmm = ijjmm - nbiss(jt)
117               IF( ijjmm <= 0 ) go to 10
118            END DO
119            jt = 12
12010          CONTINUE
121            imonth2 = jt
122            ijjmm = 0
123            DO jt = 1, jt-1
124               ijjmm = ijjmm + nbiss(jt)
125            END DO
126         ELSE
127            DO jt = 1, 12
128               ijjmm = ijjmm - nobis(jt)
129               IF( ijjmm <= 0 ) go to 15
130            END DO
131            jt = 12
13215          CONTINUE
133            imonth2 = jt
134            ijjmm = 0
135            DO jt = 1, jt-1
136               ijjmm = ijjmm + nobis(jt)
137            END DO
138         ENDIF
139         iday2 = zdate2/rjjss-365.*(iyear2-1)-ijjmm+1-(iyear2-1)/4     
140      ELSE IF( nleapy == 0 ) THEN
141         iyear2 = zdate2/raass+1
142         ijjmm  = zdate2/rjjss-raajj*(iyear2-1)
143         DO jt = 1, 12
144            ijjmm = ijjmm - nobis(jt)
145            IF(ijjmm <= 0) go to 20
146         END DO
147         jt = 12
14820       CONTINUE
149         imonth2 = jt
150         ijjmm = 0
151         DO jt = 1, jt-1
152            ijjmm = ijjmm + nobis(jt)
153         END DO
154         iday2 = zdate2/rjjss-raajj*(iyear2-1)-ijjmm+1         
155      ELSE
156         zdate2 = zdate2 / rjjss
157         imonth2 = zdate2/FLOAT(nleapy)
158         iday2 = zdate2 - imonth2*FLOAT(nleapy) + 1.
159         iyear2 = imonth2/12
160         imonth2 = imonth2 - iyear2*12
161         imonth2 = imonth2 + 1
162         iyear2 = iyear2 + 1
163         IF( iday2 == 0 ) THEN
164            iday2 = nleapy
165            imonth2 = imonth2 - 1
166            IF( imonth2 == 0 ) THEN
167               imonth2 = 12
168               iyear2 = iyear2 - 1
169            ENDIF
170         ENDIF
171      ENDIF
172
173
174      ! 1. Define time averaging period <nn><type>
175      !    ---------------------------------------
176
177      iout = 0
178#if defined key_diainstant
179      clave = 'IN'
180      IF( iyear2 <= 99 ) THEN
181         WRITE(cdfnam,9001) iyear1,imonth1,iday1,iyear2,imonth2,iday2
182      ELSE IF( iyear2 <= 999 ) THEN
183         WRITE(cdfnam,9002) iyear1,imonth1,iday1,iyear2,imonth2,iday2
184      ELSE IF( iyear2 <= 9999 ) THEN
185         WRITE(cdfnam,9003) iyear1,imonth1,iday1,iyear2,imonth2,iday2
186      ELSE
187         WRITE(cdfnam,9004) iyear1,imonth1,iday1,iyear2,imonth2,iday2
188      ENDIF
189#else
190
191      znbsec=kfreq*zdt
192      ! daily output
193      IF( znbsec == rjjss ) THEN
194         clave = '1d'
195         IF( iyear2 <= 99 ) THEN
196            WRITE(cdfnam,9001) iyear1,imonth1,iday1,iyear2,imonth2,iday2
197         ELSE IF( iyear2 <= 999 ) THEN
198            WRITE(cdfnam,9002) iyear1,imonth1,iday1,iyear2,imonth2,iday2
199         ELSE IF( iyear2 <= 9999 ) THEN
200            WRITE(cdfnam,9003) iyear1,imonth1,iday1,iyear2,imonth2,iday2
201         ELSE
202            WRITE(cdfnam,9004) iyear1,imonth1,iday1,iyear2,imonth2,iday2
203         ENDIF
204         ! 5 day output
205      ELSE IF( znbsec == z5j ) THEN
206         clave='5d'
207         IF( iyear2 <= 99 ) THEN
208            WRITE(cdfnam,9001) iyear1,imonth1,iday1,iyear2,imonth2,iday2
209         ELSE IF( iyear2 <= 999 ) THEN
210            WRITE(cdfnam,9002) iyear1,imonth1,iday1,iyear2,imonth2,iday2
211         ELSE IF( iyear2 <= 9999 ) THEN
212            WRITE(cdfnam,9003) iyear1,imonth1,iday1,iyear2,imonth2,iday2
213         ELSE
214            WRITE(cdfnam,9004) iyear1,imonth1,iday1,iyear2,imonth2,iday2
215         ENDIF
216         ! monthly ouput
217      ELSE IF( (znbsec == rmoss .AND. nleapy > 1) .OR.   &
218               (znbsec >= 28*rjjss .AND. znbsec <= 31*rjjss .AND. nleapy <= 1) ) THEN
219         clave = '1m'
220         IF( iyear2 <= 99 ) THEN
221            WRITE(cdfnam,9001) iyear1,imonth1,iday1,iyear2,imonth2,iday2
222         ELSE IF( iyear2 <= 999 ) THEN
223            WRITE(cdfnam,9002) iyear1,imonth1,iday1,iyear2,imonth2,iday2
224         ELSE IF( iyear2 <= 9999 ) THEN
225            WRITE(cdfnam,9003) iyear1,imonth1,iday1,iyear2,imonth2,iday2
226         ELSE
227            WRITE(cdfnam,9004) iyear1,imonth1,iday1,iyear2,imonth2,iday2
228         ENDIF
229         ! annual output
230      ELSE IF( (znbsec == raass .AND. nleapy > 1) .OR.   &
231               (znbsec >= 365*rjjss .AND. znbsec <= 366*rjjss .AND. nleapy <= 1) ) THEN
232         clave = '1y'
233         IF( iyear2 <= 99 ) THEN
234            WRITE(cdfnam,9001) iyear1,imonth1,iday1,iyear2,imonth2,iday2
235         ELSE IF( iyear2 <= 999 ) THEN
236            WRITE(cdfnam,9002) iyear1,imonth1,iday1,iyear2,imonth2,iday2
237         ELSE IF( iyear2 <= 9999 ) THEN
238            WRITE(cdfnam,9003) iyear1,imonth1,iday1,iyear2,imonth2,iday2
239         ELSE
240            WRITE(cdfnam,9004) iyear1,imonth1,iday1,iyear2,imonth2,iday2
241         ENDIF
242      ELSE
243         ! others
244         iout = kfreq
245         ig = 0
246         clout = ''
247         IF( iout <= 9 ) THEN
248            ig = 1
249            WRITE(clout,'(i1.1)') iout
250         ELSE IF( iout <= 99 ) THEN
251            ig = 2
252            WRITE(clout,'(i2.2)') iout
253         ELSE IF( iout <= 999 ) THEN
254            ig = 3
255            WRITE(clout,'(i3.3)') iout
256         ELSE IF( iout <= 9999 ) THEN
257            ig = 4
258            WRITE(clout,'(i4.4)') iout
259         ELSE
260            ig = 5
261            WRITE(clout,'(i5.5)') iout
262         ENDIF
263         clave = 'CU'
264         IF( iyear2 <= 99 ) THEN
265            WRITE(cdfnam,9001) iyear1,imonth1,iday1,iyear2,imonth2,iday2
266         ELSE IF( iyear2 <= 999 ) THEN
267            WRITE(cdfnam,9002) iyear1,imonth1,iday1,iyear2,imonth2,iday2
268         ELSE IF( iyear2 <= 9999 ) THEN
269            WRITE(cdfnam,9003) iyear1,imonth1,iday1,iyear2,imonth2,iday2
270         ELSE
271            WRITE(cdfnam,9004) iyear1,imonth1,iday1,iyear2,imonth2,iday2
272         ENDIF
273      ENDIF
274#endif
275      IF( iout == 0 ) THEN
276         cdfnam = TRIM(cexper)//"_"//clave//TRIM(cdfnam)//TRIM(cdsuff)
277      ELSE
278         cdfnam = TRIM(cexper)//"_"//clave//TRIM(clout)//TRIM(cdfnam)//TRIM(cdsuff)
279      ENDIF
280#if defined key_agrif
281      if ( .NOT. Agrif_Root() ) cdfnam = TRIM(Agrif_CFixed())//'_'//TRIM(cdfnam)
282#endif   
283      IF(lwp) WRITE(numout,*) cdfnam     
284      IF(lwp) WRITE(numout,*)         
285
286      ! FORMATS
287
288 9001 FORMAT("_",I4.4,2I2.2,"_",I4.4,2I2.2,"_")
289 9002 FORMAT("_",I4.4,2I2.2,"_",I4.4,2I2.2,"_")
290 9003 FORMAT("_",I4.4,2I2.2,"_",I4.4,2I2.2,"_")
291 9004 FORMAT("_",I6.6,2I2.2,"_",I6.6,2I2.2,"_")
292 9011 FORMAT("_",I4.4,I2.2,"_",I4.4,I2.2,"_")
293 9012 FORMAT("_",I4.4,I2.2,"_",I4.4,I2.2,"_")
294 9013 FORMAT("_",I4.4,I2.2,"_",I4.4,I2.2,"_")
295 9014 FORMAT("_",I6.6,I2.2,"_",I6.6,I2.2,"_")
296 9021 FORMAT("_",I4.4,"_",I4.4,"_")
297 9022 FORMAT("_",I4.4,"_",I4.4,"_")
298 9023 FORMAT("_",I4.4,"_",I4.4,"_")
299 9024 FORMAT("_",I6.6,"_",I6.6,"_")
300
301   END SUBROUTINE dia_nam
302
303   !!======================================================================
304END MODULE dianam
Note: See TracBrowser for help on using the repository browser.