source: trunk/SOURCES/Old-sources/flottab-rescue-1.f90 @ 159

Last change on this file since 159 was 62, checked in by dumas, 8 years ago

Move unused sources files in Old-sources directory

File size: 2.8 KB
Line 
1!> \file flottab-rescue-1.f90
2!! Nouvelle formulation de flottab
3!<
4
5!> SUBROUTINE: FLOTTAB_RESCUE
6!! @note Nouvelle formulation
7!! \author Cat
8!! \date aout 2006
9!! @note On suppose que le programme est passe dans flottab
10!! la seule chose qui change est
11!! @note Used modules:
12!! @note    - module3D_phy
13!!
14!<
15! =======================================================
16!
17SUBROUTINE FLOTTAB_RESCUE()
18  !
19  ! nouvelle formulation Cat aout 2006
20  ! on suppose que le programme est passe dans flottab
21  ! la seule chose qui change est
22  ! =======================================================
23
24  USE module3D_phy
25  use module_choix
26
27
28  IMPLICIT NONE
29
30  ICE(:,:)=0
31  front(:,:)=0
32  frontfacex(:,:)=0
33  frontfacey(:,:)=0
34  isolx(:,:)=.FALSE.
35  isoly(:,:)=.FALSE.
36  boost=.false.
37
38
39  ! ice a 1 sur tout le domaine flottant
40  do i=2,nx-1
41     do j=2,ny-1
42        ice(i,j)=1
43     end do
44  end do
45
46
47  do i=2,nx-1
48     do j=2,ny-1
49
50        if (ice(i,j).eq.1) then    !test si ice=1, on determine front
51           front(i,j)=(ice(i-1,j)+ice(i+1,j)+ice(i,j+1)+ice(i,j-1))
52        endif
53     end do
54  end do
55
56
57  ! calcul du front
58  !-------------------
59
60  !isolx signifie pas de voisins en x
61  !isoly signifie pas de voisins en y
62  !remarque :
63  !si isolx/y=.true. alors frontfacex/y=0 (a la fois +1 & -1 or +1-1=0)
64
65  front_g:  do j=2,ny-1
66     do i=2,nx-1               !on ne compte pas les icebergs de 2 cases (horizontales ou verticales)
67
68        if (front(i,j).eq.1) then
69           if (front(i+1,j).eq.1) then
70              ice(i,j)=0
71              ice(i+1,j)=0
72              front(i,j)=0
73              front(i+1,j)=0
74           endif
75           if (front(i,j+1).eq.1) then
76              ice(i,j)=0
77              ice(i,j+1)=0
78              front(i,j)=0
79              front(i,j+1)=0
80           endif
81        endif
82
83        if (front(i,j).ge.1.and.front(i,j).le.3) then !front(entre 1 et 3)
84
85           if ((ice(i-1,j)+ice(i+1,j)).lt.2) then
86              ! il y a un front // a x
87              if ((ice(i-1,j)+ice(i+1,j)).eq.0) then
88                 isolx(i,j)=.true.
89              elseif (ice(i-1,j).eq.0) then
90                 frontfacex(i,j)=-1    ! front  i-1 |i  i+1
91              else
92                 frontfacex(i,j)=+1    ! front  i-1  i| i+1
93              endif
94           endif
95
96
97           if ((ice(i,j-1)+ice(i,j+1)).lt.2) then
98              ! il y a un front // a y
99              if ((ice(i,j-1)+ice(i,j+1)).eq.0) then
100                 isoly(i,j)=.true.    !front   j-1 |j| j+1
101              elseif (ice(i,j-1).eq.0) then
102                 frontfacey(i,j)=-1   !front   j-1 |j j+1
103              else
104                 frontfacey(i,j)=+1   !front   j-1  j| j+1
105              endif
106           endif
107
108        end if           !fin du test il y a un front
109
110     end do
111  end do front_g
112
113  return
114end subroutine flottab_rescue
Note: See TracBrowser for help on using the repository browser.