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 @ 1656

Last change on this file since 1656 was 1473, checked in by smasson, 15 years ago

for dimgout: allow changing the number of proc for restart, see ticket:442

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 9.7 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   USE restart         ! only for lrst_oce
16
17   IMPLICIT NONE
18   PRIVATE
19 
20   PUBLIC   trd_mld_rst_read    ! routine called by trd_mld_init
21   PUBLIC   trd_mld_rst_write   ! routine called by step.F90
22 
23   INTEGER ::   nummldw         ! logical unit for mld restart
24
25   !!---------------------------------------------------------------------------------
26   !! OPA 9.0 , LOCEAN-IPSL (2006)
27   !! $Id$
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      ! to get better performances with NetCDF format:
48      ! we open and define the ocean restart_mld file one time step before writing the data (-> at nitrst - 1)
49      ! except if we write ocean restart_mld files every time step or if an ocean restart_mld file was writen at nitend - 1
50      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. MOD( nitend - 1, nstock ) == 0 ) ) THEN
51         ! beware of the format used to write kt (default is i8.8, that should be large enough...)
52         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
53         ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
54         ENDIF
55         ! create the file
56         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trdrst_out)
57         IF(lwp) THEN
58            WRITE(numout,*)
59            SELECT CASE ( jprstlib )
60            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart_mld binary file: '//clname
61            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart_mld NetCDF file: '//clname
62            END SELECT
63            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt,' date= ', ndastp
64            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt,' date= ', ndastp
65            ENDIF
66         ENDIF
67
68         CALL iom_open( clname, nummldw, ldwrt = .TRUE., kiolib = jprstlib )
69      ENDIF
70
71      IF( kt == nitrst .AND. lwp ) THEN
72         WRITE(numout,*)
73         WRITE(numout,*) 'trdmld_rst: output for ML diags. restart, with trd_mld_rst_write routine kt =', kt
74         WRITE(numout,*) '~~~~~~~~~~'
75         WRITE(numout,*)
76      ENDIF
77
78      IF( ln_trdmld_instant ) THEN 
79         !-- Temperature
80         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbb'           , tmlbb           )
81         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           )
82         CALL iom_rstput( kt, nitrst, nummldw, 'tmlatfb'         , tmlatfb         )
83
84         !-- Salinity
85         CALL iom_rstput( kt, nitrst, nummldw, 'smlbb'           , smlbb           )
86         CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           )
87         CALL iom_rstput( kt, nitrst, nummldw, 'smlatfb'         , smlatfb         )
88      ELSE
89         CALL iom_rstput( kt, nitrst, nummldw, 'rmldbn'          , rmldbn          )
90
91         !-- Temperature
92         CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           )
93         CALL iom_rstput( kt, nitrst, nummldw, 'tml_sumb'        , tml_sumb        )
94         DO jk = 1, jpltrd
95            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)") jk
96            ELSE                 ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I2)") jk
97            ENDIF
98            CALL iom_rstput( kt, nitrst, nummldw, charout,  tmltrd_csum_ub(:,:,jk) )
99         ENDDO
100         CALL iom_rstput( kt, nitrst, nummldw, 'tmltrd_atf_sumb' , tmltrd_atf_sumb )
101
102         !-- Salinity
103         CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           )
104         CALL iom_rstput( kt, nitrst, nummldw, 'sml_sumb'        , sml_sumb        )
105         DO jk = 1, jpltrd
106            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('smltrd_csum_ub_', I1)") jk
107            ELSE                 ;   WRITE(charout,FMT="('smltrd_csum_ub_', I2)") jk
108            ENDIF
109            CALL iom_rstput( kt, nitrst, nummldw, charout , smltrd_csum_ub(:,:,jk) )
110         ENDDO
111         CALL iom_rstput( kt, nitrst, nummldw, 'smltrd_atf_sumb' , smltrd_atf_sumb )
112      ENDIF
113      !
114      IF( kt == nitrst ) THEN
115         CALL iom_close( nummldw )     ! close the restart file (only at last time step)
116         lrst_oce = .FALSE.
117      ENDIF
118      !
119      !   
120   END SUBROUTINE trd_mld_rst_write
121
122
123   SUBROUTINE trd_mld_rst_read
124    !!----------------------------------------------------------------------------
125    !!                   ***  SUBROUTINE trd_mld_rst_lec  ***
126    !!                   
127    !! ** Purpose :   Read file for mixed-layer diagnostics restart.
128    !!----------------------------------------------------------------------------
129    INTEGER  ::  inum       ! temporary logical unit
130    !
131    CHARACTER (len=35) :: charout
132    INTEGER ::   jk         ! loop indice
133    INTEGER ::   jlibalt = jprstlib
134    LOGICAL ::   llok
135    !!-----------------------------------------------------------------------------
136
137    IF(lwp)  THEN
138       WRITE(numout,*)
139       WRITE(numout,*) ' trd_mld_rst_read : read the NetCDF MLD restart file'
140       WRITE(numout,*) ' ~~~~~~~~~~~~~~~~'
141    ENDIF
142    IF ( jprstlib == jprstdimg ) THEN
143       ! eventually read netcdf file (monobloc)  for restarting on different number of processors
144       ! if {cn_trdrst_in}.nc exists, then set jlibalt to jpnf90
145       INQUIRE( FILE = TRIM(cn_trdrst_in)//'.nc', EXIST = llok )
146       IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
147    ENDIF
148
149    CALL iom_open( cn_trdrst_in, inum, kiolib = jlibalt ) 
150
151    IF( ln_trdmld_instant ) THEN 
152       !-- Temperature
153       CALL iom_get( inum, jpdom_autoglo, 'tmlbb'           , tmlbb          )
154       CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn          )
155       CALL iom_get( inum, jpdom_autoglo, 'tmlatfb'         , tmlatfb        )
156
157       !-- Salinity
158       CALL iom_get( inum, jpdom_autoglo, 'smlbb'           , smlbb          )
159       CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          )
160       CALL iom_get( inum, jpdom_autoglo, 'smlatfb'         , smlatfb        )
161    ELSE
162       CALL iom_get( inum, jpdom_autoglo, 'rmldbn'          , rmldbn         ) ! needed for rmld_sum
163
164       !-- Temperature
165       CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn          ) ! needed for tml_sum
166       CALL iom_get( inum, jpdom_autoglo, 'tml_sumb'        , tml_sumb       )
167       DO jk = 1, jpltrd
168          IF( jk < 10 )   THEN
169             WRITE(charout,FMT="('tmltrd_csum_ub_', I1)") jk
170          ELSE
171             WRITE(charout,FMT="('tmltrd_csum_ub_', I2)") jk
172          ENDIF
173          CALL iom_get( inum, jpdom_autoglo, charout, tmltrd_csum_ub(:,:,jk) )
174       ENDDO
175       CALL iom_get( inum, jpdom_autoglo, 'tmltrd_atf_sumb' , tmltrd_atf_sumb)
176
177       !-- Salinity
178       CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          ) ! needed for sml_sum
179       CALL iom_get( inum, jpdom_autoglo, 'sml_sumb'        , sml_sumb       )
180       DO jk = 1, jpltrd
181          IF( jk < 10 )   THEN
182             WRITE(charout,FMT="('smltrd_csum_ub_', I1)") jk
183          ELSE
184             WRITE(charout,FMT="('smltrd_csum_ub_', I2)") jk
185          ENDIF
186          CALL iom_get( inum, jpdom_autoglo, charout, smltrd_csum_ub(:,:,jk) )
187       ENDDO
188       CALL iom_get( inum, jpdom_autoglo, 'smltrd_atf_sumb' , smltrd_atf_sumb)
189
190       CALL iom_close( inum )
191    ENDIF
192
193  END SUBROUTINE trd_mld_rst_read
194 
195#else
196  !!=================================================================================
197  !!                       ***  MODULE  trdmld_rst  ***
198  !! Ocean dynamic :  Input/Output files for restart on mixed-layer diagnostics
199  !!=================================================================================
200CONTAINS
201  SUBROUTINE trd_mld_rst_write( kt )           !  No ML diags ==> empty routine
202    WRITE(*,*) 'trd_mld_rst_wri: You should not have seen this print! error?', kt
203  END SUBROUTINE trd_mld_rst_write
204  SUBROUTINE trd_mld_rst_read                  !  No ML Diags ==> empty routine
205  END SUBROUTINE trd_mld_rst_read
206#endif
207
208  !!=================================================================================
209END MODULE trdmld_rst
Note: See TracBrowser for help on using the repository browser.