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/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC – NEMO

source: branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC/sbcmod.F90 @ 1938

Last change on this file since 1938 was 1938, checked in by rfurner, 14 years ago

rnf has been separated from emp and emps. Also temperature and salinity of runoff can be specified, and runoff can be added to a user specified depth

  • Property svn:keywords set to Id
File size: 15.1 KB
Line 
1MODULE sbcmod
2   !!======================================================================
3   !!                       ***  MODULE  sbcmod  ***
4   !! Surface module :  provide to the ocean its surface boundary condition
5   !!======================================================================
6   !! History :  3.0   !  07-2006  (G. Madec)  Original code
7   !!             -    !  08-2008  (S. Masson, E. .... ) coupled interface
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   sbc_init       : read namsbc namelist
12   !!   sbc            : surface ocean momentum, heat and freshwater boundary conditions
13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and tracers
15   USE dom_oce         ! ocean space and time domain
16   USE phycst          ! physical constants
17
18   USE sbc_oce         ! Surface boundary condition: ocean fields
19   USE sbc_ice         ! Surface boundary condition: ice fields
20   USE sbcssm          ! surface boundary condition: sea-surface mean variables
21   USE sbcana          ! surface boundary condition: analytical formulation
22   USE sbcflx          ! surface boundary condition: flux formulation
23   USE sbcblk_clio     ! surface boundary condition: bulk formulation : CLIO
24   USE sbcblk_core     ! surface boundary condition: bulk formulation : CORE
25   USE sbcice_if       ! surface boundary condition: ice-if sea-ice model
26   USE sbcice_lim      ! surface boundary condition: LIM 3.0 sea-ice model
27   USE sbcice_lim_2    ! surface boundary condition: LIM 2.0 sea-ice model
28   USE sbccpl          ! surface boundary condition: coupled florulation
29   USE cpl_oasis3, ONLY:lk_cpl      ! are we in coupled mode?
30   USE sbcssr          ! surface boundary condition: sea surface restoring
31   USE sbcrnf          ! surface boundary condition: runoffs
32   USE sbcfwb          ! surface boundary condition: freshwater budget
33   USE closea          ! closed sea
34
35   USE prtctl          ! Print control                    (prt_ctl routine)
36   USE restart         ! ocean restart
37   USE iom
38   USE in_out_manager  ! I/O manager
39
40   IMPLICIT NONE
41   PRIVATE
42
43   PUBLIC   sbc        ! routine called by step.F90
44   PUBLIC   sbc_init   ! routine called by opa.F90
45   
46   INTEGER ::   nsbc   ! type of surface boundary condition (deduced from namsbc informations)
47     
48   !! * Substitutions
49#  include "domzgr_substitute.h90"
50   !!----------------------------------------------------------------------
51   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
52   !! $Id$
53   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
54   !!----------------------------------------------------------------------
55
56CONTAINS
57
58   SUBROUTINE sbc_init
59      !!---------------------------------------------------------------------
60      !!                    ***  ROUTINE sbc_init ***
61      !!
62      !! ** Purpose :   Initialisation of the ocean surface boundary computation
63      !!
64      !! ** Method  :   Read the namsbc namelist and set derived parameters
65      !!
66      !! ** Action  : - read namsbc parameters
67      !!              - nsbc: type of sbc
68      !!----------------------------------------------------------------------
69      INTEGER ::   icpt      ! temporary integer
70      !!
71      NAMELIST/namsbc/ nn_fsbc, ln_ana, ln_flx, ln_blk_clio, ln_blk_core, ln_cpl,   &
72         &             nn_ice , ln_dm2dc, ln_rnf, ln_ssr, nn_fwb, nn_ico_cpl
73      !!----------------------------------------------------------------------
74
75      IF(lwp) THEN
76         WRITE(numout,*)
77         WRITE(numout,*) 'sbc_init : surface boundary condition setting'
78         WRITE(numout,*) '~~~~~~~~ '
79      ENDIF
80
81      REWIND( numnam )                   ! Read Namelist namsbc
82      READ  ( numnam, namsbc )
83
84      ! overwrite namelist parameter using CPP key information
85!!gm here no overwrite, test all option via namelist change: require more incore memory
86!!gm  IF( lk_sbc_cpl       ) THEN   ;   ln_cpl      = .TRUE.   ;   ELSE   ;   ln_cpl      = .FALSE.   ;   ENDIF
87
88      IF ( Agrif_Root() ) THEN
89        IF( lk_lim2 )            nn_ice      = 2
90        IF( lk_lim3 )            nn_ice      = 3
91      ENDIF
92      !
93      IF( cp_cfg == 'gyre' ) THEN
94          ln_ana      = .TRUE.   
95          nn_ice      =   0
96      ENDIF
97     
98      ! Control print
99      IF(lwp) THEN
100         WRITE(numout,*) '        Namelist namsbc (partly overwritten with CPP key setting)'
101         WRITE(numout,*) '           frequency update of sbc (and ice)             nn_fsbc     = ', nn_fsbc
102         WRITE(numout,*) '           Type of sbc : '
103         WRITE(numout,*) '              analytical formulation                     ln_ana      = ', ln_ana
104         WRITE(numout,*) '              flux       formulation                     ln_flx      = ', ln_flx
105         WRITE(numout,*) '              CLIO bulk  formulation                     ln_blk_clio = ', ln_blk_clio
106         WRITE(numout,*) '              CLIO bulk  formulation                     ln_blk_core = ', ln_blk_core
107         WRITE(numout,*) '              coupled    formulation (T if key_sbc_cpl)  ln_cpl      = ', ln_cpl
108         WRITE(numout,*) '           Misc. options of sbc : '
109         WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice      = ', nn_ice 
110         WRITE(numout,*) '              ice-ocean stress computation (=0/1/2)      nn_ico_cpl  = ', nn_ico_cpl
111         WRITE(numout,*) '              daily mean to diurnal cycle qsr            ln_dm2dc    = ', ln_dm2dc 
112         WRITE(numout,*) '              runoff / runoff mouths                     ln_rnf      = ', ln_rnf
113         WRITE(numout,*) '              Sea Surface Restoring on SST and/or SSS    ln_ssr      = ', ln_ssr
114         WRITE(numout,*) '              FreshWater Budget control  (=0/1/2)        nn_fwb      = ', nn_fwb
115         WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea   = ', nn_closea
116      ENDIF
117
118      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths
119         ln_rnf_mouth  = .false.                     
120         nkrnf         = 0
121         rnfmsk  (:,:) = 0.e0
122         rnfmsk_z(:)   = 0.e0
123      ENDIF
124      IF( nn_ice == 0  )   fr_i(:,:) = 0.e0        ! no ice in the domain, ice fraction is always zero
125
126      !                                            ! restartability   
127      IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   &
128          MOD( nstock             , nn_fsbc) /= 0 ) THEN
129         WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   &
130            &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')'
131         CALL ctl_stop( ctmp1, 'Impossible to properly do model restart' )
132      ENDIF
133      !
134      IF( MOD( rday, REAL(nn_fsbc, wp) * rdt ) /= 0 )   &
135         &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' )
136      !
137      IF( nn_ice == 2 .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   &
138         &   CALL ctl_stop( 'sea-ice model requires a bulk formulation or coupled configuration' )
139     
140      ! Choice of the Surface Boudary Condition (set nsbc)
141      icpt = 0
142      IF( ln_ana          ) THEN   ;   nsbc =  1   ; icpt = icpt + 1   ;   ENDIF       ! analytical      formulation
143      IF( ln_flx          ) THEN   ;   nsbc =  2   ; icpt = icpt + 1   ;   ENDIF       ! flux            formulation
144      IF( ln_blk_clio     ) THEN   ;   nsbc =  3   ; icpt = icpt + 1   ;   ENDIF       ! CLIO bulk       formulation
145      IF( ln_blk_core     ) THEN   ;   nsbc =  4   ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk       formulation
146      IF( ln_cpl          ) THEN   ;   nsbc =  5   ; icpt = icpt + 1   ;   ENDIF       ! Coupled         formulation
147      IF( cp_cfg == 'gyre') THEN   ;   nsbc =  0                       ;   ENDIF       ! GYRE analytical formulation
148      IF( lk_esopa        )            nsbc = -1                                       ! esopa test, ALL formulations
149
150      IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN
151         WRITE(numout,*)
152         WRITE(numout,*) '           E R R O R in setting the sbc, one and only one namelist/CPP key option '
153         WRITE(numout,*) '                     must be choosen. You choose ', icpt, ' option(s)'
154         WRITE(numout,*) '                     We stop'
155         nstop = nstop + 1
156      ENDIF
157      IF(lwp) THEN
158         WRITE(numout,*)
159         IF( nsbc == -1 )   WRITE(numout,*) '              ESOPA test All surface boundary conditions'
160         IF( nsbc ==  0 )   WRITE(numout,*) '              GYRE analytical formulation'
161         IF( nsbc ==  1 )   WRITE(numout,*) '              analytical formulation'
162         IF( nsbc ==  2 )   WRITE(numout,*) '              flux formulation'
163         IF( nsbc ==  3 )   WRITE(numout,*) '              CLIO bulk formulation'
164         IF( nsbc ==  4 )   WRITE(numout,*) '              CORE bulk formulation'
165         IF( nsbc ==  5 )   WRITE(numout,*) '              coupled formulation'
166      ENDIF
167      !
168   END SUBROUTINE sbc_init
169
170
171   SUBROUTINE sbc( kt )
172      !!---------------------------------------------------------------------
173      !!                    ***  ROUTINE sbc  ***
174      !!             
175      !! ** Purpose :   provide at each time-step the ocean surface boundary
176      !!                condition (momentum, heat and freshwater fluxes)
177      !!
178      !! ** Method  :   blah blah  to be written ?????????
179      !!                CAUTION : never mask the surface stress field (tke sbc)
180      !!
181      !! ** Action  : - set the ocean surface boundary condition, i.e. 
182      !!                utau, vtau, qns, qsr, emp, emps, qrp, erp
183      !!              - updte the ice fraction : fr_i
184      !!----------------------------------------------------------------------
185      INTEGER, INTENT(in) ::   kt       ! ocean time step
186      !!---------------------------------------------------------------------
187
188      emp(:,:)=0.0 
189      emps(:,:)=0.0 
190      rnf(:,:)=0.0 
191
192      CALL iom_setkt( kt + nn_fsbc - 1 )         !  in sbc, iom_put is called every nn_fsbc time step
193      !
194      ! ocean to sbc mean sea surface variables (ss._m)
195      ! ---------------------------------------
196      CALL sbc_ssm( kt )                         ! sea surface mean currents (at U- and V-points),
197      !                                          ! temperature and salinity (at T-point) over nf_sbc time-step
198      !                                          ! (i.e. sst_m, sss_m, ssu_m, ssv_m)
199
200      ! sbc formulation
201      ! ---------------
202         
203      SELECT CASE( nsbc )                        ! Compute ocean surface boundary condition
204      !                                          ! (i.e. utau,vtau, qns, qsr, emp, emps)
205      CASE(  0 )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration
206      CASE(  1 )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc
207      CASE(  2 )   ;   CALL sbc_flx     ( kt )                    ! flux formulation
208      CASE(  3 )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean
209      CASE(  4 )   ;   CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean
210      CASE(  5 )   ;   CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! coupled formulation
211      CASE( -1 )                               
212                       CALL sbc_ana     ( kt )                    ! ESOPA, test ALL the formulations
213                       CALL sbc_gyre    ( kt )                    !
214                       CALL sbc_flx     ( kt )                    !
215                       CALL sbc_blk_clio( kt )                    !
216                       CALL sbc_blk_core( kt )                    !
217                       CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   !
218      END SELECT
219
220      ! Misc. Options
221      ! -------------
222
223!!gm  IF( ln_dm2dc       )   CALL sbc_dcy( kt )                 ! Daily mean qsr distributed over the Diurnal Cycle
224     
225      SELECT CASE( nn_ice )                                     ! Update heat and freshwater fluxes over sea-ice areas
226      CASE(  1 )   ;       CALL sbc_ice_if   ( kt )                   ! Ice-cover climatology ("Ice-if" model)
227         !                                                     
228      CASE(  2 )   ;       CALL sbc_ice_lim_2( kt, nsbc )             ! LIM 2.0 ice model
229         !                                                     
230      CASE(  3 )   ;       CALL sbc_ice_lim  ( kt, nsbc, nn_ico_cpl)  ! LIM 3.0 ice model
231      END SELECT                                             
232
233      IF( ln_rnf       )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes
234 
235      IF( ln_ssr       )   CALL sbc_ssr( kt )                   ! add SST/SSS damping term
236
237      IF( nn_fwb  /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget
238
239      IF( nclosea == 1 )   CALL sbc_clo( kt )                   ! treatment of closed sea in the model domain
240      !                                                         ! (update freshwater fluxes)
241      !
242      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN
243         CALL iom_put( "emp-rnf"  , (emp-rnf)  )                ! upward water flux
244         CALL iom_put( "emps-rnf" , (emps-rnf) )                ! c/d water flux
245         CALL iom_put( "qns+qsr"  , qns + qsr  )                ! total heat flux   (caution if ln_dm2dc=true, to be
246         CALL iom_put( "qns"      , qns        )                ! solar heat flux    moved after the call to iom_setkt)
247         CALL iom_put( "qsr"      ,       qsr  )                ! solar heat flux    moved after the call to iom_setkt)
248         IF(  nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )  ! ice fraction
249      ENDIF
250      !
251      CALL iom_setkt( kt )           ! iom_put outside of sbc is called at every time step
252      !
253      CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at
254      CALL iom_put( "vtau", vtau )   ! j-wind stress    each time step in sea-ice)
255      CALL iom_put( "taum", taum )   ! wind stress module
256      CALL iom_put( "wspd", wndm )   ! wind speed  module
257      !
258      IF(ln_ctl) THEN         ! print mean trends (used for debugging)
259         CALL prt_ctl(tab2d_1=fr_i   , clinfo1=' fr_i - : ', mask1=tmask, ovlap=1 )
260         CALL prt_ctl(tab2d_1=(emp-rnf) , clinfo1=' emp-rnf  - : ', mask1=tmask, ovlap=1 ) 
261         CALL prt_ctl(tab2d_1=(emps-rnf), clinfo1=' emps-rnf - : ', mask1=tmask, ovlap=1 ) 
262         CALL prt_ctl(tab2d_1=qns    , clinfo1=' qns  - : ', mask1=tmask, ovlap=1 )
263         CALL prt_ctl(tab2d_1=qsr    , clinfo1=' qsr  - : ', mask1=tmask, ovlap=1 )
264         CALL prt_ctl(tab3d_1=tmask  , clinfo1=' tmask  : ', mask1=tmask, ovlap=1, kdim=jpk )
265         CALL prt_ctl(tab3d_1=tn     , clinfo1=' sst  - : ', mask1=tmask, ovlap=1, kdim=1   )
266         CALL prt_ctl(tab3d_1=sn     , clinfo1=' sss  - : ', mask1=tmask, ovlap=1, kdim=1   )
267         CALL prt_ctl(tab2d_1=utau   , clinfo1=' utau - : ', mask1=umask,                      &
268            &         tab2d_2=vtau   , clinfo2=' vtau - : ', mask2=vmask, ovlap=1 )
269      ENDIF
270      !
271   END SUBROUTINE sbc
272
273   !!======================================================================
274END MODULE sbcmod
Note: See TracBrowser for help on using the repository browser.