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 branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DIA/dianam.F90 @ 4427

Last change on this file since 4427 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 8.9 KB
Line 
1MODULE dianam
2   !!======================================================================
3   !!                       ***  MODULE  dianam  ***
4   !! Ocean diagnostics:  Builds output file name
5   !!=====================================================================
6   !! History :  OPA  ! 1999-02  (E. Guilyardi)  Creation for 30 days/month
7   !!   NEMO     1.0  ! 2002-06  (G. Madec)  F90: Free form and module
8   !!            3.2  ! 2009-11  (S. Masson) complete rewriting, works for all calendars...
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   dia_nam       : Builds output file name
13   !!----------------------------------------------------------------------
14   USE dom_oce         ! ocean space and time domain
15   USE phycst          ! physical constants
16   USE in_out_manager  ! I/O manager
17   USE ioipsl, ONLY :  ju2ymds    ! for calendar
18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC dia_nam
23
24   !! * Control permutation of array indices
25#  include "dom_oce_ftrans.h90"
26
27   !!----------------------------------------------------------------------
28   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
29   !! $Id$
30   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
31   !!----------------------------------------------------------------------
32
33CONTAINS
34
35   SUBROUTINE dia_nam( cdfnam, kfreq, cdsuff, ldfsec )
36      !!---------------------------------------------------------------------
37      !!                  ***  ROUTINE dia_nam  ***
38      !!                   
39      !! ** Purpose :   Builds output file name
40      !!
41      !! ** Method  :   File name is a function of date and output frequency
42      !!      cdfnam=<cexper>_<clave>_<idtbeg>_<idtend>_<cdsuff>
43      !!      <clave> = averaging frequency (DA, MO, etc...)
44      !!      <idtbeg>,<idtend> date of beginning and end of run
45      !!
46      !!----------------------------------------------------------------------
47      CHARACTER (len=*), INTENT(  out)           ::   cdfnam   ! file name
48      CHARACTER (len=*), INTENT(in   )           ::   cdsuff   ! to be added at the end of the file name
49      INTEGER          , INTENT(in   )           ::   kfreq    ! output frequency: > 0 in time-step (or seconds see ldfsec)
50      !                                                                            < 0 in months
51      !                                                                            = 0 no frequency
52      LOGICAL          , INTENT(in   ), OPTIONAL ::   ldfsec   ! kfreq in second(in time-step) if .true.(.false. default)
53      !
54      CHARACTER (len=20) ::   clfmt, clfmt0                    ! writing format
55      CHARACTER (len=20) ::   clave                            ! name for output frequency
56      CHARACTER (len=20) ::   cldate1                          ! date of the beginning of run
57      CHARACTER (len=20) ::   cldate2                          ! date of the end       of run
58      LOGICAL            ::   llfsec                           ! local value of ldfsec
59      INTEGER            ::   iyear1, imonth1, iday1           ! year, month, day of the first day of the run
60      INTEGER            ::   iyear2, imonth2, iday2           ! year, month, day of the last  day of the run
61      INTEGER            ::   indg                             ! number of digits needed to write a number     
62      INTEGER            ::   inbsec, inbmn, inbhr             ! output frequency in seconds, minutes and hours
63      INTEGER            ::   inbday, inbmo, inbyr             ! output frequency in days, months and years
64      INTEGER            ::   iyyss, iddss, ihhss, immss       ! number of seconds in 1 year, 1 day, 1 hour and 1 minute
65      INTEGER            ::   iyymo                            ! number of months in 1 year
66      REAL(wp)           ::   zsec1, zsec2                     ! not used
67      REAL(wp)           ::   zdrun, zjul                      ! temporary scalars
68      !!----------------------------------------------------------------------
69
70      ! name for output frequency
71
72      IF( PRESENT(ldfsec) ) THEN   ;   llfsec = ldfsec
73      ELSE                         ;   llfsec = .FALSE.
74      ENDIF
75
76      IF( llfsec .OR. kfreq < 0 ) THEN   ;   inbsec = kfreq                       ! output frequency already in seconds
77      ELSE                               ;   inbsec = kfreq * NINT( rdttra(1) )   ! from time-step to seconds
78      ENDIF
79      iddss = NINT( rday          )                                         ! number of seconds in 1 day
80      ihhss = NINT( rmmss * rhhmm )                                         ! number of seconds in 1 hour
81      immss = NINT( rmmss         )                                         ! number of seconds in 1 minute
82      iyymo = NINT( raamo         )                                         ! number of months  in 1 year
83      iyyss = iddss * nyear_len(1)                                          ! seconds in 1 year (not good: multi years with leap)
84      clfmt0 = "('(a,i',i1,',a)')"                                          ! format '(a,ix,a)' with x to be defined
85      !
86      IF(          inbsec == 0           ) THEN   ;   clave = ''            ! no frequency
87      ELSEIF(      inbsec <  0           ) THEN       
88         inbmo = -inbsec                                                    ! frequency in month
89         IF( MOD( inbmo, iyymo  ) == 0 ) THEN                               ! frequency in years
90            inbyr  = inbmo / iyymo
91            indg   = INT(LOG10(REAL(inbyr,wp))) + 1                         ! number of digits needed to write years   frequency
92            WRITE(clfmt, clfmt0) indg             ;   WRITE(clave, clfmt) '_', inbyr , 'y'
93         ELSE                                                               ! frequency in month
94            indg   = INT(LOG10(REAL(inbmo,wp))) + 1                         ! number of digits needed to write months  frequency
95            WRITE(clfmt, clfmt0) indg             ;   WRITE(clave, clfmt) '_', inbmo, 'm'
96         ENDIF
97      ELSEIF( MOD( inbsec, iyyss  ) == 0 ) THEN                             ! frequency in years
98         inbyr  = inbsec / iyyss
99         indg   = INT(LOG10(REAL(inbyr ,wp))) + 1                           ! number of digits needed to write years   frequency
100         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbyr , 'y'
101      ELSEIF( MOD( inbsec, iddss  ) == 0 ) THEN                             ! frequency in days
102         inbday = inbsec / iddss
103         indg   = INT(LOG10(REAL(inbday,wp))) + 1                           ! number of digits needed to write days    frequency
104         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbday, 'd'
105         IF( inbday == nmonth_len(nmonth) )           clave = '_1m'
106      ELSEIF( MOD( inbsec, ihhss ) == 0 ) THEN                              ! frequency in hours
107         inbhr  = inbsec / ihhss
108         indg   = INT(LOG10(REAL(inbhr ,wp))) + 1                           ! number of digits needed to write hours   frequency
109         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbhr , 'h'
110      ELSEIF( MOD( inbsec, immss ) == 0 ) THEN                              ! frequency in minutes
111         inbmn  = inbsec / immss
112         indg   = INT(LOG10(REAL(inbmn ,wp))) + 1                           ! number of digits needed to write minutes frequency
113         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbmn , 'mn'
114      ELSE                                                                  ! frequency in seconds
115         indg   = INT(LOG10(REAL(inbsec,wp))) + 1                           ! number of digits needed to write seconds frequency
116         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbsec, 's'
117      ENDIF
118
119      ! date of the beginning and the end of the run
120
121      zdrun = rdttra(1) / rday * REAL( nitend - nit000, wp )                ! length of the run in days
122      zjul  = fjulday - rdttra(1) / rday
123      CALL ju2ymds( zjul        , iyear1, imonth1, iday1, zsec1 )           ! year/month/day of the beginning of run
124      CALL ju2ymds( zjul + zdrun, iyear2, imonth2, iday2, zsec2 )           ! year/month/day of the end       of run
125
126      IF( iyear2 < 10000 ) THEN   ;   clfmt = "(i4.4,2i2.2)"                ! format used to write the date
127      ELSE                        ;   WRITE(clfmt, "('(i',i1,',2i2.2)')") INT(LOG10(REAL(iyear2,wp))) + 1
128      ENDIF
129
130      WRITE(cldate1, clfmt) iyear1, imonth1, iday1                          ! date of the beginning of run
131      WRITE(cldate2, clfmt) iyear2, imonth2, iday2                          ! date of the end       of run
132 
133      cdfnam = TRIM(cexper)//TRIM(clave)//"_"//TRIM(cldate1)//"_"//TRIM(cldate2)//"_"//TRIM(cdsuff)
134      IF( .NOT. Agrif_Root() ) cdfnam = TRIM(Agrif_CFixed())//'_'//TRIM(cdfnam)
135
136   END SUBROUTINE dia_nam
137
138   !!======================================================================
139END MODULE dianam
Note: See TracBrowser for help on using the repository browser.