dianam.F90 8.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136
  1. MODULE 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. !! dia_nam : Builds output file name
  12. !!----------------------------------------------------------------------
  13. USE dom_oce ! ocean space and time domain
  14. USE phycst ! physical constants
  15. USE in_out_manager ! I/O manager
  16. USE ioipsl, ONLY : ju2ymds ! for calendar
  17. IMPLICIT NONE
  18. PRIVATE
  19. PUBLIC dia_nam
  20. !!----------------------------------------------------------------------
  21. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  22. !! $Id: dianam.F90 2528 2010-12-27 17:33:53Z rblod $
  23. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  24. !!----------------------------------------------------------------------
  25. CONTAINS
  26. SUBROUTINE dia_nam( cdfnam, kfreq, cdsuff, ldfsec )
  27. !!---------------------------------------------------------------------
  28. !! *** ROUTINE dia_nam ***
  29. !!
  30. !! ** Purpose : Builds output file name
  31. !!
  32. !! ** Method : File name is a function of date and output frequency
  33. !! cdfnam=<cexper>_<clave>_<idtbeg>_<idtend>_<cdsuff>
  34. !! <clave> = averaging frequency (DA, MO, etc...)
  35. !! <idtbeg>,<idtend> date of beginning and end of run
  36. !!
  37. !!----------------------------------------------------------------------
  38. CHARACTER (len=*), INTENT( out) :: cdfnam ! file name
  39. CHARACTER (len=*), INTENT(in ) :: cdsuff ! to be added at the end of the file name
  40. INTEGER , INTENT(in ) :: kfreq ! output frequency: > 0 in time-step (or seconds see ldfsec)
  41. ! < 0 in months
  42. ! = 0 no frequency
  43. LOGICAL , INTENT(in ), OPTIONAL :: ldfsec ! kfreq in second(in time-step) if .true.(.false. default)
  44. !
  45. CHARACTER (len=20) :: clfmt, clfmt0 ! writing format
  46. CHARACTER (len=20) :: clave ! name for output frequency
  47. CHARACTER (len=20) :: cldate1 ! date of the beginning of run
  48. CHARACTER (len=20) :: cldate2 ! date of the end of run
  49. LOGICAL :: llfsec ! local value of ldfsec
  50. INTEGER :: iyear1, imonth1, iday1 ! year, month, day of the first day of the run
  51. INTEGER :: iyear2, imonth2, iday2 ! year, month, day of the last day of the run
  52. INTEGER :: indg ! number of digits needed to write a number
  53. INTEGER :: inbsec, inbmn, inbhr ! output frequency in seconds, minutes and hours
  54. INTEGER :: inbday, inbmo, inbyr ! output frequency in days, months and years
  55. INTEGER :: iyyss, iddss, ihhss, immss ! number of seconds in 1 year, 1 day, 1 hour and 1 minute
  56. INTEGER :: iyymo ! number of months in 1 year
  57. REAL(wp) :: zsec1, zsec2 ! not used
  58. REAL(wp) :: zdrun, zjul ! temporary scalars
  59. !!----------------------------------------------------------------------
  60. ! name for output frequency
  61. IF( PRESENT(ldfsec) ) THEN ; llfsec = ldfsec
  62. ELSE ; llfsec = .FALSE.
  63. ENDIF
  64. IF( llfsec .OR. kfreq < 0 ) THEN ; inbsec = kfreq ! output frequency already in seconds
  65. ELSE ; inbsec = kfreq * NINT( rdttra(1) ) ! from time-step to seconds
  66. ENDIF
  67. iddss = NINT( rday ) ! number of seconds in 1 day
  68. ihhss = NINT( rmmss * rhhmm ) ! number of seconds in 1 hour
  69. immss = NINT( rmmss ) ! number of seconds in 1 minute
  70. iyymo = NINT( raamo ) ! number of months in 1 year
  71. iyyss = iddss * nyear_len(1) ! seconds in 1 year (not good: multi years with leap)
  72. clfmt0 = "('(a,i',i1,',a)')" ! format '(a,ix,a)' with x to be defined
  73. !
  74. IF( inbsec == 0 ) THEN ; clave = '' ! no frequency
  75. ELSEIF( inbsec < 0 ) THEN
  76. inbmo = -inbsec ! frequency in month
  77. IF( MOD( inbmo, iyymo ) == 0 ) THEN ! frequency in years
  78. inbyr = inbmo / iyymo
  79. indg = INT(LOG10(REAL(inbyr,wp))) + 1 ! number of digits needed to write years frequency
  80. WRITE(clfmt, clfmt0) indg ; WRITE(clave, clfmt) '_', inbyr , 'y'
  81. ELSE ! frequency in month
  82. indg = INT(LOG10(REAL(inbmo,wp))) + 1 ! number of digits needed to write months frequency
  83. WRITE(clfmt, clfmt0) indg ; WRITE(clave, clfmt) '_', inbmo, 'm'
  84. ENDIF
  85. ELSEIF( MOD( inbsec, iyyss ) == 0 ) THEN ! frequency in years
  86. inbyr = inbsec / iyyss
  87. indg = INT(LOG10(REAL(inbyr ,wp))) + 1 ! number of digits needed to write years frequency
  88. WRITE(clfmt, clfmt0) indg ; WRITE(clave, clfmt) '_', inbyr , 'y'
  89. ELSEIF( MOD( inbsec, iddss ) == 0 ) THEN ! frequency in days
  90. inbday = inbsec / iddss
  91. indg = INT(LOG10(REAL(inbday,wp))) + 1 ! number of digits needed to write days frequency
  92. WRITE(clfmt, clfmt0) indg ; WRITE(clave, clfmt) '_', inbday, 'd'
  93. IF( inbday == nmonth_len(nmonth) ) clave = '_1m'
  94. ELSEIF( MOD( inbsec, ihhss ) == 0 ) THEN ! frequency in hours
  95. inbhr = inbsec / ihhss
  96. indg = INT(LOG10(REAL(inbhr ,wp))) + 1 ! number of digits needed to write hours frequency
  97. WRITE(clfmt, clfmt0) indg ; WRITE(clave, clfmt) '_', inbhr , 'h'
  98. ELSEIF( MOD( inbsec, immss ) == 0 ) THEN ! frequency in minutes
  99. inbmn = inbsec / immss
  100. indg = INT(LOG10(REAL(inbmn ,wp))) + 1 ! number of digits needed to write minutes frequency
  101. WRITE(clfmt, clfmt0) indg ; WRITE(clave, clfmt) '_', inbmn , 'mn'
  102. ELSE ! frequency in seconds
  103. indg = INT(LOG10(REAL(inbsec,wp))) + 1 ! number of digits needed to write seconds frequency
  104. WRITE(clfmt, clfmt0) indg ; WRITE(clave, clfmt) '_', inbsec, 's'
  105. ENDIF
  106. ! date of the beginning and the end of the run
  107. zdrun = rdttra(1) / rday * REAL( nitend - nit000, wp ) ! length of the run in days
  108. zjul = fjulday - rdttra(1) / rday
  109. CALL ju2ymds( zjul , iyear1, imonth1, iday1, zsec1 ) ! year/month/day of the beginning of run
  110. CALL ju2ymds( zjul + zdrun, iyear2, imonth2, iday2, zsec2 ) ! year/month/day of the end of run
  111. IF( iyear2 < 10000 ) THEN ; clfmt = "(i4.4,2i2.2)" ! format used to write the date
  112. ELSE ; WRITE(clfmt, "('(i',i1,',2i2.2)')") INT(LOG10(REAL(iyear2,wp))) + 1
  113. ENDIF
  114. WRITE(cldate1, clfmt) iyear1, imonth1, iday1 ! date of the beginning of run
  115. WRITE(cldate2, clfmt) iyear2, imonth2, iday2 ! date of the end of run
  116. cdfnam = TRIM(cexper)//TRIM(clave)//"_"//TRIM(cldate1)//"_"//TRIM(cldate2)//"_"//TRIM(cdsuff)
  117. IF( .NOT. Agrif_Root() ) cdfnam = TRIM(Agrif_CFixed())//'_'//TRIM(cdfnam)
  118. END SUBROUTINE dia_nam
  119. !!======================================================================
  120. END MODULE dianam