My Project
calc_vort.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 ! CALCULATE VORTICITY FIELD AT NODES |
42 ! OPTIONAL INPUT: VTYPE |
43 ! 1 CURL OF VERTICALLY-AVERAGED VELOCITY (DEFAULT) |
44 ! 2 CURL OF FLUX (For Streamfunctions) |
45 ! RETURNS: VORT(1:M) |
46 ! |
47 ! CHECK, INITIALIZE WITH ANALYTICAL VELOCITY FIELD (UA = -.5YC, VA = .5XC) !
48 !==============================================================================|
49  SUBROUTINE calc_vort(VTYPE)
50 !==============================================================================|
51  USE all_vars
52  IMPLICIT NONE
53  INTEGER, OPTIONAL, INTENT(IN) :: VTYPE
54  REAL(SP) :: XFLUX(0:M)
55  REAL(SP) :: UIJ,VIJ,EXFLUX,AVE
56  INTEGER :: I,J,IA,IB,I1,CNT,JNODE,MY_VTYPE
57  INTEGER, ALLOCATABLE :: LIST(:)
58 !==============================================================================|
59 
60  !---------------------------------------------
61  !Process input arguments
62  !---------------------------------------------
63  my_vtype = 1
64  IF(present(vtype))Then
65  my_vtype = vtype
66  ENDIF
67 
68  !---------------------------------------------
69  !Initialize Fields
70  !---------------------------------------------
71  ALLOCATE(list(m)) ; list = 0
72  vort = 0.0
73 
74  !===================================================================
75  ! Calculate vorticity at all nodes using c.v. half edges
76  ! Note minus sign (nodes are order clockwise [against convention])
77  !===================================================================
78 
79  SELECT CASE(my_vtype)
80 
81  !----------------------------------------------
82  CASE(1) !Curl of Vert-Avged Velocity
83  !----------------------------------------------
84  DO i=1,ncv
85  i1 = ntrg(i)
86  ia = niec(i,1)
87  ib = niec(i,2)
88  uij = ua(i1)
89  vij = va(i1)
90  exflux = -(uij*dltxe(i) + vij*dltye(i))
91  vort(ia) = vort(ia)-exflux
92  vort(ib) = vort(ib)+exflux
93  END DO
94  !----------------------------------------------
95  CASE(2) !Curl of Flux
96  !----------------------------------------------
97  DO i=1,ncv
98  i1 = ntrg(i)
99  ia = niec(i,1)
100  ib = niec(i,2)
101  uij = ua(i1)
102  vij = va(i1)
103  exflux = -d1(i1)*(uij*dltxe(i) + vij*dltye(i))
104  vort(ia) = vort(ia)-exflux
105  vort(ib) = vort(ib)+exflux
106  END DO
107  !----------------------------------------------
108  CASE DEFAULT
109  !ERROR AND HALT
110  END SELECT
111 
112  vort = vort/art1
113 
114  !===================================================================
115  !Correction at Boundaries (May no longer be necessary for 2.5+)
116  !===================================================================
117 
118  do i=1,m
119  if(isonb(i) > 0)then
120  ave = 0.
121  cnt = 0
122  do j=1,ntsn(i)
123  jnode = nbsn(i,j)
124  if(jnode /= i .and. isonb(jnode) == 0)then
125  ave = ave + vort(jnode)
126  cnt = cnt + 1
127  end if
128  end do
129  vort(i) = ave/float(cnt)
130  if(cnt == 0) list(i) = 1
131  end if
132  end do
133 
134  do i=1,m
135  if(list(i) > 0)then
136  ave = 0.
137  cnt = 0
138  do j=1,ntsn(i)
139  jnode = nbsn(i,j)
140  if(jnode /= i .and. list(jnode) == 0)then
141  ave = ave + vort(jnode)
142  cnt = cnt + 1
143  end if
144  end do
145  vort(i) = ave/float(cnt)
146  end if
147  end do
148 
149 
150  RETURN
151  END SUBROUTINE calc_vort
152 !==============================================================================|
153 
integer, dimension(:), allocatable, target ntsn
Definition: mod_main.f90:1023
real(sp), dimension(:), allocatable, target va
Definition: mod_main.f90:1104
real(sp), dimension(:), allocatable, target d1
Definition: mod_main.f90:1116
real(sp), dimension(:), allocatable, target art1
Definition: mod_main.f90:1010
integer, dimension(:), allocatable, target ntrg
Definition: mod_main.f90:1033
integer, dimension(:,:), allocatable, target niec
Definition: mod_main.f90:1032
real(sp), dimension(:), allocatable, target vort
Definition: mod_main.f90:1165
real(sp), dimension(:), allocatable, target dltye
Definition: mod_main.f90:1051
real(sp), dimension(:), allocatable, target ua
Definition: mod_main.f90:1103
integer, dimension(:,:), allocatable, target nbsn
Definition: mod_main.f90:1030
subroutine calc_vort(VTYPE)
Definition: calc_vort.f90:50
real(sp), dimension(:), allocatable, target dltxe
Definition: mod_main.f90:1050
integer, dimension(:), allocatable, target isonb
Definition: mod_main.f90:1024