source: trunk/SOURCES/ablation_month.f90 @ 23

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

initial import GRISLI trunk

File size: 9.1 KB
Line 
1!> \file ablation_month.f90
2!! Pour le calcul de l'ablation mensuelle
3!<
4
5!> \namespace ablation_month
6!! Calcule l ablation mensuelle
7!! \author ...
8!! \date ...
9!! @note  Used modules:
10!! @note  - declare_month
11!! @note  - printtable
12!<
13
14
15module ablation_month
16
17use declare_month
18use printtable
19
20implicit none
21
22! parametres pour le bilan de masse
23
24real,dimension(nx,ny) :: snow, melt
25real                  :: frac, frac_min, frac_tot
26integer               :: meth_abl_vi
27! dimensionnements locaux
28real ::  dtp                   !< integrating step for positive degree days (degrees)
29real ::  pddct                 !< ct for PDD calculation
30real ::  py                    !< ct for PDD calculation
31real ::  s22                   !< ct for PDD calculation
32real ::  nyear                 !< number of months in 1 year, st. dev. for temp *)
33
34! parametres qui seront lus dans le fichier param
35
36real ::  sigma                 !< variabilite Tday
37real ::  CSI                   !< proportion of melted water that can refreeze *)
38real ::  Cice                  !< melting factors for ice
39real ::  Csnow                 !< melting factors for snow
40
41!!$! aurel (greeneem) : pour comparer les deux approches de calcul de pdd ->
42!!$real,dimension(nx,ny) :: pddann
43!!$real,dimension(nx,ny) :: bmann
44
45
46contains
47!--------------------------------------------------------------------------------
48!> SUBROUTINE: init_ablation
49!! @note Attribution et initialisation des parametres lies a la methode de calcul
50!! Used modules:
51!! - module3D_phy
52!>
53subroutine init_ablation
54
55namelist/ablation_month/Cice,Csnow,csi,sigma
56
57! lecture des parametres
58
59rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
60read(num_param,ablation_month)
61
62write(num_rep_42,*)'!___________________________________________________________'
63write(num_rep_42,*)'!              ablation_month     PDD base Tann et Tjuly'
64write(num_rep_42,ablation_month)                   ! pour ecrire les parametres lus
65write(num_rep_42,*)
66write(num_rep_42,*)
67write(num_rep_42,*)'! Cice and Csnow, melting factors for ice and snow '
68write(num_rep_42,*)'! sigma variabilite Tday'
69write(num_rep_42,*)'! csi proportion of melted water that can refreeze '
70
71! attribution des parametres lies a la methode de calcul
72dtp=2.0
73nyear=12
74s22=0.5/sigma/sigma
75py=2*pi/nyear
76pddct=dtp/sigma/sqrt(2.*pi)/nyear*365.
77
78end subroutine init_ablation
79
80!-------------------------------------------------------
81!> SUBROUTINE: Ablation
82!! @note Calcul l'ablation de chaque mois
83!>
84subroutine ablation
85
86if (itracebug.eq.1)  call tracebug(' Passage dans ablation_month')
87
88!------ Mass balance options
89
90        meth_abl_vi=1    ! pdd Reeh
91        !meth_abl_vi=2    ! Parametrization Thompson and Pollard 1997
92
93
94
95! Calcul du PDD
96!----------------------------
97do i=1,nx
98   do j=1,ny
99        summ=0.0
100
101! On a deja calcule Tm_surf(i,j,m) : temperature moyenne de chaque mois
102
103        month: do mo=1,mois                    ! boucle sur les mois
104
105            temp=0.0                             ! variable d'integration
106            average_day: do k=1,50               ! pdd d'un jour par mois
107               if (temp.gt.tm_surf(i,j,mo)+2.5*sigma) goto 209
108
109               summ=summ+temp* &
110                    exp(-((temp-tm_surf(i,j,mo))*(temp-tm_surf(i,j,mo)))*s22)
111               
112               temp=temp+dtp                   ! pdtp pas d'integration
113
114            end do average_day
115
116209         continue
117
118        end do month                             !  boucle sur le mois
119
120        pdd(i,j)=summ*pddct                      ! pdd pour toute l'annee
121
122  end do
123end do
124debug_3d(:,:,58)=pdd(:,:)   
125
126!!$
127!!$!_____________________________________________________________
128!!$!
129!!$! aurel : je rajoute un calcul de PDD avec Tann et Tjuly pour comparer les deux approches
130!!$! positive degree day
131!!$do j=1,ny
132!!$   do i=1,nx
133!!$        summ=0.0
134!!$        do nday=1,nyear   
135!!$           tt(nday)=tann_par(i,j)+(tjuly_par(i,j)-tann_par(i,j))*cos(py*nday)
136!!$           temp=0.0
137!!$           do k=1,50
138!!$              if (temp.gt.tt(nday)+2.5*sigma) goto 205
139!!$              summ=summ+temp*exp(-(temp-tt(nday))*(temp-tt(nday))*s22)
140!!$              temp=temp+dtp
141!!$           end do
142!!$205        continue
143!!$        end do
144!!$        pddann(i,j)=summ*pddct
145!!$     end do
146!!$  end do
147!!$
148!!$!sorties debug3d
149!!$debug_3d(:,:,43)=pdd(:,:)     
150!!$debug_3d(:,:,44)=pdd(:,:)-pddann(:,:)
151
152
153!-----------------------
154
155! calcul du bilan de masse :
156!
157
158do i=1,nx
159   do j=1,ny
160
161!        Positive degrees required to melt the snow layer
162!
163     snow(i,j)=precip(i,j)           ! voir routine accum_month
164
165     pds=snow(i,j)/Csnow             ! nombre de pdd pour fondre cette neige
166
167     simax=snow(i,j)*csi             ! csi defini dans initial-phy-2.f90 (0.6)
168                                      ! simax : Maximum amount of super. ice that can be formed
169
170     pdsi=simax/cice                 ! Pos. degrees required to melt the superimposed ice
171
172
173
174!-------- Ablation et Bilan de masse Reeh (1991)
175!-----------------------------------------------------------------
176
177     if (meth_abl_vi==1) then
178
179
180        ! aurel 11/09 on rajoute l'impact du regel sur la temperature de surface.
181        if (pdd(i,j).le.csi*pds) then
182           sif=pdd(i,j)*csnow
183        else
184           sif=simax 
185        endif
186        !     impact of refreesing on surface temperature
187        ts(i,j)=(tann(i,j)+26.6*sif)
188        ts(i,j)=min(0.0,ts(i,j))
189        tshelf(i,j)=ts(i,j)
190
191
192           ! if pdd*csnow < thickness of melted snow that refreze: no ablation
193           if (pdd(i,j).le.csi*pds) &
194              bm(i,j)=acc(i,j)                                  ! toute la neige fondue regele
195
196           ! if melted snow that refreze < pdd*csnow < snow
197           if ((csi*pds.lt.pdd(i,j)).and.(pdd(i,j).le.pds))  &
198              bm(i,j)=acc(i,j)+simax-pdd(i,j)*csnow             ! simax regel, le reste s'en va
199
200           ! if snow < pdd*csnow <snow (pds) + surimposed ice (pdsi)
201           if ((pds.lt.pdd(i,j)).and.(pdd(i,j).le.pds+pdsi)) &
202              bm(i,j)=simax-(pdd(i,j)-pds)*cice                 ! attaque la glace de regele
203
204           ! melting of old ice bm<0 with the remaining pdd
205           if (pds+pdsi.le.pdd(i,j)) &
206              bm(i,j)=(pds+pdsi-pdd(i,j))*cice                  ! attaque la vieille glace
207
208
209           abl(i,j) = acc(i,j) - bm(i,j)                        ! Ablation
210           frac=0.6
211
212
213!-------- Energy surface mass balance (Thompson and Pollard 1997)
214!----------------------------------------------------------------
215
216    else if (meth_abl_vi==2) then               ! abla vince 2006
217
218! aurel 11/09 on rajoute l'impact du regel sur la temperature de surface.
219        if (pdd(i,j).le.csi*pds) then
220           sif=pdd(i,j)*csnow
221        else
222           sif=simax 
223        endif
224!     impact of refreesing on surface temperature
225        ts(i,j)=(tann(i,j)+26.6*sif)
226        ts(i,j)=min(0.0,ts(i,j))
227        tshelf(i,j)=ts(i,j)
228
229
230        melt(i,j)=pdd(i,j)*Csnow
231        melt(i,j)=min(snow(i,j),melt(i,j))
232
233!----- refreezing fraction of precipiations (liquid and solid)
234
235        if (snow(i,j)==0.) then
236           frac=1
237        else
238           frac=1-((melt(i,j)/snow(i,j))-.7)/.3
239           frac_min=min(1.,frac)
240           frac_tot=max(0.,frac_min)
241
242        endif
243
244!------ Ablation
245
246        if (frac_tot.lt.1.) then
247           abl(i,j)= frac_tot*melt(i,j)
248
249           if (pdd(i,j).gt.pds ) then   ! enough pdd to totaly melt the snow
250
251              melt(i,j) = melt(i,j)+(pdd(i,j)-pds)*cice
252              abl(i,j)  = abl(i,j)+(pdd(i,j)-pds)*cice
253
254           endif
255
256        else
257           abl(i,j)=melt(i,j)
258        endif
259
260!------ Accumulation and mass balance
261
262    acc(i,j)=snow(i,j)
263
264       if (frac_tot.lt.1. .and. frac_tot.gt.0.) then
265          acc(i,j)= acc(i,j) + (precip(i,j)-snow(i,j))
266          !acc(i,j)= acc(i,j) + (precip(i,j)*48-precip(i,j))*(1-frac_tot)  ! voir la routine accum_month
267       endif
268
269    bm(i,j) = acc(i,j) - abl(i,j)
270
271    endif
272
273  end do
274end do
275
276!!$!_____________________________________________________________
277!!$!
278!!$! aurel : je rajoute un calcul de bm avec Tann et Tjuly pour comparer les deux approches
279!!$do j=1,ny
280!!$   do i=1,nx
281!!$      pds=acc(i,j)/csnow        !  positive degrees required to melt the snow laye
282!!$      simax=acc(i,j)*csi        !  maximum amount of super. ice that can be formed
283!!$      pdsi=simax/cice           !  pos. degrees required to melt the superimposed ice
284!!$      if (pddann(i,j).le.csi*pds) then
285!!$         sif=pddann(i,j)*csnow
286!!$      else
287!!$         sif=simax
288!!$      endif
289!!$!      mass balance
290!!$        if (pddann(i,j).le.csi*pds)  bmann(i,j)=acc(i,j)
291!!$        if ((csi*pds.lt.pddann(i,j)).and.(pddann(i,j).le.pds))       &
292!!$             bmann(i,j)=acc(i,j)+simax-pddann(i,j)*csnow
293!!$        if ((pds.lt.pddann(i,j)).and.(pddann(i,j).le.pds+pdsi))      &
294!!$             bmann(i,j)=simax-(pddann(i,j)-pds)*cice
295!!$        if (pds+pdsi.le.pddann(i,j))   bmann(i,j)=(pds+pdsi-pddann(i,j))*cice
296!!$     end do
297!!$  end do
298!!$! sortie debug
299!!$debug_3d(:,:,45)=bm(:,:)-bmann(:,:)
300
301
302!!$!aurel : pour experience de calibration : je force avec les donnees de bilan de masse MAR
303!!$do j=1,ny
304!!$   do i=1,nx
305!!$      bm(i,j)=sum(bm_mar(i,j,:))/12
306!!$   end do
307!!$end do
308
309
310end subroutine ablation
311
312end module ablation_month
Note: See TracBrowser for help on using the repository browser.