source: trunk/SOURCES/Ant40_files/dragging_stream_impose_vitbil_mod.f90 @ 93

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

initial import GRISLI trunk

File size: 6.5 KB
Line 
1!> \file dragging_stream_impose_vitbil_mod.f90
2!! Module qui defini les zones de stream d'apres les vitesses de bilan
3!<
4
5!> \namespace dragging_vitbil
6!! Module qui defini les zones de stream d'apres les vitesses de bilan
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12module dragging_vitbil
13! Défini les zones de stream d'apres les vitesses de bilan
14
15USE module3D_phy
16
17implicit none
18character(len=80) :: fil_vitbil
19integer,dimension(nx,ny) :: uxbil
20integer,dimension(nx,ny) :: uybil
21integer :: icfcote
22real :: cfcote
23
24contains
25
26!-------------------------------------------------------------------------------
27subroutine init_dragging      ! Cette routine fait l'initialisation du dragging.
28
29implicit none
30
31integer :: ii,jj
32integer,parameter :: ntotbil=50
33integer :: kux,kuy,ncolbil
34integer,dimension(ntotbil) :: index
35real,dimension(ntotbil) :: variables
36real :: seuil_stream
37
38if (itracebug.eq.1)  call tracebug(' Dragging avec vitbil')
39
40fil_vitbil='./Balance_velocities/depart-Camb-004+c01/vitbil_iter_100000'
41!fil_vitbil='file_vitbil-impose'
42
43betamax=200.   ! frottement maxi  (utilise dans remplimat-ant-0.4-40km
44              ! pour le calcul de frotmx
45
46toblim=0.25e5 ! test pour les iles
47seuil_stream=50
48cf=-10.e-5    ! coefficient de la loi de frottement fonction
49              ! de la vitesse et pression effective
50icfcote=0     ! traitement particulier pour la cote
51cfcote=0      ! valeur de cf pour la cote
52
53!    ecriture dans le fichier parametres
54     write(num_rep_42,*)'dragging vitbil-  initialisation '
55     write(num_rep_42,*)'vitesses venant du fichier',fil_vitbil
56     write(num_rep_42,*)'seuil stream=',seuil_stream,'(m)'
57     write(num_rep_42,*)' frottement maxi, betamax=',betamax
58     write(num_rep_42,fmt='(a,e10.3)') ' coefficient de frottement: cf=',cf
59
60     if (icfcote.eq.1) then
61        write(num_rep_42,*)'traitement particulier cote,  cfcote=',cfcote
62     else
63        write(num_rep_42,*)'pas de traitement particulier cote'
64     endif
65
66
67     write(num_rep_42,*)'----------------------------------------------------------'
68
69! lecture des masques dans un fichier hz ------------------------
70
71open(12,file=trim(fil_vitbil))
72read(12,*)   ! lecture ligne 1
73read(12,*)  i,ncolbil ! lecture ligne 2, 2eme position, nb de colonnes
74read(12,*) (index(k),k=1,ncolbil)   
75
76do k=1,ntotbil
77   if (index(k).eq.32) kux=k   ! colonne ux
78   if (index(k).eq.33) kuy=k   ! colonne uy
79end do
80
81read(12,*)   ! lecture ligne titres variables
82do j=1,ny
83   do i=1,nx
84      read(12,*)(variables(k),k=1,ncolbil)
85      uxbil(i,j)=variables(kux)
86      uybil(i,j)=variables(kuy)
87   end do
88end do
89
90close(12)
91
92!-------------------------------------------------------------------
93! masque stream
94
95mstream_mx(:,:)=0
96mstream_my(:,:)=0
97
98do j=2,ny-1
99   do i=2,nx-1
100      if (abs(uxbil(i,j)).ge.seuil_stream) then
101         mstream_mx(i,j)=1
102      endif
103
104      if (abs(uybil(i,j)).ge.seuil_stream) then
105         mstream_my(i,j)=1
106      endif
107   end do
108end do
109
110open(122,file='masque-vitbil')
111do j=1,ny
112   do i=1,nx
113      write(122,*) i,j,mstream_mx(i,j),mstream_my(i,j)
114   end do
115end do
116
117! coefficient permettant de modifier le basal drag.
118drag_mx(:,:)=1.
119drag_my(:,:)=1.
120
121! idee future : pour les points limite mer : drag_mx=0.
122
123 
124return
125end subroutine init_dragging
126!________________________________________________________________________________
127
128
129!-------------------------------------------------------------------------
130subroutine dragging   ! defini la localisation des streams et le frottement basal
131
132implicit none
133integer :: ii,jj
134
135!         les iles n'ont pas de condition neff mais ont la condition toblim
136!         (ce bloc etait avant dans flottab)
137
138do j=2,ny
139   do i=2,nx
140      ilemx(i,j)=ilemx(i,j).and.(abs(tobmx(i,j)).lt.toblim)
141      ilemy(i,j)=ilemy(i,j).and.(abs(tobmy(i,j)).lt.toblim)
142   end do
143end do
144
145
146gzm_x: do j=2,ny
147   do i=2,nx-1
148   
149! gzmx pour les hauteurs d'eau supérieures à un seuil
150! attention, il semble qu'il y avait une erreur dans la precedente
151! formulation car le test etait seulement sur hwater(i,j).
152
153      gzmx(i,j)=gzmx(i,j).or. & 
154           ((mstream_mx(i,j).eq.1) &
155           .and..not.flotmx(i,j))
156
157
158! calcul du frottement basal (ce bloc etait avant dans neffect)
159      if (gzmx(i,j)) then                          ! stream
160         betamx(i,j)=cf*neffmx(i,j) 
161
162! si limite region flottante       
163       if (icfcote.eq.1) then
164         if ((flot(i,j).and..not.flot(i-1,j)) &                !    F x  P
165             .or.(.not.flot(i,j).and.flot(i-1,j))) then        !    P x  F
166            betamx(i,j)=cfcote*neffmx(i,j)
167         endif
168      endif
169
170! limite sur deux points de grille
171      if (icfcote.eq.2) then
172         ii=max(1,i-2)
173         if (flot(i,j).or.flot(i+1,j) &               !  P x F  ou P x P    F
174              .or. flot(i-1,j).or.flot(ii,j)) then    !  F x P  ou F  P x P
175            betamx(i,j)=cfcote*neffmx(i,j)
176         end if
177      end if
178
179
180
181
182      else if (flotmx(i,j).or.ilemx(i,j)) then     ! flottant ou ile
183         betamx(i,j)=0.
184      else                                         ! grounded, SIA
185         betamx(i,j)=1.e5                          ! frottement 1 bar
186      endif     
187
188   end do
189end do gzm_x
190
191gzm_y: do j=2,ny-1
192   do i=2,nx
193   
194! gzmy pour les hauteurs d'eau supérieures à un seuil
195! attention, il semble qu'il y avait une erreur dans la precedente
196! formulation car le test etait seulement sur hwater(i,j).
197
198      gzmy(i,j)=gzmy(i,j).or. & 
199           ((mstream_my(i,j).eq.1) &
200           .and..not.flotmy(i,j))
201
202
203 ! calcul du frottement basal (ce bloc etait avant dans neffect)
204      if (gzmy(i,j)) then                ! stream
205         betamy(i,j)=cf*neffmy(i,j) 
206
207! si limite region flottante       
208       if (icfcote.eq.1) then
209         if ((flot(i,j).and..not.flot(i,j-1)) &                !    F    P
210             .or.(.not.flot(i,j).and.flot(i,j-1))) then        !    P    F
211            betamy(i,j)=cfcote*neffmy(i,j) 
212         endif
213      endif
214
215! limite sur deux points de grille
216      if (icfcote.eq.2) then
217         jj=max(1,j-2)
218         if (flot(i,j).or.flot(i,j+1) &               !  P x F  ou P x P    F
219              .or. flot(i,j-1).or.flot(i,jj)) then    !  F x P  ou F  P x P
220            betamy(i,j)=cfcote*neffmy(i,j)
221         end if
222      end if
223
224
225      else if (flotmy(i,j).or.ilemy(i,j)) then     ! flottant ou ile
226         betamy(i,j)=0.
227      else                               ! grounded, SIA
228         betamy(i,j)=1.e5                ! frottement 1 bar
229      endif     
230
231   end do
232end do gzm_y
233
234return
235end subroutine dragging
236
237end module dragging_vitbil
238
Note: See TracBrowser for help on using the repository browser.