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.
sbcmod.F90 in trunk/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90 @ 4769

Last change on this file since 4769 was 4624, checked in by acc, 10 years ago

#1305. Fix slow start-up problems on some systems by introducing and using lwm logical to restrict output of merged namelists to the first (or only) processor. lwm is true only on the first processor regardless of ln_ctl. Small changes to all flavours of nemogcm.F90 are also required to write namctl and namcfg after the call to mynode which now opens output.namelist.dyn and writes nammpp.

  • Property svn:keywords set to Id
File size: 26.7 KB
Line 
1MODULE sbcmod
2   !!======================================================================
3   !!                       ***  MODULE  sbcmod  ***
4   !! Surface module :  provide to the ocean its surface boundary condition
5   !!======================================================================
6   !! History :  3.0  ! 2006-07  (G. Madec)  Original code
7   !!            3.1  ! 2008-08  (S. Masson, A. Caubel, E. Maisonnave, G. Madec) coupled interface
8   !!            3.3  ! 2010-04  (M. Leclair, G. Madec)  Forcing averaged over 2 time steps
9   !!            3.3  ! 2010-10  (S. Masson)  add diurnal cycle
10   !!            3.3  ! 2010-09  (D. Storkey) add ice boundary conditions (BDY)
11   !!             -   ! 2010-11  (G. Madec) ice-ocean stress always computed at each ocean time-step
12   !!             -   ! 2010-10  (J. Chanut, C. Bricaud, G. Madec)  add the surface pressure forcing
13   !!            3.4  ! 2011-11  (C. Harris) CICE added as an option
14   !!            3.5  ! 2012-11  (A. Coward, G. Madec) Rethink of heat, mass and salt surface fluxes
15   !!----------------------------------------------------------------------
16
17   !!----------------------------------------------------------------------
18   !!   sbc_init       : read namsbc namelist
19   !!   sbc            : surface ocean momentum, heat and freshwater boundary conditions
20   !!----------------------------------------------------------------------
21   USE oce              ! ocean dynamics and tracers
22   USE dom_oce          ! ocean space and time domain
23   USE phycst           ! physical constants
24   USE sbc_oce          ! Surface boundary condition: ocean fields
25   USE sbc_ice          ! Surface boundary condition: ice fields
26   USE sbcdcy           ! surface boundary condition: diurnal cycle
27   USE sbcssm           ! surface boundary condition: sea-surface mean variables
28   USE sbcapr           ! surface boundary condition: atmospheric pressure
29   USE sbcana           ! surface boundary condition: analytical formulation
30   USE sbcflx           ! surface boundary condition: flux formulation
31   USE sbcblk_clio      ! surface boundary condition: bulk formulation : CLIO
32   USE sbcblk_core      ! surface boundary condition: bulk formulation : CORE
33   USE sbcblk_mfs       ! surface boundary condition: bulk formulation : MFS
34   USE sbcice_if        ! surface boundary condition: ice-if sea-ice model
35   USE sbcice_lim       ! surface boundary condition: LIM 3.0 sea-ice model
36   USE sbcice_lim_2     ! surface boundary condition: LIM 2.0 sea-ice model
37   USE sbcice_cice      ! surface boundary condition: CICE    sea-ice model
38   USE sbccpl           ! surface boundary condition: coupled florulation
39   USE cpl_oasis3, ONLY:lk_cpl      ! are we in coupled mode?
40   USE sbcssr           ! surface boundary condition: sea surface restoring
41   USE sbcrnf           ! surface boundary condition: runoffs
42   USE sbcfwb           ! surface boundary condition: freshwater budget
43   USE closea           ! closed sea
44   USE icbstp           ! Icebergs!
45
46   USE prtctl           ! Print control                    (prt_ctl routine)
47   USE iom              ! IOM library
48   USE in_out_manager   ! I/O manager
49   USE lib_mpp          ! MPP library
50   USE timing           ! Timing
51   USE sbcwave          ! Wave module
52
53   IMPLICIT NONE
54   PRIVATE
55
56   PUBLIC   sbc        ! routine called by step.F90
57   PUBLIC   sbc_init   ! routine called by opa.F90
58   
59   INTEGER ::   nsbc   ! type of surface boundary condition (deduced from namsbc informations)
60     
61   !! * Substitutions
62#  include "domzgr_substitute.h90"
63   !!----------------------------------------------------------------------
64   !! NEMO/OPA 4.0 , NEMO-consortium (2011)
65   !! $Id$
66   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
67   !!----------------------------------------------------------------------
68CONTAINS
69
70   SUBROUTINE sbc_init
71      !!---------------------------------------------------------------------
72      !!                    ***  ROUTINE sbc_init ***
73      !!
74      !! ** Purpose :   Initialisation of the ocean surface boundary computation
75      !!
76      !! ** Method  :   Read the namsbc namelist and set derived parameters
77      !!                Call init routines for all other SBC modules that have one
78      !!
79      !! ** Action  : - read namsbc parameters
80      !!              - nsbc: type of sbc
81      !!----------------------------------------------------------------------
82      INTEGER ::   icpt   ! local integer
83      !!
84      NAMELIST/namsbc/ nn_fsbc   , ln_ana    , ln_flx,  ln_blk_clio, ln_blk_core, ln_cpl,   &
85         &             ln_blk_mfs, ln_apr_dyn, nn_ice,  nn_ice_embd, ln_dm2dc   , ln_rnf,   &
86         &             ln_ssr    , nn_fwb    , ln_cdgw , ln_wave , ln_sdw, nn_lsm, cn_iceflx
87      INTEGER  ::   ios
88      !!----------------------------------------------------------------------
89
90      IF(lwp) THEN
91         WRITE(numout,*)
92         WRITE(numout,*) 'sbc_init : surface boundary condition setting'
93         WRITE(numout,*) '~~~~~~~~ '
94      ENDIF
95
96      REWIND( numnam_ref )              ! Namelist namsbc in reference namelist : Surface boundary
97      READ  ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901)
98901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in reference namelist', lwp )
99
100      REWIND( numnam_cfg )              ! Namelist namsbc in configuration namelist : Parameters of the run
101      READ  ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 )
102902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in configuration namelist', lwp )
103      IF(lwm) WRITE ( numond, namsbc )
104
105      !                          ! overwrite namelist parameter using CPP key information
106      IF( Agrif_Root() ) THEN                ! AGRIF zoom
107        IF( lk_lim2 )   nn_ice      = 2
108        IF( lk_lim3 )   nn_ice      = 3
109        IF( lk_cice )   nn_ice      = 4
110      ENDIF
111      IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration
112          ln_ana      = .TRUE.   
113          nn_ice      =   0
114      ENDIF
115     
116      IF(lwp) THEN               ! Control print
117         WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)'
118         WRITE(numout,*) '           frequency update of sbc (and ice)             nn_fsbc     = ', nn_fsbc
119         WRITE(numout,*) '           Type of sbc : '
120         WRITE(numout,*) '              analytical formulation                     ln_ana      = ', ln_ana
121         WRITE(numout,*) '              flux       formulation                     ln_flx      = ', ln_flx
122         WRITE(numout,*) '              CLIO bulk  formulation                     ln_blk_clio = ', ln_blk_clio
123         WRITE(numout,*) '              CORE bulk  formulation                     ln_blk_core = ', ln_blk_core
124         WRITE(numout,*) '              MFS  bulk  formulation                     ln_blk_mfs  = ', ln_blk_mfs
125         WRITE(numout,*) '              coupled    formulation (T if key_sbc_cpl)  ln_cpl      = ', ln_cpl
126         WRITE(numout,*) '              Flux handling over ice categories          cn_iceflx   = ', TRIM (cn_iceflx)
127         WRITE(numout,*) '           Misc. options of sbc : '
128         WRITE(numout,*) '              Patm gradient added in ocean & ice Eqs.    ln_apr_dyn  = ', ln_apr_dyn
129         WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice      = ', nn_ice 
130         WRITE(numout,*) '              ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd = ', nn_ice_embd
131         WRITE(numout,*) '              daily mean to diurnal cycle qsr            ln_dm2dc    = ', ln_dm2dc 
132         WRITE(numout,*) '              runoff / runoff mouths                     ln_rnf      = ', ln_rnf
133         WRITE(numout,*) '              Sea Surface Restoring on SST and/or SSS    ln_ssr      = ', ln_ssr
134         WRITE(numout,*) '              FreshWater Budget control  (=0/1/2)        nn_fwb      = ', nn_fwb
135         WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea   = ', nn_closea
136         WRITE(numout,*) '              n. of iterations if land-sea-mask applied  nn_lsm      = ', nn_lsm
137      ENDIF
138
139      !   Flux handling over ice categories
140#if defined key_coupled 
141      SELECT CASE ( TRIM (cn_iceflx))
142      CASE ('ave')
143         ln_iceflx_ave    = .TRUE.
144         ln_iceflx_linear = .FALSE.
145      CASE ('linear')
146         ln_iceflx_ave    = .FALSE.
147         ln_iceflx_linear = .TRUE.
148      CASE default
149         ln_iceflx_ave    = .FALSE.
150         ln_iceflx_linear = .FALSE.
151      END SELECT
152      IF(lwp) WRITE(numout,*) '              Fluxes averaged over all ice categories         ln_iceflx_ave    = ', ln_iceflx_ave
153      IF(lwp) WRITE(numout,*) '              Fluxes distributed linearly over ice categories ln_iceflx_linear = ', ln_iceflx_linear
154#endif
155      !
156#if defined key_top && ! defined key_offline
157      ltrcdm2dc = (ln_dm2dc .AND. ln_blk_core .AND. nn_ice==2)
158      IF( ltrcdm2dc )THEN
159         IF(lwp)THEN
160            WRITE(numout,*)"analytical diurnal cycle, core bulk formulation and LIM2 use: "
161            WRITE(numout,*)"Diurnal cycle on physics but not in passive tracers"
162         ENDIF
163      ENDIF
164#else
165      ltrcdm2dc =  .FALSE.
166#endif
167
168      !
169      !                              ! allocate sbc arrays
170      IF( sbc_oce_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_oce arrays' )
171
172      !                          ! Checks:
173      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths
174         ln_rnf_mouth  = .false.                     
175         IF( sbc_rnf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_rnf arrays' )
176         nkrnf         = 0
177         rnf     (:,:) = 0.0_wp
178         rnf_b   (:,:) = 0.0_wp
179         rnfmsk  (:,:) = 0.0_wp
180         rnfmsk_z(:)   = 0.0_wp
181      ENDIF
182      IF( nn_ice == 0  )   fr_i(:,:) = 0.e0        ! no ice in the domain, ice fraction is always zero
183
184      sfx(:,:) = 0.0_wp                            ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero)
185                                                   ! only if sea-ice is present
186 
187      fmmflx(:,:) = 0.0_wp                        ! freezing-melting array initialisation
188
189      !                                            ! restartability   
190      IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   &
191          MOD( nstock             , nn_fsbc) /= 0 ) THEN
192         WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   &
193            &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')'
194         CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' )
195      ENDIF
196      !
197      IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 )   &
198         &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' )
199      !
200      IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   &
201         &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' )
202      IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. lk_cpl ) )   &
203         &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or lk_cpl' )
204      IF( nn_ice == 4 .AND. lk_agrif )   &
205         &   CALL ctl_stop( 'CICE sea-ice model not currently available with AGRIF' )
206      IF( ( nn_ice == 3 .OR. nn_ice == 4 ) .AND. nn_ice_embd == 0 )   &
207         &   CALL ctl_stop( 'LIM3 and CICE sea-ice models require nn_ice_embd = 1 or 2' )
208#if defined key_coupled
209      IF( ln_iceflx_ave .AND. ln_iceflx_linear ) &
210         &   CALL ctl_stop( ' ln_iceflx_ave and ln_iceflx_linear options are not compatible' )
211      IF( ( nn_ice ==3 .AND. lk_cpl) .AND. .NOT. ( ln_iceflx_ave .OR. ln_iceflx_linear ) ) &
212         &   CALL ctl_stop( ' With lim3 coupled, either ln_iceflx_ave or ln_iceflx_linear must be set to .TRUE.' )
213#endif     
214      IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag
215
216      IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) )   &
217         &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' )
218     
219      IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) )  < 8 ) )   &
220         &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' )
221
222      IF ( ln_wave ) THEN
223      !Activated wave module but neither drag nor stokes drift activated
224         IF ( .NOT.(ln_cdgw .OR. ln_sdw) )   THEN
225            CALL ctl_warn( 'Ask for wave coupling but nor drag coefficient (ln_cdgw=F) neither stokes drift activated (ln_sdw=F)' )
226      !drag coefficient read from wave model definable only with mfs bulk formulae and core
227         ELSEIF (ln_cdgw .AND. .NOT.(ln_blk_mfs .OR. ln_blk_core) )       THEN       
228             CALL ctl_stop( 'drag coefficient read from wave model definable only with mfs bulk formulae and core')
229         ENDIF
230      ELSE
231      IF ( ln_cdgw .OR. ln_sdw  )                                         & 
232         &   CALL ctl_stop('Not Activated Wave Module (ln_wave=F) but     &
233         & asked coupling with drag coefficient (ln_cdgw =T) or Stokes drift (ln_sdw=T) ')
234      ENDIF 
235     
236      !                          ! Choice of the Surface Boudary Condition (set nsbc)
237      icpt = 0
238      IF( ln_ana          ) THEN   ;   nsbc =  1   ; icpt = icpt + 1   ;   ENDIF       ! analytical      formulation
239      IF( ln_flx          ) THEN   ;   nsbc =  2   ; icpt = icpt + 1   ;   ENDIF       ! flux            formulation
240      IF( ln_blk_clio     ) THEN   ;   nsbc =  3   ; icpt = icpt + 1   ;   ENDIF       ! CLIO bulk       formulation
241      IF( ln_blk_core     ) THEN   ;   nsbc =  4   ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk       formulation
242      IF( ln_blk_mfs      ) THEN   ;   nsbc =  6   ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk       formulation
243      IF( ln_cpl          ) THEN   ;   nsbc =  5   ; icpt = icpt + 1   ;   ENDIF       ! Coupled         formulation
244      IF( cp_cfg == 'gyre') THEN   ;   nsbc =  0                       ;   ENDIF       ! GYRE analytical formulation
245      IF( lk_esopa        )            nsbc = -1                                       ! esopa test, ALL formulations
246      !
247      IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN
248         WRITE(numout,*)
249         WRITE(numout,*) '           E R R O R in setting the sbc, one and only one namelist/CPP key option '
250         WRITE(numout,*) '                     must be choosen. You choose ', icpt, ' option(s)'
251         WRITE(numout,*) '                     We stop'
252         nstop = nstop + 1
253      ENDIF
254      IF(lwp) THEN
255         WRITE(numout,*)
256         IF( nsbc == -1 )   WRITE(numout,*) '              ESOPA test All surface boundary conditions'
257         IF( nsbc ==  0 )   WRITE(numout,*) '              GYRE analytical formulation'
258         IF( nsbc ==  1 )   WRITE(numout,*) '              analytical formulation'
259         IF( nsbc ==  2 )   WRITE(numout,*) '              flux formulation'
260         IF( nsbc ==  3 )   WRITE(numout,*) '              CLIO bulk formulation'
261         IF( nsbc ==  4 )   WRITE(numout,*) '              CORE bulk formulation'
262         IF( nsbc ==  5 )   WRITE(numout,*) '              coupled formulation'
263         IF( nsbc ==  6 )   WRITE(numout,*) '              MFS Bulk formulation'
264      ENDIF
265      !
266                          CALL sbc_ssm_init               ! Sea-surface mean fields initialisation
267      !
268      IF( ln_ssr      )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation
269      !
270      IF( nn_ice == 4 )   CALL cice_sbc_init( nsbc )      ! CICE initialisation
271      !
272   END SUBROUTINE sbc_init
273
274
275   SUBROUTINE sbc( kt )
276      !!---------------------------------------------------------------------
277      !!                    ***  ROUTINE sbc  ***
278      !!             
279      !! ** Purpose :   provide at each time-step the ocean surface boundary
280      !!                condition (momentum, heat and freshwater fluxes)
281      !!
282      !! ** Method  :   blah blah  to be written ?????????
283      !!                CAUTION : never mask the surface stress field (tke sbc)
284      !!
285      !! ** Action  : - set the ocean surface boundary condition at before and now
286      !!                time step, i.e. 
287      !!                utau_b, vtau_b, qns_b, qsr_b, emp_n, sfx_b, qrp_b, erp_b
288      !!                utau  , vtau  , qns  , qsr  , emp  , sfx  , qrp  , erp
289      !!              - updte the ice fraction : fr_i
290      !!----------------------------------------------------------------------
291      INTEGER, INTENT(in) ::   kt       ! ocean time step
292      !!---------------------------------------------------------------------
293      !
294      IF( nn_timing == 1 )  CALL timing_start('sbc')
295      !
296      !                                            ! ---------------------------------------- !
297      IF( kt /= nit000 ) THEN                      !          Swap of forcing fields          !
298         !                                         ! ---------------------------------------- !
299         utau_b(:,:) = utau(:,:)                         ! Swap the ocean forcing fields
300         vtau_b(:,:) = vtau(:,:)                         ! (except at nit000 where before fields
301         qns_b (:,:) = qns (:,:)                         !  are set at the end of the routine)
302         ! The 3D heat content due to qsr forcing is treated in traqsr
303         ! qsr_b (:,:) = qsr (:,:)
304         emp_b(:,:) = emp(:,:)
305         sfx_b(:,:) = sfx(:,:)
306      ENDIF
307      !                                            ! ---------------------------------------- !
308      !                                            !        forcing field computation         !
309      !                                            ! ---------------------------------------- !
310      !
311      IF( ln_apr_dyn ) CALL sbc_apr( kt )                ! atmospheric pressure provided at kt+0.5*nn_fsbc
312                                                         ! (caution called before sbc_ssm)
313      !
314      CALL sbc_ssm( kt )                                 ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m)
315      !                                                  ! averaged over nf_sbc time-step
316
317      IF (ln_wave) CALL sbc_wave( kt )
318                                                   !==  sbc formulation  ==!
319                                                           
320      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition
321      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, sfx)
322      CASE(  0 )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration
323      CASE(  1 )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc
324      CASE(  2 )   ;   CALL sbc_flx     ( kt )                    ! flux formulation
325      CASE(  3 )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean
326      CASE(  4 )   ;   CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean
327      CASE(  5 )   ;   CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! coupled formulation
328      CASE(  6 )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean
329      CASE( -1 )                               
330                       CALL sbc_ana     ( kt )                    ! ESOPA, test ALL the formulations
331                       CALL sbc_gyre    ( kt )                    !
332                       CALL sbc_flx     ( kt )                    !
333                       CALL sbc_blk_clio( kt )                    !
334                       CALL sbc_blk_core( kt )                    !
335                       CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   !
336      END SELECT
337
338      !                                            !==  Misc. Options  ==!
339     
340      SELECT CASE( nn_ice )                                       ! Update heat and freshwater fluxes over sea-ice areas
341      CASE(  1 )   ;         CALL sbc_ice_if   ( kt )                ! Ice-cover climatology ("Ice-if" model)
342      CASE(  2 )   ;         CALL sbc_ice_lim_2( kt, nsbc )          ! LIM-2 ice model
343      CASE(  3 )   ;         CALL sbc_ice_lim  ( kt, nsbc )          ! LIM-3 ice model
344      !is it useful?
345      CASE(  4 )   ;         CALL sbc_ice_cice ( kt, nsbc )          ! CICE ice model
346      END SELECT                                             
347
348      IF( ln_icebergs    )   CALL icb_stp( kt )                   ! compute icebergs
349
350      IF( ln_rnf         )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes
351 
352      IF( ln_ssr         )   CALL sbc_ssr( kt )                   ! add SST/SSS damping term
353
354      IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget
355
356      IF( nn_closea == 1 )   CALL sbc_clo( kt )                   ! treatment of closed sea in the model domain
357      !                                                           ! (update freshwater fluxes)
358!RBbug do not understand why see ticket 667
359      !clem-bugsal CALL lbc_lnk( emp, 'T', 1. )
360      !
361      IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    !
362         !                                             ! ---------------------------------------- !
363         IF( ln_rstart .AND.    &                               !* Restart: read in restart file
364            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN
365            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file'
366            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b )   ! before i-stress  (U-point)
367            CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b )   ! before j-stress  (V-point)
368            CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b  )   ! before non solar heat flux (T-point)
369            ! The 3D heat content due to qsr forcing is treated in traqsr
370            ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b  ) ! before     solar heat flux (T-point)
371            CALL iom_get( numror, jpdom_autoglo, 'emp_b', emp_b  )    ! before     freshwater flux (T-point)
372            ! To ensure restart capability with 3.3x/3.4 restart files    !! to be removed in v3.6
373            IF( iom_varid( numror, 'sfx_b', ldstop = .FALSE. ) > 0 ) THEN
374               CALL iom_get( numror, jpdom_autoglo, 'sfx_b', sfx_b )  ! before salt flux (T-point)
375            ELSE
376               sfx_b (:,:) = sfx(:,:)
377            ENDIF
378         ELSE                                                   !* no restart: set from nit000 values
379            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields set to nit000'
380            utau_b(:,:) = utau(:,:) 
381            vtau_b(:,:) = vtau(:,:)
382            qns_b (:,:) = qns (:,:)
383            emp_b (:,:) = emp(:,:)
384            sfx_b (:,:) = sfx(:,:)
385         ENDIF
386      ENDIF
387      !                                                ! ---------------------------------------- !
388      IF( lrst_oce ) THEN                              !      Write in the ocean restart file     !
389         !                                             ! ---------------------------------------- !
390         IF(lwp) WRITE(numout,*)
391         IF(lwp) WRITE(numout,*) 'sbc : ocean surface forcing fields written in ocean restart file ',   &
392            &                    'at it= ', kt,' date= ', ndastp
393         IF(lwp) WRITE(numout,*) '~~~~'
394         CALL iom_rstput( kt, nitrst, numrow, 'utau_b' , utau )
395         CALL iom_rstput( kt, nitrst, numrow, 'vtau_b' , vtau )
396         CALL iom_rstput( kt, nitrst, numrow, 'qns_b'  , qns  )
397         ! The 3D heat content due to qsr forcing is treated in traqsr
398         ! CALL iom_rstput( kt, nitrst, numrow, 'qsr_b'  , qsr  )
399         CALL iom_rstput( kt, nitrst, numrow, 'emp_b'  , emp  )
400         CALL iom_rstput( kt, nitrst, numrow, 'sfx_b' , sfx )
401      ENDIF
402
403      !                                                ! ---------------------------------------- !
404      !                                                !        Outputs and control print         !
405      !                                                ! ---------------------------------------- !
406      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN
407         CALL iom_put( "empmr" , emp  - rnf )                   ! upward water flux
408         CALL iom_put( "saltflx", sfx  )                        ! downward salt flux 
409                                                                ! (includes virtual salt flux beneath ice
410                                                                ! in linear free surface case)
411         CALL iom_put( "fmmflx", fmmflx  )                      ! Freezing-melting water flux
412         CALL iom_put( "qt"    , qns  + qsr )                   ! total heat flux
413         CALL iom_put( "qns"   , qns        )                   ! solar heat flux
414         CALL iom_put( "qsr"   ,       qsr  )                   ! solar heat flux
415         IF( nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction
416      ENDIF
417      !
418      CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at
419      CALL iom_put( "vtau", vtau )   ! j-wind stress    each time step in sea-ice)
420      CALL iom_put( "taum", taum )   ! wind stress module
421      CALL iom_put( "wspd", wndm )   ! wind speed  module
422      !
423      IF(ln_ctl) THEN         ! print mean trends (used for debugging)
424         CALL prt_ctl(tab2d_1=fr_i             , clinfo1=' fr_i     - : ', mask1=tmask, ovlap=1 )
425         CALL prt_ctl(tab2d_1=(emp-rnf)        , clinfo1=' emp-rnf  - : ', mask1=tmask, ovlap=1 )
426         CALL prt_ctl(tab2d_1=(sfx-rnf)        , clinfo1=' sfx-rnf  - : ', mask1=tmask, ovlap=1 )
427         CALL prt_ctl(tab2d_1=qns              , clinfo1=' qns      - : ', mask1=tmask, ovlap=1 )
428         CALL prt_ctl(tab2d_1=qsr              , clinfo1=' qsr      - : ', mask1=tmask, ovlap=1 )
429         CALL prt_ctl(tab3d_1=tmask            , clinfo1=' tmask    - : ', mask1=tmask, ovlap=1, kdim=jpk )
430         CALL prt_ctl(tab3d_1=tsn(:,:,:,jp_tem), clinfo1=' sst      - : ', mask1=tmask, ovlap=1, kdim=1   )
431         CALL prt_ctl(tab3d_1=tsn(:,:,:,jp_sal), clinfo1=' sss      - : ', mask1=tmask, ovlap=1, kdim=1   )
432         CALL prt_ctl(tab2d_1=utau             , clinfo1=' utau     - : ', mask1=umask,                      &
433            &         tab2d_2=vtau             , clinfo2=' vtau     - : ', mask2=vmask, ovlap=1 )
434      ENDIF
435
436      IF( kt == nitend )   CALL sbc_final         ! Close down surface module if necessary
437      !
438      IF( nn_timing == 1 )  CALL timing_stop('sbc')
439      !
440   END SUBROUTINE sbc
441
442
443   SUBROUTINE sbc_final
444      !!---------------------------------------------------------------------
445      !!                    ***  ROUTINE sbc_final  ***
446      !!
447      !! ** Purpose :   Finalize CICE (if used)
448      !!---------------------------------------------------------------------
449      !
450      IF( nn_ice == 4 )   CALL cice_sbc_final
451      !
452   END SUBROUTINE sbc_final
453
454   !!======================================================================
455END MODULE sbcmod
Note: See TracBrowser for help on using the repository browser.