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.
diadimg.F90 in trunk/NEMO/OPA_SRC/DIA – NEMO

source: trunk/NEMO/OPA_SRC/DIA/diadimg.F90 @ 216

Last change on this file since 216 was 216, checked in by opalod, 19 years ago

CT : UPDATE151 : New trends organization

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.4 KB
Line 
1MODULE 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   !! * Modules used
9   USE oce             ! ocean dynamics and tracers
10   USE dom_oce         ! ocean space and time domain
11   USE in_out_manager  ! I/O manager
12   USE daymod          ! calendar
13
14   IMPLICIT NONE
15   PRIVATE
16
17   !! * Accessibility
18   PUBLIC dia_wri_dimg            ! called by trd_mld (eg)
19
20   !! * Substitutions
21#  include "domzgr_substitute.h90"
22   !!----------------------------------------------------------------------
23   !!   OPA 9.0 , LODYC-IPSL  (2003)
24   !!----------------------------------------------------------------------
25
26CONTAINS
27
28  SUBROUTINE dia_wri_dimg(cd_name, cd_text, ptab, klev, cd_type , ksubi )
29    !!-------------------------------------------------------------------------
30    !!        *** ROUTINE dia_wri_dimg ***
31    !!
32    !! ** Purpose : write ptab in the dimg file cd_name, with comment cd_text.
33    !!       ptab has klev x 2D fields
34    !!
35    !! ** Action :
36    !!       Define header variables from the config parameters
37    !!       Open the dimg file on unit inum = 14 ( IEEE I4R4 file )
38    !!       Write header on record 1
39    !!       Write ptab on the following klev records
40    !!
41    !! History :
42    !!   03-12 (J.M. Molines ) : Original. Replace ctlopn, writn2d
43    !!---------------------------------------------------------------------------
44    !! * Arguments
45    CHARACTER(len=*),INTENT(in) ::   &
46         &                            cd_name,  &  ! dimg file name
47         &                            cd_text      ! comment to write on record #1
48    INTEGER, INTENT(in) ::            klev         ! number of level in ptab to write
49    REAL(wp),INTENT(in), DIMENSION(:,:,:) :: ptab  ! 3D array to write
50    CHARACTER(LEN=1),INTENT(in) ::    cd_type      ! either 'T', 'W' or '2' , depending on the vertical
51    !                                              ! grid for ptab. 2 stands for 2D file
52    INTEGER, INTENT(in), OPTIONAL, DIMENSION(klev) :: ksubi 
53
54    !! * Local declarations
55    INTEGER :: jk, jn           ! dummy loop indices
56    INTEGER :: irecl4,             &    ! record length in bytes
57         &       inum,             &    ! logical unit (set to 14)
58         &       irec                   ! current record to be written
59    REAL(sp)                    :: zdx,zdy,zspval,zwest,ztimm
60    REAL(sp)                    :: zsouth
61    REAL(sp),DIMENSION(jpi,jpj) :: z42d        ! 2d temporary workspace (sp)
62    REAL(sp),DIMENSION(jpk)     :: z4dep       ! vertical level (sp)
63
64    CHARACTER(LEN=4) :: clver='@!01'
65    !!---------------------------------------------------------------------------
66
67    !! * Initialisations
68
69    irecl4 = MAX(jpi*jpj*sp , 84+18*sp + (jpk+8)*jpnij*sp  )
70    inum = 14
71
72    zspval=0.0_sp    ! special values on land
73    !  the 'numerical' grid is described. The geographical one is in a grid file
74    zdx=1._sp
75    zdy=1._sp
76    zsouth=njmpp * 1._sp
77    zwest=nimpp * 1._sp
78    !  time in days since the historical begining of the run (nit000 = 0 )
79    ztimm=adatrj
80
81    SELECT CASE ( cd_type )
82
83    CASE ( 'T')
84       z4dep(:)=fsdept(1,1,:)
85
86    CASE ( 'W' )
87       z4dep(:)=fsdepw(1,1,:)
88
89    CASE ( '2' )
90       z4dep(1:klev) =(/(jk, jk=1,klev)/)
91
92    CASE ( 'I' )
93       z4dep(1:klev) = ksubi(1:klev)
94
95    CASE DEFAULT
96       IF(lwp) WRITE(numout,*) ' E R R O R : bad cd_type in dia_wri_dimg '
97       STOP 'dia_wri_dimg'
98
99    END SELECT
100
101    !! * Open file
102    OPEN (inum, FILE=cd_name, FORM='UNFORMATTED', ACCESS='DIRECT', RECL=irecl4 )
103
104    !! * Write header on record #1
105    IF(lwp) WRITE(inum,REC=1 ) clver, cd_text, irecl4, &
106         &     jpi,jpj, klev*jpnij, 1 , 1 ,            &
107         &     zwest, zsouth, zdx, zdy, zspval,  &
108         &     (z4dep(1:klev),jn=1,jpnij),       &
109         &     ztimm,                            &
110         &     narea, jpnij,jpiglo,jpjglo,jpizoom, jpjzoom,    &    ! extension to dimg for mpp output
111         &     nlcit,nlcjt, nldit, nldjt, nleit, nlejt, nimppt, njmppt  !
112
113    !! * Write klev levels
114    IF ( cd_type == 'I' ) THEN
115
116       DO jk = 1, klev
117          irec =1 + klev * (narea -1) + jk
118          z42d(:,:) = ptab(:,:,ksubi(jk))
119          WRITE(inum,REC=irec)  z42d(:,:)
120       END DO
121    ELSE
122       DO jk = 1, klev
123          irec =1 + klev * (narea -1) + jk
124          z42d(:,:) = ptab(:,:,jk)
125          WRITE(inum,REC=irec)  z42d(:,:)
126       END DO
127    ENDIF
128
129    !! * Close the file
130    CLOSE(inum)
131
132  END SUBROUTINE dia_wri_dimg
133
134#  else
135   !!----------------------------------------------------------------------
136   !!   Default option :                                       Empty module
137   !!----------------------------------------------------------------------
138CONTAINS
139
140   SUBROUTINE dia_wri_dimg( cd_name, cd_exper, ptab, klev, cd_type )
141      REAL, DIMENSION(:,:,:) :: ptab
142      INTEGER :: klev
143      CHARACTER(LEN=80) :: cd_name, cd_exper,cd_type
144      WRITE(*,*) ' This print must never occur ', cd_name, cd_exper,ptab, klev, cd_type
145      WRITE(*,*) ' this routine is here just for compilation '
146   END SUBROUTINE dia_wri_dimg
147# endif
148   !!======================================================================
149END MODULE diadimg
Note: See TracBrowser for help on using the repository browser.