My Project
edge_len.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 SUBROUTINE edge_len
42  use mod_spherical
43  use mod_northpole
44  use mod_utils
45 
46  implicit none
47  INTEGER :: I,IP,I1,I2,IA,IB,J,J1
48  REAL(SP) :: XI, YI, X11,X33,Y11,Y33
49 
50  INTEGER :: JTMP,J2
51 
52 
53 
54  ! Distance between control volue edge and the node
55 
56  DO i=1,ncv_i
57  ia=niec(i,1)
58  ib=niec(i,2)
59  xi=0.5_sp*(xije(i,1)+xije(i,2))
60  yi=0.5_sp*(yije(i,1)+yije(i,2))
61  dltxncve(i,1)=xi-vx(ia)
62  dltyncve(i,1)=yi-vy(ia)
63  dltxncve(i,2)=xi-vx(ib)
64  dltyncve(i,2)=yi-vy(ib)
65 
66  END DO
67 
68 
69  ! Set the distance between Nodes
70 
71  IF(maxval(ntsn) > 13) CALL fatal_error &
72  & ("THERE ARE MORE THAN 12 NODES AROUND ONE NODE:",&
73  "PLEASE INCREASE THE SIZE OF DLTXPI AND DLTYPI IN MOD_MAIN",&
74  "BUT REALLY, WHAT IS WRONG WITH YOUR MESH?")
75 
76  DO i=1,m
77  DO j=1,ntsn(i)-1
78  i1=nbsn(i,j)
79  i2=nbsn(i,j+1)
80 
81  dltytrie(i,j) = vy(i1)-vy(i2)
82  dltxtrie(i,j) = vx(i2)-vx(i1)
83 
84  END DO
85  END DO
86 
87  ! Set the distance between Nodes for the North Pole region
88 
89  ! Set the distance between triangle edge centers
90  IF(maxval(ntve) > 13) CALL fatal_error &
91  & ("THERE ARE MORE THAN 12 CELLS AROUND ONE NODE:",&
92  "PLEASE INCREASE THE SIZE OF DLVISCXPI AND DLVISCYPI IN MOD_MAIN",&
93  "BUT REALLY, WHAT IS WRONG WITH YOUR MESH?")
94 
95 
96  DO i=1,m
97  DO j=1,ntve(i)
98  i1=nbve(i,j)
99  jtmp=nbvt(i,j)
100  j1=jtmp+1-(jtmp+1)/4*3
101  j2=jtmp+2-(jtmp+2)/4*3
102  x11=0.5_sp*(vx(i)+vx(nv(i1,j1)))
103  y11=0.5_sp*(vy(i)+vy(nv(i1,j1)))
104 ! X22=XC(I1)
105 ! Y22=YC(I1)
106  x33=0.5_sp*(vx(i)+vx(nv(i1,j2)))
107  y33=0.5_sp*(vy(i)+vy(nv(i1,j2)))
108 
109 
110  dltyecec(i,j)=(y11-y33)
111  dltxecec(i,j)=(x33-x11)
112 
113 
114 
115 ! Set the distance between the node and the edge Center
116 ! NOTE: THE SIGN MATTERS!
117  dltynec(i,j)=(vy(i)-y11)
118  dltxnec(i,j)=(x11-vx(i))
119 
120 
121  END DO
122  END DO
123 
124 
125  END SUBROUTINE edge_len
integer, dimension(:), allocatable, target ntsn
Definition: mod_main.f90:1023
real(sp), dimension(:,:), allocatable, target yije
Definition: mod_main.f90:1048
real(sp), dimension(:,:), allocatable, target dltxnec
Definition: mod_main.f90:1069
real(sp), dimension(:,:), allocatable, target dltxncve
Definition: mod_main.f90:1059
real(sp), dimension(:,:), allocatable, target dltytrie
Definition: mod_main.f90:1063
real(sp), dimension(:,:), allocatable, target xije
Definition: mod_main.f90:1047
real(sp), dimension(:,:), allocatable, target dltyncve
Definition: mod_main.f90:1060
integer, dimension(:,:), allocatable, target niec
Definition: mod_main.f90:1032
integer, dimension(:,:), allocatable, target nbvt
Definition: mod_main.f90:1036
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 ntve
Definition: mod_main.f90:1022
integer, dimension(:,:), allocatable, target nv
Definition: mod_main.f90:1018
real(sp), dimension(:,:), allocatable, target dltyecec
Definition: mod_main.f90:1067
real(sp), dimension(:,:), allocatable, target dltynec
Definition: mod_main.f90:1070
real(sp), dimension(:,:), allocatable, target dltxtrie
Definition: mod_main.f90:1064
integer, dimension(:,:), allocatable, target nbve
Definition: mod_main.f90:1034
subroutine edge_len
Definition: edge_len.f90:41
subroutine fatal_error(ER1, ER2, ER3, ER4)
Definition: mod_utils.f90:230
real(sp), dimension(:,:), allocatable, target dltxecec
Definition: mod_main.f90:1066
integer, dimension(:,:), allocatable, target nbsn
Definition: mod_main.f90:1030