My Project
wreal.f90
Go to the documentation of this file.
1 
2 
3 
4 
5 
6 
7 
8 
9 
10 
11 
12 !/===========================================================================/
13 ! Copyright (c) 2007, The University of Massachusetts Dartmouth
14 ! Produced at the School of Marine Science & Technology
15 ! Marine Ecosystem Dynamics Modeling group
16 ! All rights reserved.
17 !
18 ! FVCOM has been developed by the joint UMASSD-WHOI research team. For
19 ! details of authorship and attribution of credit please see the FVCOM
20 ! technical manual or contact the MEDM group.
21 !
22 !
23 ! This file is part of FVCOM. For details, see http://fvcom.smast.umassd.edu
24 ! The full copyright notice is contained in the file COPYRIGHT located in the
25 ! root directory of the FVCOM code. This original header must be maintained
26 ! in all distributed versions.
27 !
28 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
29 ! AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO,
30 ! THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
31 ! PURPOSE ARE DISCLAIMED.
32 !
33 !/---------------------------------------------------------------------------/
34 ! CVS VERSION INFORMATION
35 ! $Id$
36 ! $Name$
37 ! $Revision$
38 !/===========================================================================/
39 
40 !==============================================================================|
41 ! Compute Cartesian Vertical Velocity |
42 !==============================================================================|
43  SUBROUTINE wreal
44 !==============================================================================|
45  USE all_vars
46  USE mod_utils
47  USE mod_wd
48  USE mod_nesting
49  IMPLICIT NONE
50  REAL(SP) :: DDDX,DDDY,DEDX,DEDY,ETF1AA,WW1,WW2
51  INTEGER :: I,K,J1,J2,J3
52  INTEGER :: J, II
53  REAL(SP) :: U_TMP, V_TMP
54 !==============================================================================|
55 
56  IF(dbg_set(dbg_sbr)) WRITE(ipt,*) "Start: wreal"
57 
58 !------------------------------------------------------------------------------!
59 ! SAVE OMEGA VELOCITY FROM PREVIOUS TIMESTEP (USED FOR LAGRANGIAN TRACKING) !
60 !------------------------------------------------------------------------------!
61 
62  wtts = wts
63 
64 !------------------------------------------------------------------------------!
65 ! CALCULATE A NEW OMEGA VELOCITY !
66 !------------------------------------------------------------------------------!
67 
68 !!===========yding==================
69 
70 
71  DO i=1,n
72  IF(iswetc(i) == 1)THEN
73  j1=nv(i,1)
74  j2=nv(i,2)
75  j3=nv(i,3)
76  dddx=awx(i,1) * d(j1)+awx(i,2) * d(j2)+awx(i,3)*d(j3)
77  dddy=awy(i,1) * d(j1)+awy(i,2) * d(j2)+awy(i,3)*d(j3)
78  dedx=awx(i,1)*elf(j1)+awx(i,2)*elf(j2)+awx(i,3)*elf(j3)
79  dedy=awy(i,1)*elf(j1)+awy(i,2)*elf(j2)+awy(i,3)*elf(j3)
80  etf1aa=one_third*(el(nv(i,1))+el(nv(i,2))+el(nv(i,3)))
81  DO k=1,kbm1
82  ww1=0.5_sp*(w(i,k)+w(i,k+1))+u(i,k)*(zz1(i,k)*dddx+dedx)+ &
83  v(i,k)*(zz1(i,k)*dddy+dedy)
84  ww2=(zz1(i,k)+1.)*(etf1aa-et1(i))/dti
85  ww(i,k)=ww1+ww2
86  END DO
87  ELSE
88  DO k=1,kbm1
89  ww(i,k)=0.0_sp
90  END DO
91  END IF
92  END DO
93 
94 
95 
96  IF(dbg_set(dbg_sbr)) WRITE(ipt,*) "End: wreal"
97 
98  END SUBROUTINE wreal
99 !==============================================================================|
real(sp), dimension(:), allocatable, target d
Definition: mod_main.f90:1132
real(sp), dimension(:), allocatable, target el
Definition: mod_main.f90:1134
real(sp), dimension(:,:), allocatable, target v
Definition: mod_main.f90:1269
logical function dbg_set(vrb)
Definition: mod_utils.f90:182
real(sp), dimension(:,:), allocatable, target w
Definition: mod_main.f90:1279
real(sp), dimension(:,:), allocatable, target awx
Definition: mod_main.f90:1333
real(sp), dimension(:,:), allocatable, target ww
Definition: mod_main.f90:1280
real(sp), dimension(:,:), allocatable, target u
Definition: mod_main.f90:1268
real(sp), dimension(:,:), allocatable, target awy
Definition: mod_main.f90:1334
real(sp), dimension(:,:), allocatable, target wtts
Definition: mod_main.f90:1322
real(sp), dimension(:), allocatable, target elf
Definition: mod_main.f90:1140
integer, dimension(:,:), allocatable, target nv
Definition: mod_main.f90:1018
real(sp), dimension(:,:), allocatable, target zz1
Definition: mod_main.f90:1095
integer, dimension(:), allocatable iswetc
Definition: mod_wd.f90:52
real(sp), dimension(:,:), allocatable, target wts
Definition: mod_main.f90:1321
integer, parameter dbg_sbr
Definition: mod_utils.f90:69
real(sp), dimension(:), allocatable, target et1
Definition: mod_main.f90:1119
subroutine wreal
Definition: wreal.f90:44