1 |
#include "STREAMICE_OPTIONS.h" |
2 |
|
3 |
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
4 |
CBOP 0 |
5 |
C !ROUTINE: STREAMICE_INIT_FIXED |
6 |
|
7 |
C !INTERFACE: |
8 |
SUBROUTINE STREAMICE_INIT_PHI( myThid ) |
9 |
|
10 |
C !DESCRIPTION: |
11 |
C Initialize STREAMICE nodal basis gradients for FEM solver |
12 |
|
13 |
C !USES: |
14 |
IMPLICIT NONE |
15 |
#include "EEPARAMS.h" |
16 |
#include "SIZE.h" |
17 |
#include "PARAMS.h" |
18 |
#include "STREAMICE.h" |
19 |
#include "STREAMICE_CG.h" |
20 |
#include "GRID.h" |
21 |
|
22 |
C myThid :: my Thread Id number |
23 |
INTEGER myThid |
24 |
CEOP |
25 |
|
26 |
C !LOCAL VARIABLES: |
27 |
C === Local variables === |
28 |
INTEGER bi, bj, i, j, xnode, ynode, xq, yq, m, n, p, kx, ky |
29 |
REAL gradx(2), grady(2) ! gradients at quadrature points |
30 |
|
31 |
C here the terms used to calculate matrix terms in the |
32 |
C velocity solve are initialized |
33 |
C |
34 |
C this is a quasi-finite element method; the gradient |
35 |
C of the basis functions are approximated based on knowledge |
36 |
C of the grid |
37 |
C |
38 |
C Dphi (i,j,bi,bj,m,n,p): |
39 |
C gradient (in p-direction) of nodal basis function in |
40 |
C cell (i,j) on thread (bi,bj) which is centered on node m, |
41 |
C at quadrature point n |
42 |
C |
43 |
C % 3 - 4 |
44 |
C % | | |
45 |
C % 1 - 2 |
46 |
C |
47 |
C NOTE 2x2 quadrature is hardcoded - might make it specifiable through CPP |
48 |
C |
49 |
C this will not be updated in overlap cells - so we extend it as far as we can |
50 |
|
51 |
DO bj = myByLo(myThid), myByHi(myThid) |
52 |
DO bi = myBxLo(myThid), myBxHi(myThid) |
53 |
DO j=1-Oly,sNy+Oly-1 |
54 |
DO i=1-Olx,sNx+Olx-1 |
55 |
|
56 |
DO xq = 1,2 |
57 |
gradx(xq) = Xquad(3-xq) * recip_dxG (i,j,bi,bj) + |
58 |
& Xquad(xq) * recip_dxG (i+1,j,bi,bj) |
59 |
grady(xq) = Xquad(3-xq) * recip_dyG (i,j,bi,bj) + |
60 |
& Xquad(xq) * recip_dyG (i,j+1,bi,bj) |
61 |
ENDDO |
62 |
|
63 |
DO n = 1,4 |
64 |
|
65 |
xq = 2 - mod(n,2) |
66 |
yq = floor ((n+1)/2.0) |
67 |
|
68 |
DO m = 1,4 |
69 |
|
70 |
xnode = 2 - mod(m,2) |
71 |
ynode = floor ((m+1)/2.0) |
72 |
|
73 |
kx = 1 ; ky = 1 |
74 |
if (xq.eq.xnode) kx = 2 |
75 |
if (yq.eq.ynode) ky = 2 |
76 |
|
77 |
|
78 |
Dphi (i,j,bi,bj,m,n,1) = |
79 |
& (2*xnode-3) * Xquad(ky) * gradx(yq) |
80 |
Dphi (i,j,bi,bj,m,n,2) = |
81 |
& (2*ynode-3) * Xquad(kx) * grady(xq) |
82 |
|
83 |
ENDDO |
84 |
|
85 |
grid_jacq_streamice (i,j,bi,bj,n) = |
86 |
& (Xquad(3-xq)*dyG(i,j,bi,bj) + Xquad(xq)*dyG(i+1,j,bi,bj)) * |
87 |
& (Xquad(3-yq)*dxG(i,j,bi,bj) + Xquad(yq)*dxG(i,j+1,bi,bj)) |
88 |
|
89 |
ENDDO |
90 |
ENDDO |
91 |
ENDDO |
92 |
ENDDO |
93 |
ENDDO |
94 |
|
95 |
RETURN |
96 |
END |