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_tam.F90 in branches/2010_and_older/TAM_V3_2_2/NEMOTAM/OPATAM_SRC/SBC – NEMO

source: branches/2010_and_older/TAM_V3_2_2/NEMOTAM/OPATAM_SRC/SBC/sbcmod_tam.F90 @ 7797

Last change on this file since 7797 was 2578, checked in by rblod, 13 years ago

first import of NEMOTAM 3.2.2

File size: 14.6 KB
Line 
1MODULE sbcmod_tam
2#ifdef key_tam
3   !!======================================================================
4   !!                       ***  MODULE  sbcmod_tam  ***
5   !! Surface module :  provide to the ocean its surface boundary condition
6   !!                       Tangent&Adjoint module
7   !!======================================================================
8   !! History of the direct module : 
9   !!            3.0   !  07-2006  (G. Madec)  Original code
10   !!             -    !  08-2008  (S. Masson, E. .... ) coupled interface
11   !! History of the T&A module :
12   !!            3.0   !  11-2008  (A. Vidard) TAM of the 2006-07 version
13   !!            3.2   !  04-2010  (A. Vidard) Nemo3.2 update
14   !!----------------------------------------------------------------------
15
16   !!----------------------------------------------------------------------
17   !!   sbc_init       : read namsbc namelist
18   !!   sbc            : surface ocean momentum, heat and freshwater boundary conditions
19   !!----------------------------------------------------------------------
20   USE par_kind      , ONLY: & ! Precision variables
21      & wp
22   USE phycst        , ONLY: & !
23      & rday
24   USE lbclnk        , ONLY: &
25      & lbc_lnk
26   USE lbclnk_tam    , ONLY: &
27      & lbc_lnk_adj
28   !   USE ice_oce         ! sea-ice model : LIM
29   USE dom_oce       , ONLY: & ! ocean space domain variables
30      & rdt,          cp_cfg,       nclosea
31   USE sbc_oce       , ONLY: & ! Surface boundary condition: ocean fields
32      & nn_fsbc,      nn_ice,           &
33      & nn_fwb,       ln_ana,       ln_flx,           &
34      & ln_ssr,       ln_rnf,       ln_cpl,           &
35      & ln_dm2dc,     ln_blk_clio,  ln_blk_core
36   USE sbcmod        , ONLY: &
37      & sbc_init
38   USE sbc_oce_tam   , ONLY: & ! Surface boundary condition: ocean fields
39      & fr_i_tl,      emp_tl,       emp_ad
40   USE sbcssm_tam    , ONLY: & ! surface boundary condition: sea-surface mean variables
41      & sbc_ssm_tan,  sbc_ssm_adj,  sbc_ssm_adj_tst
42   USE sbcana_tam, ONLY:  & ! surface boundary condition: analytical formulation
43      & sbc_gyre_tan, sbc_gyre_adj, sbc_gyre_adj_tst
44!*B      & sbc_ana_tan,       &
45!*B      & sbc_ana_adj,       &
46!*B      & sbc_ana_adj_tst
47   USE sbcflx_tam    , ONLY: & ! surface boundary condition: flux formulation
48      & sbc_flx_tan,  sbc_flx_adj,  sbc_flx_adj_tst
49!   USE sbcblk_clio     ! surface boundary condition: bulk formulation : CLIO
50!   USE sbcblk_core     ! surface boundary condition: bulk formulation : CORE
51!   USE sbcice_if       ! surface boundary condition: ice-if sea-ice model
52!   USE sbcice_lim      ! surface boundary condition: LIM 3.0 sea-ice model
53!   USE sbcice_lim_2    ! surface boundary condition: LIM 2.0 sea-ice model
54!   USE sbccpl          ! surface boundary condition: coupled florulation
55   USE sbcssr_tam    , ONLY: & ! surface boundary condition: sea surface restoring
56      & sbc_ssr_tan,  sbc_ssr_adj,  sbc_ssr_adj_tst
57   USE closea_tam    , ONLY: & !specific treatments associated with closed seas
58      & sbc_clo_tan,  sbc_clo_adj,  sbc_clo_adj_tst
59!   USE sbcrnf_tam          ! surface boundary condition: runoffs
60   USE sbcrnf        , ONLY: & ! surface boundary condition: runoffs
61      & rnfmsk,       rnfmsk_z,     ln_rnf_mouth,     &
62      & nkrnf
63   USE sbcfwb_tam    , ONLY: & ! surface boundary condition: freshwater budget
64      & sbc_fwb_tan,  sbc_fwb_adj,  sbc_fwb_adj_tst
65   USE in_out_manager, ONLY: & ! I/O manager
66      & lwp,          ctl_warn,     numout,           &
67      & numnam,       nit000,       nitend,           &
68      & nstop
69
70   IMPLICIT NONE
71   PRIVATE
72
73   PUBLIC   sbc_init_tam ! routine called by step_tam.F90
74   PUBLIC   sbc_tan      ! routine called by step_tam.F90
75   PUBLIC   sbc_adj      ! routine called by step_tam.F90
76   PUBLIC   sbc_adj_tst  ! routine called by tst.F90
77   
78   INTEGER          ::   nn_ico_cpl  = 0         !: ice-ocean coupling indicator
79   !                                             !  = 0   LIM-3 old case
80   !                                             !  = 1   stresses computed using now ocean velocity
81   !                                             !  = 2   combination of 0 and 1 cases
82
83   INTEGER ::   nsbc   ! type of surface boundary condition (deduced from namsbc informations)
84   INTEGER ::   nice   ! type of ice in the surface boundary condition (deduced from namsbc informations)
85   LOGICAL :: lfirst = .TRUE. ! initialisation flag
86     
87   !! * Substitutions
88#  include "domzgr_substitute.h90"
89   !!----------------------------------------------------------------------
90   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
91   !! $Id: sbcmod.F90 1172 2008-09-10 15:32:47Z ctlod $
92   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
93   !!----------------------------------------------------------------------
94
95CONTAINS
96
97   SUBROUTINE sbc_init_tam
98      !!---------------------------------------------------------------------
99      !!                    ***  ROUTINE sbc_init_tam ***
100      !!
101      !! ** Purpose of the direct routine:
102      !!           Initialisation of the ocean surface boundary computation
103      !!
104      !! ** Method  :   Read the namsbc namelist and set derived parameters
105      !!
106      !! ** Action  : - read namsbc parameters
107      !!              - nsbc: type of sbc
108      !!----------------------------------------------------------------------
109      INTEGER ::   icpt      ! temporary integer
110      !!
111      NAMELIST/namsbc/ nn_fsbc, ln_ana, ln_flx, ln_blk_clio, ln_blk_core, ln_cpl,   &
112         &             ln_dm2dc, ln_rnf, ln_ssr, nn_fwb, nn_ico_cpl
113      !!----------------------------------------------------------------------
114
115      IF (lfirst) THEN
116
117         CALL sbc_init
118         IF( nn_ice == 0  )   fr_i_tl(:,:) = 0.e0       ! no ice in the domain, ice fraction is always zero
119         lfirst = .FALSE.
120      END IF
121      !
122   END SUBROUTINE sbc_init_tam
123
124
125   SUBROUTINE sbc_tan( kt )
126      !!---------------------------------------------------------------------
127      !!                    ***  ROUTINE sbc_tan  ***
128      !!             
129      !! ** Purpose of the direct routine:
130      !!                provide at each time-step the ocean surface boundary
131      !!                condition (momentum, heat and freshwater fluxes)
132      !!
133      !! ** Method  :   blah blah  to be written ?????????
134      !!                CAUTION : never mask the surface stress field (tke sbc)
135      !!
136      !! ** Action  : - set the ocean surface boundary condition, i.e. 
137      !!                utau, vtau, qns, qsr, emp, emps, qrp, erp
138      !!              - updte the ice fraction : fr_i
139      !!----------------------------------------------------------------------
140      INTEGER, INTENT(in) ::   kt       ! ocean time step
141      !!---------------------------------------------------------------------
142
143      ! ocean to sbc mean sea surface variables (ss._m)
144      ! ---------------------------------------
145      CALL sbc_ssm_tan( kt )                         ! sea surface mean currents (at U- and V-points),
146      !                                          ! temperature and salinity (at T-point) over nf_sbc time-step
147      !                                          ! (i.e. sst_m, sss_m, ssu_m, ssv_m)
148
149      ! sbc formulation
150      ! ---------------
151         
152      SELECT CASE( nsbc )                        ! Compute ocean surface boundary condition
153      !                                          ! (i.e. utau,vtau, qns, qsr, emp, emps)
154      CASE(  0 )   ;   CALL sbc_gyre_tan    ( kt )      ! analytical formulation : GYRE configuration
155         ! no! in default
156      !CASE(  1 )   ;   CALL sbc_ana_tan     ( kt )      ! analytical formulation : uniform sbc
157      CASE(  2 )   ;   CALL sbc_flx_tan     ( kt )      ! flux formulation
158      !CASE(  3 )   ;   CALL sbc_blk_clio_tan( kt )      ! bulk formulation : CLIO for the ocean
159      !CASE(  4 )   ;   CALL sbc_blk_core_tan( kt )      ! bulk formulation : CORE for the ocean
160      !CASE(  5 )   ;   CALL sbc_cpl_tan     ( kt )      ! coupled formulation
161      END SELECT
162
163      ! Misc. Options
164      ! -------------
165      ! not available
166!*B      SELECT CASE( nn_ice )                                     ! Update heat and freshwater fluxes over sea-ice areas
167!*B      CASE(  1 )   ;       CALL sbc_ice_if_tan   ( kt )                   ! Ice-cover climatology ("Ice-if" model)
168!*B         !                                                     
169!*B      CASE(  2 )   ;       CALL sbc_ice_lim_2_tan( kt, nsbc )             ! LIM 2.0 ice model
170!*B         !                                                     
171!*B      CASE(  3 )   ;       CALL sbc_ice_lim_tan  ( kt, nsbc, nn_ico_cpl)  ! LIM 3.0 ice model
172!*B      END SELECT                                             
173
174      ! add runoffs to fresh water fluxes... not needed in tangent
175 
176      IF( ln_ssr       )   CALL sbc_ssr_tan( kt )                   ! add SST/SSS damping term
177
178      IF( nn_fwb  /= 0 )   CALL sbc_fwb_tan( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget
179
180      IF( nclosea == 1 )   CALL sbc_clo_tan( kt )                   ! treatment of closed sea in the model domain
181      !                                                         ! (update freshwater fluxes)
182      !
183!RBbug do not understand why see ticket 667
184      CALL lbc_lnk( emp_tl, 'T', 1. ) 
185      !
186      !
187   END SUBROUTINE sbc_tan
188
189   !!======================================================================
190   SUBROUTINE sbc_adj( kt )
191      !!---------------------------------------------------------------------
192      !!                    ***  ROUTINE sbc_adj  ***
193      !!             
194      !! ** Purpose of the direct routine:
195      !!                provide at each time-step the ocean surface boundary
196      !!                condition (momentum, heat and freshwater fluxes)
197      !!
198      !! ** Method  :   blah blah  to be written ?????????
199      !!                CAUTION : never mask the surface stress field (tke sbc)
200      !!
201      !! ** Action  : - set the ocean surface boundary condition, i.e. 
202      !!                utau, vtau, qns, qsr, emp, emps, qrp, erp
203      !!              - updte the ice fraction : fr_i
204      !!----------------------------------------------------------------------
205      INTEGER, INTENT(in) ::   kt       ! ocean time step
206      !!---------------------------------------------------------------------
207
208      ! Misc. Options
209      ! -------------
210!RBbug do not understand why see ticket 667
211      CALL lbc_lnk_adj( emp_ad, 'T', 1. ) 
212      !
213      IF( nclosea == 1 )   CALL sbc_clo_adj( kt )                   ! treatment of closed sea in the model domain
214      IF( nn_fwb  /= 0 )   CALL sbc_fwb_adj( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget
215      IF( ln_ssr       )   CALL sbc_ssr_adj( kt )                   ! add SST/SSS damping term
216      SELECT CASE( nn_ice )                                     ! Update heat and freshwater fluxes over ice-covered areas
217!      CASE(  1 )   ;       CALL sbc_ice_if_adj ( kt )                     ! Ice-cover climatology ("Ice-if" model)
218         !                                                     
219!      CASE(  2 )   ;       CALL sbc_ice_lim_2_adj( kt, nsbc )             ! LIM 2.0 ice model
220         !                                                     
221!      CASE(  3 )   ;       CALL sbc_ice_lim_adj  ( kt, nsbc, nn_ico_cpl)  ! LIM 3.0 ice model
222      END SELECT                                             
223      ! sbc formulation
224      ! ---------------
225         
226      SELECT CASE( nsbc )                        ! Compute ocean surface boundary condition
227      !                                          ! (i.e. utau,vtau, qns, qsr, emp, emps)
228      CASE(  0 )   ;   CALL sbc_gyre_adj    ( kt )      ! analytical formulation : GYRE configuration
229!      CASE(  1 )   ;   CALL sbc_ana_adj     ( kt )      ! analytical formulation : uniform sbc
230      CASE(  2 )   ;   CALL sbc_flx_adj     ( kt )      ! flux formulation
231!      CASE(  3 )   ;   CALL sbc_blk_clio_adj( kt )      ! bulk formulation : CLIO for the ocean
232!      CASE(  4 )   ;   CALL sbc_blk_core_adj( kt )      ! bulk formulation : CORE for the ocean
233!      CASE(  5 )   ;   CALL sbc_cpl_adj     ( kt )      ! coupled formulation
234      END SELECT
235      ! ocean to sbc mean sea surface variables (ss._m)
236      ! ---------------------------------------
237      CALL sbc_ssm_adj( kt )                         ! sea surface mean currents (at U- and V-points),
238      !                                          ! temperature and salinity (at T-point) over nf_sbc time-step
239      !                                          ! (i.e. sst_m, sss_m, ssu_m, ssv_m)
240
241
242   END SUBROUTINE sbc_adj
243   SUBROUTINE sbc_adj_tst( kumadt )
244      !!-----------------------------------------------------------------------
245      !!
246      !!                  ***  ROUTINE sbc_adj_tst ***
247      !!
248      !! ** Purpose : Test the adjoint routine.
249      !!
250      !! ** Method  : Verify the scalar product
251      !!           
252      !!                 ( L dx )^T W dy  =  dx^T L^T W dy
253      !!
254      !!              where  L   = tangent routine
255      !!                     L^T = adjoint routine
256      !!                     W   = diagonal matrix of scale factors
257      !!                     dx  = input perturbation (random field)
258      !!                     dy  = L dx
259      !!
260      !!-----------------------------------------------------------------------
261      !! * Modules used
262
263      !! * Arguments
264      INTEGER, INTENT(IN) :: &
265         & kumadt             ! Output unit
266      CALL sbc_init_tam         ! Read namsbc namelist : surface module     
267!
268      CALL sbc_fwb_adj_tst( kumadt )       ! control the freshwater budget
269      CALL sbc_ssr_adj_tst( kumadt )       ! add SST/SSS damping term
270!      CALL sbc_rnf_adj_tst( kumadt )       ! add runoffs to fresh water fluxes
271!      CALL sbc_ice_if_adj_tst( kumadt )    ! Ice-cover climatology ("Ice-if" model)
272!      CALL sbc_ice_lim_2_adj_tst( kumadt ) ! LIM 2.0 ice model
273!      CALL sbc_ice_lim_adj_tst( kumadt )   ! LIM 3.0 ice model
274      CALL sbc_gyre_adj_tst( kumadt )      ! analytical formulation : GYRE configuration
275!      CALL sbc_ana_adj_tst( kumadt )       ! analytical formulation : uniform sbc
276      CALL sbc_flx_adj_tst( kumadt )        ! flux formulation
277!      CALL sbc_blk_clio_adj_tst( kumadt )  ! bulk formulation : CLIO for the ocean
278!      CALL sbc_blk_core_adj_tst( kumadt )  ! bulk formulation : CORE for the ocean
279!      CALL sbc_cpl_adj_tst( kumadt )       ! coupled formulation
280      CALL sbc_ssm_adj_tst( kumadt )       ! sea surface mean currents (at U- and V-points),
281      IF( nclosea == 1 ) CALL sbc_clo_adj_tst( kumadt )       ! closed seas,
282
283   END SUBROUTINE sbc_adj_tst
284   !!======================================================================
285#endif
286END MODULE sbcmod_tam
Note: See TracBrowser for help on using the repository browser.