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 branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/UKMO/dev_r5518_GO6_package_text_diagnostics/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl_rst.F90 @ 10774

Last change on this file since 10774 was 10774, checked in by andmirek, 5 years ago

GMED 450 add flush after prints

File size: 10.1 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   USE timing
19
20   IMPLICIT NONE
21   PRIVATE
22 
23   PUBLIC   trd_mxl_rst_read    ! routine called by trd_mxl_init
24   PUBLIC   trd_mxl_rst_write   ! routine called by step.F90
25 
26   INTEGER ::   nummxlw         ! logical unit for mxl restart
27
28   !!---------------------------------------------------------------------------------
29   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
30   !! $Id$
31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
32   !!---------------------------------------------------------------------------------
33CONTAINS
34 
35   SUBROUTINE trd_mxl_rst_write( kt )
36      !!--------------------------------------------------------------------------------
37      !!                  ***  SUBROUTINE trd_mxl_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   ! output restart file name
47      CHARACTER(LEN=256)  ::   clpath   ! full path to restart file
48      !!--------------------------------------------------------------------------------
49
50      ! to get better performances with NetCDF format:
51      ! we open and define the ocean restart_mxl file one time step before writing the data (-> at nitrst - 1)
52      ! except if we write ocean restart_mxl files every time step or if an ocean restart_mxl file was writen at nitend - 1
53      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. MOD( nitend - 1, nstock ) == 0 ) ) THEN
54         ! beware of the format used to write kt (default is i8.8, that should be large enough...)
55         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
56         ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
57         ENDIF
58         ! create the file
59         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trdrst_out)
60         clpath = TRIM(cn_ocerst_outdir)
61         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
62         IF(lwp) THEN
63            WRITE(numout,*)
64            SELECT CASE ( jprstlib )
65            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart_mxl binary file: '//clname
66            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart_mxl NetCDF file: '//clname
67            END SELECT
68            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt,' date= ', ndastp
69            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt,' date= ', ndastp
70            ENDIF
71            IF(lflush) CALL flush(numout)
72         ENDIF
73
74         CALL iom_open( TRIM(clpath)//TRIM(clname), nummxlw, ldwrt = .TRUE., kiolib = jprstlib )
75      ENDIF
76
77      IF( kt == nitrst .AND. lwp ) THEN
78         WRITE(numout,*)
79         WRITE(numout,*) 'trdmxl_rst: output for ML diags. restart, with trd_mxl_rst_write routine kt =', kt
80         WRITE(numout,*) '~~~~~~~~~~'
81         WRITE(numout,*)
82         IF(lflush) CALL flush(numout)
83      ENDIF
84      IF(nn_timing == 2)  CALL timing_start('iom_rstput')
85      IF( ln_trdmxl_instant ) THEN 
86         !-- Temperature
87         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbb'           , tmlbb           )
88         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbn'           , tmlbn           )
89         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlatfb'         , tmlatfb         )
90
91         !-- Salinity
92         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbb'           , smlbb           )
93         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbn'           , smlbn           )
94         CALL iom_rstput( kt, nitrst, nummxlw, 'smlatfb'         , smlatfb         )
95      ELSE
96         CALL iom_rstput( kt, nitrst, nummxlw, 'hmxlbn'          , hmxlbn          )
97
98         !-- Temperature
99         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbn'           , tmlbn           )
100         CALL iom_rstput( kt, nitrst, nummxlw, 'tml_sumb'        , tml_sumb        )
101         DO jk = 1, jpltrd
102            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)")   jk
103            ELSE                 ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I2)")   jk
104            ENDIF
105            CALL iom_rstput( kt, nitrst, nummxlw, charout,  tmltrd_csum_ub(:,:,jk) )
106         ENDDO
107         CALL iom_rstput( kt, nitrst, nummxlw, 'tmltrd_atf_sumb' , tmltrd_atf_sumb )
108
109         !-- Salinity
110         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbn'           , smlbn           )
111         CALL iom_rstput( kt, nitrst, nummxlw, 'sml_sumb'        , sml_sumb        )
112         DO jk = 1, jpltrd
113            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('smltrd_csum_ub_', I1)")   jk
114            ELSE                 ;   WRITE(charout,FMT="('smltrd_csum_ub_', I2)")   jk
115            ENDIF
116            CALL iom_rstput( kt, nitrst, nummxlw, charout , smltrd_csum_ub(:,:,jk) )
117         ENDDO
118         CALL iom_rstput( kt, nitrst, nummxlw, 'smltrd_atf_sumb' , smltrd_atf_sumb )
119      ENDIF
120      IF(nn_timing == 2)  CALL timing_stop('iom_rstput')
121      !
122      IF( kt == nitrst ) THEN
123         CALL iom_close( nummxlw )     ! close the restart file (only at last time step)
124         lrst_oce = .FALSE.
125      ENDIF
126      !
127   END SUBROUTINE trd_mxl_rst_write
128
129
130   SUBROUTINE trd_mxl_rst_read
131      !!----------------------------------------------------------------------------
132      !!                   ***  SUBROUTINE trd_mxl_rst_lec  ***
133      !!                   
134      !! ** Purpose :   Read file for mixed-layer diagnostics restart.
135      !!----------------------------------------------------------------------------
136      INTEGER  ::  inum       ! temporary logical unit
137      !
138      CHARACTER (len=35) :: charout
139      INTEGER ::   jk         ! loop indice
140      INTEGER ::   jlibalt = jprstlib
141      LOGICAL ::   llok
142      CHARACTER(LEN=256)  ::   clpath   ! full path to restart file
143      !!-----------------------------------------------------------------------------
144
145      IF(lwp)  THEN
146         WRITE(numout,*)
147         WRITE(numout,*) ' trd_mxl_rst_read : read the NetCDF mixed layer trend restart file'
148         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~'
149         IF(lflush) CALL flush(numout)
150      ENDIF
151
152      clpath = TRIM(cn_ocerst_indir)
153      IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
154
155      IF ( jprstlib == jprstdimg ) THEN
156         ! eventually read netcdf file (monobloc)  for restarting on different number of processors
157         ! if {cn_trdrst_in}.nc exists, then set jlibalt to jpnf90
158         INQUIRE( FILE = TRIM(clpath)//TRIM(cn_trdrst_in)//'.nc', EXIST = llok )
159         IF ( llok ) THEN   ;   jlibalt = jpnf90   
160         ELSE               ;   jlibalt = jprstlib   
161         ENDIF
162      ENDIF
163
164      CALL iom_open( TRIM(clpath)//TRIM(cn_trdrst_in), inum, kiolib = jlibalt ) 
165      IF(nn_timing == 2)  CALL timing_start('iom_rstget')
166      IF( ln_trdmxl_instant ) THEN 
167         !-- Temperature
168         CALL iom_get( inum, jpdom_autoglo, 'tmlbb'           , tmlbb          )
169         CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn          )
170         CALL iom_get( inum, jpdom_autoglo, 'tmlatfb'         , tmlatfb        )
171         !
172         !-- Salinity
173         CALL iom_get( inum, jpdom_autoglo, 'smlbb'           , smlbb          )
174         CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          )
175         CALL iom_get( inum, jpdom_autoglo, 'smlatfb'         , smlatfb        )
176      ELSE
177         CALL iom_get( inum, jpdom_autoglo, 'hmxlbn'          , hmxlbn         ) ! needed for hmxl_sum
178         !
179         !-- Temperature
180         CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn          ) ! needed for tml_sum
181         CALL iom_get( inum, jpdom_autoglo, 'tml_sumb'        , tml_sumb       )
182         DO jk = 1, jpltrd
183            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)")   jk
184            ELSE                 ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I2)")   jk
185            ENDIF
186            CALL iom_get( inum, jpdom_autoglo, charout, tmltrd_csum_ub(:,:,jk) )
187         END DO
188         CALL iom_get( inum, jpdom_autoglo, 'tmltrd_atf_sumb' , tmltrd_atf_sumb)
189         !
190         !-- Salinity
191         CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          ) ! needed for sml_sum
192         CALL iom_get( inum, jpdom_autoglo, 'sml_sumb'        , sml_sumb       )
193         DO jk = 1, jpltrd
194            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('smltrd_csum_ub_', I1)")   jk
195            ELSE                 ;   WRITE(charout,FMT="('smltrd_csum_ub_', I2)")   jk
196            ENDIF
197            CALL iom_get( inum, jpdom_autoglo, charout, smltrd_csum_ub(:,:,jk) )
198         END DO
199         CALL iom_get( inum, jpdom_autoglo, 'smltrd_atf_sumb' , smltrd_atf_sumb)
200         !
201      ENDIF
202      IF(nn_timing == 2)  CALL timing_stop('iom_rstget')
203      CALL iom_close( inum )
204      !
205   END SUBROUTINE trd_mxl_rst_read
206 
207  !!=================================================================================
208END MODULE trdmxl_rst
Note: See TracBrowser for help on using the repository browser.