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

source: trunk/NEMO/OPA_SRC/SBC/sbc_oce.F90 @ 1534

Last change on this file since 1534 was 1534, checked in by cetlod, 15 years ago

Improve the coupling interface for the carbon cycle, see ticket:488

  • Property svn:keywords set to Id
File size: 6.8 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   !!----------------------------------------------------------------------
9   USE par_oce          ! ocean parameters
10
11   IMPLICIT NONE
12   PRIVATE
13   
14   PUBLIC sbc_tau2wnd   ! compute wind speed based on the wind stress
15   
16   !!----------------------------------------------------------------------
17   !!           Namelist for the Ocean Surface Boundary Condition
18   !!----------------------------------------------------------------------
19   !                                             !! * namsbc namelist *
20   LOGICAL , PUBLIC ::   ln_ana      = .FALSE.   !: analytical boundary condition flag
21   LOGICAL , PUBLIC ::   ln_flx      = .FALSE.   !: flux      formulation
22   LOGICAL , PUBLIC ::   ln_blk_clio = .FALSE.   !: CLIO bulk formulation
23   LOGICAL , PUBLIC ::   ln_blk_core = .FALSE.   !: CORE bulk formulation
24   LOGICAL , PUBLIC ::   ln_cpl      = .FALSE.   !: coupled   formulation (overwritten by key_sbc_coupled )
25   LOGICAL , PUBLIC ::   ln_dm2dc    = .FALSE.   !: Daily mean to Diurnal Cycle short wave (qsr)
26   LOGICAL , PUBLIC ::   ln_rnf      = .FALSE.   !: runoffs / runoff mouths
27   LOGICAL , PUBLIC ::   ln_ssr      = .FALSE.   !: Sea Surface restoring on SST and/or SSS     
28   INTEGER , PUBLIC ::   nn_ice      = 0         !: flag on ice in the surface boundary condition (=0/1/2/3)
29   INTEGER , PUBLIC ::   nn_fwb      = 0         !: FreshWater Budget:
30   !                                             !:  = 0 unchecked
31   !                                             !:  = 1 global mean of e-p-r set to zero at each nn_fsbc time step
32   !                                             !:  = 2 annual global mean of e-p-r set to zero
33  INTEGER , PUBLIC ::   nn_ico_cpl  = 0          !: ice-ocean coupling indicator
34   !                                             !:  = 0   LIM-3 old case
35   !                                             !:  = 1   stresses computed using now ocean velocity
36   !                                             !:  = 2   combination of 0 and 1 cases
37
38   !!----------------------------------------------------------------------
39   !!              Ocean Surface Boundary Condition fields
40   !!----------------------------------------------------------------------
41   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   utau      !: sea surface i-stress (ocean referential)     [N/m2]
42   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   vtau      !: sea surface j-stress (ocean referential)     [N/m2]
43   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   wndm      !: wind speed module at T-point (=|U10m-Uoce|)  [m/s]
44   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qsr       !: sea heat flux:     solar                     [W/m2]
45   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qns       !: sea heat flux: non solar                     [W/m2]
46   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qsr_tot   !: total     solar heat flux (over sea and ice) [W/m2]
47   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qns_tot   !: total non solar heat flux (over sea and ice) [W/m2]
48   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp       !: freshwater budget: volume flux               [Kg/m2/s]
49   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emps      !: freshwater budget: concentration/dillution   [Kg/m2/s]
50   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp_tot   !: total evaporation - (liquid + solid) precpitation over oce and ice
51   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   tprecip   !: total precipitation           [Kg/m2/s]
52   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sprecip   !: solid precipitation           [Kg/m2/s]
53!!$   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rrunoff       !: runoff
54!!$   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   calving       !: calving
55   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr_i      !: ice fraction  (between 0 to 1)               -
56#if defined key_cpl_carbon_cycle
57   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   atm_co2   !: atmospheric pCO2                             [ppm]
58#endif
59
60   !!----------------------------------------------------------------------
61   !!                     Sea Surface Mean fields
62   !!----------------------------------------------------------------------
63   INTEGER , PUBLIC                     ::   nn_fsbc   !: frequency of sbc computation (as well as sea-ice model)
64   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ssu_m     !: mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
65   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ssv_m     !: mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
66   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sst_m     !: mean (nn_fsbc time-step) surface sea temperature     [Celsius]
67   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   sss_m     !: mean (nn_fsbc time-step) surface sea salinity            [psu]
68   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ssh_m     !: mean (nn_fsbc time-step) sea surface height                [m]
69
70   !!----------------------------------------------------------------------
71   !!   OPA 9.0 , LOCEAN-IPSL (2006)
72   !! $ Id: $
73   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
74   !!======================================================================
75CONTAINS
76
77   SUBROUTINE sbc_tau2wnd
78      !!---------------------------------------------------------------------
79      !!                    ***  ROUTINE sbc_tau2wnd  ***
80      !!                   
81      !! ** Purpose : Estimation of wind speed as a function of wind stress   
82      !!
83      !! ** Method  : |tau|=rhoa*Cd*|U|^2
84      !!---------------------------------------------------------------------
85      USE dom_oce         ! ocean space and time domain
86      USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
87      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
88      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
89      REAL(wp) ::   ztx, zty, ztau, zcoef ! temporary variables
90      INTEGER  ::   ji, jj                ! dummy indices
91      !! * Substitutions
92#  include "vectopt_loop_substitute.h90"
93      !!---------------------------------------------------------------------
94      zcoef = 0.5 / ( zrhoa * zcdrag ) 
95!CDIR NOVERRCHK
96      DO jj = 2, jpjm1
97!CDIR NOVERRCHK
98         DO ji = fs_2, fs_jpim1   ! vect. opt.
99            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
100            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
101            ztau = SQRT( ztx * ztx + zty * zty )
102            wndm(ji,jj) = SQRT ( ztau * zcoef ) * tmask(ji,jj,1)
103         END DO
104      END DO
105      CALL lbc_lnk( wndm(:,:) , 'T', 1. )
106
107   END SUBROUTINE sbc_tau2wnd
108
109END MODULE sbc_oce
Note: See TracBrowser for help on using the repository browser.