source: iLOVECLIM-branch/SOURCES/Hemin40_files/bmelt-hemin40-regions_mod.f90 @ 28

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

initial import GRISLI trunk

File size: 7.4 KB
Line 
1!> \file bmelt-hemin40-regions_mod.f90
2!! Module qui calcule la fusion basale (grounded ou ice shelves)
3!<
4
5!> \namespace  BMELT_NOR_REGIONS
6!! Calcule la fusion basale (grounded ou ice shelves)
7!! @note Pour les ice shelves Antarctique, tient compte des différentes régions
8!! @note A choisir dans le module_choix
9!! \author Christophe
10!! \date Octobre 2008
11!! @note Used module
12!! @note   - use module3D_phy
13!<
14
15
16MODULE  BMELT_NOR_REGIONS
17
18! christophe Octobre 2008
19! calcule la fusion basale (grounded ou ice shelves)
20! pour les ice shelves du nord, tient compte des différentes régions
21! A choisir dans le module_choix
22
23  use module3D_phy
24  use printtable
25
26  implicit none
27
28
29  REAL,dimension(nx,ny) ::  bmgrz       !< fusion basale a la grounding zone
30  real,dimension(nx,ny) ::  bmshelf     !< fusion basale sous shelf
31
32!REAL,dimension(nx,ny) :: dist_talu    ! distance du point au talu continental
33  INTEGER,dimension(nx,ny) :: typeshelf    !< Type de shelf Ronne->1 Ross ->2 ....
34                                      !< utilises pour moduler la fusion sous le shelf
35  integer, dimension(10) :: region     !< pour écrire dans le fichier param
36  character(len=30),dimension(10) :: regname !< nom des régions
37  real :: bsupshelf
38
39CONTAINS
40!-------------------------------------------------------------------------------
41
42!>SUBROUTINE: init_bmelt 
43!! Cette routine fait l'initialisation pour la fusion basale.
44!<
45subroutine init_bmelt
46
47! Cette routine fait l'initialisation pour la fusion basale.
48! Elle est appelée par inputfile-vec-0.5.f90
49
50
51
52! lecture du fichier contenant les distances au talu continental (m)
53!      open(88,file=TRIM(DIRNAMEINP)//'distance_talu-40km.xy')
54!      do j=1,ny
55!         do i=1,nx
56!            read(88,'(i3,1x,i3,1x,f10.2)') k,k,dist_talu(i,j)
57!         enddo
58!      enddo
59!      close(88)
60
61! lecture du fichier contenant les types de shelves
62!  Pacific ->1,...
63
64!     open(88,file=TRIM(DIRNAMEINP)//'region_ocean-hn40.dat')
65      open(88,file=TRIM(DIRNAMEINP)//'region_ocean-2006-hn40.dat')
66      typeshelf(:,:)=100
67      do k=1,nx*ny
68        read(88,*,end=36) i,j,typeshelf(i,j)
69      end do
7036      close(88)
71 
72!        print*,'APRES',typeshelf(:,:)
73       
74 region(:)=0
75 regname(1)='Pacific'
76 regname(2)='deep Arctic'
77 regname(3)='deep Atlantic'
78 regname(4)='Udson'
79 regname(5)='Shallow Arctic'
80 regname(6)='Barents sea'
81 regname(7)='Shallow Atlantic'
82!regname(8)='Continent' !! YA PAS DE 8 !!
83 regname(9)='Continent'
84 
85 bms_init:    do j=1,ny
86    do i=1,nx
87
88!            if ((sealevel-bsoc(i,j)).lt.600) then
89!                    bmshelf(i,j)=0.2 ! 0.45!   0.65  ;  bmgrz(i,j)=0.2 ! 0.45 !  0.65
90!            else   
91!                   
92!                    bmshelf(i,j)= 2.45!   0.65  ;   bmgrz(i,j)= 2.45 !  0.65
93!            endif 
94       if (typeshelf(i,j).eq.1) then ! Pacific
95          bmshelf(i,j)=5.45!   0.65 
96          bmgrz(i,j)=5.45 !  0.65
97          if (region(1).eq.0) then
98             region(1)=1
99             write(42,80)regname(1),bmshelf(i,j),bmgrz(i,j)
100             write(6,80)regname(1),bmshelf(i,j),bmgrz(i,j)
101          endif
102
103
104       else  if (typeshelf(i,j).eq.2) then ! Deep Arctic
105          bmshelf(i,j)= 0.25!1.5   
106          bmgrz(i,j)=0.25   !1.5     
107          if (region(2).eq.0) then
108             region(2)=1
109             write(42,80)regname(2),bmshelf(i,j),bmgrz(i,j)
110             write(6,80)regname(2),bmshelf(i,j),bmgrz(i,j)
111          endif
112       else  if (typeshelf(i,j).eq.3) then ! Deep Atlantic
113          bmshelf(i,j)=5.45 
114          bmgrz(i,j)=5.45
115          if (region(3).eq.0) then
116             region(3)=1
117             write(42,80)regname(3),bmshelf(i,j),bmgrz(i,j)
118             write(6,80)regname(3),bmshelf(i,j),bmgrz(i,j)
119          endif
120
121
122       else  if (typeshelf(i,j).eq.4) then ! Udson
123          bmshelf(i,j)=.3 
124          bmgrz(i,j)=.3
125          if (region(4).eq.0) then
126             region(4)=1
127             write(42,80)regname(4),bmshelf(i,j),bmgrz(i,j)
128          endif
129       else  if (typeshelf(i,j).eq.5) then ! 'Shallow Arctic'
130          bmshelf(i,j)=.15 
131          bmgrz(i,j)=0.15
132          if (region(5).eq.0) then
133             region(5)=1
134             write(42,80)regname(5),bmshelf(i,j),bmgrz(i,j)
135          endif
136       else  if (typeshelf(i,j).eq.6) then !  'Barents sea'
137          bmshelf(i,j)=0.21 
138          bmgrz(i,j)=0.21
139          if (region(6).eq.0) then  !'Barents sea'
140             region(6)=1
141             write(42,80)regname(6),bmshelf(i,j),bmgrz(i,j)
142          endif
143!               if (region(6).eq.0) then
144!                  region(6)=1
145!                  write(42,80)regname(6),bmshelf(i,j),bmgrz(i,j)
146!               endif
147
148       else  if (typeshelf(i,j).eq.7) then !'Shallow Atlantic'
149          bmshelf(i,j)=0.55
150          bmgrz(i,j)=0.55 
151          if (region(7).eq.0) then  !
152             region(7)=1 
153             write(42,80)regname(7),bmshelf(i,j),bmgrz(i,j)     
154          endif
155!           else if (region(7).eq.0) then !'Shallow Atlantic'
156!                    bmshelf(i,j)=0.55 
157!                    bmgrz(i,j)=0.55
158!               if (region(7).eq.0) then
159!                  region(7)=1
160!                  write(42,80)regname(7),bmshelf(i,j),bmgrz(i,j)
161               
162!       else if (region(9).eq.0) then !'Continent =eau douce'
163       else  if (typeshelf(i,j).eq.9) then !'Shallow Atlantic'
164          bmshelf(i,j)=0.1 
165          bmgrz(i,j)=0.1
166          if (region(9).eq.0) then
167             region(9)=1
168             write(42,80)regname(9),bmshelf(i,j),bmgrz(i,j)
169          endif
170
171       endif
172    enddo
173 enddo bms_init
17480 format(a32,' bmshelf=',f8.4,'  bmgrz=',f8.4)
175
176 nom_table='bmshe'
177!cdc call printtable_r(bmshelf,nom_table)
178     
179!stop
180 bsupshelf=.2
181! write(32,*)
182! write(6,*) "fin subroutine init_bmelt"
183
184 return
185end subroutine init_bmelt
186
187!________________________________________________________________________________
188
189!> SUBROUTINE: bmeltshelf
190!! Cette routine calcule la fusion basale proprement dite
191!<
192
193subroutine bmeltshelf
194
195
196! cette routine calcule la fusion basale proprement dite
197
198  integer :: ngr           ! nombre de voisins flottants
199
200 
201  do j=2,ny-1
202     do i=2,nx-1
203 
204
205        shelf: if (flot(i,j)) then    ! partie flottante
206
207!           if ((sealevel-bsoc(i,j)).lt.600) then
208!                   if ((j.lt.75).and.(i.lt.145) ) then  !Atlantique
209!                   bmelt(i,j)=(.6+.4*coefbmshelf)*bmshelf(i,j)
210!                   else
211           bmelt(i,j)=coefbmshelf*bmshelf(i,j)
212!                   endif
213!           else
214!           bmelt(i,j)=bmshelf(i,j)
215!           endif
216
217           if (fbm(i,j))  bmelt(i,j)=coefbmshelf*bmgrz(i,j)
218
219
220!                  if (time.gt.5000.) then
221!                     bmelt(i,j)=bmelt(i,j)+bsupshelf
222!                  endif   
223
224! ATTENTION LE BLOC SUIVANT SERT A FAIRE DES ICE SHELVES STATIONNAIRES
225! igrdline est défini dans itnitial1
226
227           if (igrdline.eq.1) then
228              corrbmelt(i,j)=corrbmelt(i,j)+hdot(i,j)*0.8
229              bmelt(i,j)=bmelt(i,j)+corrbmelt(i,j)
230           endif
231
232
233        else                   ! point posé, on compte le nombre de voisins flottants
234           ngr=0
235           if (flot(i+1,j)) ngr=ngr+1
236           if (flot(i-1,j)) ngr=ngr+1
237           if (flot(i,j+1)) ngr=ngr+1
238           if (flot(i,j-1)) ngr=ngr+1
239
240!   la fusion des points limites est une combinaison entre valeur posée et valeur flottante
241!   en fonction du nombre de points flottants
242
243           bmelt(i,j)= ngr/4.*bmgrz(i,j)*coefbmshelf+(1.-ngr/4.)*bmelt(i,j)
244
245           
246
247        endif shelf
248
249     end do
250  end do
251
252
253  return
254end subroutine  bmeltshelf
255
256
257
258END MODULE  BMELT_NOR_REGIONS
Note: See TracBrowser for help on using the repository browser.