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

source: trunk/NEMO/OPA_SRC/TRD/trdmld_rst.F90 @ 526

Last change on this file since 526 was 521, checked in by opalod, 18 years ago

nemo_v1_update_73 : CT : build Mixed Layer restart files using iom

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 7.7 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 daymod          ! calendar
14   USE iom             ! I/O module
15   USE restart         ! ocean restart
16
17   IMPLICIT NONE
18   PRIVATE
19 
20   PUBLIC   trd_mld_rst_read    ! routine called by trd_mld_init
21   PUBLIC   trd_mld_rst_write   ! routine called by step.F90
22 
23   CHARACTER (len=48) ::   crestart = 'initial.nc'   ! restart file name
24   !!---------------------------------------------------------------------------------
25   !!   OPA 9.0 , LOCEAN-IPSL (2005)
26   !!---------------------------------------------------------------------------------
27 
28CONTAINS
29 
30   SUBROUTINE trd_mld_rst_write( kt )
31      !!--------------------------------------------------------------------------------
32      !!                  ***  SUBROUTINE trd_mld_rst_wri  ***
33      !!               
34      !! ** Purpose :   Write mixed-layer diagnostics restart fields.
35      !!--------------------------------------------------------------------------------
36      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
37      !
38      CHARACTER (len=35) :: charout
39      INTEGER ::   jk                 ! loop indice
40      !!--------------------------------------------------------------------------------
41   
42      IF( ( mod( kt, nstock ) == 0 ) .OR. ( kt == nitend ) ) THEN
43             
44         IF(lwp) THEN
45            WRITE(numout,*)
46            WRITE(numout,*) 'trdmld_rst: output for ML diags. restart, with trd_mld_rst_write routine'
47            WRITE(numout,*) '~~~~~~~~~~'
48            WRITE(numout,*)
49         ENDIF
50
51         IF( ln_trdmld_instant ) THEN 
52            !-- Temperature
53            CALL iom_rstput( kt, nitrst, nummldw, 'tmlbb'           , tmlbb           )
54            CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           )
55            CALL iom_rstput( kt, nitrst, nummldw, 'tmlatfb'         , tmlatfb         )
56
57            !-- Salinity
58            CALL iom_rstput( kt, nitrst, nummldw, 'smlbb'           , smlbb           )
59            CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           )
60            CALL iom_rstput( kt, nitrst, nummldw, 'smlatfb'         , smlatfb         )
61         ELSE
62            CALL iom_rstput( kt, nitrst, nummldw, 'rmldbn'          , rmldbn          )
63
64            !-- Temperature
65            CALL iom_rstput( kt, nitrst, nummldw, 'tmlbn'           , tmlbn           )
66            CALL iom_rstput( kt, nitrst, nummldw, 'tml_sumb'        , tml_sumb        )
67            DO jk = 1, jpltrd
68               IF( jk < 10 )   THEN
69                  WRITE(charout,FMT="('tmltrd_csum_ub_', I1)") jk
70               ELSE
71                  WRITE(charout,FMT="('tmltrd_csum_ub_', I2)") jk
72               ENDIF
73               CALL iom_rstput( kt, nitrst, nummldw, charout,  tmltrd_csum_ub(:,:,jk) )
74            ENDDO
75            CALL iom_rstput( kt, nitrst, nummldw, 'tmltrd_atf_sumb' , tmltrd_atf_sumb )
76
77            !-- Salinity
78            CALL iom_rstput( kt, nitrst, nummldw, 'smlbn'           , smlbn           )
79            CALL iom_rstput( kt, nitrst, nummldw, 'sml_sumb'        , sml_sumb        )
80            DO jk = 1, jpltrd
81               IF( jk < 10 )   THEN
82                  WRITE(charout,FMT="('smltrd_csum_ub_', I1)") jk
83               ELSE
84                  WRITE(charout,FMT="('smltrd_csum_ub_', I2)") jk
85               ENDIF
86               CALL iom_rstput( kt, nitrst, nummldw, charout , smltrd_csum_ub(:,:,jk) )
87            ENDDO
88            CALL iom_rstput( kt, nitrst, nummldw, 'smltrd_atf_sumb' , smltrd_atf_sumb )
89         ENDIF
90         !
91         CALL iom_close( nummldw )     ! close the restart file (only at last time step)
92         !
93      ENDIF
94      !   
95   END SUBROUTINE trd_mld_rst_write
96
97
98   SUBROUTINE trd_mld_rst_read
99    !!----------------------------------------------------------------------------
100    !!                   ***  SUBROUTINE trd_mld_rst_lec  ***
101    !!                   
102    !! ** Purpose :   Read file for mixed-layer diagnostics restart.
103    !!----------------------------------------------------------------------------
104    INTEGER  ::  inum       ! temporary logical unit
105    !
106    CHARACTER (len=35) :: charout
107    INTEGER ::   jk         ! loop indice
108    !!-----------------------------------------------------------------------------
109
110    IF(lwp)  THEN
111       WRITE(numout,*)
112       WRITE(numout,*) ' trd_mld_rst_read : read the NetCDF MLD restart file'
113       WRITE(numout,*) ' ~~~~~~~~~~~~~~~~'
114    ENDIF
115
116    inum = 10
117    CALL iom_open( 'restart_mld', inum )                       ! Open
118
119    IF( ln_trdmld_instant ) THEN 
120       !-- Temperature
121       CALL iom_get( inum, jpdom_local, 'tmlbb'           , tmlbb          )
122       CALL iom_get( inum, jpdom_local, 'tmlbn'           , tmlbn          )
123       CALL iom_get( inum, jpdom_local, 'tmlatfb'         , tmlatfb        )
124
125       !-- Salinity
126       CALL iom_get( inum, jpdom_local, 'smlbb'           , smlbb          )
127       CALL iom_get( inum, jpdom_local, 'smlbn'           , smlbn          )
128       CALL iom_get( inum, jpdom_local, 'smlatfb'         , smlatfb        )
129    ELSE
130       CALL iom_get( inum, jpdom_local, 'rmldbn'          , rmldbn         ) ! needed for rmld_sum
131
132       !-- Temperature
133       CALL iom_get( inum, jpdom_local, 'tmlbn'           , tmlbn          ) ! needed for tml_sum
134       CALL iom_get( inum, jpdom_local, 'tml_sumb'        , tml_sumb       )
135       DO jk = 1, jpltrd
136          IF( jk < 10 )   THEN
137             WRITE(charout,FMT="('tmltrd_csum_ub_', I1)") jk
138          ELSE
139             WRITE(charout,FMT="('tmltrd_csum_ub_', I2)") jk
140          ENDIF
141          CALL iom_get( inum, jpdom_local, charout, tmltrd_csum_ub(:,:,jk) )
142       ENDDO
143       CALL iom_get( inum, jpdom_local, 'tmltrd_atf_sumb' , tmltrd_atf_sumb)
144
145       !-- Salinity
146       CALL iom_get( inum, jpdom_local, 'smlbn'           , smlbn          ) ! needed for sml_sum
147       CALL iom_get( inum, jpdom_local, 'sml_sumb'        , sml_sumb       )
148       DO jk = 1, jpltrd
149          IF( jk < 10 )   THEN
150             WRITE(charout,FMT="('smltrd_csum_ub_', I1)") jk
151          ELSE
152             WRITE(charout,FMT="('smltrd_csum_ub_', I2)") jk
153          ENDIF
154          CALL iom_get( inum, jpdom_local, charout, smltrd_csum_ub(:,:,jk) )
155       ENDDO
156       CALL iom_get( inum, jpdom_local, 'smltrd_atf_sumb' , smltrd_atf_sumb)
157
158       CALL iom_close( inum )
159    ENDIF
160
161  END SUBROUTINE trd_mld_rst_read
162 
163#else
164  !!=================================================================================
165  !!                       ***  MODULE  trdmld_rst  ***
166  !! Ocean dynamic :  Input/Output files for restart on mixed-layer diagnostics
167  !!=================================================================================
168CONTAINS
169  SUBROUTINE trd_mld_rst_write( kt )           !  No ML diags ==> empty routine
170    WRITE(*,*) 'trd_mld_rst_wri: You should not have seen this print! error?', kt
171  END SUBROUTINE trd_mld_rst_write
172  SUBROUTINE trd_mld_rst_read                  !  No ML Diags ==> empty routine
173  END SUBROUTINE trd_mld_rst_read
174#endif
175
176  !!=================================================================================
177END MODULE trdmld_rst
Note: See TracBrowser for help on using the repository browser.