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

Last change on this file since 239 was 239, checked in by opalod, 19 years ago

CT : UPDATE172 : remove all direct acces modules and the related cpp key key_fdir

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