My Project
ghostuv.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 GHOST VELOCITY FOR EXTERNAL MODE !
42 !==============================================================================|
43  SUBROUTINE ghostuv2(I,JJ,UAKK,VAKK)
44 !==============================================================================|
45 
46  USE all_vars
47  USE bcs
48  IMPLICIT NONE
49  INTEGER, INTENT(IN) :: I,JJ
50  INTEGER :: J1,J2
51  REAL(SP) :: DELTX,DELTY,ALPHA1
52  REAL(SP) :: UTMP,VTMP
53  REAL(SP), INTENT(OUT):: UAKK,VAKK
54 
55  uakk = 0.0_sp; vakk = 0.0_sp
56 
57  IF(isbce(i) /= 2)THEN
58  j1 = jj+1-int((jj+1)/4)*3
59  j2 = jj+2-int((jj+2)/4)*3
60  deltx = vx(nv(i,j1))-vx(nv(i,j2))
61  delty = vy(nv(i,j1))-vy(nv(i,j2))
62 
63  alpha1 = atan2(delty,deltx)
64 
65  utmp = ua(i)*cos(alpha1)+va(i)*sin(alpha1)
66  vtmp = -ua(i)*sin(alpha1)+va(i)*cos(alpha1)
67 
68 ! VTMP = -VTMP
69  vtmp = 0.0_sp
70 
71  uakk = utmp*cos(alpha1)-vtmp*sin(alpha1)
72  vakk = utmp*sin(alpha1)+vtmp*cos(alpha1)
73  ELSE IF(isbce(i) == 2)THEN
74  uakk = ua(i)
75  vakk = va(i)
76  END IF
77 
78  RETURN
79  END SUBROUTINE ghostuv2
80 
81 
82 !==============================================================================|
83 ! CALCULATE GHOST VELOCITY FOR INTERNAL MODE !
84 !==============================================================================|
85  SUBROUTINE ghostuv3(I,JJ,UAKK,VAKK)
86 !==============================================================================|
87 
88  USE all_vars
89  USE bcs
90  IMPLICIT NONE
91  INTEGER, INTENT(IN) :: I,JJ
92  INTEGER :: J1,J2,K
93  REAL(SP) :: DELTX,DELTY,ALPHA1
94  REAL(SP) :: UTMP,VTMP
95  REAL(SP), INTENT(OUT):: UAKK(KB),VAKK(KB)
96 
97  uakk = 0.0_sp; vakk = 0.0_sp
98 
99  IF(isbce(i) /= 2)THEN
100  j1 = jj+1-int((jj+1)/4)*3
101  j2 = jj+2-int((jj+2)/4)*3
102  deltx = vx(nv(i,j1))-vx(nv(i,j2))
103  delty = vy(nv(i,j1))-vy(nv(i,j2))
104 
105  alpha1 = atan2(delty,deltx)
106 
107  DO k = 1,kbm1
108  utmp = u(i,k)*cos(alpha1)+v(i,k)*sin(alpha1)
109  vtmp = -u(i,k)*sin(alpha1)+v(i,k)*cos(alpha1)
110 
111 ! VTMP = -VTMP
112  vtmp = 0.0_sp
113 
114  uakk(k) = utmp*cos(alpha1)-vtmp*sin(alpha1)
115  vakk(k) = utmp*sin(alpha1)+vtmp*cos(alpha1)
116  END DO
117 
118  ELSE IF(isbce(i) == 2)THEN
119  uakk = u(i,:)
120  vakk = v(i,:)
121  END IF
122 
123  RETURN
124  END SUBROUTINE ghostuv3
real(sp), dimension(:), allocatable, target va
Definition: mod_main.f90:1104
subroutine ghostuv2(I, JJ, UAKK, VAKK)
Definition: ghostuv.f90:44
real(sp), dimension(:,:), allocatable, target v
Definition: mod_main.f90:1269
subroutine ghostuv3(I, JJ, UAKK, VAKK)
Definition: ghostuv.f90:86
real(sp), dimension(:,:), allocatable, target u
Definition: mod_main.f90:1268
real(sp), dimension(:), allocatable, target vx
Definition: mod_main.f90:1001
real(sp), dimension(:), allocatable, target vy
Definition: mod_main.f90:1002
integer, dimension(:,:), allocatable, target nv
Definition: mod_main.f90:1018
real(sp), dimension(:), allocatable, target ua
Definition: mod_main.f90:1103
integer, dimension(:), allocatable, target isbce
Definition: mod_main.f90:1027