source: trunk/SOURCES/Eurasie40_files/bmelt-eurasie-depth-lake_mod.f90 @ 237

Last change on this file since 237 was 237, checked in by aquiquet, 6 years ago

Sealevel is now treated as a 2D variable (sealevel_2d while sealevel remains the eustatic sea level), results should remain identical as sealevel_2d is equal to sealevel in this revision.

File size: 5.4 KB
Line 
1!> \file bmelt-eurasie-depth-lake_mod.f90
2!! Module qui calcule la fusion basale (grounded ou ice shelves)
3!<
4
5!> \namespace  bmelt_eurasie_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!! A choisir dans le module_choix
9!! \author Catherine
10!! \date Juiilet 2005
11!! @note Used module
12!! @note   - use module3D_phy
13!<
14
15
16module  bmelt_eurasie_regions       ! cat juillet 2005
17
18! calcule la fusion basale (grounded ou ice shelves)
19! pour les ice shelves Antarctique, tient compte des différentes régions
20! A choisir dans le module_choix
21
22       USE module3D_phy
23
24implicit none
25
26
27REAL,dimension(nx,ny) ::  bmgrz       !< fusion basale a la grounding zone
28real,dimension(nx,ny) ::  bmshelf     !< fusion basale sous shelf
29
30!REAL,dimension(nx,ny) :: dist_talu    ! distance du point au talu continental
31!REAL,dimension(nx,ny) :: typeshelf    ! Type de shelf Ronne->1 Ross ->2 ....
32                                      ! utilises pour moduler la fusion sous le shelf
33!integer, dimension(10) :: region     ! pour écrire dans le fichier param
34!character(len=30),dimension(10) :: regname ! nom des régions
35real :: bsupshelf
36
37CONTAINS
38!-------------------------------------------------------------------------------
39
40!>
41!!SUBROUTINE: init_bmelt
42!! Cette routine fait l'initialisation pour la fusion basale.
43!! Elle est appelée par inputfile-vec-0.5.f90
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!    ecriture dans le fichier parametres
51     write(42,*)'fusion basale sous les ice shelves : bmelt-constant_mod'
52     write(42,*)'-------------------------------------------------------'
53
54! lecture du fichier contenant les distances au talu continental (m)
55!      open(88,file=TRIM(DIRNAMEINP)//'distance_talu-40km.xy')
56!      do j=1,ny
57!         do i=1,nx
58!            read(88,'(i3,1x,i3,1x,f10.2)') k,k,dist_talu(i,j)
59!         enddo
60!      enddo
61!      close(88)
62
63! lecture du fichier contenant les types de shelves
64!  Ronne-Flichner ->1, Ross -> 2 , Amery -> 3,
65!  PIG-> 4, les petits shelves au dessus de PIG -> 5
66
67!      open(88,file=TRIM(DIRNAMEINP)//'numer-ice-shelves-av05')
68!      typeshelf(:,:)=100
69!      do k=1,nx*ny
70!        read(88,*,end=36) i,j,typeshelf(i,j)
71!      end do
72!36      close(88)
73
74
75! region(:)=0
76! regname(1)='Ronne-Fichner'
77! regname(2)='Ross'
78! regname(3)='Amery'
79! regname(4)='Pig'
80! regname(5)='Petits ice shelves peninsule'
81! regname(6)='autres ice shelves'
82! regname(7)='Au dela du talus continental'
83 
84bms_init:    do j=1,ny
85         do i=1,nx
86
87            if ((sealevel_2d(i,j)-BSOC(i,j)).lt.450) then
88                    bmshelf(i,j)=2.00 !3.00! 2.55! 0.45!   0.65 
89                    bmgrz(i,j)=2.00 !3.00! 2.55! 0.45 !  0.65
90!                   if (i.lt.141.and. j.lt.121) then
91!                  bmshelf(i,j)=0.55!   0.65 
92!                  bmgrz(i,j)=-1.55 !  0.65
93!                   endif       
94            else         
95                    bmshelf(i,j)=8.15 ! 1.45!   0.65 
96                    bmgrz(i,j)=8.15 ! 1.45 !  0.65
97            endif 
98
99         enddo
100      enddo bms_init
101
102
103      bsupshelf=.2
104      write(32,*)
105
106
107      return
108      end subroutine init_bmelt
109
110!________________________________________________________________________________
111
112!>
113!!SUBROUTINE: bmeltshelf
114!!Cette routine calcule la fusion basale proprement dite
115!<
116subroutine bmeltshelf
117
118
119! cette routine calcule la fusion basale proprement dite
120
121integer :: ngr           ! nombre de voisins flottants
122
123print*,coefbmshelf
124
125    do j=2,ny-1
126      do i=2,nx-1
127 
128
129                   if (sealevel_2d(i,j).gt.0) then
130                         bmshelf(i,j)=0.05!5.0   
131                         bmgrz(i,j)=0.05!5.0
132                   endif
133                   
134shelf:    if (flot(i,j)) then    ! partie flottante
135       
136                     
137             if (sealevel_2d(i,j).gt.sealevel) then
138                     bmelt(i,j)=bmshelf(i,j)
139                     if (fbm(i,j))  bmelt(i,j)=bmgrz(i,j)
140             else       
141                     bmelt(i,j)=coefbmshelf*bmshelf(i,j)
142                     if (fbm(i,j))  bmelt(i,j)=coefbmshelf*bmgrz(i,j)
143             endif 
144!                           bmelt(i,j)=bmshelf(i,j)
145!                  if (time.gt.5000.) then
146!                     bmelt(i,j)=bmelt(i,j)+bsupshelf
147!                  endif   
148
149! ATTENTION LE BLOC SUIVANT SERT A FAIRE DES ICE SHELVES STATIONNAIRES
150! igrdline est défini dans itnitial1
151
152  if (igrdline.eq.1) then
153      corrbmelt(i,j)=corrbmelt(i,j)+hdot(i,j)*0.8
154      bmelt(i,j)=bmelt(i,j)+corrbmelt(i,j)
155  endif
156
157
158        else                   ! point posé, on compte le nombre de voisins flottants
159           ngr=0
160           if (flot(i+1,j)) ngr=ngr+1
161           if (flot(i-1,j)) ngr=ngr+1
162           if (flot(i,j+1)) ngr=ngr+1
163           if (flot(i,j-1)) ngr=ngr+1
164
165!   la fusion des points limites est une combinaison entre valeur posée et valeur flottante
166!   en fonction du nombre de points flottants
167
168           if (sealevel_2d(i,j).gt.sealevel) then
169                 bmelt(i,j)= ngr/4.*bmgrz(i,j)+(1.-ngr/4.)*bmelt(i,j)         
170           else
171                 bmelt(i,j)= ngr/4.*bmgrz(i,j)*coefbmshelf+(1.-ngr/4.)*bmelt(i,j)
172           endif       
173
174           
175
176        endif shelf
177
178      end do
179    end do
180
181
182    return
183    end subroutine  bmeltshelf
184
185
186end module  bmelt_eurasie_regions       ! cat juillet 2005
Note: See TracBrowser for help on using the repository browser.