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

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

CT : UPDATE001 : First major NEMO update

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.5 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
16   IMPLICIT NONE
17   PRIVATE
18
19   !! * Routine accessibility
20   PUBLIC tau                ! routine called by step.F90
21
22   !! * Share modules variables
23   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &
24      taux, tauy,      &  !: surface stress components in (i,j) referential
25      tauxg, tauyg        !: surface stress components in geographical
26      !                   !  referential (used in output)
27   !!----------------------------------------------------------------------
28   !!   OPA 9.0 , LODYC-IPSL  (2003)
29   !!----------------------------------------------------------------------
30
31#if defined key_tau_monthly
32   ! Monthly climatology in (i,j) referential  (i-comp. at U-pt and j-comp. at V-pt)
33#  if defined key_fdir
34   !!----------------------------------------------------------------------
35   !!   'key_tau_monthly'                        MONTHLY climatology stress
36   !!   'key_fdir'                                  direct access files
37   !!----------------------------------------------------------------------
38#   include "tau_forced_monthly_fdir.h90"
39#  else
40   !!----------------------------------------------------------------------
41   !!   'key_tau_monthly'                        MONTHLY climatology stress
42   !!   default case                                   NetCDF files
43   !!----------------------------------------------------------------------
44#   include "tau_forced_monthly.h90"
45#  endif
46
47# elif defined key_tau_daily
48   !!----------------------------------------------------------------------
49   !!   'key_tau_daily'                                 DAILY stress
50   !!                                                   NetCDF files
51   !!----------------------------------------------------------------------
52   ! Daily climatology/interannual in (i,j) referential  (i-comp. at U-pt and j-comp. at V-pt)
53#   include "tau_forced_daily.h90"
54
55#elif defined key_coupled
56   ! Coupled case : stress at the coupling frequency
57# if defined key_ice_lim
58   !!----------------------------------------------------------------------
59   !!   'key_coupled'                              Coupled Ocean/Atmosphere
60   !!   'key_ice_lim'                                   LIM sea-ice
61   !!----------------------------------------------------------------------
62   ! New way: 3D referential link to the earth (avoid north pole pb)
63   ! (3 component stress defined at U- and V-points)
64#  include "tau_coupled_ice.h90"
65# else
66   !!----------------------------------------------------------------------
67   !!   'key_coupled'                              Coupled Ocean/Atmosphere
68   !!   Default case                                  NO sea-ice
69   !!----------------------------------------------------------------------
70   ! old fashion: geographical referential
71   ! (zonal and meridional stress defined at U- and V-points)
72#  include "tau_coupled.h90"
73# endif
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      !!              - update tauxg, tauyg the stress in geographic ref.
101      !!
102      !! History :
103      !!   4.0  !  91-03  (G. Madec)  Original code
104      !!   8.5  !  02-11  (G. Madec)  F90: Free form and module
105      !!----------------------------------------------------------------------
106      !! * Arguments
107      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
108
109      !! * Local declarations
110      REAL(wp) ::   zfacto             !
111
112      NAMELIST/namtau/ ntau000, tau0x, tau0y
113      !!---------------------------------------------------------------------
114
115      IF( kt == nit000 ) THEN
116
117         ! Read Namelist namtau : surface wind stress
118         ! --------------------
119         REWIND ( numnam )
120         READ   ( numnam, namtau )
121
122         IF(lwp) WRITE(numout,*)' '
123         IF(lwp) WRITE(numout,*)' tau     : Constant surface wind stress read in namelist'
124         IF(lwp) WRITE(numout,*)' ~~~~~~~ '
125         IF(lwp) WRITE(numout,*)'           Namelist namtau: set the constant stress values'
126         IF(lwp) WRITE(numout,*)'              spin up of the stress  ntau000 = ', ntau000, ' time-steps'
127         IF(lwp) WRITE(numout,*)'              constant i-stress      tau0x   = ', tau0x  , ' N/m2'
128         IF(lwp) WRITE(numout,*)'              constant j-stress      tau0y   = ', tau0y  , ' N/m2'
129
130         ntau000 = MAX( ntau000, 1 )   ! must be >= 1
131
132      ENDIF
133
134      ! Increase the surface stress to its nominal value in ntau000 time-step
135     
136      IF( kt <= ntau000 ) THEN
137         zfacto = 0.5 * (  1. - COS( rpi * FLOAT( kt ) / FLOAT( ntau000 ) )  )
138         taux (:,:) = zfacto * tau0x
139         tauy (:,:) = zfacto * tau0y
140         tauxg(:,:) = zfacto * tau0x
141         tauyg(:,:) = zfacto * tau0y
142      ENDIF
143     
144   END SUBROUTINE tau
145#endif
146   !!======================================================================
147END MODULE taumod
Note: See TracBrowser for help on using the repository browser.