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.
sbc_oce.F90 in branches/2012/dev_r3389_INGV4_stokes/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2012/dev_r3389_INGV4_stokes/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90 @ 3529

Last change on this file since 3529 was 3529, checked in by adani, 11 years ago

Read 2d Stokes Drift (U,V) and wavenumber, compute the 3D fields and the vertical component of the Stokes Drift.

  • Property svn:keywords set to Id
File size: 10.3 KB
Line 
1MODULE sbc_oce
2   !!======================================================================
3   !!                       ***  MODULE  sbc_oce  ***
4   !! Surface module :   variables defined in core memory
5   !!======================================================================
6   !! History :  3.0  ! 2006-06  (G. Madec)  Original code
7   !!             -   ! 2008-08  (G. Madec)  namsbc moved from sbcmod
8   !!            3.3  ! 2010-04  (M. Leclair, G. Madec)  Forcing averaged over 2 time steps
9   !!             -   ! 2010-11  (G. Madec) ice-ocean stress always computed at each ocean time-step
10   !!            3.3  ! 2010-10  (J. Chanut, C. Bricaud)  add the surface pressure forcing
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   sbc_oce_alloc : allocation of sbc arrays
15   !!   sbc_tau2wnd   : wind speed estimated from wind stress
16   !!----------------------------------------------------------------------
17   USE par_oce        ! ocean parameters
18   USE in_out_manager ! I/O manager
19   USE lib_mpp        ! MPP library
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   sbc_oce_alloc   ! routine called in sbcmod.F90
25   PUBLIC   sbc_tau2wnd     ! routine called in several sbc modules
26   
27   !!----------------------------------------------------------------------
28   !!           Namelist for the Ocean Surface Boundary Condition
29   !!----------------------------------------------------------------------
30   !                                            !!* namsbc namelist *
31   LOGICAL , PUBLIC ::   ln_ana      = .FALSE.   !: analytical boundary condition flag
32   LOGICAL , PUBLIC ::   ln_flx      = .FALSE.   !: flux      formulation
33   LOGICAL , PUBLIC ::   ln_blk_clio = .FALSE.   !: CLIO bulk formulation
34   LOGICAL , PUBLIC ::   ln_blk_core = .FALSE.   !: CORE bulk formulation
35   LOGICAL , PUBLIC ::   ln_blk_mfs  = .FALSE.   !: MFS  bulk formulation
36   LOGICAL , PUBLIC ::   ln_cpl      = .FALSE.   !: coupled   formulation (overwritten by key_sbc_coupled )
37   LOGICAL , PUBLIC ::   ln_dm2dc    = .FALSE.   !: Daily mean to Diurnal Cycle short wave (qsr)
38   LOGICAL , PUBLIC ::   ln_rnf      = .FALSE.   !: runoffs / runoff mouths
39   LOGICAL , PUBLIC ::   ln_ssr      = .FALSE.   !: Sea Surface restoring on SST and/or SSS     
40   LOGICAL , PUBLIC ::   ln_apr_dyn  = .FALSE.   !: Atmospheric pressure forcing used on dynamics (ocean & ice)
41   INTEGER , PUBLIC ::   nn_ice      = 0         !: flag on ice in the surface boundary condition (=0/1/2/3)
42   INTEGER , PUBLIC ::   nn_fwb      = 0         !: FreshWater Budget:
43   !                                             !:  = 0 unchecked
44   !                                             !:  = 1 global mean of e-p-r set to zero at each nn_fsbc time step
45   !                                             !:  = 2 annual global mean of e-p-r set to zero
46   LOGICAL , PUBLIC ::   ln_wave     = .FALSE.   !: true if some coupling with wave model
47   LOGICAL , PUBLIC ::   ln_cdgw     = .FALSE.   !: true if neutral drag coefficient from wave model
48   LOGICAL , PUBLIC ::   ln_sdw      = .FALSE.   !: true if 3d stokes drift from wave model
49
50   !!----------------------------------------------------------------------
51   !!              Ocean Surface Boundary Condition fields
52   !!----------------------------------------------------------------------
53   LOGICAL , PUBLIC ::   lhftau = .FALSE.        !: HF tau used in TKE: mean(stress module) - module(mean stress)
54   !!                                   !!   now    ! before   !!
55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   utau   , utau_b   !: sea surface i-stress (ocean referential)     [N/m2]
56   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vtau   , vtau_b   !: sea surface j-stress (ocean referential)     [N/m2]
57   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   taum              !: module of sea surface stress (at T-point)    [N/m2]
58   !! wndm is used onmpute surface gases exchanges in ice-free ocean or leads
59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wndm              !: wind speed module at T-point (=|U10m-Uoce|)  [m/s]
60   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsr               !: sea heat flux:     solar                     [W/m2]
61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qns    , qns_b    !: sea heat flux: non solar                     [W/m2]
62   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsr_tot           !: total     solar heat flux (over sea and ice) [W/m2]
63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qns_tot           !: total non solar heat flux (over sea and ice) [W/m2]
64   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emp    , emp_b    !: freshwater budget: volume flux               [Kg/m2/s]
65   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emps   , emps_b   !: freshwater budget: concentration/dillution   [Kg/m2/s]
66   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emp_tot           !: total E-P over ocean and ice                 [Kg/m2/s]
67   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rnf    , rnf_b    !: river runoff   [Kg/m2/s] 
68   !!
69   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  sbc_tsc, sbc_tsc_b  !: sbc content trend                      [K.m/s] jpi,jpj,jpts
70   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  qsr_hc , qsr_hc_b   !: heat content trend due to qsr flux     [K.m/s] jpi,jpj,jpk
71   !!
72   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tprecip           !: total precipitation                          [Kg/m2/s]
73   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sprecip           !: solid precipitation                          [Kg/m2/s]
74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fr_i              !: ice fraction = 1 - lead fraction      (between 0 to 1)
75#if defined key_cpl_carbon_cycle
76   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   atm_co2           !: atmospheric pCO2                             [ppm]
77#endif
78
79   !!----------------------------------------------------------------------
80   !!                     Sea Surface Mean fields
81   !!----------------------------------------------------------------------
82   INTEGER , PUBLIC                     ::   nn_fsbc   !: frequency of sbc computation (as well as sea-ice model)
83   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssu_m     !: mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
84   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssv_m     !: mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
85   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sst_m     !: mean (nn_fsbc time-step) surface sea temperature     [Celsius]
86   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sss_m     !: mean (nn_fsbc time-step) surface sea salinity            [psu]
87   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssh_m     !: mean (nn_fsbc time-step) sea surface height                [m]
88
89   !! * Substitutions
90#  include "vectopt_loop_substitute.h90"
91   !!----------------------------------------------------------------------
92   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
93   !! $Id$
94   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
95   !!----------------------------------------------------------------------
96CONTAINS
97
98   INTEGER FUNCTION sbc_oce_alloc()
99      !!---------------------------------------------------------------------
100      !!                  ***  FUNCTION sbc_oce_alloc  ***
101      !!---------------------------------------------------------------------
102      INTEGER :: ierr(4)
103      !!---------------------------------------------------------------------
104      ierr(:) = 0
105      !
106      ALLOCATE( utau(jpi,jpj) , utau_b(jpi,jpj) , taum(jpi,jpj) ,     &
107         &      vtau(jpi,jpj) , vtau_b(jpi,jpj) , wndm(jpi,jpj) , STAT=ierr(1) ) 
108         !
109      ALLOCATE( qns_tot(jpi,jpj) , qns   (jpi,jpj) , qns_b(jpi,jpj),        &
110         &      qsr_tot(jpi,jpj) , qsr   (jpi,jpj) ,                        &
111         &      emp    (jpi,jpj) , emp_b (jpi,jpj) ,                        &
112         &      emps   (jpi,jpj) , emps_b(jpi,jpj) , emp_tot(jpi,jpj) , STAT=ierr(2) )
113         !
114      ALLOCATE( rnf  (jpi,jpj) , sbc_tsc  (jpi,jpj,jpts) , qsr_hc  (jpi,jpj,jpk) ,     &
115         &      rnf_b(jpi,jpj) , sbc_tsc_b(jpi,jpj,jpts) , qsr_hc_b(jpi,jpj,jpk) , STAT=ierr(3) )
116         !
117      ALLOCATE( tprecip(jpi,jpj) , sprecip(jpi,jpj) , fr_i(jpi,jpj) ,     &
118#if defined key_cpl_carbon_cycle
119         &      atm_co2(jpi,jpj) ,                                        &
120#endif
121         &      ssu_m  (jpi,jpj) , sst_m(jpi,jpj) ,                       &
122         &      ssv_m  (jpi,jpj) , sss_m  (jpi,jpj), ssh_m(jpi,jpj) , STAT=ierr(4) )
123         !
124      sbc_oce_alloc = MAXVAL( ierr )
125      IF( lk_mpp            )   CALL mpp_sum ( sbc_oce_alloc )
126      IF( sbc_oce_alloc > 0 )   CALL ctl_warn('sbc_oce_alloc: allocation of arrays failed')
127      !
128   END FUNCTION sbc_oce_alloc
129
130
131   SUBROUTINE sbc_tau2wnd
132      !!---------------------------------------------------------------------
133      !!                    ***  ROUTINE sbc_tau2wnd  ***
134      !!                   
135      !! ** Purpose : Estimation of wind speed as a function of wind stress   
136      !!
137      !! ** Method  : |tau|=rhoa*Cd*|U|^2
138      !!---------------------------------------------------------------------
139      USE dom_oce         ! ocean space and time domain
140      USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
141      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
142      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
143      REAL(wp) ::   ztx, zty, ztau, zcoef ! temporary variables
144      INTEGER  ::   ji, jj                ! dummy indices
145      !!---------------------------------------------------------------------
146      zcoef = 0.5 / ( zrhoa * zcdrag ) 
147!CDIR NOVERRCHK
148      DO jj = 2, jpjm1
149!CDIR NOVERRCHK
150         DO ji = fs_2, fs_jpim1   ! vect. opt.
151            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
152            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
153            ztau = SQRT( ztx * ztx + zty * zty )
154            wndm(ji,jj) = SQRT ( ztau * zcoef ) * tmask(ji,jj,1)
155         END DO
156      END DO
157      CALL lbc_lnk( wndm(:,:) , 'T', 1. )
158      !
159   END SUBROUTINE sbc_tau2wnd
160
161   !!======================================================================
162END MODULE sbc_oce
Note: See TracBrowser for help on using the repository browser.