/[MITgcm]/MITgcm_contrib/ksnow/press_release/code/pressure_release_salt.F
ViewVC logotype

Annotation of /MITgcm_contrib/ksnow/press_release/code/pressure_release_salt.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (hide annotations) (download)
Mon Jan 30 16:32:18 2017 UTC (8 years, 10 months ago) by ksnow
Branch: MAIN
Changes since 1.1: +40 -15 lines
update darcy pressure release source code

1 ksnow 1.1 C $Header: /u/gcmpack/MITgcm_contrib/verification_other/../pressure_release_thermodynamics.F,v 1.2 2016/12/12 11:32:17 ksnow Exp $
2     C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     CBOP
8     SUBROUTINE PRESSURE_RELEASE_SALT(
9     U gS_arr,
10     I iMin,iMax,jMin,jMax, k, bi,bj,
11     I myTime, myIter, myThid )
12     C *============================================================*
13     C | SUBROUTINE PRESSURE_RELEASE_SALT
14     C | o Transport salt with darcy flux
15     C *============================================================*
16     IMPLICIT NONE
17    
18     C === Global variables ===
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "GRID.h"
23     #include "DYNVARS.h"
24     #include "SURFACE.h"
25     #include "FFIELDS.h"
26    
27     C === Routine arguments ===
28     C myThid - Number of this instance
29    
30     _RL gS_arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
31     INTEGER k,bi,bj
32     INTEGER iMin,iMax,jMin,jMax
33     _RL myTime
34     INTEGER myIter
35     INTEGER myThid
36    
37     CEndOfInterface
38    
39 ksnow 1.2 #ifdef ALLOW_PRESSURE_RELEASE_CODE
40 ksnow 1.1
41 ksnow 1.2 C === Local Variables ===
42     INTEGER i,j,k_e,k_ce,k_s,k_cs,k_w,k_cw,k_n,k_cn
43     _RL S_trans_west,S_trans_east,S_trans_south,S_trans_north
44 ksnow 1.1
45     DO j=jMin+1,jMax-1
46     DO i=iMin+1,iMax-1
47    
48 ksnow 1.2 S_trans_west = 0.0
49     S_trans_north = 0.0
50     S_trans_east = 0.0
51     S_trans_south = 0.0
52    
53 ksnow 1.1 C calculate the k cells the tracers are transferred between in north,
54     C south east and west cells.
55 ksnow 1.2 C Need to find if adjacent cells are deeper or shallower
56 ksnow 1.1 IF (kLowC(i,j,bi,bj) .GE. kLowC(i+1,j,bi,bj)) THEN
57     k_e = kLowC(i+1,j,bi,bj)
58     k_ce = kSurfC(i,j,bi,bj)
59     ELSE
60     k_e = kSurfC(i+1,j,bi,bj)
61     k_ce = kLowC(i,j,bi,bj)
62     ENDIF
63    
64     IF (kLowC(i,j,bi,bj) .GE. kLowC(i-1,j,bi,bj)) THEN
65     k_w = kLowC(i-1,j,bi,bj)
66     k_cw = kSurfC(i,j,bi,bj)
67     ELSE
68     k_w = kSurfC(i-1,j,bi,bj)
69     k_cw = kLowC(i,j,bi,bj)
70     ENDIF
71    
72     IF (kLowC(i,j,bi,bj) .GE. kLowC(i,j+1,bi,bj)) THEN
73     k_n = kLowC(i,j+1,bi,bj)
74     k_cn = kSurfC(i,j,bi,bj)
75     ELSE
76     k_n = kSurfC(i,j+1,bi,bj)
77     k_cn = kLowC(i,j,bi,bj)
78     ENDIF
79    
80     IF (kLowC(i,j,bi,bj) .GE. kLowC(i,j-1,bi,bj)) THEN
81     k_s = kLowC(i,j-1,bi,bj)
82     k_cs = kSurfC(i,j,bi,bj)
83     ELSE
84     k_s = kSurfC(i,j-1,bi,bj)
85     k_cs = kLowC(i,j,bi,bj)
86     ENDIF
87    
88     C calculate the net tracer flux through north, south east and west
89     C faces.
90 ksnow 1.2
91     IF (k .EQ. k_cw) THEN
92     S_trans_west =pReleaseTransX(i,j,bi,bj)*
93 ksnow 1.1 & (salt(i-1,j,k_w,bi,bj) -salt(i,j,k_cw,bi,bj))
94     C & *rhoFacC(k)*mass2rUnit
95     C & *_dyG(i,j,bi,bj)*recip_rA(i,j,bi,bj)*
96     & *recip_dxG(i,j,bi,bj)
97     & *recip_drF(k_cw)*_recip_hFacC(i,j,k_cw,bi,bj)
98 ksnow 1.2 ENDIF
99     IF (k .EQ. k_ce) THEN
100     S_trans_east =pReleaseTransX(i+1,j,bi,bj)*
101 ksnow 1.1 & (salt(i,j,k_ce,bi,bj) -salt(i+1,j,k_e,bi,bj))
102 ksnow 1.2 & *recip_dxG(i,j,bi,bj)
103     & *recip_drF(k_ce)*_recip_hFacC(i,j,k_ce,bi,bj)
104     ENDIF
105     IF (k .EQ. k_cs) THEN
106     S_trans_south =pReleaseTransY(i,j,bi,bj)*
107 ksnow 1.1 & (salt(i,j-1,k_s,bi,bj) -salt(i,j,k_cs,bi,bj))
108     & *recip_dyG(i,j,bi,bj)
109     & *recip_drF(k_cs)*_recip_hFacC(i,j,k_cs,bi,bj)
110 ksnow 1.2 ENDIF
111     IF (k .EQ. k_cn) THEN
112     S_trans_north =pReleaseTransY(i,j+1,bi,bj)*
113     & (salt(i,j,k_cn,bi,bj) -salt(i,j+1,k_n,bi,bj))
114     & *recip_dyG(i,j,bi,bj)
115     & *recip_drF(k_cn)*_recip_hFacC(i,j,k_cn,bi,bj)
116     ENDIF
117 ksnow 1.1
118 ksnow 1.2 C IF ((k .LE. 72) .AND. (k .GE. 68)) THEN
119     C IF (i .EQ. 10) THEN
120     C IF ((j .LE.100) .AND. (j .GE. 80)) THEN
121     C print *,'KS_ks',j,k,k_cn,k_cs,k_n,k_s,salt(i,j-1,k_s,bi,bj)
122     C & ,salt(i,j+1,k_n,bi,bj),S_trans_north,S_trans_south,
123     C & pReleaseTransY(i,j,bi,bj), pReleaseTransY(i,j+1,bi,bj)
124     C & ,pReleaseTransY(i,j-1,bi,bj)
125     C ENDIF
126     C ENDIF
127     C ENDIF
128 ksnow 1.1
129     C Add to get total tracer tendency.
130     gS_arr(i,j) = gS_arr(i,j) + S_trans_west - S_trans_east
131     & + S_trans_south - S_trans_north
132    
133     ENDDO
134     ENDDO
135    
136 ksnow 1.2 #endif /* ALLOW_PRESSURE_RELEASE_CODE */
137    
138 ksnow 1.1 RETURN
139     END

  ViewVC Help
Powered by ViewVC 1.1.22