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.
trdmld_rst.F90 in tags/nemo_v1_13_dev7/NEMO/OPA_SRC/TRD – NEMO

source: tags/nemo_v1_13_dev7/NEMO/OPA_SRC/TRD/trdmld_rst.F90 @ 7415

Last change on this file since 7415 was 503, checked in by opalod, 18 years ago

nemo_v1_update_064 : CT : general trends update including the addition of mean windows analysis possibility in the mixed layer

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.0 KB
Line 
1MODULE trdmld_rst
2   !!=================================================================================
3   !!                       ***  MODULE  trdmld_rst  ***
4   !! Ocean dynamic :  Input/Output files for restart on mixed-layer diagnostics
5   !!=================================================================================
6   !! History :  9.0  ! 05-05 (C. Deltel) Original code
7   !!---------------------------------------------------------------------------------
8#if defined key_trdmld
9   !!---------------------------------------------------------------------------------
10   USE dom_oce         ! ocean space and time domain
11   USE trdmod_oce      ! ocean variables for trend diagnostics (i.e. icp/mixed-layer/vorticity)
12   USE in_out_manager  ! I/O manager
13   USE daymod          ! calendar
14   USE ioipsl          !
15
16   IMPLICIT NONE
17   PRIVATE
18 
19   PUBLIC   trd_mld_rst_read    ! routine called by trd_mld_init
20   PUBLIC   trd_mld_rst_write   ! routine called by step.F90
21 
22   CHARACTER (len=48) ::   crestart = 'initial.nc'   ! restart file name
23   !!---------------------------------------------------------------------------------
24   !!   OPA 9.0 , LOCEAN-IPSL (2005)
25   !!---------------------------------------------------------------------------------
26 
27CONTAINS
28 
29   SUBROUTINE trd_mld_rst_write( kt )
30      !!--------------------------------------------------------------------------------
31      !!                  ***  SUBROUTINE trd_mld_rst_wri  ***
32      !!               
33      !! ** Purpose :   Write mixed-layer diagnostics restart fields.
34      !!-----------------------------------------------------------------------------------
35      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
36      !!   
37      LOGICAL ::   llbon
38      CHARACTER (len=50) ::   clname, cln
39      REAL(wp) ::   zdate0
40      REAL(wp), DIMENSION(1) :: zdept
41      INTEGER ::   ic, jc, itime, inumwrs_mld
42      !!-----------------------------------------------------------------------------
43   
44      IF( ( mod( kt, nstock ) == 0 ) .OR. ( kt == nitend ) ) THEN
45             
46         inumwrs_mld = 47
47         !-- Delete the restart file if it exists
48         INQUIRE( FILE=crestart, EXIST=llbon )
49         IF(llbon) THEN
50            OPEN( UNIT=inumwrs_mld, FILE=crestart, STATUS='old' )
51            CLOSE( inumwrs_mld, STATUS='delete' )
52         ENDIF
53
54         !-- Name of the new restart file
55         ic = 1
56         DO jc = 1, 16
57            IF( cexper(jc:jc) /= ' ' )   ic = jc
58         END DO
59         WRITE(cln,'("_",i4.4,i2.2,i2.2,"_restart_mld")') nyear, nmonth, nday
60         clname = cexper(1:ic)//cln
61         ic = 1
62         DO jc = 1, 48
63            IF( clname(jc:jc) /= ' ' ) ic = jc
64         END DO
65         crestart = clname(1:ic)//".nc"
66         itime = 0
67         CALL ymds2ju( nyear, nmonth, nday, 0.e0, zdate0 )
68
69         IF(lwp) THEN
70            WRITE(numout,*)
71            WRITE(numout,*) 'trdmld_rst: output for ML diags. restart, with trd_mld_rst_write routine'
72            WRITE(numout,*) '~~~~~~~~~~'
73            WRITE(numout,*) '            in file : ', TRIM(crestart), ' at it= ', kt, ' date= ', ndastp
74            WRITE(numout,*)
75         ENDIF
76
77         !-- Create the NetCDF restart file and write tje appropriate fields
78         !   N.B. In this section, 3rd dimension in arrays is NOT depth
79         zdept(1) = 1.
80         CALL restini( 'NONE', jpi, jpj, glamt, gphit, 1, zdept, clname,   &
81            &          itime, zdate0, rdt*nstock ,inumwrs_mld, domain_id=nidom )
82       
83         IF( ln_trdmld_instant ) THEN
84            CALL restput( inumwrs_mld, 'tmlbb'           , jpi, jpj,      1, 0, tmlbb           )
85            CALL restput( inumwrs_mld, 'tmlbn'           , jpi, jpj,      1, 0, tmlbn           )
86            CALL restput( inumwrs_mld, 'tmlatfb'         , jpi, jpj,      1, 0, tmlatfb         )
87
88            CALL restput( inumwrs_mld, 'smlbb'           , jpi, jpj,      1, 0, smlbb           )
89            CALL restput( inumwrs_mld, 'smlbn'           , jpi, jpj,      1, 0, smlbn           )
90            CALL restput( inumwrs_mld, 'smlatfb'         , jpi, jpj,      1, 0, smlatfb         )
91         ELSE
92            CALL restput( inumwrs_mld, 'rmldbn'          , jpi, jpj,      1, 0, rmldbn          )
93
94            !-- Temperature
95            CALL restput( inumwrs_mld, 'tmlbn'           , jpi, jpj,      1, 0, tmlbn           )
96            CALL restput( inumwrs_mld, 'tml_sumb'        , jpi, jpj,      1, 0, tml_sumb        )
97            CALL restput( inumwrs_mld, 'tmltrd_csum_ub'  , jpi, jpj, jpltrd, 0, tmltrd_csum_ub  )
98            CALL restput( inumwrs_mld, 'tmltrd_atf_sumb' , jpi, jpj,      1, 0, tmltrd_atf_sumb )
99
100            !-- Salinity
101            CALL restput( inumwrs_mld, 'smlbn'           , jpi, jpj,      1, 0, smlbn           )
102            CALL restput( inumwrs_mld, 'sml_sumb'        , jpi, jpj,      1, 0, sml_sumb        )
103            CALL restput( inumwrs_mld, 'smltrd_csum_ub'  , jpi, jpj, jpltrd, 0, smltrd_csum_ub  )
104            CALL restput( inumwrs_mld, 'smltrd_atf_sumb' , jpi, jpj,      1, 0, smltrd_atf_sumb )
105         ENDIF
106         !
107         CALL restclo( inumwrs_mld )
108         !
109      ENDIF
110      !   
111   END SUBROUTINE trd_mld_rst_write
112
113
114   SUBROUTINE trd_mld_rst_read
115    !!----------------------------------------------------------------------------
116    !!                   ***  SUBROUTINE trd_mld_rst_lec  ***
117    !!                   
118    !! ** Purpose :   Read file for mixed-layer diagnostics restart.
119    !!----------------------------------------------------------------------------
120    LOGICAL ::   llog
121    REAL(wp) ::  zlamt(jpi,jpj), zphit(jpi,jpj)
122    CHARACTER (len=8 ) ::   clvnames(30)
123    CHARACTER (len=32) ::   clname = 'restart_mld'
124    INTEGER  ::  itime, ibvar, & 
125                 inum  ! temporary logical unit
126    REAL(wp) ::   zdate0, zdt
127    REAL(wp), DIMENSION(1) :: zdept
128    !!-----------------------------------------------------------------------------
129
130    IF(lwp)  THEN
131       WRITE(numout,*)
132       WRITE(numout,*) ' trd_mld_rst_read : read the NetCDF MLD restart file'
133       WRITE(numout,*) ' ~~~~~~~~~~~~~~~~'
134    ENDIF
135
136    itime = 0
137    llog  = .FALSE.
138    zlamt(:,:) = 0.e0   ;   zphit(:,:) = 0.e0   ;   zdept(1)   = 0.e0
139    CALL restini( clname, jpi, jpj, zlamt, zphit, 1, zdept, 'NONE',   &
140       &          itime, zdate0, zdt, inum, domain_id=nidom )
141 
142    CALL ioget_vname( inum, ibvar, clvnames)
143
144    IF(lwp) THEN
145       WRITE(numout,*) 
146       WRITE(numout,*) '                    Info on the MLD restart file read : '
147       WRITE(numout,*) '                      File name           : ', clname
148       WRITE(numout,*) '                      number of variables : ', ibvar
149       WRITE(numout,*) '                      NetCDF variables    : ', clvnames
150       WRITE(numout,*)
151    ENDIF
152
153    IF( ln_trdmld_instant ) THEN
154       CALL restget( inum, 'tmlbb'           , jpi, jpj,      1, 0, llog, tmlbb          )
155       CALL restget( inum, 'tmlbn'           , jpi, jpj,      1, 0, llog, tmlbn          )
156       CALL restget( inum, 'tmlatfb'         , jpi, jpj,      1, 0, llog, tmlatfb        )
157
158       CALL restget( inum, 'smlbb'           , jpi, jpj,      1, 0, llog, smlbb          )
159       CALL restget( inum, 'smlbn'           , jpi, jpj,      1, 0, llog, smlbn          )
160       CALL restget( inum, 'smlatfb'         , jpi, jpj,      1, 0, llog, smlatfb        )
161    ELSE
162       CALL restget( inum, 'rmldbn'          , jpi, jpj,      1, 0, llog, rmldbn         ) ! needed for rmld_sum
163
164       !-- Temperature
165       CALL restget( inum, 'tmlbn'           , jpi, jpj,      1, 0, llog, tmlbn          ) ! needed for tml_sum
166       CALL restget( inum, 'tml_sumb'        , jpi, jpj,      1, 0, llog, tml_sumb       )
167       CALL restget( inum, 'tmltrd_csum_ub'  , jpi, jpj, jpltrd, 0, llog, tmltrd_csum_ub )
168       CALL restget( inum, 'tmltrd_atf_sumb' , jpi, jpj,      1, 0, llog, tmltrd_atf_sumb)
169
170       !-- Salinity
171       CALL restget( inum, 'smlbn'           , jpi, jpj,      1, 0, llog, smlbn          ) ! needed for sml_sum
172       CALL restget( inum, 'sml_sumb'        , jpi, jpj,      1, 0, llog, sml_sumb       )
173       CALL restget( inum, 'smltrd_csum_ub'  , jpi, jpj, jpltrd, 0, llog, smltrd_csum_ub )
174       CALL restget( inum, 'smltrd_atf_sumb' , jpi, jpj,      1, 0, llog, smltrd_atf_sumb)
175
176       CALL restclo( inum )
177    ENDIF
178
179  END SUBROUTINE trd_mld_rst_read
180 
181#else
182  !!=================================================================================
183  !!                       ***  MODULE  trdmld_rst  ***
184  !! Ocean dynamic :  Input/Output files for restart on mixed-layer diagnostics
185  !!=================================================================================
186CONTAINS
187  SUBROUTINE trd_mld_rst_write( kt )           !  No ML diags ==> empty routine
188    WRITE(*,*) 'trd_mld_rst_wri: You should not have seen this print! error?', kt
189  END SUBROUTINE trd_mld_rst_write
190  SUBROUTINE trd_mld_rst_read                  !  No ML Diags ==> empty routine
191  END SUBROUTINE trd_mld_rst_read
192#endif
193
194  !!=================================================================================
195END MODULE trdmld_rst
Note: See TracBrowser for help on using the repository browser.