source: branches/GRISLIv3/SOURCES/celltest_tracer.f90

Last change on this file was 486, checked in by aquiquet, 5 months ago

Cleaning branch: some cleaning and checking of passive tracers

File size: 4.9 KB
Line 
1    subroutine CellTest(time_tra, ic, jc, kc, v_x, v_y, v_E, xtracer, &
2      ytracer, E_k, im, jm, km, fx, fy, fz)
3
4
5
6      !!  Find the cell origin index for the previous time_tra step
7      use module3d_phy, only: e,uybar,flotmy,uy,gzmy
8      use geography, only: nx,ny,nz,dx,dy
9      use tracer_vars, only: xgrid,ygrid
10
11      implicit none
12
13      integer, intent(IN) :: time_tra
14      integer, intent(IN) :: ic, jc, kc
15      real, intent(IN) :: v_x, v_y, v_E
16      real, intent(IN) :: xtracer, ytracer
17      real, intent(INOUT) :: E_k
18      integer, intent(OUT) :: im, jm, km
19      real, intent(OUT) :: fx, fy, fz
20
21      integer :: kk   ! indice vertical pour definition de E, mais on veut conserver la valeur de k
22
23      if(v_x>0.0) then
24        im = ic-1
25        do
26          if(xtracer>=xgrid(im) .and. xtracer<=xgrid(im+1)) exit
27          !! PRINT *,"CellTest(x-): Multiple decrement required (",ic,",",jc,",",kc,")"
28          im = im-1
29          if(im<1) then
30            print *,"CellTest(x-;",time_tra,"): Out-of_range decrement (",ic,",",jc,",",kc,")", v_x
31!           STOP
32           im =ic
33           exit
34         end if
35        end do
36      else
37        im = ic
38        do
39          if(xtracer>=xgrid(im) .and. xtracer<=xgrid(im+1)) exit
40          !! PRINT *,"CellTest(x+): Multiple increment required (",ic,",",jc,",",kc,")"
41          im = im+1
42          if(im==nx-1) then
43            print *,"CellTest(x+;",time_tra,"): Out-of_range increment (",ic,",",jc,",",kc,")", v_x
44!           STOP
45             im = ic -1
46             exit
47          end if
48        end do
49      end if
50
51      fx = abs(xtracer-xgrid(im))/dx
52  if (fx>1.00)    fx = fx - aint(fx)
53
54!     if((fx>1.0).or.(fx<0.0)) THEN
55!       PRINT *,"Cell test(!!!)", ic,jc, kc,im, fx
56!     END IF
57!----------------------------------------------------------------------------------
58
59      if(v_y>0.0) then
60        jm = jc -1
61        do
62          if(ytracer>=ygrid(jm) .and. ytracer<=ygrid(jm+1)) exit
63          !! PRINT *,"CellTest(y-): Multiple decrement required (",ic,",",jc,",",kc,")"
64          jm = jm-1
65          if(jm<1) then
66            print *,"CellTest(y-;",time_tra,"): Out-of_range decrement (",ic,",",jc,",",kc,")", v_y
67!           STOP
68              jm =jc
69              exit
70          end if
71        end do
72      else
73        jm = jc
74        do
75          if(ytracer>=ygrid(jm) .and. ytracer<=ygrid(jm+1)) exit
76          !! PRINT *,"CellTest(y+): Multiple increment required (",ic,",",jc,",",kc,")"
77          jm = jm+1
78          if(jm==ny-1) then
79            print *,"CellTest(y+;",time_tra,"): Out-of-range increment (",ic,",",jc,",",kc,")", v_y
80!           print*, ytracer, ygrid(jm)
81            print*, uybar(ic,jc), uybar(ic,jc+1), flotmy(ic,jc), flotmy(ic, jc+1)
82            print *, uy(ic,jc,:)
83            print *, uy(ic,jc+1,:)
84            print*, gzmy(ic, jc), gzmy(ic,jc+1)
85!           STOP
86             jm = jc-1
87             exit
88          end if
89        end do
90      end if
91
92      fy = abs(ytracer-ygrid(jm))/dy
93  if (fy>1.00)    fy = fy - aint(fy)
94
95!     if((fy>1.0).or.(fy<0.0)) THEN
96!       PRINT *,"Cell test(!!!)", ic,jc,kc,im,jm, fy
97!     END IF
98 
99!-------------------------------------------------------------------------------
100
101      !! Note that v_E is "velocity" in E coordinate system which is
102      !! positive DOWN
103      ! also note that in Catritz code k=1 for surface
104
105   
106  if(E_k < E(1)) then
107        E_k = E(1)
108        km=1
109   
110  else if(E_k > E(nz)) then
111        E_k = E(nz)
112        km=nz-1
113
114  else   ! this used to be a loop on its own, now shortcuts if E_k is special
115
116      if(v_E>=0.0) then   !! Downward flow of ice in E system
117        if (kc==1) then
118          !! No action, pending tactical discussion with GKCC
119          km = 1
120        else
121          km=kc - 1
122          do
123            if( (E_k >= E(km)) .and. (E_k <= E(km+1)) ) exit
124            km = km - 1
125            if(km==0) then
126              print *,"CellTest(z+;",time_tra,"): Out-of-range increment (",ic,",",jc,",",kc,")", v_E
127!             STOP
128              km = kc
129              exit
130            end if
131          end do
132        end if
133      else                             !! Upward flow of ice in E system
134        if(kc==nz) then   
135        ! this is incomplete: ice comes from below, cannot use above layer, fix in interpolate
136          km = kc-1
137        else
138          km = kc
139         do
140          if( (E_k >= E(km)) .and. (E_k <= E(km+1)) ) exit
141          !! PRINT *,"CellTest(z,",time_tra,"): Decrementing km=",km
142          km = km + 1
143          if(km==nz) then
144            print *,"CellTest(z-;",time_tra,"): Out-of-range decrement (",ic,",",jc,",",kc,")", v_E
145!           STOP
146             km = kc-1
147             exit
148          end if
149         end do
150       end if
151
152     end if  ! velocity direction
153
154      fz = abs((E_k-E(km))/(E(km+1)-E(km)))
155  if (fz>1.00)    fz = fz - aint(fz)
156
157  end if
158
159    end subroutine CellTest
160!===========================================================================
Note: See TracBrowser for help on using the repository browser.