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 trunk/NEMO/OPA_SRC/TRD – NEMO

source: trunk/NEMO/OPA_SRC/TRD/trdmld_rst.F90 @ 557

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

nemo_v1_bugfix_069: SM+CT+CE: bugfix of mld restart + OFF line compatibiblity

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.2 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 iom             ! I/O module
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   INTEGER ::   nummldw                    ! logical unit for mld restart (write)
24
25   !!---------------------------------------------------------------------------------
26   !! OPA 9.0 , LOCEAN-IPSL (2006)
27   !! $Header$
28   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
29   !!---------------------------------------------------------------------------------
30 
31CONTAINS
32 
33   SUBROUTINE trd_mld_rst_write( kt )
34      !!--------------------------------------------------------------------------------
35      !!                  ***  SUBROUTINE trd_mld_rst_wri  ***
36      !!               
37      !! ** Purpose :   Write mixed-layer diagnostics restart fields.
38      !!--------------------------------------------------------------------------------
39      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
40      !
41      CHARACTER (len=35) :: charout
42      INTEGER ::   jk                 ! loop indice
43      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
44      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name
45      !!--------------------------------------------------------------------------------
46
47      IF( kt == nitrst-1 ) THEN
48         IF( nitrst > 1.0e9 ) THEN   
49            WRITE(clkt,*) nitrst
50         ELSE
51            WRITE(clkt,'(i8.8)') nitrst
52         ENDIF
53         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart_mld"
54         IF(lwp) WRITE(numout,*) '             open ocean restart_mld NetCDF file: '//clname
55         CALL iom_open( clname, nummldw, ldwrt = .TRUE., kiolib = jprstlib )
56      ENDIF
57
58      IF( kt == nitrst .AND. lwp ) THEN
59         WRITE(numout,*)
60         WRITE(numout,*) 'trdmld_rst: output for ML diags. restart, with trd_mld_rst_write routine'
61         WRITE(numout,*) '~~~~~~~~~~'
62         WRITE(numout,*)
63      ENDIF
64
65      IF( ln_trdmld_instant ) THEN 
66         !-- Temperature
67         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbb'           , tmlbb           )
68         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           )
69         CALL iom_rstput( kt, nitrst, nummldw, 'tmlatfb'         , tmlatfb         )
70
71         !-- Salinity
72         CALL iom_rstput( kt, nitrst, nummldw, 'smlbb'           , smlbb           )
73         CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           )
74         CALL iom_rstput( kt, nitrst, nummldw, 'smlatfb'         , smlatfb         )
75      ELSE
76         CALL iom_rstput( kt, nitrst, nummldw, 'rmldbn'          , rmldbn          )
77
78         !-- Temperature
79         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           )
80         CALL iom_rstput( kt, nitrst, nummldw, 'tml_sumb'        , tml_sumb        )
81         DO jk = 1, jpltrd
82            IF( jk < 10 )   THEN
83               WRITE(charout,FMT="('tmltrd_csum_ub_', I1)") jk
84            ELSE
85               WRITE(charout,FMT="('tmltrd_csum_ub_', I2)") jk
86            ENDIF
87            CALL iom_rstput( kt, nitrst, nummldw, charout,  tmltrd_csum_ub(:,:,jk) )
88         ENDDO
89         CALL iom_rstput( kt, nitrst, nummldw, 'tmltrd_atf_sumb' , tmltrd_atf_sumb )
90
91         !-- Salinity
92         CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           )
93         CALL iom_rstput( kt, nitrst, nummldw, 'sml_sumb'        , sml_sumb        )
94         DO jk = 1, jpltrd
95            IF( jk < 10 )   THEN
96               WRITE(charout,FMT="('smltrd_csum_ub_', I1)") jk
97            ELSE
98               WRITE(charout,FMT="('smltrd_csum_ub_', I2)") jk
99            ENDIF
100            CALL iom_rstput( kt, nitrst, nummldw, charout , smltrd_csum_ub(:,:,jk) )
101         ENDDO
102         CALL iom_rstput( kt, nitrst, nummldw, 'smltrd_atf_sumb' , smltrd_atf_sumb )
103      ENDIF
104      !
105      CALL iom_close( nummldw )     ! close the restart file (only at last time step)
106      !
107      !   
108   END SUBROUTINE trd_mld_rst_write
109
110
111   SUBROUTINE trd_mld_rst_read
112    !!----------------------------------------------------------------------------
113    !!                   ***  SUBROUTINE trd_mld_rst_lec  ***
114    !!                   
115    !! ** Purpose :   Read file for mixed-layer diagnostics restart.
116    !!----------------------------------------------------------------------------
117    INTEGER  ::  inum       ! temporary logical unit
118    !
119    CHARACTER (len=35) :: charout
120    INTEGER ::   jk         ! loop indice
121    !!-----------------------------------------------------------------------------
122
123    IF(lwp)  THEN
124       WRITE(numout,*)
125       WRITE(numout,*) ' trd_mld_rst_read : read the NetCDF MLD restart file'
126       WRITE(numout,*) ' ~~~~~~~~~~~~~~~~'
127    ENDIF
128
129    CALL iom_open( 'restart_mld', inum, kiolib = jprstlib ) 
130
131    IF( ln_trdmld_instant ) THEN 
132       !-- Temperature
133       CALL iom_get( inum, jpdom_local, 'tmlbb'           , tmlbb          )
134       CALL iom_get( inum, jpdom_local, 'tmlbn'           , tmlbn          )
135       CALL iom_get( inum, jpdom_local, 'tmlatfb'         , tmlatfb        )
136
137       !-- Salinity
138       CALL iom_get( inum, jpdom_local, 'smlbb'           , smlbb          )
139       CALL iom_get( inum, jpdom_local, 'smlbn'           , smlbn          )
140       CALL iom_get( inum, jpdom_local, 'smlatfb'         , smlatfb        )
141    ELSE
142       CALL iom_get( inum, jpdom_local, 'rmldbn'          , rmldbn         ) ! needed for rmld_sum
143
144       !-- Temperature
145       CALL iom_get( inum, jpdom_local, 'tmlbn'           , tmlbn          ) ! needed for tml_sum
146       CALL iom_get( inum, jpdom_local, 'tml_sumb'        , tml_sumb       )
147       DO jk = 1, jpltrd
148          IF( jk < 10 )   THEN
149             WRITE(charout,FMT="('tmltrd_csum_ub_', I1)") jk
150          ELSE
151             WRITE(charout,FMT="('tmltrd_csum_ub_', I2)") jk
152          ENDIF
153          CALL iom_get( inum, jpdom_local, charout, tmltrd_csum_ub(:,:,jk) )
154       ENDDO
155       CALL iom_get( inum, jpdom_local, 'tmltrd_atf_sumb' , tmltrd_atf_sumb)
156
157       !-- Salinity
158       CALL iom_get( inum, jpdom_local, 'smlbn'           , smlbn          ) ! needed for sml_sum
159       CALL iom_get( inum, jpdom_local, 'sml_sumb'        , sml_sumb       )
160       DO jk = 1, jpltrd
161          IF( jk < 10 )   THEN
162             WRITE(charout,FMT="('smltrd_csum_ub_', I1)") jk
163          ELSE
164             WRITE(charout,FMT="('smltrd_csum_ub_', I2)") jk
165          ENDIF
166          CALL iom_get( inum, jpdom_local, charout, smltrd_csum_ub(:,:,jk) )
167       ENDDO
168       CALL iom_get( inum, jpdom_local, 'smltrd_atf_sumb' , smltrd_atf_sumb)
169
170       CALL iom_close( inum )
171    ENDIF
172
173  END SUBROUTINE trd_mld_rst_read
174 
175#else
176  !!=================================================================================
177  !!                       ***  MODULE  trdmld_rst  ***
178  !! Ocean dynamic :  Input/Output files for restart on mixed-layer diagnostics
179  !!=================================================================================
180CONTAINS
181  SUBROUTINE trd_mld_rst_write( kt )           !  No ML diags ==> empty routine
182    WRITE(*,*) 'trd_mld_rst_wri: You should not have seen this print! error?', kt
183  END SUBROUTINE trd_mld_rst_write
184  SUBROUTINE trd_mld_rst_read                  !  No ML Diags ==> empty routine
185  END SUBROUTINE trd_mld_rst_read
186#endif
187
188  !!=================================================================================
189END MODULE trdmld_rst
Note: See TracBrowser for help on using the repository browser.