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.
Changeset 1734 for trunk – NEMO

Changeset 1734 for trunk


Ignore:
Timestamp:
2009-11-16T16:32:00+01:00 (14 years ago)
Author:
cetlod
Message:

update dianam.F90 module for OFFLINE, see ticket:597

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OFF_SRC/DIA/dianam.F90

    r1715 r1734  
    3030CONTAINS 
    3131 
    32    SUBROUTINE dia_nam( cdfnam, kfreq, cdsuff ) 
     32   SUBROUTINE dia_nam( cdfnam, kfreq, cdsuff, ldfsec ) 
    3333      !!--------------------------------------------------------------------- 
    3434      !!                  ***  ROUTINE dia_nam  *** 
     
    4242      !! 
    4343      !!---------------------------------------------------------------------- 
    44       CHARACTER (len=*), INTENT(  out) ::   cdfnam           ! file name 
    45       CHARACTER (len=*), INTENT(in   ) ::   cdsuff           ! to be added at the end of the file name 
    46       INTEGER,           INTENT(in   ) ::   kfreq            ! output frequency (in time-step): < 0 for monthly outputs 
    47       !                                                                                         0 if no frequency 
    48       CHARACTER (len=20) ::   clfmt, clfmt0                       ! writing format 
    49       CHARACTER (len=20) ::   clave                               ! name for output frequency 
    50       CHARACTER (len=20) ::   cldate1                             ! date of the beginning of run 
    51       CHARACTER (len=20) ::   cldate2                             ! date of the end       of run 
    52       INTEGER            ::   iyear1, imonth1, iday1              ! year, month, day of the first day of the run 
    53       INTEGER            ::   iyear2, imonth2, iday2              ! year, month, day of the last  day of the run 
    54       INTEGER            ::   indg                                ! number of digits needed to write a number      
    55       INTEGER            ::   inbsec, inbmn, inbhr, inbday, inbyr ! output frequency in seconds, minutes, hours, days and years 
    56       INTEGER            ::   iddss, ihhss, immss                 ! number of seconds in 1 day, 1 hour and 1 minute 
    57       REAL(wp)           ::   zsec1, zsec2                        ! not used 
    58       REAL(wp)           ::   zdrun, zjul                         ! temporary scalars 
     44      CHARACTER (len=*), INTENT(  out)           ::   cdfnam   ! file name 
     45      CHARACTER (len=*), INTENT(in   )           ::   cdsuff   ! to be added at the end of the file name 
     46      INTEGER          , INTENT(in   )           ::   kfreq    ! output frequency: > 0 in time-step (or seconds see ldfsec) 
     47      !                                                                            < 0 in months 
     48      !                                                                            = 0 no frequency 
     49      LOGICAL          , INTENT(in   ), OPTIONAL ::   ldfsec   ! kfreq in second(in time-step) if .true.(.false. default) 
     50      ! 
     51      CHARACTER (len=20) ::   clfmt, clfmt0                    ! writing format 
     52      CHARACTER (len=20) ::   clave                            ! name for output frequency 
     53      CHARACTER (len=20) ::   cldate1                          ! date of the beginning of run 
     54      CHARACTER (len=20) ::   cldate2                          ! date of the end       of run 
     55      LOGICAL            ::   llfsec                           ! local value of ldfsec 
     56      INTEGER            ::   iyear1, imonth1, iday1           ! year, month, day of the first day of the run 
     57      INTEGER            ::   iyear2, imonth2, iday2           ! year, month, day of the last  day of the run 
     58      INTEGER            ::   indg                             ! number of digits needed to write a number      
     59      INTEGER            ::   inbsec, inbmn, inbhr             ! output frequency in seconds, minutes and hours 
     60      INTEGER            ::   inbday, inbmo, inbyr             ! output frequency in days, months and years 
     61      INTEGER            ::   iyyss, iddss, ihhss, immss       ! number of seconds in 1 year, 1 day, 1 hour and 1 minute 
     62      INTEGER            ::   iyymo                            ! number of months in 1 year 
     63      REAL(wp)           ::   zsec1, zsec2                     ! not used 
     64      REAL(wp)           ::   zdrun, zjul                      ! temporary scalars 
    5965      !!---------------------------------------------------------------------- 
    60  
    61       IF(lwp) WRITE(numout,*) 
    62       IF(lwp) WRITE(numout,*) ' dia_nam: building output file name' 
    63       IF(lwp) WRITE(numout,*) ' ~~~~~~~' 
    64       IF(lwp) WRITE(numout,*) 
    6566 
    6667      ! name for output frequency 
    6768 
    68       inbsec = kfreq * NINT( rdttra(1) )                                    ! output frequency in seconds 
     69      IF( PRESENT(ldfsec) ) THEN   ;   llfsec = ldfsec 
     70      ELSE                         ;   llfsec = .FALSE. 
     71      ENDIF 
     72 
     73      IF( llfsec .OR. kfreq < 0 ) THEN   ;   inbsec = kfreq                       ! output frequency already in seconds 
     74      ELSE                               ;   inbsec = kfreq * NINT( rdttra(1) )   ! from time-step to seconds 
     75      ENDIF 
    6976      iddss = NINT( rday          )                                         ! number of seconds in 1 day 
    7077      ihhss = NINT( rmmss * rhhmm )                                         ! number of seconds in 1 hour 
    7178      immss = NINT( rmmss         )                                         ! number of seconds in 1 minute 
     79      iyymo = NINT( raamo         )                                         ! number of months  in 1 year 
     80      iyyss = iddss * nyear_len(1)                                          ! seconds in 1 year (not good: multi years with leap) 
    7281      clfmt0 = "('(a,i',i1,',a)')"                                          ! format '(a,ix,a)' with x to be defined 
    7382      !  
    7483      IF(          inbsec == 0           ) THEN   ;   clave = ''            ! no frequency 
    75       ELSEIF(      inbsec <  0           ) THEN   ;   clave = '_1m'         ! frequency in month 
     84      ELSEIF(      inbsec <  0           ) THEN         
     85         inbmo = -inbsec                                                    ! frequency in month 
     86         IF( MOD( inbmo, iyymo  ) == 0 ) THEN                               ! frequency in years 
     87            inbyr  = inbmo / iyymo 
     88            indg   = INT(LOG10(REAL(inbyr,wp))) + 1                         ! number of digits needed to write years   frequency 
     89            WRITE(clfmt, clfmt0) indg             ;   WRITE(clave, clfmt) '_', inbyr , 'y' 
     90         ELSE                                                               ! frequency in month 
     91            indg   = INT(LOG10(REAL(inbmo,wp))) + 1                         ! number of digits needed to write months  frequency 
     92            WRITE(clfmt, clfmt0) indg             ;   WRITE(clave, clfmt) '_', inbmo, 'm' 
     93         ENDIF 
     94      ELSEIF( MOD( inbsec, iyyss  ) == 0 ) THEN                             ! frequency in years 
     95         inbyr  = inbsec / iyyss 
     96         indg   = INT(LOG10(REAL(inbyr ,wp))) + 1                           ! number of digits needed to write years   frequency 
     97         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbyr , 'y' 
    7698      ELSEIF( MOD( inbsec, iddss  ) == 0 ) THEN                             ! frequency in days 
    7799         inbday = inbsec / iddss 
    78          indg = INT(LOG10(REAL(inbday,wp))) + 1                             ! number of digits needed to write days    frequency 
     100         indg   = INT(LOG10(REAL(inbday,wp))) + 1                           ! number of digits needed to write days    frequency 
    79101         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbday, 'd' 
    80102         IF( inbday == nmonth_len(nmonth) )           clave = '_1m' 
    81          IF( MOD( inbday, nyear_len(1) ) == 0 ) THEN                        ! frequency in years 
    82             inbyr = inbday / nyear_len(1) 
    83             indg  = INT(LOG10(REAL(inbyr ,wp))) + 1                         ! number of digits needed to write years   frequency 
    84             WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbyr, 'y' 
    85          ENDIF 
    86103      ELSEIF( MOD( inbsec, ihhss ) == 0 ) THEN                              ! frequency in hours 
    87          inbhr = inbsec / ihhss 
    88          indg = INT(LOG10(REAL(inbhr ,wp))) + 1                             ! number of digits needed to write hours   frequency 
    89          WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbhr, 'h' 
     104         inbhr  = inbsec / ihhss 
     105         indg   = INT(LOG10(REAL(inbhr ,wp))) + 1                           ! number of digits needed to write hours   frequency 
     106         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbhr , 'h' 
    90107      ELSEIF( MOD( inbsec, immss ) == 0 ) THEN                              ! frequency in minutes 
    91          inbmn = inbsec / immss 
    92          indg = INT(LOG10(REAL(inbmn ,wp))) + 1                             ! number of digits needed to write minutes frequency 
    93          WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbmn, 'mn' 
     108         inbmn  = inbsec / immss 
     109         indg   = INT(LOG10(REAL(inbmn ,wp))) + 1                           ! number of digits needed to write minutes frequency 
     110         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbmn , 'mn' 
    94111      ELSE                                                                  ! frequency in seconds 
    95          indg = INT(LOG10(REAL(inbsec,wp))) + 1                             ! number of digits needed to write seconds frequency 
     112         indg   = INT(LOG10(REAL(inbsec,wp))) + 1                           ! number of digits needed to write seconds frequency 
    96113         WRITE(clfmt, clfmt0) indg                ;   WRITE(clave, clfmt) '_', inbsec, 's' 
    97114      ENDIF 
     
    116133#endif     
    117134 
    118       IF(lwp) WRITE(numout,*) cdfnam      
    119       IF(lwp) WRITE(numout,*)           
    120  
    121135   END SUBROUTINE dia_nam 
    122136 
Note: See TracChangeset for help on using the changeset viewer.