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 @ 93

Last change on this file since 93 was 93, checked in by opalod, 20 years ago

CT : UPDATE060 : A new configuration, named GYRE, has been added.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 11.1 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   IMPLICIT NONE
18   PRIVATE
19
20   !! * Routine accessibility
21   PUBLIC tau                ! routine called by step.F90
22
23   !! * Share modules variables
24   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &
25      taux, tauy,      &  !: surface stress components in (i,j) referential
26      tauxg, tauyg        !: surface stress components in geographical
27      !                   !  referential (used in output)
28   !!----------------------------------------------------------------------
29   !!   OPA 9.0 , LODYC-IPSL  (2003)
30   !!----------------------------------------------------------------------
31
32#if defined key_tau_monthly
33   ! Monthly climatology in (i,j) referential  (i-comp. at U-pt and j-comp. at V-pt)
34#  if defined key_fdir
35   !!----------------------------------------------------------------------
36   !!   'key_tau_monthly'                        MONTHLY climatology stress
37   !!   'key_fdir'                                  direct access files
38   !!----------------------------------------------------------------------
39#   include "tau_forced_monthly_fdir.h90"
40#  else
41   !!----------------------------------------------------------------------
42   !!   'key_tau_monthly'                        MONTHLY climatology stress
43   !!   default case                                   NetCDF files
44   !!----------------------------------------------------------------------
45#   include "tau_forced_monthly.h90"
46#  endif
47
48# elif defined key_tau_daily
49   !!----------------------------------------------------------------------
50   !!   'key_tau_daily'                                 DAILY stress
51   !!                                                   NetCDF files
52   !!----------------------------------------------------------------------
53   ! Daily climatology/interannual in (i,j) referential  (i-comp. at U-pt and j-comp. at V-pt)
54#   include "tau_forced_daily.h90"
55
56#elif defined key_coupled
57   ! Coupled case : stress at the coupling frequency
58# if defined key_ice_lim
59   !!----------------------------------------------------------------------
60   !!   'key_coupled'                              Coupled Ocean/Atmosphere
61   !!   'key_ice_lim'                                   LIM sea-ice
62   !!----------------------------------------------------------------------
63   ! New way: 3D referential link to the earth (avoid north pole pb)
64   ! (3 component stress defined at U- and V-points)
65#  include "tau_coupled_ice.h90"
66# else
67   !!----------------------------------------------------------------------
68   !!   'key_coupled'                              Coupled Ocean/Atmosphere
69   !!   Default case                                  NO sea-ice
70   !!----------------------------------------------------------------------
71   ! old fashion: geographical referential
72   ! (zonal and meridional stress defined at U- and V-points)
73#  include "tau_coupled.h90"
74# endif
75#else
76   !!----------------------------------------------------------------------
77   !!   Default option                                     constant forcing
78   !!----------------------------------------------------------------------
79   !! * local modules variables
80   INTEGER  ::       & !!! * Namelist numtau *
81      ntau000 = 1       ! nb of time-step during which the surface stress
82      !                 ! increase from 0 to its nominal value (taudta) (>0)
83   REAL(wp) ::       & !!! * Namelist numtau *
84      tau0x = 0.e0 , &  ! constant wind stress value in i-direction
85      tau0y = 0.e0      ! constant wind stress value in j-direction
86   !!----------------------------------------------------------------------
87
88CONTAINS
89
90   SUBROUTINE tau( kt )
91      !!---------------------------------------------------------------------
92      !!                    ***  ROUTINE tau  ***
93      !!
94      !! ** Purpose :   provide the ocean surface stress at each time step
95      !!
96      !! ** Method  :   Constant surface stress increasing from 0 to taudta
97      !!      value during the first ntau000 time-step (namelist)
98      !!        CAUTION: never mask the surface stress field !
99      !!
100      !! ** Action  : - update taux , tauy the stress in (i,j) ref.
101      !!              - update tauxg, tauyg the stress in geographic ref.
102      !!
103      !! History :
104      !!   4.0  !  91-03  (G. Madec)  Original code
105      !!   8.5  !  02-11  (G. Madec)  F90: Free form and module
106      !!----------------------------------------------------------------------
107      !! * Arguments
108      INTEGER, INTENT( in  ) ::   kt    ! ocean time step
109      REAL(wp) ::   ztau, ztau_sais, &  ! wind intensity and of the seasonal cycle
110         ztime,                      &  ! time in hour
111         ztimemax, ztimemin,         &  ! 21th June, and 21th decem. if date0 = 1st january
112         ztaun                          ! intensity
113      INTEGER  ::   ji, jj, &           ! dummy loop indices
114         js                             ! indice for months
115      INTEGER  ::           &
116         zyear0,            &           ! initial year
117         zmonth0,           &           ! initial month
118         zday0,             &           ! initial day
119         zday_year0,        &           ! initial day since january 1st
120         zdaymax
121
122      !! * Local declarations
123      REAL(wp) ::   zfacto              !
124
125      NAMELIST/namtau/ ntau000, tau0x, tau0y
126      !!---------------------------------------------------------------------
127
128      IF( cp_cfg == 'gyre' ) THEN
129
130         ! same wind as in Wico
131         !test date0 : ndate0 = 010203
132         zyear0  = ndate0 / 10000
133         zmonth0 = ( ndate0 - zyear0 * 10000 ) / 100
134         zday0   = ndate0 - zyear0 * 10000 - zmonth0 * 100
135         !Calculates nday_year, day since january 1st
136         zday_year0 = zday0
137         !accumulates days of previous months of this year
138
139         DO js = 1, zmonth0
140            IF(nleapy > 1) THEN
141               zday_year0 = zday_year0 + nleapy
142            ELSE
143               IF( MOD(zyear0, 4 ) == 0 ) THEN
144                  zday_year0 = zday_year0 + nbiss(js)
145               ELSE
146                  zday_year0 = zday_year0 + nobis(js)
147               ENDIF
148            ENDIF
149         END DO
150   
151         ! day (in hours) since january the 1st
152         ztime = FLOAT( kt ) * rdt / (rmmss * rhhmm)  &  ! incrementation in hour
153            &     - (nyear - 1) * rjjhh * raajj       &  !  - nber of hours the precedent years
154            &     + zday_year0 / 24                      ! nber of hours initial date
155         ! day 21th counted since the 1st January
156         zdaymax = 21                                    ! 21th day of the month
157         DO js = 1, 5                                    ! count each day  until end May
158           IF(nleapy > 1) THEN
159               zdaymax = zdaymax + nleapy
160           ELSE
161               IF( MOD(zyear0, 4 ) == 0 ) THEN
162                   zdaymax = zdaymax + nbiss(js)
163               ELSE
164                   zdaymax = zdaymax + nobis(js)
165               ENDIF
166           ENDIF
167         END DO
168        ! 21th june in hours
169         ztimemax = zdaymax * 24
170         ! 21th december day in hours
171         ztimemin = ztimemax + rjjhh * raajj / 2  ! rjjhh * raajj / 4 = 1 seasonal cycle in hours
172   
173         ztau = 0.105 / SQRT(2.)            ! mean intensity at 0.105 ; srqt(2) because projected with 45° angle
174         ztau_sais = 0.015                  ! seasonal oscillation intensity
175         ztaun = ztau - ztau_sais * COS( (ztime - ztimemax) / (ztimemin - ztimemax) * rpi )
176         DO jj = 1, jpj
177            DO ji = 1, jpi
178              ! domain from 15° to 50° and 1/2 period along 14° so 5/4 of half period with seasonal cycle
179              taux (ji,jj) = - ztaun * SIN( rpi * (gphiu(ji,jj) - 15.) / (29.-15.) )
180              tauy (ji,jj) =   ztaun * SIN( rpi * (gphiv(ji,jj) - 15.) / (29.-15.) )
181            END DO
182         END DO
183   
184         IF( kt == nit000 ) THEN
185            IF(lwp) WRITE(numout,*)' tau     : Constant surface wind stress read in namelist'
186            IF(lwp) WRITE(numout,*)' ~~~~~~~ '
187            IF(lwp) WRITE(numout,*)'nyear      = ', nyear
188            IF(lwp) WRITE(numout,*)'nmonth     = ', nmonth
189            IF(lwp) WRITE(numout,*)'nday       = ', nday
190            IF(lwp) WRITE(numout,*)'nday_year  = ',nday_year
191            IF(lwp) WRITE(numout,*)'ndastp     = ',ndastp
192            IF(lwp) WRITE(numout,*)'adatrj     = ',adatrj
193            IF(lwp) WRITE(numout,*)'ztime      = ',ztime
194            IF(lwp) WRITE(numout,*)'zdaymax    = ',zdaymax
195   
196            IF(lwp) WRITE(numout,*)'ztimemax   = ',ztimemax
197            IF(lwp) WRITE(numout,*)'ztimemin   = ',ztimemin
198            IF(lwp) WRITE(numout,*)'zyear0     = ', zyear0
199            IF(lwp) WRITE(numout,*)'zmonth0    = ', zmonth0
200            IF(lwp) WRITE(numout,*)'zday0      = ', zday0
201            IF(lwp) WRITE(numout,*)'zday_year0 = ',zday_year0
202            IF(lwp) WRITE(numout,*)'nobis(2)', nobis(2)
203            IF(lwp) WRITE(numout,*)'nobis(5)', nobis(5)
204            IF(lwp) WRITE(numout,*)'nobis(6)', nobis(6)
205            IF(lwp) WRITE(numout,*)'nobis(1)', nobis(1)
206            IF(lwp) WRITE(numout,*)'nobis(zmonth0 -1)', nobis(zmonth0 - 1)
207            IF(lwp) WRITE(numout,*)'raajj  = ', raajj
208         ENDIF
209   
210      ELSE
211
212         IF( kt == nit000 ) THEN
213   
214            ! Read Namelist namtau : surface wind stress
215            ! --------------------
216            REWIND ( numnam )
217            READ   ( numnam, namtau )
218   
219            IF(lwp) WRITE(numout,*)' '
220            IF(lwp) WRITE(numout,*)' tau     : Constant surface wind stress read in namelist'
221            IF(lwp) WRITE(numout,*)' ~~~~~~~ '
222            IF(lwp) WRITE(numout,*)'           Namelist namtau: set the constant stress values'
223            IF(lwp) WRITE(numout,*)'              spin up of the stress  ntau000 = ', ntau000, ' time-steps'
224            IF(lwp) WRITE(numout,*)'              constant i-stress      tau0x   = ', tau0x  , ' N/m2'
225            IF(lwp) WRITE(numout,*)'              constant j-stress      tau0y   = ', tau0y  , ' N/m2'
226   
227            ntau000 = MAX( ntau000, 1 )   ! must be >= 1
228   
229         ENDIF
230   
231         ! Increase the surface stress to its nominal value in ntau000 time-step
232         
233         IF( kt <= ntau000 ) THEN
234            zfacto = 0.5 * (  1. - COS( rpi * FLOAT( kt ) / FLOAT( ntau000 ) )  )
235            taux (:,:) = zfacto * tau0x
236            tauy (:,:) = zfacto * tau0y
237            tauxg(:,:) = zfacto * tau0x
238            tauyg(:,:) = zfacto * tau0y
239         ENDIF
240
241      ENDIF
242     
243   END SUBROUTINE tau
244#endif
245   !!======================================================================
246END MODULE taumod
Note: See TracBrowser for help on using the repository browser.