source: trunk/SOURCES/climat-perturb_mod-0.4.f90 @ 111

Last change on this file since 111 was 93, checked in by dumas, 7 years ago

First version with Schoof flux parameterisation at the grounding line. | New module furst_schoof_mod.f90 | New flag Schoof in grdline namelist (see in SOURCES/Fichiers-parametres/A-LBq15_param_list_Schoof.dat)

File size: 11.8 KB
Line 
1!> \file climat-perturb_mod-0.4.f90
2!! Module pour les variations temporelles des variables climatiques
3!<
4
5!> \namespace  climat_perturb_mod
6!!Module pour les variations temporelles des variables climatiques
7!! \author C. Dumas
8!! \date 12/2015
9!! @note Used modules:
10!! @note   - use module3D_phy
11!<
12module  climat_perturb_mod
13
14
15use module3d_phy,only:nx,ny,S,S0,Tann,Tjuly,precip,acc,Ylat,num_forc,num_param,num_rep_42,dirforcage,dirnameinp,tafor,time,sealevel,coefbmshelf
16use netcdf
17use io_netcdf_grisli
18
19implicit none
20
21integer nft             !< nombre de lignes a lire dans le fichier forcage climatique
22real,dimension(:),allocatable :: tdate          !< time for climate forcing
23real,dimension(:),allocatable :: tpert          !< temperature for climate forcing
24real,dimension(:),allocatable :: spert          !< sea surface perturbation
25
26real,dimension(nx,ny) :: ta0          !< initial air temperature at sea level annual
27
28real :: coefT                   !< pour modifier l'amplitude de la perturb. T
29real :: rappact                 !< pour le calcul du rapport 'accumulation
30integer :: retroac              !< 1-> full retroactions accum
31real :: rapbmshelf              !< pour calcul coefbmshelf
32real :: mincoefbmelt            !< butoirs mini
33real :: maxcoefbmelt            !< butoirs maxi de coefbmelt
34character(len=80) :: filforc    !< nom du fichier forcage
35
36! Pour l'instant tafor est global meme si inutile si on utilise
37! un forcage  (variation spatiales)
38
39contains
40
41!--------------------------------------------------------------------------------
42!> SUBROUTINE: input_clim 
43!! Routine qui permet d'initialiser les variations temporelles des variables climatiques
44!>
45
46  subroutine input_clim
47
48    implicit none
49                character(len=100) :: precip_file        ! fichier precipitations
50    character(len=100) :: temp_annual_file   ! fichier temperature annuelle
51    real               :: coef_dens          ! pour corriger si donnees en eq. eau
52    logical            :: temp_param         ! si utilisation de temperature parametree
53    real*8, dimension(:,:), pointer :: data_2D => null() ! donnees lues dans le netcdf
54   
55   
56    character(len=8) :: control      !label to check clim. forc. file (filin) is usable
57    character(len=80):: filin
58    integer ::  err                       !< pour l'allocation des tableaux
59    integer :: i,j
60   
61    namelist/climat_acc_T_gen/precip_file,coef_dens,temp_annual_file
62
63428 format(A)
64    rewind(num_param)                     ! pour revenir au debut du fichier param_list.dat
65    read(num_param,climat_acc_T_gen)
66
67    write(num_rep_42,428)'!___________________________________________________________' 
68    write(num_rep_42,428)'!  module  lect_clim_acc_T_ant_gen                          '
69    write(num_rep_42,climat_acc_T_gen)
70    write(num_rep_42,428)'!___________________________________________________________' 
71
72
73    ! precipitation
74    precip_file  = trim(dirnameinp)//trim(precip_file)
75   
76    call Read_ncdf_var('precip',trim(precip_file),data_2D)
77    precip(:,:)=data_2D(:,:)
78    !call lect_datfile(nx,ny,precip,1,precip_file)                 
79
80    precip(:,:)=precip(:,:)*coef_dens
81    acc(:,:)=precip(:,:)
82
83    if ((trim(temp_annual_file).eq.'no').or.(trim(temp_annual_file).eq.'NO')) then
84       temp_param=.true.
85    else
86       temp_param=.false.
87    end if
88
89    !    temperature en surface
90
91    test_param: if (.not.temp_param) then
92       temp_annual_file = trim(dirnameinp)//trim(temp_annual_file)
93
94
95                         call Read_ncdf_var('Tann',trim(temp_annual_file),data_2D)
96                         Tann(:,:)=data_2D(:,:)
97!       call lect_input(3,'Tann',1,Tann,temp_annual_file,trim(dirnameinp)//trim(runname)//'.nc')
98       !call lect_datfile(nx,ny,Tann,1,temp_annual_file)               ! temperature annuelle
99
100    else                        !    parametrisation de Fortuin pour la temperature annuelle.
101
102       do j=1,ny
103          do i=1,nx
104
1057            if (s0(i,j).le.200.) then                                    ! shelfs
106                tann(i,j)=49.642-0.943*abs(ylat(i,j))
107             else if ((s0(i,j).gt.200.).and.(s0(i,j).lt.1500.)) then      ! pente
108                tann(i,j)=36.689-0.005102*s0(i,j)-0.725*abs(ylat(i,j))
109             else if (s0(i,j).ge.1500.) then                              ! plateau
110                tann(i,j)=7.405-0.014285*s0(i,j)-0.180*abs(ylat(i,j))
111             endif
112          end do
113       end do
114    end if test_param
115
116    ta0(:,:)=tann(:,:)
117
118
119    !           pour la temperature d'ete, idem parametrisation huybrechts
120    do j=1,ny
121       do i=1,nx
122
123          tjuly(i,j)=tann(i,j)-17.65+0.00222*s0(i,j)&
124               +0.40802*abs(ylat(i,j))
125       end do
126    end do
127
128
129
130
131
132    ! Lecture du forcage
133    !-----------------------
134    ! Le fichier de forcage est lu dans le fichier entree parametres
135
136    filin=trim(dirforcage)//trim(filforc)
137
138    open(num_forc,file=filin,status='old')
139
140    read(num_forc,*) control,nft
141
142    ! Determination of file size (line nb), allocation of perturbation array
143
144    if (control.ne.'nb_lines') then
145       write(6,*) filin,'indiquer le nb de ligne en debut de fichier:'
146       write(6,*) 'le nb de lignes et le label de control nb_lines'
147       stop
148    endif
149
150    ! Dimensionnement des tableaux tdate, ....
151
152    if (.not.allocated(tdate)) then
153       allocate(tdate(nft),stat=err)
154       if (err/=0) then
155          print *,"erreur a l'allocation du tableau Tdate",err
156          stop 4
157       end if
158    end if
159
160    if (.not.allocated(spert)) then
161       allocate(spert(nft),stat=err)
162       if (err/=0) then
163          print *,"erreur a l'allocation du tableau Spert",err
164          stop 4
165       end if
166    end if
167
168
169    if (.not.allocated(tpert)) then
170       allocate(tpert(nft),stat=err)
171       if (err/=0) then
172          print *,"erreur a l'allocation du tableau Tpert",err
173          stop 4
174       end if
175    end if
176
177    do i=1,nft
178       read(num_forc,*) tdate(i),spert(i),tpert(i)
179    end do
180    close(num_forc)
181
182    tpert(:)=tpert(:)*coefT
183
184
185  end subroutine input_clim
186
187!--------------------------------------------------------------------------------
188!> SUBROUTINE: init_forclim
189!! Routine qui permet d'initialiser les variables climatiques au cours du temps
190!>
191subroutine init_forclim
192
193
194  character(len=80):: filin
195  integer :: i,j
196  integer :: ivo,jvo
197
198namelist/clim_pert/coefT,rappact,retroac,rapbmshelf,mincoefbmelt,maxcoefbmelt,filforc
199
200rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
201read(num_param,clim_pert)
202
203! formats pour les ecritures dans 42
204428 format(A)
205
206write(num_rep_42,428)'!___________________________________________________________' 
207write(num_rep_42,428) '&clim_pert                      ! module climat_perturb_mod '
208write(num_rep_42,*)
209write(num_rep_42,*) 'coefT        = ', coefT 
210write(num_rep_42,*) 'rappact      = ', rappact 
211write(num_rep_42,*) 'rretroac     = ', retroac 
212write(num_rep_42,*) 'rapbmshelf   = ', rapbmshelf 
213write(num_rep_42,*) 'mincoefbmelt = ', mincoefbmelt
214write(num_rep_42,*) 'maxcoefbmelt = ', maxcoefbmelt
215write(num_rep_42,'(A,A)') ' filforc      = ', filforc
216write(num_rep_42,*)'/'                           
217write(num_rep_42,*)
218
219
220
221!cdc Commente pour être compatible avec lecture fichiers Cat Schoofing
222
223!~ !!!!!!!! ATTENTION AJOUTE POUR TEST MAIS A REMETTRE AU PROPRE PLUS TARD C. DUMAS !!!!!!!!!!
224!~ !!!!!!!! ancien input_climat_ref de lect_clim_act_anteis
225!~ !     accumulation de Philippe
226!~       filin='accumHUY40km.dat'
227!~       call lect_eis(nx,ny,precip,filin,DIRNAMEINP)
228!~ !====================================== La reponse est 42 ===========
229!~       write(num_rep_42,*) 'fichier accum : ', filin
230
231!~ !     cas particulier de Vostok
232!~       ivo=101
233!~       jvo=62
234!~       do j=jvo-1,jvo+1
235!~         do i=ivo-1,ivo+1
236!~             precip(i,j)=0.02         ! valeur plus faible a Vostok.
237!~         end do
238!~       end do
239!~       acc(:,:)=precip(:,:)
240
241!~ !    temperature en surface :
242!~ !    parametrisation de Fortuin pour la temperature annuelle.
243!~       do j=1,ny
244!~         do i=1,nx
245
246!~             if (s0(i,j).le.200.) then   ! shelfs
247!~                tann(i,j)=49.642-0.943*abs(ylat(i,j))
248!~             else if ((s0(i,j).gt.200.).and.(s0(i,j).lt.1500.)) then ! pente
249!~                tann(i,j)=36.689-0.005102*s0(i,j)-0.725*abs(ylat(i,j))
250!~             else if (s0(i,j).ge.1500.) then        ! plateau
251!~                tann(i,j)=7.405-0.014285*s0(i,j)-0.180*abs(ylat(i,j))
252!~             endif
253
254!~             ta0(i,j)=tann(i,j)
255!~ !           pour la temperature d'ete, idem parametrisation huybrechts
256!~             tjuly(i,j)=tann(i,j)-17.65+0.00222*s0(i,j)&
257!~                          +0.40802*abs(ylat(i,j))
258!~         end do
259!~       end do
260!~ !!!!!!!! FIN MODIF  TEMPORAIRE !!!!!!!!!!
261!cdc fin Commente pour être compatible avec lecture fichiers Cat Schoofing
262
263return
264end subroutine init_forclim
265
266!--------------------------------------------------------------------------------
267!> SUBROUTINE: forclim
268!! 
269!!  Routine qui permet le calcule climatiques au cours du temps
270!!  @note Au temps considere (time) attribue les scalaires
271!!  @note   - tafor : forcage en temperature
272!!  @note   - sealevel : forcage niveau des mers
273!!  @note   - coefbmelt : forcage fusion basale ice shelves
274!>
275subroutine forclim               !  au temps considere (time) attribue les scalaires
276  !  tafor : forcage en temperature
277  !  sealevel : forcage niveau des mers
278  !  coefbmelt : forcage fusion basale ice shelves
279
280!  use module3d_phy
281  implicit none
282  integer :: i,ift
283
284  !       time en dehors des limites du fichier forcage
285  if(time.lt.tdate(1)) then
286     tafor=tpert(1)
287     sealevel=spert(1)
288     ift=1
289
290  else if (time.ge.tdate(nft)) then
291     tafor=tpert(nft)
292     sealevel=spert(nft)
293     ift=nft
294
295  else
296     do i=1,nft-1 
297        if((time.ge.tdate(i)).and.(time.lt.tdate(i+1))) then ! entre i et i+1 : cas general
298           tafor=tpert(i)+(tpert(i+1)-tpert(i))*       &
299                (time-tdate(i))/(tdate(i+1)-tdate(i))
300           sealevel=spert(i)+(spert(i+1)-spert(i))*    &
301                (time-tdate(i))/(tdate(i+1)-tdate(i))
302           ift=i
303           goto 100
304        endif
305     end do
306  endif
307100 continue
308
309
310  !  coefmshelf est un coefficient qui fait varier bmgrz et bmshelf
311  !  en fonction de tafor
312
313  !   coefbmshelf=(1.+tafor/10.)           ! coefbmshelf=0 pour tafor=-10deg
314
315  if ((tafor.le.0).and.(tafor.gt.-5.)) then
316     coefbmshelf=(1.+tafor/rapbmshelf)     ! coefbmshelf=0 pour tafor=-7 standard precedent
317
318  else if (tafor.le.-5) then               ! lineaire en 0 a -10 et la valeur a -5
319     coefbmshelf=(1.-5./rapbmshelf)/5.*(tafor+10)
320
321  else
322     coefbmshelf=(1.+5.*tafor/rapbmshelf)  ! 5 fois plus efficace vers le chaud
323  endif
324
325  coefbmshelf=max(coefbmshelf,mincoefbmelt) 
326  coefbmshelf=min(coefbmshelf,maxcoefbmelt)
327
328        call massb_perturb_Tparam 
329  !  massb_perturb_Tparam remplace desormais massb_anteis_perturb
330  !  le code est le meme pour l'Antarctique (simplement passe en format libre)
331  !  dans le fichier massb-ant_perturb_Tparam.f90
332
333
334end subroutine forclim
335
336subroutine massb_perturb_Tparam               ! calcule le mass balance en mode perturbation
337                                              ! avec la temperature parametree
338                                              ! version pour l'antarctique
339                                              ! simple copie nettoyee de massb_anteis_perturb
340  implicit none
341
342  integer :: i,j
343
344!     surface temperature et accumulation
345
346  do j=1,ny
347     do i=1,nx
348
349        if(retroac.eq.1) then
350
351           tann(i,j)=ta0(i,j)-0.00914*(s(i,j)-s0(i,j))+tafor
352           tjuly(i,j)=tann(i,j)-17.65+0.00222*s(i,j)  &
353                +0.40802*abs(ylat(i,j))
354         
355           acc(i,j)=precip(i,j)*exp(rappact*(tann(i,j)-ta0(i,j)))
356
357        else if(retroac.eq.0) then
358
359           tann(i,j)=ta0(i,j)
360           tjuly(i,j)=tann(i,j)
361           acc(i,j)=precip(i,j)*exp(rappact*(tann(i,j)-ta0(i,j)))
362        endif
363     end do
364  end do
365
366end subroutine massb_perturb_Tparam
367
368
369end module  climat_perturb_mod
Note: See TracBrowser for help on using the repository browser.