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.
taumod.F90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/taumod.F90 @ 841

Last change on this file since 841 was 841, checked in by rblod, 16 years ago

Light changes in SBC routines to use classical CLIO bulks with LIM3

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.7 KB
Line 
1MODULE taumod
2   !!======================================================================
3   !!                       ***  MODULE  taumod  ***
4   !! Ocean forcing : stress at the the ocean surface
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   tau          : define the surface stress for the ocean
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE dom_oce         ! ocean space and time domain
12   USE phycst          ! physical constants
13   USE in_out_manager  ! I/O manager
14   USE daymod          ! calendar
15   USE lbclnk          !
16
17#if defined key_oasis3 || defined key_oasis4
18   USE geo2ocean, only : repcmo
19   USE ice, only       : frld       ! : leads fraction = 1-a/totalarea
20#if defined key_oasis3
21   USE cpl_oasis3      ! OASIS3 coupling (to ECHAM5)
22#elif defined key_oasis4
23   USE cpl_oasis4      ! OASIS4 coupling (to ECHAM5)
24#endif
25#endif
26   IMPLICIT NONE
27   PRIVATE
28
29   !! * Routine accessibility
30   PUBLIC tau                ! routine called by step.F90
31
32  !! * Share modules variables
33   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &
34      taux, tauy,      &  !: surface stress components in (i,j) referential
35      ! TAU BUG
36#if defined key_lim3
37      tauxw, tauyw,    &  !: surface wind stress components in (i,j) referential
38      slotx, sloty,    &  !: time-slope for surface windstress in (i,j) referential
39      tauxg, tauyg        !: surface stress components in geographical
40      !                   !  referential (used in output)
41#endif
42
43   !!----------------------------------------------------------------------
44   !!   OPA 9.0 , LOCEAN-IPSL (2005)
45   !! $Header$
46   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
47   !!----------------------------------------------------------------------
48
49#if defined key_tau_monthly
50   ! Monthly climatology in (i,j) referential  (i-comp. at U-pt and j-comp. at V-pt)
51   !!----------------------------------------------------------------------
52   !!   'key_tau_monthly'                        MONTHLY climatology stress
53   !!   default case                                   NetCDF files
54   !!----------------------------------------------------------------------
55#   include "tau_forced_monthly.h90"
56
57# elif defined key_tau_daily
58   !!----------------------------------------------------------------------
59   !!   'key_tau_daily'                                 DAILY stress
60   !!                                                   NetCDF files
61   !!----------------------------------------------------------------------
62   ! Daily climatology/interannual in (i,j) referential  (i-comp. at U-pt and j-comp. at V-pt)
63#   include "tau_forced_daily.h90"
64
65#elif defined key_oasis3  ||  defined key_oasis4
66   ! Coupled case : stress at the coupling frequency
67   !!----------------------------------------------------------------------
68   !!   'key_oasis3' or 'key_oasis4' and           Coupled Ocean/Atmosphere
69   !!   'key_lim3'or 'key_lim2'                              LIM sea-ice
70   !!----------------------------------------------------------------------
71   ! New way: 3D referential link to the earth (avoid north pole pb)
72   ! (3 component stress defined at U- and V-points)
73#  include "tau_oasis_ice.h90"
74#else
75   !!----------------------------------------------------------------------
76   !!   Default option                                     constant forcing
77   !!----------------------------------------------------------------------
78   !! * local modules variables
79   INTEGER  ::       & !!! * Namelist numtau *
80      ntau000 = 1       ! nb of time-step during which the surface stress
81      !                 ! increase from 0 to its nominal value (taudta) (>0)
82   REAL(wp) ::       & !!! * Namelist numtau *
83      tau0x = 0.e0 , &  ! constant wind stress value in i-direction
84      tau0y = 0.e0      ! constant wind stress value in j-direction
85   !!----------------------------------------------------------------------
86
87CONTAINS
88
89   SUBROUTINE tau( kt )
90      !!---------------------------------------------------------------------
91      !!                    ***  ROUTINE tau  ***
92      !!
93      !! ** Purpose :   provide the ocean surface stress at each time step
94      !!
95      !! ** Method  :   Constant surface stress increasing from 0 to taudta
96      !!      value during the first ntau000 time-step (namelist)
97      !!        CAUTION: never mask the surface stress field !
98      !!
99      !! ** Action  : - update taux , tauy the stress in (i,j) ref.
100      !!
101      !! History :
102      !!   4.0  !  91-03  (G. Madec)  Original code
103      !!   8.5  !  02-11  (G. Madec)  F90: Free form and module
104      !!----------------------------------------------------------------------
105      !! * Arguments
106      INTEGER, INTENT( in  ) ::   kt    ! ocean time step
107      REAL(wp) ::   ztau, ztau_sais, &  ! wind intensity and of the seasonal cycle
108         ztime,                      &  ! time in hour
109         ztimemax, ztimemin,         &  ! 21th June, and 21th decem. if date0 = 1st january
110         ztaun                          ! intensity
111      INTEGER  ::   ji, jj              ! dummy loop indices
112
113      INTEGER  ::           &
114         zyear0,            &           ! initial year
115         zmonth0,           &           ! initial month
116         zday0,             &           ! initial day
117         zday_year0                    ! initial day since january 1st
118       
119
120      !! * Local declarations
121      REAL(wp) ::   zfacto              !
122
123      NAMELIST/namtau/ ntau000, tau0x, tau0y
124      !!---------------------------------------------------------------------
125
126      IF( cp_cfg == 'gyre' ) THEN
127
128         zyear0  = ndate0 / 10000                             ! initial year
129         zmonth0 = ( ndate0 - zyear0 * 10000 ) / 100          ! initial month
130         zday0   = ndate0 - zyear0 * 10000 - zmonth0 * 100    ! initial day betwen 1 and 30
131
132         zday_year0 = (zmonth0-1)*30.+zday0                   ! initial day betwen 1 and 360
133
134         ! current day (in hours) since january the 1st of the current year
135          ztime = FLOAT( kt ) * rdt / (rmmss * rhhmm)  &    !  total incrementation (in hours)
136             &     - (nyear  - 1) * rjjhh * raajj           !  minus years since beginning of experiment (in hours)
137
138
139        ! 21th june at 24h in hours
140         ztimemax = ((5.*30.)+21.)* 24.
141         ! 21th december day in hours
142         ! rjjhh * raajj / 4 = 1 seasonal cycle in hours
143         ztimemin = ztimemax + rjjhh * raajj / 2 
144
145         ! mean intensity at 0.105/srqt(2) because projected with 45deg angle
146         ztau = 0.105 / SQRT(2.)           
147         ! seasonal oscillation intensity
148         ztau_sais = 0.015                 
149         ztaun = ztau - ztau_sais * COS( (ztime - ztimemax) / (ztimemin - ztimemax) * rpi )
150         DO jj = 1, jpj
151            DO ji = 1, jpi
152              ! domain from 15deg to 50deg and 1/2 period along 14deg
153              ! so 5/4 of half period with seasonal cycle
154              taux (ji,jj) = - ztaun * SIN( rpi * (gphiu(ji,jj) - 15.) / (29.-15.) )
155              tauy (ji,jj) =   ztaun * SIN( rpi * (gphiv(ji,jj) - 15.) / (29.-15.) )
156            END DO
157         END DO
158   
159         IF( kt == nit000 .AND. lwp ) THEN
160            WRITE(numout,*)' tau    : analytical formulation for gyre'
161            WRITE(numout,*)' ~~~~~~~ '
162            WRITE(numout,*)'          nyear      = ', nyear
163            WRITE(numout,*)'          nmonth     = ', nmonth
164            WRITE(numout,*)'          nday       = ', nday
165            WRITE(numout,*)'          nday_year  = ',nday_year
166            WRITE(numout,*)'          ndastp     = ',ndastp
167            WRITE(numout,*)'          adatrj     = ',adatrj
168            WRITE(numout,*)'          ztime      = ',ztime
169            WRITE(numout,*)'          ztimemax   = ',ztimemax
170            WRITE(numout,*)'          ztimemin   = ',ztimemin
171            WRITE(numout,*)'          zyear0     = ', zyear0
172            WRITE(numout,*)'          zmonth0    = ', zmonth0
173            WRITE(numout,*)'          zday0      = ', zday0
174            WRITE(numout,*)'          zday_year0 = ',zday_year0
175            WRITE(numout,*)'          raajj      = ', raajj
176            WRITE(numout,*)'          ztau       = ', ztau
177            WRITE(numout,*)'          ztau_sais  = ', ztau_sais
178            WRITE(numout,*)'          ztaun      = ', ztaun
179         ENDIF
180   
181      ELSE
182
183         IF( kt == nit000 ) THEN
184   
185            ! Read Namelist namtau : surface wind stress
186            ! --------------------
187            REWIND ( numnam )
188            READ   ( numnam, namtau )
189   
190            IF(lwp) WRITE(numout,*)' '
191            IF(lwp) WRITE(numout,*)' tau     : Constant surface wind stress read in namelist'
192            IF(lwp) WRITE(numout,*)' ~~~~~~~ '
193            IF(lwp) WRITE(numout,*)'           Namelist namtau: set the constant stress values'
194            IF(lwp) WRITE(numout,*)'              spin up of the stress  ntau000 = ', ntau000, ' time-steps'
195            IF(lwp) WRITE(numout,*)'              constant i-stress      tau0x   = ', tau0x  , ' N/m2'
196            IF(lwp) WRITE(numout,*)'              constant j-stress      tau0y   = ', tau0y  , ' N/m2'
197   
198            ntau000 = MAX( ntau000, 1 )   ! must be >= 1
199   
200         ENDIF
201   
202         ! Increase the surface stress to its nominal value in ntau000 time-step
203         
204         IF( kt <= ntau000 ) THEN
205            zfacto = 0.5 * (  1. - COS( rpi * FLOAT( kt ) / FLOAT( ntau000 ) )  )
206            taux (:,:) = zfacto * tau0x
207            tauy (:,:) = zfacto * tau0y
208         ENDIF
209
210      ENDIF
211     
212   END SUBROUTINE tau
213#endif
214   !!======================================================================
215END MODULE taumod
Note: See TracBrowser for help on using the repository browser.