source: trunk/SOURCES/interpolate_tracer.f90 @ 10

Last change on this file since 10 was 4, checked in by dumas, 10 years ago

initial import GRISLI trunk

File size: 7.9 KB
Line 
1subroutine interpolate(ic, jc, kc, im, jm, km, fx,fy,fz, E_k)
2 
3  use module3d_phy
4  use tracer_vars
5  use climat_perturb_mois_mod ! on en a besoin, notamment pour NFT
6
7  implicit none
8  integer, intent(IN) :: ic, jc, kc, im, jm, km
9  real, intent(INOUT) :: fx, fy, fz, E_k
10  real :: fx_1, fy_1, fz_1, a_xy, a_xy_p, f_zt, a_tmp, ac , al
11  real :: fra1, fra2, fra0, accucumul1, accucumul2, accucumul0, &
12       thinning, thinning2, f_k, a_xy_m, fzz, fprime, fsec
13  integer :: index1, index2, index0
14 
15  integer :: kk   ! indice vertical pour definition de E, mais on veut conserver la valeur de k
16!  real,dimension(nz) :: E   ! vertical coordinate in ice, scaled to H zeta
17 
18  !! Note that input (im,jm,km) refer to points on (ij,jj) grid
19  !! whereas CellTest search was performed on (i,j) grid
20
21
22  E(1)=0.
23  E(NZ)=1.
24  do KK=1,NZ
25     if ((KK.ne.1).and.(KK.ne.NZ)) E(KK)=(KK-1.)/(NZ-1.)
26  end do
27
28  fx_1 = 1.0-fx
29  fy_1 = 1.0-fy
30  fz_1 = 1.0-fz
31
32  ! start with bilinear interp in horizontal plane
33  ! above
34  a_xy   = fx_1*fy_1*tdepk(km,im,jm)+fx*fy_1*tdepk(km,im+1,jm)+ &
35       fx_1*fy*tdepk(km,im,jm+1)+fx*fy*tdepk(km,im+1,jm+1)
36  ! below
37  a_xy_p = fx_1*fy_1*tdepk(km+1,im,jm)+fx*fy_1*tdepk(km+1,im+1,jm)+ &
38       fx_1*fy*tdepk(km+1,im,jm+1)+fx*fy*tdepk(km+1,im+1,jm+1)
39
40
41  if  ( ((a_xy - a_xy_p) < 200.).or.(H(ic+1,jc+1)<100.)) then
42     tdep(kc,ic,jc) = fz_1*a_xy+fz*a_xy_p
43     
44  else if ((a_xy_p<time_max_accu +1000.) &
45       .or.(fz<1.E-7).or.(fz_1<1.E-7) ) then   ! added 25/03/04: don t bother for < 1/50mm
46     
47     a_tmp = fz_1*a_xy+fz*a_xy_p
48     
49     if  ((km==1).and.(fz<0.5)) then
50        tdep(kc,ic,jc) = a_tmp
51       
52     else  ! cubic interp from the closest neighbour
53        if (fz>0.5) then  ! furthest to km, use km+2 unless bottom
54           a_xy_m= a_xy
55           a_xy = a_xy_p
56           if (km+1==nz) then
57              a_xy_p = a_xy + 1.3*(a_xy - a_xy_m) ! like articially old 22nd layer
58           else
59              a_xy_p = fx_1*fy_1*tdepk(km+2,im,jm)+fx*fy_1*tdepk(km+2,im+1,jm)+ &
60                   fx_1*fy*tdepk(km+2,im,jm+1)+fx*fy*tdepk(km+2,im+1,jm+1)
61           end if
62           fzz= - fz_1  ! because km+1 closer than km and E_D<E(km+1)
63        else       
64           a_xy_m = fx_1*fy_1*tdepk(km-1,im,jm)+fx*fy_1*tdepk(km-1,im+1,jm)+ &
65                fx_1*fy*tdepk(km-1,im,jm+1)+fx*fy*tdepk(km-1,im+1,jm+1)
66           fzz = fz
67        end if
68        fprime = - abs(a_xy_p - a_xy_m)/2.  ! /E(km+1)-E(km) included in fz
69        fsec = - abs(a_xy_p - 2.*a_xy + a_xy_m)   ! idem
70        ! there is a risk of overshooting, limit change to 1.3x linear change
71        al  = abs(tdepk(kc,ic,jc) - a_tmp)
72        ac  = abs(tdepk(kc,ic,jc) - (a_xy + fzz*fprime + fzz**2*fsec/2.))
73        if (ac<(1.3*al)) then   
74           tdep(kc,ic,jc) = a_xy + fzz*fprime + fzz**2*fsec/2.
75        else
76           tdep(kc,ic,jc) = a_tmp
77        end if
78     end if
79     
80     
81  else
82     
83     index1  = floor(-a_xy/100.)           ! gives the youngest: ind1+1 < tdepk < ind1
84     fra1 = real((-a_xy/100.) - index1)
85     accucumul1 = real(  -fra1*(accucumul(index1)-accucumul(index1+1))  +  accucumul(index1) )
86     index2  = floor(-a_xy_p/100.)
87     fra2 = real((-a_xy_p/100.) - index2)
88     accucumul2 = real( -fra2 * (accucumul(index2)-accucumul(index2+1)) + accucumul(index2) )
89     
90     !print*, 'ic,jc,kc :',ic,jc,kc
91     !print*, 'a_xy et a_xy_p', a_xy, a_xy_p
92     !print*, 'index1 et 2',index1,index2
93     !print*, 'fra1 et 2', fra1,fra2
94     !print*, 'accucumul 1 et 2 :', accucumul1, accucumul2,accucumul2-accucumul1  !aurel neem
95     thinning =    ( real( -(E(km+1)-E(km)) / (accucumul2 - accucumul1)) )      ! checked
96     !print*, 'thinning ', thinning  !aurel neem
97
98     if (fz < 0.5) then
99        !======= closer to km, probably upward motion, rather seldom NL thinks
100        if (km>1) then
101           a_xy_m = fx_1*fy_1*tdepk(km-1,im,jm)+fx*fy_1*tdepk(km-1,im+1,jm)+ &
102                fx_1*fy*tdepk(km-1,im,jm+1)+fx*fy*tdepk(km-1,im+1,jm+1)
103           ! should be a_xy_m - a_xy > 0
104           if ((a_xy_m>time_max_accu+ 500.).and.(   (a_xy_m - a_xy) > 200.)) then
105              index0  = floor(-a_xy_m/100.)
106              fra0 = real((-a_xy_m/100.) - index0)
107              accucumul0 = real( -fra0 * (accucumul(index0)-accucumul(index0+1)) &
108                   + accucumul(index0) )
109              ! acc0 > acc1
110
111              !print*, 'ic,jc,kc :',ic,jc,kc
112              !print*, 'accucumul 0 et 1 : ', accucumul0, accucumul1,accucumul1-accucumul0 !aurel neem
113              thinning2 =    ( real( -(E(km)-E(km-1)) / (accucumul1 - accucumul0)) )            ! ok
114              !print*, 'thinning2 ', thinning2  !aurel neem
115
116              thinning =  max(1.e-8, (0.5-fz/2.0)*thinning2 + (0.5+fz/2.0)*thinning)
117             
118              ! fz/c2 says my theory, though for Greenland I find that /c3 or /c4 may be better...
119           end if
120        end if
121 
122        f_k = real( accucumul1 - (E_k - E(km) ) / thinning )           ! ok: f_k < acc1
123        ! downward search
124        index0=index1-1   ! no inversion in stratigraphy
125        L4: do
126           index0 = index0 + 1
127           if ((index0>=NFT-1).or.(accucumul(index0)  < f_k )) exit L4 
128           ! index < ind(t) < index-1,  t(i+1) < t < t(i)
129        end do L4
130        index0 = index0-1
131       
132        !=========================================
133     else                               !  fz> 0.5, probably downwards
134       
135        if (km<nz-1) then
136           a_xy_m = fx_1*fy_1*tdepk(km+2,im,jm)+fx*fy_1*tdepk(km+2,im+1,jm)+ &
137                fx_1*fy*tdepk(km+2,im,jm+1)+fx*fy*tdepk(km+2,im+1,jm+1)
138           if ((a_xy_m>time_max_accu+ 500.).and.(   (a_xy_m - a_xy_p) < -200.)) then
139              index0  = floor(-a_xy_m/100.)
140              fra0 = real((-a_xy_m/100.) - index0)
141              accucumul0 = real( -fra0 * (accucumul(index0)-accucumul(index0+1)) &
142                   + accucumul(index0) )
143             ! print*, 'ic,jc,kc :',ic,jc,kc
144             ! print*, 'accucumul 0 et 2 : ', accucumul0, accucumul2,accucumul0-accucumul2 !aurel neem
145              thinning2 =     ( real( -(E(km+2)-E(km+1)) / (accucumul0 - accucumul2)) )     
146             ! print*, 'thinning2 ', thinning2  !aurel neem
147              ! E decreases upwards!
148              thinning =  max(1.e-8, (0.5-fz_1/2.0)*thinning2 + (0.5+fz_1/2.0)*thinning)
149           end if
150        end if
151       
152        f_k = real( accucumul2 + (E(km+1) - E_k) / thinning )
153        ! upward search
154        index0=index2+2   ! no inversion in stratigraphy
155        L5: do
156           index0 = index0 - 1
157           if ((index0<=1).or.(accucumul(index0)> f_k )) exit L5
158           ! index < ind(t) < index+1,  t(i+1) < t < t(i)
159        end do L5
160     end if
161     ! now we know that we have index-1 < tdep(k) < index   from accucumul condition
162     
163     if ((index0==1).or.(index0==NFT-1)) then
164        fzz=2.
165     else 
166        fzz = real( (accucumul(index0) - f_k)/ (accucumul(index0)-accucumul(index0+1)) )
167     end if
168
169     if ((fzz>1.0).or.(fzz<0.0)) then
170        tdep(kc,ic,jc) = fz_1*a_xy + fz*a_xy_p
171     else
172        tdep(kc,ic,jc) = ( fzz + real(index0) ) * real(-100)
173     end if
174     
175  end if
176
177!=============== end tdep-interp ====================
178
179!       f_zt = (tdep(kc,ic,jc) - a_xy) / (a_xy_p - a_xy)
180! NL 21/11/02: use only fz, not f_zt, i don't think f_zt is right
181
182      a_xy   = fx_1*fy_1*xdepk(km,im,jm)+fx*fy_1*xdepk(km,im+1,jm)+ &
183               fx_1*fy*xdepk(km,im,jm+1)+fx*fy*xdepk(km,im+1,jm+1)
184      a_xy_p = fx_1*fy_1*xdepk(km+1,im,jm)+fx*fy_1*xdepk(km+1,im+1,jm)+ &
185               fx_1*fy*xdepk(km+1,im,jm+1)+fx*fy*xdepk(km+1,im+1,jm+1)
186
187      xdep(kc,ic,jc) = fz_1*a_xy+fz*a_xy_p
188
189!========= YDEP ===================
190
191      a_xy   = fx_1*fy_1*ydepk(km,im,jm)+fx*fy_1*ydepk(km,im+1,jm)+ &
192               fx_1*fy*ydepk(km,im,jm+1)+fx*fy*ydepk(km,im+1,jm+1)
193      a_xy_p = fx_1*fy_1*ydepk(km+1,im,jm)+fx*fy_1*ydepk(km+1,im+1,jm)+ &
194               fx_1*fy*ydepk(km+1,im,jm+1)+fx*fy*ydepk(km+1,im+1,jm+1)
195
196      ydep(kc,ic,jc) = fz_1*a_xy+fz*a_xy_p
197
198
199end subroutine interpolate
200!==========================================================================
Note: See TracBrowser for help on using the repository browser.