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/2012/dev_r3452_UKMO9_RESTART/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/2012/dev_r3452_UKMO9_RESTART/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld_rst.F90 @ 3594

Last change on this file since 3594 was 3594, checked in by rfurner, 11 years ago

code not tested through SETTEE, builds and runs, but has not been thoroughly tested, so will not be included in 2012 merge, however submitted back to keep record of work done for 2013 developments

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