source: trunk/SOURCES/Hudson_files/climat-hudson_mod.f90 @ 4

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

initial import GRISLI trunk

File size: 4.9 KB
Line 
1!> \file climat-hudson_mod.f90
2!! Module pour le le calcul du climat des experiences Heino avec shelf
3!<
4
5!> \namespace  climat_hudson
6!! Module pour le calcule du climat des experiences Heino avec shelf
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12module  climat_hudson               ! pour le climat des experiences Heino avec shelf
13
14
15use module3d_phy
16implicit none
17
18real, dimension(nx,ny) :: dist_heino     !< distance au centre
19real,dimension(nx,ny) ::  xcc , ycc      !< coordeonnes en m
20real :: bilmin                           !< bilan min
21real :: bilmax                           !< bilan max
22real :: coefbil
23real :: Rcal                             !< rayon de la calotte
24real :: Tsmin                            !< Temperature min
25real :: St                               !< gradient horizontal de temperature
26real :: time_change                      !< temps apres lequel on met un changement
27real :: deltaTann                        !< changement de temeprature
28real :: ratiobil                         !< changement de bilan (facteur)
29
30
31contains
32!______________________________________________________________________________
33
34!>SUBROUTINE: input_clim
35!! Initialise la distance au centre
36!<
37
38subroutine input_clim                  ! initialise la distance au centre
39
40real :: xcentre !< dist centre en km
41real :: ycentre
42real :: coefbil
43
44!cdc if (itracebug.eq.1)  call tracebug(' Heino: entree dans routine input_clim')
45
46xcentre=((NX-1)/2)*DX/1000.
47ycentre=((NY-1)/2)*DX/1000.
48
49!jalv: rayon de la calotte virtuelle dont ses bords sont determinés par le bilan de masse, car le domaine sur Hudson est maintenant (à differnece de Heino) entierement CONTINENTALE(sauf la baie)
50 
51Rcal=2400.    ! en km mais la distance l'est aussi
52
53print*,'xcentre,ycentre', xcentre,ycentre
54
55do j=1,ny
56   do i=1,nx
57     xcc(i,j)=(i-1)*dx
58     ycc(i,j)=(j-1)*dy
59   end do
60end do
61
62xcc(:,:)=xcc(:,:)/1000.
63ycc(:,:)=ycc(:,:)/1000.
64
65
66dist_heino(:,:)=(xcc(:,:)-xcentre)**2+(ycc(:,:)-ycentre)**2
67dist_heino(:,:)=dist_heino(:,:)**0.5
68
69write(42,*)
70write(42,*)'bilan Heino------------------------------------'
71write(42,*)'initialisation distance au centre en km'
72
73bilmin=0.15   ! en m/an
74bilmax=0.30    ! en m/an
75
76coefbil=(bilmax-bilmin)/Rcal
77
78!jalv bm(:,:)=bilmin+coefbil*dist_heino(:,:)
79
80acc(:,:)=bilmin+coefbil*dist_heino(:,:)
81
82!Acc(:,:)=bm(:,:)
83
84!jalv:
85! Hudson: bords de la calotte definies par bilan de masse=0
86
87where (dist_heino(:,:).gt.2400.) acc(:,:)=0.
88
89abl(:,:)=0.
90
91!jalv:
92! Hudson: bords de la calotte definies par une ablation tres tres forte Abl=10.
93
94where (dist_heino(:,:).gt.2400.) abl(:,:)=-20.
95
96!where (flot(:,:)) abl(:,:)=0.
97!where (flot(:,:)) acc(:,:)=0.
98
99!where (mk(:,:).lt.9) acc(:,:)=0.   ! Heino: bilan de masse=0 dans l'ocean
100!where (mk(:,:).lt.9) abl(:,:)=0.
101
102!jalv: test pour que le bilan de masse soit 0 sur l'ocean plus profond de 600 m:
103!      c'est le bon critere??:
104where (sealevel-BSOC(:,:).gt.600) acc(:,:)=0.
105where (sealevel-BSOC(:,:).gt.600) abl(:,:)=0.
106
107where ((sealevel-BSOC(:,:).gt.100).and.(dist_heino(:,:).gt.2500.)) abl(:,:)=-1.
108where ((sealevel-BSOC(:,:).gt.100).and.(dist_heino(:,:).gt.2600.)) abl(:,:)=-5.
109where ((sealevel-BSOC(:,:).gt.100).and.(dist_heino(:,:).gt.2650.)) abl(:,:)=-10.
110where ((sealevel-BSOC(:,:).gt.100).and.(dist_heino(:,:).gt.2700.)) abl(:,:)=-20.
111
112bm(:,:)=acc(:,:)+abl(:,:)
113
114write(42,*) 'bilmin,bilmax (m/an)',bilmin,bilmax
115
116Tsmin=-40.0    ! run standard
117
118!jalv: pour que la temp soit pas positive dans les bords de la calotte dans l'experience
119!      Hudson il faut une Tmin plus basse: on prens celle du run T1-Heino
120!      (pas forcement vrai)
121
122!Tsmin=-50.0    ! run T1
123St=2.5e-9
124
125write(42,*)'Temperature, Tsmin (deg C), gradient (deg/km-3)',Tsmin,St
126
127Tann(:,:)=Tsmin+St*dist_heino(:,:)**3
128
129
130! Attention dans la version shelf on utilise mk et pas mk0
131!where (mk(:,:).eq.1) Tann(:,:)=0.
132!where (flot(:,:)) Tann(:,:)=0.
133
134!jalv: test pour que la Temp soit 0 sur l'ocean plus profond que 600 m:
135!      c'est le bon critere??:
136!where (BSOC(:,:).lt.B(:,:)) Tann(:,:)=0.
137where (sealevel-BSOC(:,:).gt.600) Tann(:,:)=0. 
138
139
140Ts(:,:)=Tann(:,:)
141
142time_change=1.e6
143deltaTann=0.
144ratiobil=1.
145
146write(42,*)'Ces valeurs sont gardee jusqu a',time_change,'ans'
147write(42,*)'apres : T=T+',deltaTann,'        bilan=bilan*',ratiobil
148
149!jalv Acc(:,:)=bm(:,:)
150
151! calcul de la fusion basale :
152! premier essai : fusion basale cte :
153!where (flot(:,:)) bmelt(:,:)=0.30
154
155return
156end subroutine input_clim 
157
158!> SUBROUTINE: init_forclim
159!! Suroutine pour la coherence des modules
160!<
161subroutine init_forclim
162! on ne fait rien !
163end subroutine init_forclim
164
165
166!__________________________________________________________________________
167
168!>SUBROUTINE: forclim
169!!
170!<
171subroutine forclim
172!cdc if (itracebug.eq.1)  call tracebug(' Heino: entree dans routine forclim')
173
174if (time.gt.time_change) then
175   Tann(:,:)=Tann(:,:)+deltaTann
176   Ts(:,:)=Tann(:,:)
177   bm(:,:)=bm(:,:)*ratiobil
178endif
179
180
181end subroutine forclim
182
183end module climat_hudson
Note: See TracBrowser for help on using the repository browser.