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.
trdmxl_rst.F90 in NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRD – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRD/trdmxl_rst.F90 @ 12143

Last change on this file since 12143 was 12143, checked in by mathiot, 4 years ago

update ENHANCE-02_ISF_nemo to 12072 (sette in progress)

  • Property svn:keywords set to Id
File size: 9.2 KB
Line 
1MODULE trdmxl_rst
2   !!=================================================================================
3   !!                       ***  MODULE  trdmxl_rst  ***
4   !! Ocean dynamic :  Input/Output files for restart on mixed-layer diagnostics
5   !!=================================================================================
6   !! History :  1.0  ! 2005-05 (C. Deltel)  Original code
7   !!---------------------------------------------------------------------------------
8
9   !!---------------------------------------------------------------------------------
10   !!  trd_mxl_rst_write : write mixed layer trend restart
11   !!  trd_mxl_rst_read  : read  mixed layer trend restart
12   !!---------------------------------------------------------------------------------
13   USE dom_oce         ! ocean space and time domain
14   USE trd_oce         ! trends: ocean variables
15   USE in_out_manager  ! I/O manager
16   USE iom             ! I/O module
17   USE restart         ! only for lrst_oce
18
19   IMPLICIT NONE
20   PRIVATE
21 
22   PUBLIC   trd_mxl_rst_read    ! routine called by trd_mxl_init
23   PUBLIC   trd_mxl_rst_write   ! routine called by step.F90
24 
25   INTEGER ::   nummxlw         ! logical unit for mxl restart
26
27   !!---------------------------------------------------------------------------------
28   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
29   !! $Id$
30   !! Software governed by the CeCILL license (see ./LICENSE)
31   !!---------------------------------------------------------------------------------
32CONTAINS
33 
34   SUBROUTINE trd_mxl_rst_write( kt )
35      !!--------------------------------------------------------------------------------
36      !!                  ***  SUBROUTINE trd_mxl_rst_wri  ***
37      !!               
38      !! ** Purpose :   Write mixed-layer diagnostics restart fields.
39      !!--------------------------------------------------------------------------------
40      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
41      !
42      CHARACTER (len=35) :: charout
43      INTEGER ::   jk                 ! loop indice
44      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character
45      CHARACTER(LEN=50)   ::   clname   ! output restart file name
46      CHARACTER(LEN=256)  ::   clpath   ! full path to restart file
47      !!--------------------------------------------------------------------------------
48
49      IF( .NOT. ln_rst_list .AND. nn_stock == -1 )   RETURN   ! we will never do any restart
50
51      ! to get better performances with NetCDF format:
52      ! we open and define the ocean restart_mxl file one time step before writing the data (-> at nitrst - 1)
53      ! except if we write ocean restart_mxl files every time step or if an ocean restart_mxl file was writen at nitend - 1
54      IF( kt == nitrst - 1 .OR. nn_stock == 1 .OR. ( kt == nitend .AND. MOD( nitend - 1, nn_stock ) == 0 ) ) THEN
55         ! beware of the format used to write kt (default is i8.8, that should be large enough...)
56         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
57         ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
58         ENDIF
59         ! create the file
60         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trdrst_out)
61         clpath = TRIM(cn_ocerst_outdir)
62         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
63         IF(lwp) THEN
64            WRITE(numout,*)
65            WRITE(numout,*) '             open ocean restart_mxl NetCDF file: '//clname
66            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt,' date= ', ndastp
67            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt,' date= ', ndastp
68            ENDIF
69         ENDIF
70
71         CALL iom_open( TRIM(clpath)//TRIM(clname), nummxlw, ldwrt = .TRUE. )
72      ENDIF
73
74      IF( kt == nitrst .AND. lwp ) THEN
75         WRITE(numout,*)
76         WRITE(numout,*) 'trdmxl_rst: output for ML diags. restart, with trd_mxl_rst_write routine kt =', kt
77         WRITE(numout,*) '~~~~~~~~~~'
78         WRITE(numout,*)
79      ENDIF
80
81      IF( ln_trdmxl_instant ) THEN 
82         !-- Temperature
83         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbb'           , tmlbb           )
84         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbn'           , tmlbn           )
85         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlatfb'         , tmlatfb         )
86
87         !-- Salinity
88         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbb'           , smlbb           )
89         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbn'           , smlbn           )
90         CALL iom_rstput( kt, nitrst, nummxlw, 'smlatfb'         , smlatfb         )
91      ELSE
92         CALL iom_rstput( kt, nitrst, nummxlw, 'hmxlbn'          , hmxlbn          )
93
94         !-- Temperature
95         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbn'           , tmlbn           )
96         CALL iom_rstput( kt, nitrst, nummxlw, 'tml_sumb'        , tml_sumb        )
97         DO jk = 1, jpltrd
98            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)")   jk
99            ELSE                 ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I2)")   jk
100            ENDIF
101            CALL iom_rstput( kt, nitrst, nummxlw, charout,  tmltrd_csum_ub(:,:,jk) )
102         ENDDO
103         CALL iom_rstput( kt, nitrst, nummxlw, 'tmltrd_atf_sumb' , tmltrd_atf_sumb )
104
105         !-- Salinity
106         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbn'           , smlbn           )
107         CALL iom_rstput( kt, nitrst, nummxlw, 'sml_sumb'        , sml_sumb        )
108         DO jk = 1, jpltrd
109            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('smltrd_csum_ub_', I1)")   jk
110            ELSE                 ;   WRITE(charout,FMT="('smltrd_csum_ub_', I2)")   jk
111            ENDIF
112            CALL iom_rstput( kt, nitrst, nummxlw, charout , smltrd_csum_ub(:,:,jk) )
113         ENDDO
114         CALL iom_rstput( kt, nitrst, nummxlw, 'smltrd_atf_sumb' , smltrd_atf_sumb )
115      ENDIF
116      !
117      IF( kt == nitrst ) THEN
118         CALL iom_close( nummxlw )     ! close the restart file (only at last time step)
119         lrst_oce = .FALSE.
120      ENDIF
121      !
122   END SUBROUTINE trd_mxl_rst_write
123
124
125   SUBROUTINE trd_mxl_rst_read
126      !!----------------------------------------------------------------------------
127      !!                   ***  SUBROUTINE trd_mxl_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      LOGICAL ::   llok
136      CHARACTER(LEN=256)  ::   clpath   ! full path to restart file
137      !!-----------------------------------------------------------------------------
138
139      IF(lwp)  THEN
140         WRITE(numout,*)
141         WRITE(numout,*) ' trd_mxl_rst_read : read the NetCDF mixed layer trend restart file'
142         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~'
143      ENDIF
144
145      clpath = TRIM(cn_ocerst_indir)
146      IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
147      CALL iom_open( TRIM(clpath)//TRIM(cn_trdrst_in), inum ) 
148
149      IF( ln_trdmxl_instant ) THEN 
150         !-- Temperature
151         CALL iom_get( inum, jpdom_autoglo, 'tmlbb'           , tmlbb          )
152         CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn          )
153         CALL iom_get( inum, jpdom_autoglo, 'tmlatfb'         , tmlatfb        )
154         !
155         !-- Salinity
156         CALL iom_get( inum, jpdom_autoglo, 'smlbb'           , smlbb          )
157         CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          )
158         CALL iom_get( inum, jpdom_autoglo, 'smlatfb'         , smlatfb        )
159      ELSE
160         CALL iom_get( inum, jpdom_autoglo, 'hmxlbn'          , hmxlbn         ) ! needed for hmxl_sum
161         !
162         !-- Temperature
163         CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn          ) ! needed for tml_sum
164         CALL iom_get( inum, jpdom_autoglo, 'tml_sumb'        , tml_sumb       )
165         DO jk = 1, jpltrd
166            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)")   jk
167            ELSE                 ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I2)")   jk
168            ENDIF
169            CALL iom_get( inum, jpdom_autoglo, charout, tmltrd_csum_ub(:,:,jk) )
170         END DO
171         CALL iom_get( inum, jpdom_autoglo, 'tmltrd_atf_sumb' , tmltrd_atf_sumb)
172         !
173         !-- Salinity
174         CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          ) ! needed for sml_sum
175         CALL iom_get( inum, jpdom_autoglo, 'sml_sumb'        , sml_sumb       )
176         DO jk = 1, jpltrd
177            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('smltrd_csum_ub_', I1)")   jk
178            ELSE                 ;   WRITE(charout,FMT="('smltrd_csum_ub_', I2)")   jk
179            ENDIF
180            CALL iom_get( inum, jpdom_autoglo, charout, smltrd_csum_ub(:,:,jk) )
181         END DO
182         CALL iom_get( inum, jpdom_autoglo, 'smltrd_atf_sumb' , smltrd_atf_sumb)
183         !
184         CALL iom_close( inum )
185      ENDIF
186      !
187   END SUBROUTINE trd_mxl_rst_read
188 
189  !!=================================================================================
190END MODULE trdmxl_rst
Note: See TracBrowser for help on using the repository browser.