The TELEMAC-MASCARET system  trunk
uvstokes.f
Go to the documentation of this file.
1 !#######################################################################
2  SUBROUTINE uvstokes
3  & (ust, vst, wst, fs, npoin2, xk, zfj, ndire, ztel, nz, nf)
4 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
5 ! calculation of the three components of the stokes drift
6 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
7 !| FS |-->| VARIANCE DENSITY DIRECTIONAL SPECTRUM
8 !| NF |-->| NUMBER OF FREQUENCIES
9 !| NDIRE |-->| NUMBER OF DIRECTIONS
10 !| NPOIN2 |-->| NUMBER OF POINTS IN 2D MESH
11 !| NZ |-->| NUMBER OF PLAN IN TELEMAC3D
12 !| XK |-->| DISCRETIZED WAVE NUMBER
13 !| UST |<--| STOKES COMPONENT ALONG X
14 !| VST |<--| STOKES COMPONENT ALONG Y
15 !| WST |<--| STOKES COMPONENT ALONG Z
16 !| ZFJ |-->| BOTTOM ELEVATION
17 !| ZTEL |-->| ELEVATION IN TELEMAC3D
18 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
19  USE bief
21  & depth, deupi
22  USE interface_tomawac, ex_uvstokes => uvstokes
23 
24 !NDIRE - number of direction discretization
25  IMPLICIT NONE
26 
27 !.....VARIABLES IN ARGUMENT
28 ! """"""""""""""""""""
29  INTEGER, INTENT(IN) :: NZ,NF
30  INTEGER, INTENT(IN) :: NPOIN2, NDIRE
31  DOUBLE PRECISION, INTENT(IN) :: FS(npoin2,ndire,nf)
32  DOUBLE PRECISION, INTENT(IN) :: ZFJ(npoin2)
33  DOUBLE PRECISION, INTENT(IN) :: XK(npoin2,nf)
34  DOUBLE PRECISION, INTENT(INOUT) :: UST(npoin2,nz)
35  DOUBLE PRECISION, INTENT(INOUT) :: VST(npoin2,nz)
36  DOUBLE PRECISION, INTENT(INOUT) :: WST(npoin2)
37  DOUBLE PRECISION, INTENT(IN) :: ZTEL(npoin2,nz)
38 !.....LOCAL VARIABLES
39 ! """""""""""""""""
40  INTEGER JP , JF , IP, INZ
41  DOUBLE PRECISION SIGMA, DTETAR, AUX1
42 !
43  dtetar=deupi/dble(ndire)
44 
45 !begin mjt- initialize variables
46  DO ip=1,npoin2
47  DO inz=1,nz
48  ust(ip,inz) = 0.d0
49  vst(ip,inz) = 0.d0
50  ENDDO
51  ENDDO
52  DO jp=1,ndire
53  DO jf=1,nf
54  sigma=deupi*freq(jf)
55  aux1=dfreq(jf)*dtetar
56  DO ip=1,npoin2
57  DO inz=1, nz
58  ust(ip,inz)=ust(ip,inz)+(sigma*xk(ip,jf)*sintet(jp)
59  & *fs(ip,jp,jf)*(cosh(2.d0*xk(ip,jf)*ztel(ip,inz)
60  & +2.d0*xk(ip,jf)*(-zfj(ip)))
61  & /sinh(xk(ip,jf)*depth(ip))**2.d0))*aux1
62 
63  vst(ip,inz)=vst(ip,inz)+(sigma*xk(ip,jf)
64  & *costet(jp)*fs(ip,jp,jf)*(cosh(2.d0*xk(ip,jf)*ztel(ip,inz)
65  & +2.d0*xk(ip,jf)*(-zfj(ip)))
66  & /sinh(xk(ip,jf)*depth(ip))**2.d0))*aux1
67  ENDDO
68  ENDDO
69  ENDDO
70  ENDDO
71  DO ip=1,npoin2
72  wst(ip)=-ust(ip,1)*dzx(ip)-vst(ip,1)*dzy(ip)
73  ENDDO
74 
75  RETURN
76  END
double precision, dimension(:), pointer sintet
double precision, dimension(:), pointer freq
double precision, dimension(:), pointer dzy
double precision, dimension(:), pointer dfreq
subroutine uvstokes(UST, VST, WST, FS, NPOIN2, XK, ZFJ, NDIRE, ZTEL, NZ, NF)
Definition: uvstokes.f:5
double precision, dimension(:), pointer dzx
double precision, dimension(:), pointer costet
Definition: bief.f:3