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/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/DIA/dianam.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 9.2 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   USE yomhook, ONLY: lhook, dr_hook
20   USE parkind1, ONLY: jprb, jpim
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC dia_nam
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      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
69      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
70      REAL(KIND=jprb)               :: zhook_handle
71
72      CHARACTER(LEN=*), PARAMETER :: RoutineName='DIA_NAM'
73
74      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
75
76      !!----------------------------------------------------------------------
77
78      ! name for output frequency
79
80      IF( PRESENT(ldfsec) ) THEN   ;   llfsec = ldfsec
81      ELSE                         ;   llfsec = .FALSE.
82      ENDIF
83
84      IF( llfsec .OR. kfreq < 0 ) THEN   ;   inbsec = kfreq                       ! output frequency already in seconds
85      ELSE                               ;   inbsec = kfreq * NINT( rdttra(1) )   ! from time-step to seconds
86      ENDIF
87      iddss = NINT( rday          )                                         ! number of seconds in 1 day
88      ihhss = NINT( rmmss * rhhmm )                                         ! number of seconds in 1 hour
89      immss = NINT( rmmss         )                                         ! number of seconds in 1 minute
90      iyymo = NINT( raamo         )                                         ! number of months  in 1 year
91      iyyss = iddss * nyear_len(1)                                          ! seconds in 1 year (not good: multi years with leap)
92      clfmt0 = "('(a,i',i1,',a)')"                                          ! format '(a,ix,a)' with x to be defined
93      !
94      IF(          inbsec == 0           ) THEN   ;   clave = ''            ! no frequency
95      ELSEIF(      inbsec <  0           ) THEN       
96         inbmo = -inbsec                                                    ! frequency in month
97         IF( MOD( inbmo, iyymo  ) == 0 ) THEN                               ! frequency in years
98            inbyr  = inbmo / iyymo
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         ELSE                                                               ! frequency in month
102            indg   = INT(LOG10(REAL(inbmo,wp))) + 1                         ! number of digits needed to write months  frequency
103            WRITE(clfmt, clfmt0) indg             ;   WRITE(clave, clfmt) '_', inbmo, 'm'
104         ENDIF
105      ELSEIF( MOD( inbsec, iyyss  ) == 0 ) THEN                             ! frequency in years
106         inbyr  = inbsec / iyyss
107         indg   = INT(LOG10(REAL(inbyr ,wp))) + 1                           ! number of digits needed to write years   frequency
108         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbyr , 'y'
109      ELSEIF( MOD( inbsec, iddss  ) == 0 ) THEN                             ! frequency in days
110         inbday = inbsec / iddss
111         indg   = INT(LOG10(REAL(inbday,wp))) + 1                           ! number of digits needed to write days    frequency
112         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbday, 'd'
113         IF( inbday == nmonth_len(nmonth) )           clave = '_1m'
114      ELSEIF( MOD( inbsec, ihhss ) == 0 ) THEN                              ! frequency in hours
115         inbhr  = inbsec / ihhss
116         indg   = INT(LOG10(REAL(inbhr ,wp))) + 1                           ! number of digits needed to write hours   frequency
117         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbhr , 'h'
118      ELSEIF( MOD( inbsec, immss ) == 0 ) THEN                              ! frequency in minutes
119         inbmn  = inbsec / immss
120         indg   = INT(LOG10(REAL(inbmn ,wp))) + 1                           ! number of digits needed to write minutes frequency
121         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbmn , 'mn'
122      ELSE                                                                  ! frequency in seconds
123         indg   = INT(LOG10(REAL(inbsec,wp))) + 1                           ! number of digits needed to write seconds frequency
124         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbsec, 's'
125      ENDIF
126
127      ! date of the beginning and the end of the run
128
129      zdrun = rdttra(1) / rday * REAL( nitend - nit000, wp )                ! length of the run in days
130      zjul  = fjulday - rdttra(1) / rday
131      CALL ju2ymds( zjul        , iyear1, imonth1, iday1, zsec1 )           ! year/month/day of the beginning of run
132      CALL ju2ymds( zjul + zdrun, iyear2, imonth2, iday2, zsec2 )           ! year/month/day of the end       of run
133
134      IF( iyear2 < 10000 ) THEN   ;   clfmt = "(i4.4,2i2.2)"                ! format used to write the date
135      ELSE                        ;   WRITE(clfmt, "('(i',i1,',2i2.2)')") INT(LOG10(REAL(iyear2,wp))) + 1
136      ENDIF
137
138      WRITE(cldate1, clfmt) iyear1, imonth1, iday1                          ! date of the beginning of run
139      WRITE(cldate2, clfmt) iyear2, imonth2, iday2                          ! date of the end       of run
140 
141      cdfnam = TRIM(cexper)//TRIM(clave)//"_"//TRIM(cldate1)//"_"//TRIM(cldate2)//"_"//TRIM(cdsuff)
142      IF( .NOT. Agrif_Root() ) cdfnam = TRIM(Agrif_CFixed())//'_'//TRIM(cdfnam)
143
144      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
145   END SUBROUTINE dia_nam
146
147   !!======================================================================
148END MODULE dianam
Note: See TracBrowser for help on using the repository browser.