trcwri.F90 7.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172
  1. MODULE trcwri
  2. !!======================================================================
  3. !! *** MODULE trcwri ***
  4. !! TOP : Output of passive tracers
  5. !!======================================================================
  6. !! History : 1.0 ! 2009-05 (C. Ethe) Original code
  7. !!----------------------------------------------------------------------
  8. #if defined key_top && defined key_iomput
  9. !!----------------------------------------------------------------------
  10. !! 'key_top' TOP models
  11. !!----------------------------------------------------------------------
  12. !! trc_wri_trc : outputs of concentration fields
  13. !!----------------------------------------------------------------------
  14. USE dom_oce ! ocean space and time domain variables
  15. USE oce_trc ! shared variables between ocean and passive tracers
  16. USE trc ! passive tracers common variables
  17. USE iom ! I/O manager
  18. USE ioipsl
  19. USE dianam ! Output file name
  20. USE trcwri_pisces
  21. USE trcwri_cfc
  22. USE trcwri_c14b
  23. USE trcwri_age
  24. USE trcwri_my_trc
  25. IMPLICIT NONE
  26. PRIVATE
  27. PUBLIC trc_wri
  28. PUBLIC trc_wri_state
  29. !! * Substitutions
  30. # include "top_substitute.h90"
  31. CONTAINS
  32. SUBROUTINE trc_wri( kt )
  33. !!---------------------------------------------------------------------
  34. !! *** ROUTINE trc_wri ***
  35. !!
  36. !! ** Purpose : output passive tracers fields and dynamical trends
  37. !!---------------------------------------------------------------------
  38. INTEGER, INTENT( in ) :: kt
  39. !
  40. INTEGER :: jn
  41. CHARACTER (len=20) :: cltra
  42. CHARACTER (len=40) :: clhstnam
  43. INTEGER :: inum = 11 ! temporary logical unit
  44. !!---------------------------------------------------------------------
  45. !
  46. IF( nn_timing == 1 ) CALL timing_start('trc_wri')
  47. !
  48. IF( lk_offline .AND. kt == nittrc000 .AND. lwp ) THEN ! WRITE root name in date.file for use by postpro
  49. CALL dia_nam( clhstnam, nn_writetrc,' ' )
  50. CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
  51. WRITE(inum,*) clhstnam
  52. CLOSE(inum)
  53. ENDIF
  54. ! write the tracer concentrations in the file
  55. ! ---------------------------------------
  56. IF( lk_offline .AND. lk_vvl ) THEN
  57. !
  58. CALL iom_put( "e3t" , fse3t_n(:,:,:) )
  59. CALL iom_put( "e3u" , fse3u_n(:,:,:) )
  60. CALL iom_put( "e3v" , fse3v_n(:,:,:) )
  61. CALL iom_put( "e3w" , fse3w_n(:,:,:) )
  62. !
  63. CALL iom_put( "ssh" , sshn ) ! sea surface height
  64. !
  65. ENDIF
  66. IF( lk_pisces ) CALL trc_wri_pisces ! PISCES
  67. IF( lk_my_trc ) CALL trc_wri_my_trc ! MY_TRC tracers
  68. IF( lk_cfc ) CALL trc_wri_cfc ! surface fluxes of CFC
  69. IF( lk_c14b ) CALL trc_wri_c14b ! surface fluxes of C14
  70. IF( lk_age ) CALL trc_wri_age ! AGE tracer
  71. !
  72. IF( nn_timing == 1 ) CALL timing_stop('trc_wri')
  73. !
  74. END SUBROUTINE trc_wri
  75. SUBROUTINE trc_wri_state( cdfile_name, kt )
  76. !!---------------------------------------------------------------------
  77. !! *** ROUTINE dia_wri_state ***
  78. !!
  79. !! ** Purpose : create a NetCDF file named cdfile_name which contains
  80. !! the instantaneous ocean state and forcing fields.
  81. !! Used to find errors in the initial state or save the last
  82. !! ocean state in case of abnormal end of a simulation
  83. !!
  84. !! ** Method : NetCDF files using ioipsl
  85. !! File 'output.init.nc' is created if ninist = 1 (namelist)
  86. !! File 'output.abort.trc.nc' is created in case of abnormal job end
  87. !!----------------------------------------------------------------------
  88. CHARACTER (len=* ), INTENT( in ) :: cdfile_name ! name of the file created
  89. INTEGER , INTENT( in ) :: kt ! ocean time-step index
  90. !!
  91. CHARACTER (len=32) :: clname
  92. CHARACTER (len=40) :: clop
  93. CHARACTER (len=20) :: cltra, cltrau
  94. CHARACTER (len=80) :: cltral
  95. INTEGER :: id_i , nz_i, nh_i, jn
  96. INTEGER, DIMENSION(1) :: idex ! local workspace
  97. REAL(wp) :: zsto, zout, zmax, zjulian, zdt
  98. !!----------------------------------------------------------------------
  99. !
  100. ! -----------------
  101. ! Define name, frequency of output and means
  102. clname = cdfile_name
  103. zdt = rdt
  104. zsto = rdt
  105. clop = "inst(x)" ! no use of the mask value (require less cpu time)
  106. zout = rdt
  107. IF(lwp) WRITE(numout,*)
  108. IF(lwp) WRITE(numout,*) 'trc_wri_state : single instantaneous ocean state'
  109. IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~ and forcing fields file created '
  110. IF(lwp) WRITE(numout,*) ' and named :', clname, '.nc'
  111. ! Compute julian date from starting date of the run
  112. CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )
  113. zjulian = zjulian - adatrj ! set calendar origin to the beginning of the experiment
  114. CALL histbeg( clname, jpi, glamt, jpj, gphit, &
  115. 1, jpi, 1, jpj, nit000-1, zjulian, zdt, nh_i, id_i, domain_id=nidom, snc4chunks=snc4set ) ! Horizontal grid : glamt and gphit
  116. CALL histvert( id_i, "deptht", "Vertical T levels", "m", jpk, gdept_1d, nz_i, "down") ! Vertical grid : gdept
  117. ! Declare all the output fields as NETCDF variables
  118. DO jn = 1, jptra
  119. cltra = TRIM( ctrcnm(jn) ) ! short title for tracer
  120. cltral = TRIM( ctrcln(jn) ) ! long title for tracer
  121. cltrau = TRIM( ctrcun(jn) ) ! UNIT for tracer
  122. CALL histdef( id_i, cltra, cltral, cltrau, jpi, jpj, nh_i, &
  123. & jpk, 1, jpk, nz_i, 32, clop, zsto, zout )
  124. END DO
  125. CALL histend( id_i, snc4chunks=snc4set )
  126. DO jn = 1, jptra
  127. cltra = TRIM( ctrcnm(jn) ) ! short title for tracer
  128. CALL histwrite( id_i, cltra, kt, trn(:,:,:,jn), jpi*jpj*jpk, idex )
  129. END DO
  130. CALL histclo( id_i )
  131. END SUBROUTINE trc_wri_state
  132. #else
  133. !!----------------------------------------------------------------------
  134. !! Dummy module : No passive tracer
  135. !!----------------------------------------------------------------------
  136. PUBLIC trc_wri
  137. CONTAINS
  138. SUBROUTINE trc_wri( kt ) ! Empty routine
  139. INTEGER, INTENT(in) :: kt
  140. END SUBROUTINE trc_wri
  141. SUBROUTINE trc_wri_state( cd_name, kt ) ! Empty routine
  142. CHARACTER (len=* ), INTENT( in ) :: cd_name ! name of the file created
  143. INTEGER, INTENT(in) :: kt
  144. END SUBROUTINE trc_wri_state
  145. #endif
  146. !!----------------------------------------------------------------------
  147. !! NEMO/TOP 3.3 , NEMO Consortium (2010)
  148. !! $Id: trcwri.F90 8353 2017-07-19 14:41:00Z lovato $
  149. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  150. !!======================================================================
  151. END MODULE trcwri