source: trunk/SOURCES/climat_forcage_mod.f90 @ 215

Last change on this file since 215 was 215, checked in by dumas, 5 years ago

New module climat_forcage_mod

File size: 12.3 KB
Line 
1module  climat_forcage_mod
2
3! Forcage climatique avec climat GCM et fichier de forcage temporel index
4! lecture de fichiers Snapshots climatiques à temps t
5! lecture d'un fichier de forcage (temp carotte de glace)
6! possibilite d'utiliser autant de snapshots que l'on veut (ntr)
7! fichiers de forcage, Snapshot et valeurs de lapse rate definis dans fichier param
8  use module3d_phy,only:nx,ny,sealevel,slv,S,S0,Tmois,Tann,Tjuly,acc,num_forc,num_param,num_rep_42,coefbmshelf,PI,ro,time,dirforcage,dirnameinp
9  use netcdf
10  use io_netcdf_grisli
11
12
13  implicit none
14  character(len=80) :: filin
15  integer :: nft             !   nft est le nombre de lignes a lire dans le fichier
16                           ! contenant le forcage climatique
17  real,dimension(:),allocatable :: tdate          ! time for climate forcing
18  real,dimension(:),allocatable :: alphat
19  real,dimension(:),allocatable :: alphap
20  real,dimension(:),allocatable :: spert
21
22
23  real :: mincoefbmelt               ! butoirs mini
24  real :: maxcoefbmelt               ! butoirs maxi de coefbmshelf
25  character(len=100) :: clim_ref_file ! climat de reference
26  character(len=100) :: forcage_file1 ! fichier de forcage 1 (climat+topo)
27  character(len=100) :: forcage_file2 ! fichier de forcage 2 (climat+topo)
28
29  character(len=80) :: filforc       ! nom du fichier forcage
30
31
32  integer,parameter :: ntr=2         ! nb of snapshot files now explicitely specified
33  character(len=200) :: filtr(ntr)   ! fichiers de forcage
34
35  real,dimension(ntr) :: ttr         !< date des tranches (snapshots)
36  real,dimension(nx,ny,ntr) :: delta, deltj, rapact
37  real,dimension(nx,ny) :: delTatime, delTjtime, rapactime
38  real,dimension(nx,ny) :: Zs        !< surface topography above sea level
39
40
41! S0 topo de ref correspondant a la climato est lu dans lect_topo
42 
43! variables pour climato mensuelle : 
44  real,dimension(nx,ny,12) :: t2m0   !< initial monthly air temperature (climato)
45  real,dimension(nx,ny,12) :: pr0    !< initial monthly precip (climato)
46 
47! climat des snapshots :
48  real,dimension(nx,ny,12,ntr) :: t2m_ss  !< t2m monthly for every GCM snapshot
49  real,dimension(nx,ny,12,ntr) :: pr_ss   !< precip monthly for every GCM snapshot
50  real,dimension(nx,ny,ntr) :: orog_ss    !< topo for every GCM snapshot
51 
52  real,dimension(nx,ny,12,ntr) :: t2m_sstopo0 !< t2m GCM snapshot on S0
53  real,dimension(nx,ny,12,ntr) :: pr_sstopo0  !< pr GCM snapshot on S0
54 
55  real :: PYY                        !< constante pour calcul de la fraction solide des precips
56  real :: psolid=2.                  !< temp limit between liquid and solid precip
57  real,dimension(nx,ny) :: FT        !< proportion of year with air temp below psolid
58  real :: lapserate                  !< gradient vertical de temp annuel et juillet
59  real :: rappact                    !< coef pour calcul du rapport accumulation
60  logical :: annual                  !< True si forcage annuel, False si forcage mensuel
61
62contains
63
64!------------------------------------------------------------------------------------------
65subroutine input_clim          !routine qui permet d'initialiser les variables climatiques
66   
67  implicit none
68  character(len=8) :: control     !< label to check clim. forc. file (filin) is usable
69  integer :: l                    !< in snapshot files:the first column is the mask, read but not used
70  integer :: err                  !< recuperation erreur
71  integer :: i,j,k,m
72  real*8, dimension(:,:), pointer   :: tab2d => null()   !< tableau 2d pointer
73  real*8, dimension(:,:,:), pointer :: tab3d => null()   !< tableau 3d pointer
74
75  deltatime(:,:)=0.
76  deltjtime(:,:)=0.
77  rapactime(:,:)=1.
78  annual=.true.  ! forcage avec fichier Tann et Tjuly
79
80! lecture du climat de reference : climato mensuelle
81  print*,'lecture du climat de reference: ',trim(DIRNAMEINP)//TRIM(clim_ref_file)
82  call Read_Ncdf_var('precip',trim(DIRNAMEINP)//TRIM(clim_ref_file),tab3d)
83  pr0(:,:,:)=tab3d(:,:,:)
84  call Read_Ncdf_var('t2m',trim(DIRNAMEINP)//TRIM(clim_ref_file),tab3d)
85  t2m0(:,:,:)=tab3d(:,:,:)
86 
87  filtr(1)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file1)
88  filtr(2)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file2)
89
90! fichiers donnant l'evolution temporelle
91! -----------------------------------------
92! Pour rappel hemin40 :
93! fichier forcage : signal-cycle-hemin.dat
94! Pour anteis :
95! fichier forcage : forcmodif4cycles.dat
96  filin=trim(dirforcage)//trim(filforc) 
97
98
99! lecture des fichiers snapshots pour n'importe quel geoplace
100! -------------------------------------------------------------
101  do k=1,ntr
102     write(6,*) 'Read climate file :',trim(filtr(k))
103     call Read_Ncdf_var('pr',trim(filtr(k)),tab3d)
104     pr_ss(:,:,:,k)=tab3d(:,:,:)
105     call Read_Ncdf_var('tas',trim(filtr(k)),tab3d)
106     t2m_ss(:,:,:,k)=tab3d(:,:,:)
107     call Read_Ncdf_var('orog',trim(filtr(k)),tab2d)
108     orog_ss(:,:,k)=tab2d(:,:)
109!~      read(num_forc,*) ttr(k)
110!~      read(num_forc,*)
111!~      read(num_forc,*)
112!~      do j=1,ny
113!~         do i=1,nx
114!~            read(num_forc,*) l,rapact(i,j,k),delta(i,j,k),deltj(i,j,k)
115!~         end do
116!~      end do
117!~      close(num_forc)
118  end do
119
120
121! calcul de t2m et pr sur la topo des obs :
122  do m=1,12
123    do k=1,ntr
124      t2m_sstopo0(:,:,m,k)=t2m_ss(:,:,m,k)-lapserate*(S0(:,:)-orog_ss(:,:,m))
125      pr_sstopo0(:,:,m,k)=pr_ss(:,:,m,k)*exp(rappact*(t2m_sstopo0(:,:,m,k)-t2m_ss(:,:,m,k)))
126    enddo
127  enddo
128
129
130! lecture des fichiers d'evolution pour tout geoplace
131! ----------------------------------------------------
132  open(num_forc,file=filin,status='old')
133!        print*,nft
134  read(num_forc,*) control,nft
135  print*,'control',control,nft
136! determination of file size (line nb), allocation of perturbation array
137
138  if (control.ne.'nb_lines') then
139     write(6,*) filin,'indiquer le nb de ligne en debut de fichier:'
140     write(6,*) 'le nb de lignes et le label de control nb_lines'
141     stop
142  endif
143
144  if (.not.allocated(tdate)) THEN
145     allocate(tdate(nft),stat=err)
146     if (err/=0) then
147        print *,"erreur à l'allocation du tableau tdate",err
148        stop 4
149     end if
150  end if
151
152  if (.not.allocated(alphat)) THEN
153     allocate(alphat(nft),stat=err)
154     if (err/=0) then
155        print *,"erreur à l'allocation du tableau tpert",err
156        stop 4
157     end if
158  end if
159
160  if (.not.allocated(alphap)) THEN
161     allocate(alphap(nft),stat=err)
162     if (err/=0) then
163        print *,"erreur à l'allocation du tableau tpert",err
164        stop 4
165     end if
166  end if
167
168  if (.not.allocated(spert)) THEN
169     allocate(spert(nft),stat=err)
170     if (err/=0) then
171        print *,"erreur à l'allocation du tableau spert",err
172        stop 4
173     end if
174  end if
175
176  do i=1,nft
177     read(num_forc,*) tdate(i),alphat(i),alphap(i),spert(i)
178  end do
179
180  close(num_forc)
181
182
183end subroutine input_clim
184
185
186!--------------------------------------------------------------------------------
187subroutine init_forclim
188
189
190  namelist/clim_forcage/clim_ref_file,ttr,forcage_file1,forcage_file2,rappact,mincoefbmelt,maxcoefbmelt,filforc,lapserate
191
192  rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
193  read(num_param,clim_forcage)
194
195
196! formats pour les ecritures dans 42
197428 format(A)
198
199  write(num_rep_42,428)'!___________________________________________________________' 
200  write(num_rep_42,428) '&clim_forcage                                ! nom du bloc '
201  write(num_rep_42,*)
202  write(num_rep_42,'(A,A)') 'clim_ref_file = ', clim_ref_file
203  write(num_rep_42,'(A,A)') 'ttr = ', ttr(:)
204  write(num_rep_42,'(A,A)') 'forcage_file1 = ', forcage_file1
205  write(num_rep_42,'(A,A)') 'forcage_file2 = ', forcage_file2
206  write(num_rep_42,'(A,A)') 'rappact = ', rappact
207  write(num_rep_42,*) 'mincoefbmelt = ', mincoefbmelt
208  write(num_rep_42,*) 'maxcoefbmelt = ', maxcoefbmelt
209  write(num_rep_42,'(A,A)') ' filforc      = ', filforc
210  write(num_rep_42,*) 'lapserate = ', lapserate
211  write(num_rep_42,*)'/'                           
212  write(num_rep_42,*)
213
214  PYY=2.*PI/50.
215
216end subroutine init_forclim
217
218
219!---------------------------------------------------------------------
220!forcage climatique au cours du temps
221
222subroutine forclim
223
224!$ USE OMP_LIB
225
226  implicit none
227  real :: coeft,coefp,coeftime       !< coeftime is not used
228  integer :: l                       !< dumm index for loops on snapsots files  l=itr,ntr-1
229  integer :: itr                     !< nb of the current snapshot file (change with time)
230  integer :: i,j,k,m
231  integer :: ift                     !< indice correspondant au pas de temps du fichier de forcage
232  real :: TEMP                       !< calcul du nbr de jour < psolid
233  real,dimension(nx,ny) :: deltaZs   ! diff temp par rapport a topo S0
234  real,dimension(nx,ny,12) :: prmois ! precip sur topo Zs
235 
236 
237 
238  if(time.le.tdate(1)) then   ! time avant le debut du fichier forcage
239     sealevel=spert(1)
240     coeft=alphat(1)
241     coefp=alphap(1)
242     ift=1
243
244  else if (time.ge.tdate(nft)) then     ! time apres la fin du fichier forcage
245     sealevel=spert(nft)
246     coeft=alphat(nft)
247     coefp=alphap(nft)
248     ift=nft
249
250  else                         ! time en general
251
252     ift = 1     
253     do i=ift,nft-1  ! interpolation entre i et i+1
254
255        if((time.ge.tdate(i)).and.(time.lt.tdate(i+1))) then  ! cas general
256           sealevel=spert(i)+(spert(i+1)-spert(i))*    &
257                (time-tdate(i))/(tdate(i+1)-tdate(i))
258
259           coeft=alphat(i)+(alphat(i+1)-alphat(i))*      &
260                (time-tdate(i))/(tdate(i+1)-tdate(i))
261
262           coefp=alphap(i)+(alphap(i+1)-alphap(i))*      &
263                (time-tdate(i))/(tdate(i+1)-tdate(i))
264               
265           ift=i
266           goto 100
267        endif
268     end do
269  endif
270100 continue
271
272  slv(:,:)=sealevel
273
274  if(time.le.ttr(1)) then   ! time en dehors des limites du fichier forcage
275    coeftime=0.
276!~     do j=1,ny
277!~       do i=1,nx
278!~         deltatime(i,j)=delta(i,j,1)
279!~         deltjtime(i,j)=deltj(i,j,1)
280!~         rapactime(i,j)=rapact(i,j,1)
281!~       end do
282!~     end do
283    itr=1
284  else if (time.ge.ttr(ntr)) then        ! mis a 0
285    coeftime=1.
286    itr=ntr
287!~     do j=1,ny
288!~       do i=1,nx
289!~         deltatime(i,j)=delta(i,j,ntr)
290!~         deltjtime(i,j)=deltj(i,j,ntr)
291!~         rapactime(i,j)=rapact(i,j,ntr)
292!~       end do
293!~     end do
294  else               !  interpolation entre l et l+1 : cas general
295     itr=1
296     do l=itr,ntr-1    ! interpolation entre i et i+1
297        if((time.ge.ttr(l)).and.(time.lt.ttr(l+1))) then  ! test tranche
298           coeftime= (time-ttr(l))/(ttr(l+1)-ttr(l))
299!           do j=1,ny
300!              do i=1,nx
301!                 delTatime(i,j)=delta(i,j,l)+             &
302!                      (delta(i,j,l+1)-delta(i,j,l))*coeft
303!                 delTjtime(i,j)=deltj(i,j,l)+             &
304!                      (deltj(i,j,l+1)-deltj(i,j,l))*coeft
305!                 rapactime(i,j)=rapact(i,j,l)+            &
306!                      (rapact(i,j,l+1)-rapact(i,j,l))*coefp
307!              end do
308!           end do
309           itr=l
310        endif        ! fin du test sur la tranche
311     end do
312  endif   ! fin du test avant,apres,milieu
313
314
315! test avec coefbmshelf fonction de coeft (1 a l'actuel et proche de 0 en glaciaire)
316  coefbmshelf=coeft
317!coefbmshelf=1. ! modif pour test de sensibilite (tof 20 avril 01)
318  coefbmshelf=max(coefbmshelf,mincoefbmelt)
319  coefbmshelf=min(coefbmshelf,maxcoefbmelt)
320
321!if (geoplace(1:5).eq.'hemin') then
322
323  !$OMP PARALLEL
324!     calcul de Tjuly et et Tann
325  !$OMP WORKSHARE
326  Zs(:,:)=max(slv(:,:),S(:,:))
327  deltaZs(:,:)= -lapserate*(Zs(:,:)-S0(:,:)) ! difference de temperature entre Zs et S0
328  !$OMP END WORKSHARE
329! correction d'altitude
330do m=1,12 
331! Temp et precip fonction de coeftime :
332  if (itr.LT.ntr) then
333    !$OMP WORKSHARE
334    Tmois(:,:,m)=  (t2m_sstopo0(:,:,m,itr) - t2m_sstopo0(:,:,m,itr+1))*(1-coeftime) + t2m0(:,:,m) + deltaZs(:,:)
335    prmois(:,:,m)= pr0(:,:,m)*(coeftime+(1-coeftime)*(pr_sstopo0(:,:,m,itr)/pr_sstopo0(:,:,m,itr+1))) * exp(rappact*(deltaZs(:,:)))
336    !$OMP END WORKSHARE
337  else ! itr=ntr (time>tsnapmax)
338    !$OMP WORKSHARE
339    Tmois(:,:,m)=  t2m0(:,:,m) + deltaZs(:,:)
340    prmois(:,:,m)= pr0(:,:,m)*exp(rappact*(deltaZs(:,:)))
341    !$OMP END WORKSHARE
342  endif           
343enddo 
344
345
346
347print*,'Tmois',Tmois(142,14,1)
348print*,'prmois',prmois(142,14,1)
349  !$OMP WORKSHARE
350  Tann=sum(Tmois,dim=3)/12.
351  Tjuly=Tmois(:,:,7)
352 
353
354
355
356! calcul de l'accumulation de neige :
357  acc(:,:)=sum(prmois,dim=3,mask=Tmois < psolid)
358  acc(:,:)=acc(:,:)*1000./ro  ! conversion en glace
359  !$OMP END WORKSHARE
360  !$OMP END PARALLEL
361!debug
362!print*,'Tann, Tjuly',Tann(142,14),Tjuly(142,14) 
363!print*,'acc',acc(142,14)
364
365end subroutine forclim
366
367end module  climat_forcage_mod
Note: See TracBrowser for help on using the repository browser.