source: trunk/SOURCES/Snowball_files/bmelt-snowball-depth_mod.f90 @ 334

Last change on this file since 334 was 237, checked in by aquiquet, 5 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: 4.3 KB
Line 
1MODULE  BMELT_SNOWBALL_DEPTH       
2
3! calcule la fusion basale (grounded ou ice shelves)
4! pour les ice shelves Antarctique, tient compte des différentes régions
5! A choisir dans le module_choix
6
7       USE module3D_phy
8
9implicit none
10
11
12REAL,dimension(nx,ny) ::  bmgrz       ! fusion basale a la grounding zone
13real,dimension(nx,ny) ::  bmshelf     ! fusion basale sous shelf
14
15!REAL,dimension(nx,ny) :: dist_talu    ! distance du point au talu continental
16!REAL,dimension(nx,ny) :: typeshelf    ! Type de shelf Ronne->1 Ross ->2 ....
17                                      ! utilises pour moduler la fusion sous le shelf
18!integer, dimension(10) :: region     ! pour écrire dans le fichier param
19!character(len=30),dimension(10) :: regname ! nom des régions
20real :: bsupshelf
21
22CONTAINS
23!-------------------------------------------------------------------------------
24subroutine init_bmelt
25
26
27
28! Cette routine fait l'initialisation pour la fusion basale.
29! Elle est appelée par inputfile-vec-0.5.f90
30
31!    ecriture dans le fichier parametres
32     write(42,*)'fusion basale sous les ice shelves : bmelt-constant_mod'
33     write(42,*)'-------------------------------------------------------'
34
35! lecture du fichier contenant les distances au talu continental (m)
36!      open(88,file=TRIM(DIRNAMEINP)//'distance_talu-40km.xy')
37!      do j=1,ny
38!         do i=1,nx
39!            read(88,'(i3,1x,i3,1x,f10.2)') k,k,dist_talu(i,j)
40!         enddo
41!      enddo
42!      close(88)
43
44! lecture du fichier contenant les types de shelves
45!  Ronne-Flichner ->1, Ross -> 2 , Amery -> 3,
46!  PIG-> 4, les petits shelves au dessus de PIG -> 5
47
48!      open(88,file=TRIM(DIRNAMEINP)//'numer-ice-shelves-av05')
49!      typeshelf(:,:)=100
50!      do k=1,nx*ny
51!        read(88,*,end=36) i,j,typeshelf(i,j)
52!      end do
53!36      close(88)
54
55
56! region(:)=0
57! regname(1)='Ronne-Fichner'
58! regname(2)='Ross'
59! regname(3)='Amery'
60! regname(4)='Pig'
61! regname(5)='Petits ice shelves peninsule'
62! regname(6)='autres ice shelves'
63! regname(7)='Au dela du talus continental'
64 
65bms_init:    do j=1,ny
66         do i=1,nx
67
68            if ((sealevel_2d(i,j)-bsoc(i,j)).lt.600) then
69                    bmshelf(i,j)=0.2 ! 0.45!   0.65 
70                    bmgrz(i,j)=0.2 ! 0.45 !  0.65
71!                   if (i.lt.141.and. j.lt.121) then
72!                   bmshelf(i,j)=0.55!   0.65 
73!                   bmgrz(i,j)=0.55 !  0.65
74!                   endif       
75            else   
76                   
77                    bmshelf(i,j)= 2.45!   0.65 
78                    bmgrz(i,j)= 2.45 !  0.65
79            endif 
80
81         enddo
82      enddo bms_init
83
84
85 
86      bsupshelf=.2
87      write(32,*)
88
89
90      return
91      end subroutine init_bmelt
92
93!________________________________________________________________________________
94subroutine bmeltshelf
95
96
97! cette routine calcule la fusion basale proprement dite
98
99integer :: ngr           ! nombre de voisins flottants
100
101
102    do j=2,ny-1
103      do i=2,nx-1
104 
105
106shelf:    if (flot(i,j)) then    ! partie flottante
107
108            if ((sealevel_2d(i,j)-bsoc(i,j)).lt.600) then
109                    if ((j.lt.75).and.(i.lt.145) ) then  !Atlantique
110                    bmelt(i,j)=(.6+.4*coefbmshelf)*bmshelf(i,j)
111                    else
112                    bmelt(i,j)=coefbmshelf*bmshelf(i,j)
113                    endif
114            else
115            bmelt(i,j)=bmshelf(i,j)
116            endif
117
118            if (fbm(i,j))  bmelt(i,j)=coefbmshelf*bmgrz(i,j)
119
120
121!                  if (time.gt.5000.) then
122!                     bmelt(i,j)=bmelt(i,j)+bsupshelf
123!                  endif   
124
125! ATTENTION LE BLOC SUIVANT SERT A FAIRE DES ICE SHELVES STATIONNAIRES
126! igrdline est défini dans itnitial1
127
128  if (igrdline.eq.1) then
129      corrbmelt(i,j)=corrbmelt(i,j)+hdot(i,j)*0.8
130      bmelt(i,j)=bmelt(i,j)+corrbmelt(i,j)
131  endif
132
133
134        else                   ! point posé, on compte le nombre de voisins flottants
135           ngr=0
136           if (flot(i+1,j)) ngr=ngr+1
137           if (flot(i-1,j)) ngr=ngr+1
138           if (flot(i,j+1)) ngr=ngr+1
139           if (flot(i,j-1)) ngr=ngr+1
140
141!   la fusion des points limites est une combinaison entre valeur posée et valeur flottante
142!   en fonction du nombre de points flottants
143
144           bmelt(i,j)= ngr/4.*bmgrz(i,j)*coefbmshelf+(1.-ngr/4.)*bmelt(i,j)
145
146           
147
148        endif shelf
149
150      end do
151    end do
152
153
154    return
155    end subroutine  bmeltshelf
156
157
158
159  END MODULE  BMELT_SNOWBALL_DEPTH
Note: See TracBrowser for help on using the repository browser.