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

source: branches/UKMO/dev_r5107_iceshelf_fw_input_coupled_model/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl_rst.F90 @ 5511

Last change on this file since 5511 was 5511, checked in by davestorkey, 9 years ago

UKMO/dev_r5107_iceshelf_fw_input_coupled_model branch: clear SVN keywords

File size: 9.4 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/OPA 3.3 , NEMO Consortium (2010)
29   !! $Id$
30   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
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   ! ice output restart file name
46      !!--------------------------------------------------------------------------------
47
48      ! to get better performances with NetCDF format:
49      ! we open and define the ocean restart_mxl file one time step before writing the data (-> at nitrst - 1)
50      ! except if we write ocean restart_mxl files every time step or if an ocean restart_mxl file was writen at nitend - 1
51      IF( kt == nitrst - 1 .OR. nstock == 1 .OR. ( kt == nitend .AND. MOD( nitend - 1, nstock ) == 0 ) ) THEN
52         ! beware of the format used to write kt (default is i8.8, that should be large enough...)
53         IF( nitrst > 999999999 ) THEN   ;   WRITE(clkt, *       ) nitrst
54         ELSE                            ;   WRITE(clkt, '(i8.8)') nitrst
55         ENDIF
56         ! create the file
57         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trdrst_out)
58         IF(lwp) THEN
59            WRITE(numout,*)
60            SELECT CASE ( jprstlib )
61            CASE ( jprstdimg )   ;   WRITE(numout,*) '             open ocean restart_mxl binary file: '//clname
62            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart_mxl NetCDF file: '//clname
63            END SELECT
64            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt,' date= ', ndastp
65            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt,' date= ', ndastp
66            ENDIF
67         ENDIF
68
69         CALL iom_open( clname, nummxlw, ldwrt = .TRUE., kiolib = jprstlib )
70      ENDIF
71
72      IF( kt == nitrst .AND. lwp ) THEN
73         WRITE(numout,*)
74         WRITE(numout,*) 'trdmxl_rst: output for ML diags. restart, with trd_mxl_rst_write routine kt =', kt
75         WRITE(numout,*) '~~~~~~~~~~'
76         WRITE(numout,*)
77      ENDIF
78
79      IF( ln_trdmxl_instant ) THEN 
80         !-- Temperature
81         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbb'           , tmlbb           )
82         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbn'           , tmlbn           )
83         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlatfb'         , tmlatfb         )
84
85         !-- Salinity
86         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbb'           , smlbb           )
87         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbn'           , smlbn           )
88         CALL iom_rstput( kt, nitrst, nummxlw, 'smlatfb'         , smlatfb         )
89      ELSE
90         CALL iom_rstput( kt, nitrst, nummxlw, 'hmxlbn'          , hmxlbn          )
91
92         !-- Temperature
93         CALL iom_rstput( kt, nitrst, nummxlw, 'tmlbn'           , tmlbn           )
94         CALL iom_rstput( kt, nitrst, nummxlw, 'tml_sumb'        , tml_sumb        )
95         DO jk = 1, jpltrd
96            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)")   jk
97            ELSE                 ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I2)")   jk
98            ENDIF
99            CALL iom_rstput( kt, nitrst, nummxlw, charout,  tmltrd_csum_ub(:,:,jk) )
100         ENDDO
101         CALL iom_rstput( kt, nitrst, nummxlw, 'tmltrd_atf_sumb' , tmltrd_atf_sumb )
102
103         !-- Salinity
104         CALL iom_rstput( kt, nitrst, nummxlw, 'smlbn'           , smlbn           )
105         CALL iom_rstput( kt, nitrst, nummxlw, 'sml_sumb'        , sml_sumb        )
106         DO jk = 1, jpltrd
107            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('smltrd_csum_ub_', I1)")   jk
108            ELSE                 ;   WRITE(charout,FMT="('smltrd_csum_ub_', I2)")   jk
109            ENDIF
110            CALL iom_rstput( kt, nitrst, nummxlw, charout , smltrd_csum_ub(:,:,jk) )
111         ENDDO
112         CALL iom_rstput( kt, nitrst, nummxlw, 'smltrd_atf_sumb' , smltrd_atf_sumb )
113      ENDIF
114      !
115      IF( kt == nitrst ) THEN
116         CALL iom_close( nummxlw )     ! close the restart file (only at last time step)
117         lrst_oce = .FALSE.
118      ENDIF
119      !
120   END SUBROUTINE trd_mxl_rst_write
121
122
123   SUBROUTINE trd_mxl_rst_read
124      !!----------------------------------------------------------------------------
125      !!                   ***  SUBROUTINE trd_mxl_rst_lec  ***
126      !!                   
127      !! ** Purpose :   Read file for mixed-layer diagnostics restart.
128      !!----------------------------------------------------------------------------
129      INTEGER  ::  inum       ! temporary logical unit
130      !
131      CHARACTER (len=35) :: charout
132      INTEGER ::   jk         ! loop indice
133      INTEGER ::   jlibalt = jprstlib
134      LOGICAL ::   llok
135      !!-----------------------------------------------------------------------------
136
137      IF(lwp)  THEN
138         WRITE(numout,*)
139         WRITE(numout,*) ' trd_mxl_rst_read : read the NetCDF mixed layer trend restart file'
140         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~'
141      ENDIF
142      IF ( jprstlib == jprstdimg ) THEN
143         ! eventually read netcdf file (monobloc)  for restarting on different number of processors
144         ! if {cn_trdrst_in}.nc exists, then set jlibalt to jpnf90
145         INQUIRE( FILE = TRIM(cn_trdrst_in)//'.nc', EXIST = llok )
146         IF ( llok ) THEN   ;   jlibalt = jpnf90   
147         ELSE               ;   jlibalt = jprstlib   
148         ENDIF
149      ENDIF
150
151      CALL iom_open( cn_trdrst_in, inum, kiolib = jlibalt ) 
152
153      IF( ln_trdmxl_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, 'hmxlbn'          , hmxlbn         ) ! needed for hmxl_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   ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)")   jk
171            ELSE                 ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I2)")   jk
172            ENDIF
173            CALL iom_get( inum, jpdom_autoglo, charout, tmltrd_csum_ub(:,:,jk) )
174         END DO
175         CALL iom_get( inum, jpdom_autoglo, 'tmltrd_atf_sumb' , tmltrd_atf_sumb)
176         !
177         !-- Salinity
178         CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          ) ! needed for sml_sum
179         CALL iom_get( inum, jpdom_autoglo, 'sml_sumb'        , sml_sumb       )
180         DO jk = 1, jpltrd
181            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('smltrd_csum_ub_', I1)")   jk
182            ELSE                 ;   WRITE(charout,FMT="('smltrd_csum_ub_', I2)")   jk
183            ENDIF
184            CALL iom_get( inum, jpdom_autoglo, charout, smltrd_csum_ub(:,:,jk) )
185         END DO
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_mxl_rst_read
192 
193  !!=================================================================================
194END MODULE trdmxl_rst
Note: See TracBrowser for help on using the repository browser.