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 branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld_rst.F90 @ 4409

Last change on this file since 4409 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

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