diadimg.F90 9.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229
  1. MODULE diadimg
  2. !!======================================================================
  3. !! *** MODULE diadimg ***
  4. !! Ocean diagnostics : write ocean output files in dimg direct access format (mpp)
  5. !!=====================================================================
  6. # if defined key_dimgout
  7. !!----------------------------------------------------------------------
  8. USE oce ! ocean dynamics and tracers
  9. USE dom_oce ! ocean space and time domain
  10. USE in_out_manager ! I/O manager
  11. USE daymod ! calendar
  12. USE lib_mpp
  13. IMPLICIT NONE
  14. PRIVATE
  15. PUBLIC dia_wri_dimg ! called by trd_mld (eg)
  16. PUBLIC dia_wri_dimg_alloc ! called by nemo_alloc in nemogcm.F90
  17. !! These workspace arrays are inside the module so that we can make them
  18. !! allocatable in a clean way. Not done in wrk_nemo because these are of KIND(sp).
  19. REAL(sp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: z42d ! 2d temporary workspace (sp)
  20. REAL(sp), ALLOCATABLE, SAVE, DIMENSION(:) :: z4dep ! vertical level (sp)
  21. !! * Substitutions
  22. # include "domzgr_substitute.h90"
  23. !!----------------------------------------------------------------------
  24. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  25. !! $Id: diadimg.F90 4292 2013-11-20 16:28:04Z cetlod $
  26. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  27. !!----------------------------------------------------------------------
  28. CONTAINS
  29. FUNCTION dia_wri_dimg_alloc()
  30. !!---------------------------------------------------------------------
  31. !! *** ROUTINE dia_wri_dimg_alloc ***
  32. !!
  33. !!---------------------------------------------------------------------
  34. INTEGER :: dia_wri_dimg_alloc ! return value
  35. !!---------------------------------------------------------------------
  36. !
  37. IF( .NOT. ALLOCATED( z42d ) )THEN
  38. ALLOCATE( z42d(jpi,jpj), z4dep(jpk), STAT=dia_wri_dimg_alloc )
  39. IF( lk_mpp ) CALL mpp_sum ( dia_wri_dimg_alloc )
  40. IF( dia_wri_dimg_alloc /= 0 ) CALL ctl_warn('dia_wri_dimg_alloc: allocation of array failed.')
  41. ELSE
  42. dia_wri_dimg_alloc = 0
  43. ENDIF
  44. !
  45. END FUNCTION dia_wri_dimg_alloc
  46. SUBROUTINE dia_wri_dimg( cd_name, cd_text, ptab, klev, cd_type , ksubi )
  47. !!-------------------------------------------------------------------------
  48. !! *** ROUTINE dia_wri_dimg ***
  49. !!
  50. !! ** Purpose : write ptab in the dimg file cd_name, with comment cd_text.
  51. !! ptab has klev x 2D fields
  52. !!
  53. !! ** Action : Define header variables from the config parameters
  54. !! Open the dimg file on unit inum = 14 ( IEEE I4R4 file )
  55. !! Write header on record 1
  56. !! Write ptab on the following klev records
  57. !!
  58. !! History : 2003-12 (J.M. Molines ) : Original. Replace ctl_opn, writn2d
  59. !!---------------------------------------------------------------------------
  60. CHARACTER(len=*),INTENT(in) :: &
  61. & cd_name, & ! dimg file name
  62. & cd_text ! comment to write on record #1
  63. INTEGER, INTENT(in) :: klev ! number of level in ptab to write
  64. REAL(wp),INTENT(in), DIMENSION(:,:,:) :: ptab ! 3D array to write
  65. CHARACTER(LEN=1),INTENT(in) :: cd_type ! either 'T', 'W' or '2' , depending on the vertical
  66. ! ! grid for ptab. 2 stands for 2D file
  67. INTEGER, INTENT(in), OPTIONAL, DIMENSION(klev) :: ksubi
  68. !! * Local declarations
  69. INTEGER :: jk, jn ! dummy loop indices
  70. INTEGER :: irecl4, & ! record length in bytes
  71. & inum, & ! logical unit (set to 14)
  72. & irec, & ! current record to be written
  73. & irecend ! record number where nclit... are stored
  74. REAL(sp) :: zdx,zdy,zspval,zwest,ztimm
  75. REAL(sp) :: zsouth
  76. CHARACTER(LEN=80) :: clname ! name of file in case of dimgnnn
  77. CHARACTER(LEN=4) :: clver='@!01' ! dimg string identifier
  78. !!---------------------------------------------------------------------------
  79. ! ! allocate dia_wri_dimg array
  80. IF( dia_wri_dimg_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'dia_wri_dimg : unable to allocate arrays' )
  81. !! * Initialisations
  82. irecl4 = MAX(jpi*jpj*sp , 84+(18+1+jpk)*sp )
  83. zspval=0.0_sp ! special values on land
  84. ! the 'numerical' grid is described. The geographical one is in a grid file
  85. zdx=1._sp
  86. zdy=1._sp
  87. zsouth=njmpp * 1._sp
  88. zwest=nimpp * 1._sp
  89. ! time in days since the historical begining of the run (nit000 = 0 )
  90. ztimm=adatrj
  91. SELECT CASE ( cd_type )
  92. CASE ( 'T')
  93. z4dep(:)=gdept_1d(:)
  94. CASE ( 'W' )
  95. z4dep(:)=gdepw_1d(:)
  96. CASE ( '2' )
  97. z4dep(1:klev) =(/(jk, jk=1,klev)/)
  98. CASE ( 'I' )
  99. z4dep(1:klev) = ksubi(1:klev)
  100. CASE DEFAULT
  101. IF(lwp) WRITE(numout,*) ' E R R O R : bad cd_type in dia_wri_dimg '
  102. STOP 'dia_wri_dimg'
  103. END SELECT
  104. IF ( ln_dimgnnn ) THEN
  105. irecl4 = MAX(jpi*jpj*sp , 84+(18+jpk)*sp + 8*jpnij*sp )
  106. WRITE(clname,'(a,a,i3.3)') TRIM(cd_name),'.',narea
  107. CALL ctl_opn(inum, clname,'UNKNOWN','UNFORMATTED','DIRECT',irecl4,numout,lwp)
  108. WRITE(inum,REC=1 ) clver, cd_text, irecl4, &
  109. & jpi,jpj, klev, 1 , 1 , &
  110. & zwest, zsouth, zdx, zdy, zspval, &
  111. & z4dep(1:klev), &
  112. & ztimm, &
  113. & narea, jpnij,jpiglo,jpjglo,jpizoom, jpjzoom, & ! extension to dimg for mpp output
  114. & nlcit,nlcjt, nldit, nldjt, nleit, nlejt, nimppt, njmppt !
  115. !! * Write klev levels
  116. IF ( cd_type == 'I' ) THEN
  117. DO jk = 1, klev
  118. irec =1 + jk
  119. z42d(:,:) = ptab(:,:,ksubi(jk))
  120. WRITE(inum,REC=irec) z42d(:,:)
  121. END DO
  122. ELSE
  123. DO jk = 1, klev
  124. irec =1 + jk
  125. z42d(:,:) = ptab(:,:,jk)
  126. WRITE(inum,REC=irec) z42d(:,:)
  127. END DO
  128. ENDIF
  129. ELSE
  130. clver='@!03' ! dimg string identifier
  131. ! note that version @!02 is optimized with respect to record length.
  132. ! The vertical dep variable is reduced to klev instead of klev*jpnij :
  133. ! this is OK for jpnij < 181 (jpk=46)
  134. ! for more processors, irecl4 get huge and that's why we switch to '@!03':
  135. ! In this case we just add an extra integer to the standard dimg structure,
  136. ! which is a record number where the arrays nlci etc... starts (1 per record)
  137. !! Standard dimgproc (1 file per variable, all procs. write to this file )
  138. !! * Open file
  139. CALL ctl_opn(inum, cd_name,'UNKNOWN','UNFORMATTED','DIRECT',irecl4,numout,lwp)
  140. !! * Write header on record #1
  141. irecend=1 + klev*jpnij
  142. IF(lwp) WRITE(inum,REC=1 ) clver, cd_text, irecl4, &
  143. & jpi,jpj, klev, 1 , 1 , &
  144. & zwest, zsouth, zdx, zdy, zspval, &
  145. & z4dep(1:klev), &
  146. & ztimm, &
  147. & narea, jpnij,jpiglo,jpjglo,jpizoom, jpjzoom, irecend
  148. IF (lwp ) THEN
  149. WRITE(inum,REC=irecend + 1 ) nlcit
  150. WRITE(inum,REC=irecend + 2 ) nlcjt
  151. WRITE(inum,REC=irecend + 3 ) nldit
  152. WRITE(inum,REC=irecend + 4 ) nldjt
  153. WRITE(inum,REC=irecend + 5 ) nleit
  154. WRITE(inum,REC=irecend + 6 ) nlejt
  155. WRITE(inum,REC=irecend + 7 ) nimppt
  156. WRITE(inum,REC=irecend + 8 ) njmppt
  157. ENDIF
  158. ! & ! extension to dimg for mpp output
  159. ! & nlcit,nlcjt, nldit, nldjt, nleit, nlejt, nimppt, njmppt !
  160. !! * Write klev levels
  161. IF ( cd_type == 'I' ) THEN
  162. DO jk = 1, klev
  163. irec =1 + klev * (narea -1) + jk
  164. z42d(:,:) = ptab(:,:,ksubi(jk))
  165. WRITE(inum,REC=irec) z42d(:,:)
  166. END DO
  167. ELSE
  168. DO jk = 1, klev
  169. irec =1 + klev * (narea -1) + jk
  170. z42d(:,:) = ptab(:,:,jk)
  171. WRITE(inum,REC=irec) z42d(:,:)
  172. END DO
  173. ENDIF
  174. ENDIF
  175. !! * Close the file
  176. CLOSE(inum)
  177. END SUBROUTINE dia_wri_dimg
  178. # else
  179. !!----------------------------------------------------------------------
  180. !! Default option : Empty module
  181. !!----------------------------------------------------------------------
  182. CONTAINS
  183. SUBROUTINE dia_wri_dimg( cd_name, cd_exper, ptab, klev, cd_type )
  184. REAL, DIMENSION(:,:,:) :: ptab
  185. INTEGER :: klev
  186. CHARACTER(LEN=80) :: cd_name, cd_exper,cd_type
  187. WRITE(*,*) ' This print must never occur ', cd_name, cd_exper,ptab, klev, cd_type
  188. WRITE(*,*) ' this routine is here just for compilation '
  189. END SUBROUTINE dia_wri_dimg
  190. # endif
  191. !!======================================================================
  192. END MODULE diadimg