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 branches/2012/dev_r3452_UKMO9_RESTART/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2012/dev_r3452_UKMO9_RESTART/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90 @ 3594

Last change on this file since 3594 was 3594, checked in by rfurner, 11 years ago

code not tested through SETTEE, builds and runs, but has not been thoroughly tested, so will not be included in 2012 merge, however submitted back to keep record of work done for 2013 developments

  • Property svn:keywords set to Id
File size: 22.9 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   !!----------------------------------------------------------------------
15
16   !!----------------------------------------------------------------------
17   !!   sbc_init       : read namsbc namelist
18   !!   sbc            : surface ocean momentum, heat and freshwater boundary conditions
19   !!----------------------------------------------------------------------
20   USE oce              ! ocean dynamics and tracers
21   USE dom_oce          ! ocean space and time domain
22   USE phycst           ! physical constants
23   USE sbc_oce          ! Surface boundary condition: ocean fields
24   USE sbc_ice          ! Surface boundary condition: ice fields
25   USE sbcdcy           ! surface boundary condition: diurnal cycle
26   USE sbcssm           ! surface boundary condition: sea-surface mean variables
27   USE sbcapr           ! surface boundary condition: atmospheric pressure
28   USE sbcana           ! surface boundary condition: analytical formulation
29   USE sbcflx           ! surface boundary condition: flux formulation
30   USE sbcblk_clio      ! surface boundary condition: bulk formulation : CLIO
31   USE sbcblk_core      ! surface boundary condition: bulk formulation : CORE
32   USE sbcblk_mfs       ! surface boundary condition: bulk formulation : MFS
33   USE sbcice_if        ! surface boundary condition: ice-if sea-ice model
34   USE sbcice_lim       ! surface boundary condition: LIM 3.0 sea-ice model
35   USE sbcice_lim_2     ! surface boundary condition: LIM 2.0 sea-ice model
36   USE sbcice_cice      ! surface boundary condition: CICE    sea-ice model
37   USE sbccpl           ! surface boundary condition: coupled florulation
38   USE cpl_oasis3, ONLY:lk_cpl      ! are we in coupled mode?
39   USE sbcssr           ! surface boundary condition: sea surface restoring
40   USE sbcrnf           ! surface boundary condition: runoffs
41   USE sbcfwb           ! surface boundary condition: freshwater budget
42   USE closea           ! closed sea
43   USE bdy_par          ! for lk_bdy
44   USE bdyice_lim2      ! unstructured open boundary data  (bdy_ice_lim_2 routine)
45
46   USE prtctl           ! Print control                    (prt_ctl routine)
47   USE restart          ! ocean restart
48   USE iom              ! IOM library
49   USE in_out_manager   ! I/O manager
50   USE lib_mpp          ! MPP library
51   USE timing           ! Timing
52   USE sbcwave          ! Wave module
53
54   IMPLICIT NONE
55   PRIVATE
56
57   PUBLIC   sbc        ! routine called by step.F90
58   PUBLIC   sbc_init   ! routine called by opa.F90
59   
60   INTEGER ::   nsbc   ! type of surface boundary condition (deduced from namsbc informations)
61     
62   !! * Substitutions
63#  include "domzgr_substitute.h90"
64   !!----------------------------------------------------------------------
65   !! NEMO/OPA 4.0 , NEMO-consortium (2011)
66   !! $Id$
67   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
68   !!----------------------------------------------------------------------
69CONTAINS
70
71   SUBROUTINE sbc_init
72      !!---------------------------------------------------------------------
73      !!                    ***  ROUTINE sbc_init ***
74      !!
75      !! ** Purpose :   Initialisation of the ocean surface boundary computation
76      !!
77      !! ** Method  :   Read the namsbc namelist and set derived parameters
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 , ln_dm2dc, ln_rnf, ln_ssr     , nn_fwb, ln_cdgw
86      !!----------------------------------------------------------------------
87
88      IF(lwp) THEN
89         WRITE(numout,*)
90         WRITE(numout,*) 'sbc_init : surface boundary condition setting'
91         WRITE(numout,*) '~~~~~~~~ '
92      ENDIF
93
94      REWIND( numnam )           ! Read Namelist namsbc
95      READ  ( numnam, namsbc )
96
97      !                          ! overwrite namelist parameter using CPP key information
98      IF( Agrif_Root() ) THEN                ! AGRIF zoom
99        IF( lk_lim2 )   nn_ice      = 2
100        IF( lk_lim3 )   nn_ice      = 3
101        IF( lk_cice )   nn_ice      = 4
102      ENDIF
103      IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration
104          ln_ana      = .TRUE.   
105          nn_ice      =   0
106      ENDIF
107     
108      IF(lwp) THEN               ! Control print
109         WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)'
110         WRITE(numout,*) '           frequency update of sbc (and ice)             nn_fsbc     = ', nn_fsbc
111         WRITE(numout,*) '           Type of sbc : '
112         WRITE(numout,*) '              analytical formulation                     ln_ana      = ', ln_ana
113         WRITE(numout,*) '              flux       formulation                     ln_flx      = ', ln_flx
114         WRITE(numout,*) '              CLIO bulk  formulation                     ln_blk_clio = ', ln_blk_clio
115         WRITE(numout,*) '              CORE bulk  formulation                     ln_blk_core = ', ln_blk_core
116         WRITE(numout,*) '              MFS  bulk  formulation                     ln_blk_mfs  = ', ln_blk_mfs
117         WRITE(numout,*) '              coupled    formulation (T if key_sbc_cpl)  ln_cpl      = ', ln_cpl
118         WRITE(numout,*) '           Misc. options of sbc : '
119         WRITE(numout,*) '              Patm gradient added in ocean & ice Eqs.    ln_apr_dyn  = ', ln_apr_dyn
120         WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice      = ', nn_ice 
121         WRITE(numout,*) '              daily mean to diurnal cycle qsr            ln_dm2dc    = ', ln_dm2dc 
122         WRITE(numout,*) '              runoff / runoff mouths                     ln_rnf      = ', ln_rnf
123         WRITE(numout,*) '              Sea Surface Restoring on SST and/or SSS    ln_ssr      = ', ln_ssr
124         WRITE(numout,*) '              FreshWater Budget control  (=0/1/2)        nn_fwb      = ', nn_fwb
125         WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea   = ', nn_closea
126      ENDIF
127
128      !                              ! allocate sbc arrays
129      IF( sbc_oce_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_oce arrays' )
130
131      !                          ! Checks:
132      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths
133         ln_rnf_mouth  = .false.                     
134         IF( sbc_rnf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_rnf arrays' )
135         nkrnf         = 0
136         rnf     (:,:) = 0.e0
137         rnfmsk  (:,:) = 0.e0
138         rnfmsk_z(:)   = 0.e0
139      ENDIF
140      IF( nn_ice == 0  )   fr_i(:,:) = 0.e0        ! no ice in the domain, ice fraction is always zero
141
142      !                                            ! restartability   
143      IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR. ANY ( MOD(nn_stock,nn_fsbc)/=0 )  ) THEN
144         WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or an entry in nn_stock (', nn_stock,   &
145            &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')'
146         CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' )
147      ENDIF
148      !
149      IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 )   &
150         &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' )
151      !
152      IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   &
153         &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' )
154      IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. lk_cpl ) )   &
155         &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or lk_cpl' )
156      IF( nn_ice == 4 .AND. ( .NOT. ( cp_cfg == 'orca' ) .OR. lk_agrif ) )   &
157         &   CALL ctl_stop( 'CICE sea-ice model currently only available in a global ORCA configuration without AGRIF' )
158     
159      IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag
160
161      IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) )   &
162         &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' )
163     
164      IF( ln_dm2dc .AND. ( ( NINT(rday) / ( nn_fsbc * NINT(rdt) ) )  < 8 ) )   &
165         &   CALL ctl_warn( 'diurnal cycle for qsr: the sampling of the diurnal cycle is too small...' )
166
167       !drag coefficient read from wave model definable only with mfs bulk formulae and core
168       IF(ln_cdgw .AND. .NOT.(ln_blk_mfs .OR. ln_blk_core) )              &
169          &   CALL ctl_stop( 'drag coefficient read from wave model definable only with mfs bulk formulae and core')
170     
171      !                          ! Choice of the Surface Boudary Condition (set nsbc)
172      icpt = 0
173      IF( ln_ana          ) THEN   ;   nsbc =  1   ; icpt = icpt + 1   ;   ENDIF       ! analytical      formulation
174      IF( ln_flx          ) THEN   ;   nsbc =  2   ; icpt = icpt + 1   ;   ENDIF       ! flux            formulation
175      IF( ln_blk_clio     ) THEN   ;   nsbc =  3   ; icpt = icpt + 1   ;   ENDIF       ! CLIO bulk       formulation
176      IF( ln_blk_core     ) THEN   ;   nsbc =  4   ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk       formulation
177      IF( ln_blk_mfs      ) THEN   ;   nsbc =  6   ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk       formulation
178      IF( ln_cpl          ) THEN   ;   nsbc =  5   ; icpt = icpt + 1   ;   ENDIF       ! Coupled         formulation
179      IF( cp_cfg == 'gyre') THEN   ;   nsbc =  0                       ;   ENDIF       ! GYRE analytical formulation
180      IF( lk_esopa        )            nsbc = -1                                       ! esopa test, ALL formulations
181      !
182      IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN
183         WRITE(numout,*)
184         WRITE(numout,*) '           E R R O R in setting the sbc, one and only one namelist/CPP key option '
185         WRITE(numout,*) '                     must be choosen. You choose ', icpt, ' option(s)'
186         WRITE(numout,*) '                     We stop'
187         nstop = nstop + 1
188      ENDIF
189      IF(lwp) THEN
190         WRITE(numout,*)
191         IF( nsbc == -1 )   WRITE(numout,*) '              ESOPA test All surface boundary conditions'
192         IF( nsbc ==  0 )   WRITE(numout,*) '              GYRE analytical formulation'
193         IF( nsbc ==  1 )   WRITE(numout,*) '              analytical formulation'
194         IF( nsbc ==  2 )   WRITE(numout,*) '              flux formulation'
195         IF( nsbc ==  3 )   WRITE(numout,*) '              CLIO bulk formulation'
196         IF( nsbc ==  4 )   WRITE(numout,*) '              CORE bulk formulation'
197         IF( nsbc ==  5 )   WRITE(numout,*) '              coupled formulation'
198         IF( nsbc ==  6 )   WRITE(numout,*) '              MFS Bulk formulation'
199      ENDIF
200
201      IF( nn_ice == 4 )   CALL cice_sbc_init (nsbc)
202      !
203   END SUBROUTINE sbc_init
204
205
206   SUBROUTINE sbc( kt )
207      !!---------------------------------------------------------------------
208      !!                    ***  ROUTINE sbc  ***
209      !!             
210      !! ** Purpose :   provide at each time-step the ocean surface boundary
211      !!                condition (momentum, heat and freshwater fluxes)
212      !!
213      !! ** Method  :   blah blah  to be written ?????????
214      !!                CAUTION : never mask the surface stress field (tke sbc)
215      !!
216      !! ** Action  : - set the ocean surface boundary condition at before and now
217      !!                time step, i.e. 
218      !!                utau_b, vtau_b, qns_b, qsr_b, emp_n, emps_b, qrp_b, erp_b
219      !!                utau  , vtau  , qns  , qsr  , emp  , emps  , qrp  , erp
220      !!              - updte the ice fraction : fr_i
221      !!----------------------------------------------------------------------
222      INTEGER, INTENT(in) ::   kt       ! ocean time step
223      !!---------------------------------------------------------------------
224      !
225      IF( nn_timing == 1 )  CALL timing_start('sbc')
226      !
227      !                                            ! ---------------------------------------- !
228      IF( kt /= nit000 ) THEN                      !          Swap of forcing fields          !
229         !                                         ! ---------------------------------------- !
230         utau_b(:,:) = utau(:,:)                         ! Swap the ocean forcing fields
231         vtau_b(:,:) = vtau(:,:)                         ! (except at nit000 where before fields
232         qns_b (:,:) = qns (:,:)                         !  are set at the end of the routine)
233         ! The 3D heat content due to qsr forcing is treated in traqsr
234         ! qsr_b (:,:) = qsr (:,:)
235         emp_b (:,:) = emp (:,:)
236         emps_b(:,:) = emps(:,:)
237      ENDIF
238      !                                            ! ---------------------------------------- !
239      !                                            !        forcing field computation         !
240      !                                            ! ---------------------------------------- !
241
242      CALL iom_setkt( kt + nn_fsbc - 1 )                 ! in sbc, iom_put is called every nn_fsbc time step
243      !
244      IF( ln_apr_dyn ) CALL sbc_apr( kt )                ! atmospheric pressure provided at kt+0.5*nn_fsbc
245                                                         ! (caution called before sbc_ssm)
246      !
247      CALL sbc_ssm( kt )                                 ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m)
248      !                                                  ! averaged over nf_sbc time-step
249
250      IF (ln_cdgw) CALL sbc_wave( kt )
251                                                   !==  sbc formulation  ==!
252                                                           
253      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition
254      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, emps)
255      CASE(  0 )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration
256      CASE(  1 )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc
257      CASE(  2 )   ;   CALL sbc_flx     ( kt )                    ! flux formulation
258      CASE(  3 )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean
259      CASE(  4 )   ;   CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean
260      CASE(  5 )   ;   CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! coupled formulation
261      CASE(  6 )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean
262      CASE( -1 )                               
263                       CALL sbc_ana     ( kt )                    ! ESOPA, test ALL the formulations
264                       CALL sbc_gyre    ( kt )                    !
265                       CALL sbc_flx     ( kt )                    !
266                       CALL sbc_blk_clio( kt )                    !
267                       CALL sbc_blk_core( kt )                    !
268                       CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   !
269      END SELECT
270
271      !                                            !==  Misc. Options  ==!
272     
273      SELECT CASE( nn_ice )                                       ! Update heat and freshwater fluxes over sea-ice areas
274      CASE(  1 )   ;         CALL sbc_ice_if   ( kt )                ! Ice-cover climatology ("Ice-if" model)
275      CASE(  2 )   ;         CALL sbc_ice_lim_2( kt, nsbc )          ! LIM-2 ice model
276              IF( lk_bdy )   CALL bdy_ice_lim_2( kt )                ! BDY boundary condition
277      CASE(  3 )   ;         CALL sbc_ice_lim  ( kt, nsbc )          ! LIM-3 ice model
278      CASE(  4 )   ;         CALL sbc_ice_cice ( kt, nsbc )          ! CICE ice model
279      END SELECT                                             
280
281      IF( ln_rnf         )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes
282 
283      IF( ln_ssr         )   CALL sbc_ssr( kt )                   ! add SST/SSS damping term
284
285      IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget
286
287      IF( nn_closea == 1 )   CALL sbc_clo( kt )                   ! treatment of closed sea in the model domain
288      !                                                           ! (update freshwater fluxes)
289!RBbug do not understand why see ticket 667
290      CALL lbc_lnk( emp, 'T', 1. )
291      !
292      IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    !
293         !                                             ! ---------------------------------------- !
294         IF( ln_rstart .AND.    &                               !* Restart: read in restart file
295            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN
296            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file'
297            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b )   ! before i-stress  (U-point)
298            CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b )   ! before j-stress  (V-point)
299            CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b  )   ! before non solar heat flux (T-point)
300            ! The 3D heat content due to qsr forcing is treated in traqsr
301            ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b  )   ! before     solar heat flux (T-point)
302            CALL iom_get( numror, jpdom_autoglo, 'emp_b' , emp_b  )   ! before     freshwater flux (T-point)
303            CALL iom_get( numror, jpdom_autoglo, 'emps_b', emps_b )   ! before C/D freshwater flux (T-point)
304         ELSE                                                   !* no restart: set from nit000 values
305            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields set to nit000'
306            utau_b(:,:) = utau(:,:) 
307            vtau_b(:,:) = vtau(:,:)
308            qns_b (:,:) = qns (:,:)
309            ! qsr_b (:,:) = qsr (:,:)
310            emp_b (:,:) = emp (:,:)
311            emps_b(:,:) = emps(:,:)
312         ENDIF
313      ENDIF
314      !                                                ! ---------------------------------------- !
315      IF( lrst_oce ) THEN                              !      Write in the ocean restart file     !
316         !                                             ! ---------------------------------------- !
317         IF(lwp) WRITE(numout,*)
318         IF(lwp) WRITE(numout,*) 'sbc : ocean surface forcing fields written in ocean restart file ',   &
319            &                    'at it= ', kt,' date= ', ndastp
320         IF(lwp) WRITE(numout,*) '~~~~'
321         CALL iom_rstput( kt, nitrst, numrow, 'utau_b' , utau )
322         CALL iom_rstput( kt, nitrst, numrow, 'vtau_b' , vtau )
323         CALL iom_rstput( kt, nitrst, numrow, 'qns_b'  , qns  )
324         ! The 3D heat content due to qsr forcing is treated in traqsr
325         ! CALL iom_rstput( kt, nitrst, numrow, 'qsr_b'  , qsr  )
326         CALL iom_rstput( kt, nitrst, numrow, 'emp_b'  , emp  )
327         CALL iom_rstput( kt, nitrst, numrow, 'emps_b' , emps )
328      ENDIF
329
330      !                                                ! ---------------------------------------- !
331      !                                                !        Outputs and control print         !
332      !                                                ! ---------------------------------------- !
333      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN
334         CALL iom_put( "empmr" , emp  - rnf )                   ! upward water flux
335         CALL iom_put( "empsmr", emps - rnf )                   ! c/d water flux
336         CALL iom_put( "qt"    , qns  + qsr )                   ! total heat flux
337         CALL iom_put( "qns"   , qns        )                   ! solar heat flux
338         CALL iom_put( "qsr"   ,       qsr  )                   ! solar heat flux
339         IF( nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction
340      ENDIF
341      !
342      CALL iom_setkt( kt )           ! iom_put outside of sbc is called at every time step
343      !
344      CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at
345      CALL iom_put( "vtau", vtau )   ! j-wind stress    each time step in sea-ice)
346      CALL iom_put( "taum", taum )   ! wind stress module
347      CALL iom_put( "wspd", wndm )   ! wind speed  module
348      !
349      IF(ln_ctl) THEN         ! print mean trends (used for debugging)
350         CALL prt_ctl(tab2d_1=fr_i             , clinfo1=' fr_i     - : ', mask1=tmask, ovlap=1 )
351         CALL prt_ctl(tab2d_1=(emp-rnf)        , clinfo1=' emp-rnf  - : ', mask1=tmask, ovlap=1 )
352         CALL prt_ctl(tab2d_1=(emps-rnf)       , clinfo1=' emps-rnf - : ', mask1=tmask, ovlap=1 )
353         CALL prt_ctl(tab2d_1=qns              , clinfo1=' qns      - : ', mask1=tmask, ovlap=1 )
354         CALL prt_ctl(tab2d_1=qsr              , clinfo1=' qsr      - : ', mask1=tmask, ovlap=1 )
355         CALL prt_ctl(tab3d_1=tmask            , clinfo1=' tmask    - : ', mask1=tmask, ovlap=1, kdim=jpk )
356         CALL prt_ctl(tab3d_1=tsn(:,:,:,jp_tem), clinfo1=' sst      - : ', mask1=tmask, ovlap=1, kdim=1   )
357         CALL prt_ctl(tab3d_1=tsn(:,:,:,jp_sal), clinfo1=' sss      - : ', mask1=tmask, ovlap=1, kdim=1   )
358         CALL prt_ctl(tab2d_1=utau             , clinfo1=' utau     - : ', mask1=umask,                      &
359            &         tab2d_2=vtau             , clinfo2=' vtau     - : ', mask2=vmask, ovlap=1 )
360      ENDIF
361
362      IF( kt == nitend )   CALL sbc_final         ! Close down surface module if necessary
363      !
364      IF( nn_timing == 1 )  CALL timing_stop('sbc')
365      !
366   END SUBROUTINE sbc
367
368   SUBROUTINE sbc_final
369      !!---------------------------------------------------------------------
370      !!                    ***  ROUTINE sbc_final  ***
371      !!---------------------------------------------------------------------
372
373      !-----------------------------------------------------------------
374      ! Finalize CICE (if used)
375      !-----------------------------------------------------------------
376
377      IF( nn_ice == 4 )   CALL cice_sbc_final
378      !
379   END SUBROUTINE sbc_final
380
381   !!======================================================================
382END MODULE sbcmod
Note: See TracBrowser for help on using the repository browser.