/[MITgcm]/MITgcm/pkg/profiles/profiles_interp_mean_ggd.F
ViewVC logotype

Contents of /MITgcm/pkg/profiles/profiles_interp_mean_ggd.F

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


Revision 1.2 - (show annotations) (download)
Fri Jun 5 02:23:25 2015 UTC (8 years, 11 months ago) by gforget
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +0 -0 lines
FILE REMOVED
- remove ALLOW_PROFILES_ANOM_COST code

1 #include "PROFILES_OPTIONS.h"
2
3 C o==========================================================o
4 C | subroutine profiles_interp |
5 C | o 3D interpolation of model counterparts |
6 C | for netcdf profiles data |
7 C | started: Gael Forget 15-March-2006 |
8 C o==========================================================o
9
10 SUBROUTINE profiles_interp_mean_ggd(
11 O traj_cur_out,
12 I i_cur,
13 I j_cur,
14 I weights_cur,
15 I type_cur,
16 I file_cur,
17 I mytime,
18 I bi,
19 I bj,
20 I myThid
21 & )
22
23 implicit none
24
25 C ==================== Global Variables ===========================
26 #include "EEPARAMS.h"
27 #include "SIZE.h"
28 #include "GRID.h"
29 c#include "DYNVARS.h"
30 #include "PARAMS.h"
31 #ifdef ALLOW_CAL
32 #include "cal.h"
33 #endif
34 #ifdef ALLOW_PROFILES
35 # include "profiles.h"
36 #else
37 integer NLEVELMAX
38 parameter (NLEVELMAX=1)
39 #endif
40 c#ifdef ALLOW_PTRACERS
41 c#include "PTRACERS_SIZE.h"
42 c#include "PTRACERS_FIELDS.h"
43 c#endif
44 C ==================== Routine Variables ==========================
45 _RL mytime
46 integer mythid
47 integer type_cur,file_cur
48 _RL traj_cur_out(NLEVELMAX)
49 _RL weights_cur(NUM_INTERP_POINTS)
50 integer i_cur(NUM_INTERP_POINTS)
51 integer j_cur(NUM_INTERP_POINTS)
52
53 #ifdef ALLOW_PROFILES
54
55 C ==================== Local Variables ==========================
56 _RL tab_coeffs1(NUM_INTERP_POINTS)
57 _RL tab_coeffs3(NUM_INTERP_POINTS)
58 _RL ponderations(NUM_INTERP_POINTS)
59 _RL pondsSUM
60 integer q,k,kk,kcur,bi,bj
61 _RL traj_cur(nR),mask_cur(nR)
62 _RL tmp_coeff
63 c-- == end of interface ==
64
65 do k=1,nr
66
67 pondsSUM=0
68 do q=1,NUM_INTERP_POINTS
69
70 C if (type_cur.EQ.6) then
71 C tab_coeffs1(q)=prof_etan_mean(i_cur(q),j_cur(q),bi,bj)
72 C tab_coeffs3(q)=maskC(i_cur(q),j_cur(q),1,bi,bj)
73 Cow only works for TS
74 if (type_cur.EQ.1) then
75 tab_coeffs1(q)=prof_tdat_mean(i_cur(q),j_cur(q),k,bi,bj)
76 tab_coeffs3(q)=maskC(i_cur(q),j_cur(q),k,bi,bj)
77 elseif (type_cur.EQ.2) then
78 tab_coeffs1(q)=prof_sdat_mean(i_cur(q),j_cur(q),k,bi,bj)
79 tab_coeffs3(q)=maskC(i_cur(q),j_cur(q),k,bi,bj)
80 else
81 tab_coeffs1(q)=0.
82 tab_coeffs3(q)=0.
83 endif
84 if(tab_coeffs1(q).EQ.0. _d 0) tab_coeffs3(q) = 0. _d 0
85
86 ponderations(q)=tab_coeffs3(q)*weights_cur(q)
87 pondsSUM=pondsSUM+ponderations(q)
88 enddo
89
90 if (pondsSUM.GT.0) then
91 mask_cur(k)=1
92 traj_cur(k)=0
93 do q=1,NUM_INTERP_POINTS
94 traj_cur(k)=traj_cur(k)+tab_coeffs1(q)*ponderations(q)/pondsSUM
95 enddo
96 else
97 traj_cur(k)=0
98 mask_cur(k)=0
99 endif
100 if(k.GE.2.AND.mask_cur(k-1).EQ.0)then
101 traj_cur(k)=0
102 mask_cur(k)=0
103 endif
104
105 enddo
106
107 cgf vertical interpolation:
108 do kk=1,NLEVELMAX
109 traj_cur_out(kk)=0
110 prof_mask1D_cur(kk,bi,bj)=0
111 enddo
112 do kk=1,ProfDepthNo(file_cur,bi,bj)
113 c case 1: above first grid center=> first grid center value
114 if (prof_depth(file_cur,kk,bi,bj).LT.-rC(1)) then
115 traj_cur_out(kk)=traj_cur(1)
116 prof_mask1D_cur(kk,bi,bj)=mask_cur(1)
117 c case 2: just below last grid center=> last cell value
118 elseif (prof_depth(file_cur,kk,bi,bj).GE.-rC(nr)) then
119 if ( prof_depth(file_cur,kk,bi,bj) .LT.
120 & (-rC(nr)+drC(nr)/2) ) then
121 traj_cur_out(kk)=traj_cur(nr)
122 prof_mask1D_cur(kk,bi,bj)=mask_cur(nr)
123 endif
124 c case 3: between two grid centers
125 else
126 kcur=0
127 do k=1,nr-1
128 if ((prof_depth(file_cur,kk,bi,bj).GE.-rC(k)).AND.
129 & (prof_depth(file_cur,kk,bi,bj).LT.-rC(k+1))) then
130 kcur=k
131 endif
132 enddo
133 if (kcur.EQ.0) then
134 WRITE(errorMessageUnit,'(A)')
135 & 'ERROR in PROFILES_INTERP: unexpected case 1'
136 STOP 'ABNORMAL END: S/R PROFILES_INTERP'
137 endif
138 if (mask_cur(kcur+1).EQ.1.) then
139 c subcase 1: 2 wet points=>linear interpolation
140 tmp_coeff=(prof_depth(file_cur,kk,bi,bj)+rC(kcur))/
141 & (-rC(kcur+1)+rC(kcur))
142 traj_cur_out(kk)=(1-tmp_coeff)*traj_cur(kcur)
143 & +tmp_coeff*traj_cur(kcur+1)
144 prof_mask1D_cur(kk,bi,bj)=1
145 if (mask_cur(kcur).EQ.0.) then
146 WRITE(errorMessageUnit,'(A)')
147 & 'ERROR in PROFILES_INTERP: unexpected case 2'
148 STOP 'ABNORMAL END: S/R PROFILES_INTERP'
149 endif
150 elseif (prof_depth(file_cur,kk,bi,bj).LT.-rF(kcur+1)) then
151 c subcase 2: only 1 wet point just above=>upper cell value
152 traj_cur_out(kk)=traj_cur(kcur)
153 prof_mask1D_cur(kk,bi,bj)=mask_cur(kcur)
154 endif
155 endif
156 enddo
157
158
159 #endif
160
161 end
162

  ViewVC Help
Powered by ViewVC 1.1.22