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

source: branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld_rst.F90 @ 3680

Last change on this file since 3680 was 3680, checked in by rblod, 11 years ago

First commit of the final branch for 2012 (future nemo_3_5), see ticket #1028

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