source: trunk/SOURCES/Eurasie40_files/climat-forcage-eurasie_mod-0.4.f90 @ 111

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

initial import GRISLI trunk

File size: 19.2 KB
Line 
1!> \file climat-forcage-eurasie_mod-0.4.f90
2!! Module de calcul du forcage climatiques
3!<
4
5!> \namespace  climat_forcage_eurasie_mod
6!! Calcule du forcage climatiques
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!! @note   - use printtable
12!<
13
14
15module climat_forcage_eurasie_mod
16
17!!!!!!!!!!!!!!!!!!!!=1=decalaration variables================!!!!!!!!!!!!!!!!!!!!
18
19       use module3D_phy
20       use printtable
21implicit none
22
23integer nft                                     !< NFT est le nombre de lignes a lire dans le fichier contenant le forcage climatique
24real,dimension(:),allocatable :: TDATE          !< time for climate forcing
25real,dimension(:),allocatable :: alphaT
26real,dimension(:),allocatable :: alphaP
27real,dimension(:),allocatable :: SPERT
28integer,parameter :: ntr=4                      !< nb of snapshot files !ntr is now explicitely specified in the climat module
29 
30REAL ttr(ntr)!< la date des tranches (snapshots)  (len=ntr)
31REAL alphaTTR(ntr) !< Le alphaT de l'index glaciologiq. aux snapshots
32REAL delTa(nx,ny,ntr),delTj(nx,ny,ntr),rapact(nx,ny,ntr)
33REAL  delTatime(nx,ny),delTjtime(nx,ny),rapactime(nx,ny)
34integer  lake(nx,ny)
35character(len=100) :: filin
36CHARACTER(LEN=120) filtr(ntr)
37!CHARACTER(LEN=80),dimension(ntr)::  filtr   !snapshot file name (len=ntr)
38
39contains
40!!!!!!!!!!!!!!!!!!!!=2=lecure des input=s====================!!!!!!!!!!!!!!!!!!!!
41
42!> SUBROUTINE: input_clim
43!!Routine qui permet d'initialiser les variables climatiques
44!<
45
46  subroutine input_clim !routine qui permet d'initialiser les variables climatiques
47    USE module3D_phy
48
49    implicit none
50    character(len=8) :: control!label to check clim. forc. file (filin) is usable
51    integer :: l !In snapshot files:the first column is the mask, read but not used
52
53    delTatime(:,:)=0.
54    delTjtime(:,:)=0.
55    rapactime(:,:)=1.
56
57    !====================================================heminor============
58    if (geoplace.eq.'heminor') then
59
60       !     atmospheric temperature gradient
61       TEMPGRAD=0.008
62       TEMPGRJUL=0.0065
63
64
65       !Pou le nord cette pariti est copiée de inputfile-hemicycle.f (3juin04)
66       ! 1_fichiers snapshots pour forcage
67       !----------------------------------
68       filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcLGM-lmd5prese.g50'
69       filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcLGM-lmd5futur.g50'
70       !           filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-100k-actu.g50'
71       !           filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-80k-115END.g50'
72       !           filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-50k-LGM.g50'
73       !           filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-50k-115END.g50'
74       !           filtr(3)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-21k.g50'
75       !           filtr(4)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-15k.g50'
76       !           filtr(5)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-09k.g50'
77       !           filtr(6)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-06k.g50'
78       !           filtr(7)=TRIM(DIRNAMEINP)//'FORCAGES/forcage-00k.g50'
79       ! 2_fichiers donnant l'evolution temporelle
80       ! -------------------HEMICYCLE ------------
81       ! lecture du fichier scalaire (sea level)
82       !        filin=TRIM(DIRNAMEINP)//'heminor-forcLGM.dat'
83       filin=TRIM(DIRNAMEINP)//'signal-cycle-hemin.dat'
84!!!this file contains TDATE(I),alphaT(I),alphaP(i),SPERT(I),I=1,nft         
85       !====================================================hemin40============
86    elseif (geoplace.eq.'hemin40') then
87
88       !     atmospheric temperature gradient
89       TEMPGRAD=0.008
90       TEMPGRJUL=0.0065
91
92       ! 1_fichiers snapshots pour forcage
93       !----------------------------------
94       filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_hemin40-21k.g40'
95       filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/file_regions_.g40'
96       filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/file_regions_2.g40'
97
98       filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/file_regions_2act.g40'
99
100       ! 2_fichiers donnant l'evolution temporelle
101       ! -----------------------------------------
102       filin=TRIM(DIRNAMEINP)//'signal-cycle-hemin.dat'
103       !====================================================eurasie============
104    elseif (geoplace.eq.'euras40') then
105
106       !     atmospheric temperature gradient
107       !       TEMPGRAD=0.008
108       !       TEMPGRJUL=0.0065
109       TEMPGRAD=0.006 ! Pour Serie 2 (grad T reduit)
110       TEMPGRJUL=0.005
111       ! 1_fichiers snapshots pour forcage
112       !      filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_eur_froid90k.dat'
113       !     filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_eur_tres_froid.dat'
114       !     filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_EUR_TRES_froid90k.dat'
115       !     filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_EGU6_TRES_froid90k.dat'
116       !     filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger_90ka_eur40.dat'
117       filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_ger_.dat'
118       !     filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_eur_lim_incep0k.dat'
119       filtr(3)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_eur_no_forca.dat' ! climat act
120       filtr(3)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_gerhard_0ka.dat' ! climat act simule
121       !     filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_95ka_mod.dat'
122       !     filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_95ka_mod.dat'   !  E6eurL02
123       !     filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_95ka_nolak_mod.dat' !
124       !     filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_95ka_nolak_mod.dat' ! E6eurN02
125       !3 snapshots
126       !    filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_gerhard_105ka.dat' ! climat act simule
127       !    filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger90_LA_se1mod.dat'
128       !    filtr(3)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_gerhard_85ka.dat' ! climat act simule
129       !4 snapshots
130       filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_gerhard_105ka.dat' ! climat act simule
131       !     filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_eur_no_forca-k105.dat'
132       !     filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger95-4A_LA_se1mod.dat'
133       !     filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forR_ger95-4A_LA_se1mod.dat'
134!!!   filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forR_ger95-2A_LA_se1mod.dat'
135       filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger95-1A_LA_se2mod.dat'
136       !     filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger95-1A_NL_se2mod.dat'
137       filtr(3)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger90_LA_se2mod.dat'
138       !     filtr(3)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger90_NL_se2mod.dat'
139       filtr(4)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_gerhard_85ka.dat' ! climat act simule
140       !     filtr(4)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_eur_no_forca-k85.dat'
141       ! NO LAKES
142       !     filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_ger_mod_nolake.dat'
143       !     filtr(:)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger95-1A_LA_se2mod.dat'
144       !      filtr(:)=TRIM(DIRNAMEINP)//'FORCAGES/forc_ger90_NL_se2mod.dat'
145       !
146       !     filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcage_95ka_noalb_mod.dat' ! E6eurL01
147       ! 2_fichiers donnant l'evolution temporelle
148       filin=TRIM(DIRNAMEINP)//'signal-seal_i_inso_90ka.data'
149       filin=TRIM(DIRNAMEINP)//'signal-sealev_inso_26jui06.dat'
150       !       filin=TRIM(DIRNAMEINP)//'signal-cycle-hemin.dat'
151
152!!!  filin=TRIM(DIRNAMEINP)//'signal-sealev_index_inso.data'
153       !    filin=TRIM(DIRNAMEINP)//'signal-sealev_index_inso_art.data'
154!!!  filin=TRIM(DIRNAMEINP)//'signal-sealev_index_inso_art2.dat'
155
156       !====================================================ant20 et 40========
157    elseif ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
158
159
160       !     atmospheric temperature gradient
161       TEMPGRAD=0.0085
162       TEMPGRJUL=0.0085
163
164       ! 1_fichiers snapshots pour forcage
165       !----------------------------------
166       filtr(1)='../INPUT-DATA/FORCAGES/forcage-ant-20k.g40'
167       filtr(2)='../INPUT-DATA/FORCAGES/forcage-ant-00k.g40'
168       print*,'lecture de ',filin,filtr
169       ! 2_fichiers donnant l'evolution temporelle
170       ! ---------------------------- ------------
171       filin=TRIM(DIRNAMEINP)//'forcmodif4cycles.dat' !forcage vostok en rapport : a creer
172
173    endif !Fin du test sur geolpace
174
175    ! 3_lecure des fichiers snapsots pour tout geoplace
176    ! -------------------------------------------------
177    write(6,*) 'fichiers snapshots'
178    do k=1,ntr
179       write(6,*) filtr(k)
180       open(20,file=filtr(k))
181       read(20,*) ttr(k)
182       read(20,*)
183       read(20,*)
184       do j=1,ny
185          do i=1,nx
186             !              read(20,*) l,rapact(i,j,k),delTa(i,j,k),delTj(i,j,k)
187             read(20,*) delTa(i,j,k),delTj(i,j,k),rapact(i,j,k)
188          end do
189       end do
190       close(20)
191    end DO
192    !       ttr(1)=-500000. !ttr est la date des tranches 3D-1.h
193    !       ttr(2)=0
194    ! 4_lecure des fichiers d'evolution pour tout geoplace
195    ! ----------------------------------------------------
196    open(20,file=filin,status='old')
197    !        print*,nft
198    read(20,*) control,nft
199    print*,'control',control,nft
200    ! Determination of file size (line nb), allocation of perturbation array
201    if (control.ne.'nb_lines') then
202       write(6,*) filin,'indiquer le nb de ligne en debut de fichier:'
203       write(6,*) 'le nb de lignes et le label de control nb_lines'
204       stop
205    endif
206
207    if (.not.allocated(tdate)) THEN
208       allocate(TDATE(nft),stat=err)
209       if (err/=0) then
210          print *,"Erreur à l'allocation du tableau TDATE",err
211          stop 4
212       end if
213    end if
214
215    if (.not.allocated(alphat)) THEN
216       allocate(alphaT(nft),stat=err)
217       if (err/=0) then
218          print *,"Erreur à l'allocation du tableau TPERT",err
219          stop 4
220       end if
221    end if
222
223    if (.not.allocated(alphap)) THEN
224       allocate(alphap(nft),stat=err)
225       if (err/=0) then
226          print *,"Erreur à l'allocation du tableau TPERT",err
227          stop 4
228       end if
229    end if
230
231    if (.not.allocated(spert)) THEN
232       allocate(spert(nft),stat=err)
233       if (err/=0) then
234          print *,"Erreur à l'allocation du tableau SPERT",err
235          stop 4
236       end if
237    end if
238
239    do I=1,NFT
240       !          read(20,*) TDATE(I),alphaT(I),alphaP(i),SPERT(I) ! forc grip
241       !          print*,i,TDATE(I),alphaT(I),alphaP(i),SPERT(I)
242       read(20,*) TDATE(I),alphaT(I),SPERT(I)           ! forc inso
243    end do
244    !RAJOUT VINCE
245    do k=1,ntr
246       do I=1,NFT
247          if (TDATE(I)==ttr(k)) then
248             alphaTTR(k)=alphaT(I)     
249          endif
250       end do
251    end do
252
253    alphaP(:)=1.0
254    !----------------------------masque de glace
255    do j=3,ny-2
256       do i=3,nx-2
257          mk0(i,j)=1
258          if ((i.lt.25).and.(j.gt.35)) mk0(i,j)=0
259       end do
260    end do
261
262    print*, 'module forcage climatique'
263    print*, 'ajout de lakes',TRIM(DIRNAMEINP)//'regions_lakes_eurasie40.ijk'
264    !open(unit=1005,file=TRIM(DIRNAMEINP)//'regions_lakes_eurasie40.ijk')
265    !open(unit=1005,file=TRIM(DIRNAMEINP)//'lak_reg40km_eu40_ij')
266    !      read(1005,*)
267    !      read(1005,*)
268    !      read(1005,*)
269    !       do j=1,ny
270    !          do i=1,nx
271    !            read(1005,*) k,k,lake(i,j)
272    !          enddo
273    !      enddo   
274    !:
275
276    ! A CREER ou organiser a partir des codes dans ! 2_fichiers donnant l'evolution temporelle
277
278  end subroutine input_clim
279!--------------------------------------------------------------------------------
280!>SUBROUTINE: init_forclim
281!!Initialisation des parametres climatiques
282!<
283subroutine init_forclim
284
285!namelist/clim_forc/
286!namelist/clim_pert/rappact,retroac,rapbmshelf,mincoefbmelt,maxcoefbmelt
287
288!rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
289!read(num_param,clim_forc)
290
291! formats pour les ecritures dans 42
292428 format(A)
293
294write(num_rep_42,428)'!___________________________________________________________' 
295write(num_rep_42,428) '&clim_forc_euras ! pour le forcage climatique par snapshots'
296write(num_rep_42,*)
297end subroutine init_forclim
298!---------------------------------------------------------------------
299!forcage climatique au cours du temps
300
301!>SUBROUTINE: forclim
302!!Forcage climatique au cours du temps
303!<
304
305subroutine forclim
306
307  implicit none
308  real COEFT,COEFP,coeftime!coeftime is not used
309  INTEGER L !dumm index for loops on snapsots files  l=ITR,NTR-1
310  INTEGER ITR !nb of the current snapshot file (change with time)
311!       time en dehors des limites du fichier forcage
312INTEGER ii,jj
313              ITR=1
314
315if(time.le.tdate(1)) then   ! time avant le debut du fichier forcage
316   sealevel=spert(1)
317   coeft=alphat(1)
318   coefp=alphap(1)
319   ift=1
320
321else if (time.ge.tdate(nft)) then     ! time apres la fin du fichier forcage
322   sealevel=spert(nft)
323   coeft=alphat(nft)
324   coefp=alphap(nft)
325   ift=nft
326
327else
328
329
330!A modifier
331    ift = 1      ! modifie par SC le 24/11/99
332   do i=ift,nft-1
333!       print*,'ds boucle1 sur snapshots',ift,TDATE(I),TDATE(I+1),time
334          if((time.ge.tdate(i)).and.(time.lt.tdate(i+1))) then
335
336!        interpolation entre I et I+1 : cas general
337!           TAFOR=TPERT(I)+(TPERT(I+1)-TPERT(I))*
338!    &            (time-TDATE(I))/(TDATE(I+1)-TDATE(I))
339          SEALEVEL=SPERT(I)+(SPERT(I+1)-SPERT(I))*    &
340                 (time-tdate(I))/(tdate(I+1)-tdate(I))
341
342          coeft=alphaT(I)+(alphaT(I+1)-alphaT(I))*      &
343                 (time-tdate(I))/(tdate(I+1)-tdate(I))
344
345!          COEFP=alphaP(I)+(alphaP(I+1)-alphaP(I))*      &
346!                 (time-TDATE(I))/(TDATE(I+1)-TDATE(I))
347
348                 do k=1,ntr-1 
349                   if((time.ge.ttr(k)).and.(time.lt.ttr(k+1))) goto 105
350
351                 enddo
352105  continue
353
354if (k==ntr) k=ntr-1
355!Rajout Vince 26 juin 2006
356! coefbmshelf est donné avec l'index d'insolation à 65°N
357          coefbmshelf=coefT
358!On retablit l'index entre
359
360                  if((time.ge.ttr(1)).and.(time.lt.ttr(ntr))) then
361                      coeft  =   ( coeft - alphaTTR(k) ) / &
362                           ( alphaTTR(k+1)-alphaTTR(k) )
363                  else
364                      print*,'on est pas dans les périodes forcé'
365                      print*,'les bornes sont ttr(1) et ttr(ntr)',ttr(1),ttr(ntr)
366                      print*,'time=',time
367                      stop
368                  endif
369
370
371
372! Pour les experiences eurasiennes coefp==coeft
373          COEFP=COEFT
374!        SEALEVEL=-50.         
375            IFT=I
376            goto 100
377          endif
378
379        end do
380      endif
381100   continue
382
383!          print*,'coeffT P',COEFT,COEFP
384!=forcage du climat
385!       time en dehors des limites du fichier forcage
386        if(time.le.Ttr(1)) then   ! mis a -500 000 ans
387          do j=1,ny
388            do i=1,nx
389              delTatime(i,j)=delTa(i,j,1)
390              delTjtime(i,j)=delTj(i,j,1)
391              rapactime(i,j)=rapact(i,j,1)
392            end do
393           end do
394              ITR=1
395        else if (time.ge.ttr(Ntr)) then        ! mis a 0
396          do j=1,ny
397            do i=1,nx
398             delTatime(i,j)=delTa(i,j,ntr)
399             delTjtime(i,j)=delTj(i,j,ntr)
400             rapactime(i,j)=rapact(i,j,ntr)
401            end do
402           end do
403           ITR=NTR
404        else               !  interpolation entre l et l+1 : cas general
405
406        itr=max(itr,1)
407       WRITE(6,*)'itr = !',itr
408
409
410!parametres du fit
411        do l=ITR,NTR-1
412        print*,'ds boucle2 sur snapshots',l,ttr(l) 
413           if((time.ge.ttr(l)).and.(time.lt.ttr(l+1))) then  ! test tranche
414
415           coeftime= (time-TTR(l))/(TTR(l+1)-TTR(l))
416           do j=1,ny
417            do i=1,nx
418            delTatime(i,j)=delTa(i,j,l)+             &
419               (delTa(i,j,l+1)-delTa(i,j,l))*coefT
420
421            delTjtime(i,j)=delTj(i,j,l)+             &
422               (delTj(i,j,l+1)-delTj(i,j,l))*coefT
423
424            rapactime(i,j)=rapact(i,j,l)+            &
425               (rapact(i,j,l+1)-rapact(i,j,l))*coefP
426             end do
427           end do
428              print*,'l= ',l,delTj(40,30,l),delTj(40,30,l+1),delTjtime(40,30)
429           ITR=l
430            goto 200
431
432            endif        ! fin du test sur la tranche
433         end do
434       endif   ! fin du test avant,apres,milieu
435
436200   continue
437print*,'l= ',l,'itr= ',itr
438!     sortie pour verifier les valeurs
439!      print*,time ,coefT,coefP,sealevel
440!0print*,'dans le forclim climat coefbmshelf nest pas defini'
441!! coefmshelf est un coefficient qui fait vairier bmgrz et bmshelf
442!! en fonction de TAFOR (deplace depuis icetemp 16juin2004(au LSCE))
443!! coefbmshelf=(1.+TAFOR/10.)    ! coefbmshelf=0 pour TAFOR=-10deg
444!           do j=60,120!1,ny
445!            do i=50,100 !1,nx
446!                 if ((flot(i,j).and.time.lt.130000).and.  &
447!                     .not.(i.gt.75.and.j.lt.75)) then
448!                   delTjtime(i,j)=delTjtime(i,j)-4.
449!                   delTatime(i,j)=delTatime(i,j)-4.
450!                endif
451!             end do
452!           end do
453
454!    delTatime=-8.
455!    delTjtime=-8.
456!    sealevel=-50.
457!    TAFOR=delTatime(90,100)
458! coefbmshelf=(1.+TAFOR/7.)    ! coefbmshelf=0 pour TAFOR=-7deg standard
459!do j=1,ny 
460! do i=1,nx   
461!    if ( (S0(i,j).eq.0.) .and. (S(i,j).gt.sealevel) .and. (ICE(i,j)==0) ) then !exp B
462!    if ( (S0(i,j).eq.0.) .and. (S(i,j).gt.sealevel) ) then !exp d
463!          if (j.lt.55.and.i.gt.35) then
464!         else       
465!        delTjtime(i,j)=delTjtime(i,j)+5.
466!         endif
467!    endif
468! enddo
469!enddo
470!NIVEAU DES MERS ET DES LAKES
471     
472if ((time.lt.-95000.).or.(time.gt.-85500.)) then ! time SANS lacs
473                levelflot=sealevel
474else
475   do j=1,ny 
476     do i=1,nx   
477!!if (ice(i,j)==1) delTjtime(i,j)=delTjtime(i,j)-3. ! correction effet albedo
478!             if ( lake(i,j)==2 ) then     !KOMI
479!               levelflot(i,j)=100.
480!             elseif ( lake(i,j)==3 ) then !SIBERIAN
481!               levelflot(i,j)=60.
482!               if ((.not.flot(i,j)).and.(flot(i+1,j)) ) print*,i,j,h(i,j),bmelt(i,j)
483!            else
484!               levelflot(i,j)=sealevel       
485!            endif
486             levelflot(i,j)=-60.
487     enddo
488   enddo 
489endif
490     levelflot(:,:)=max(levelflot(:,:),bsoc(:,:))
491   nom_table='flot'
492   call printtable_l(flot,nom_table)
493   nom_table='lvflo'
494   call printtable_r(levelflot,nom_table)
495   
496!   coefbmshelf(:,:)=(1.+delTatime(:,:)/7.) 
497!coefbmshelf=1. ! modif pour test de sensibilite (tof 20 avril 01)
498!coefbmshelf=coefT
499    coefbmshelf=max(coefbmshelf,0.1)
500    coefbmshelf=min(coefbmshelf,2.)
501tafor=delTjtime(40,30)   
502
503print*,'time, coefbmshelf ',time, coefbmshelf
504print*,'SEA,COEFT,COEFP', SEALEVEL,COEFT,COEFP
505!rint*,'= t,sea,tafor',time,sealevel,tafor
506print*,'==========================='
507if ((geoplace(1:5).eq.'hemin').or.(geoplace(1:5).eq.'euras')) then       
508call accum7() ! ds le main
509call ablation_2007pey_et_al()
510!forcage stationnaire
511!      open(111,file='ger/tjja_90LA_EURAS40.ijk')
512!      open(112,file='ger/tann_90LA_EURAS40.ijk')
513!      open(113,file='ger/mb_90LA_EURAS40.ijk')
514!      open(114,file='ger/melt_90LA_EURAS40.ijk')
515!      do J=1,NY
516!       do I=1,NX
517!!      print*,i,j
518!       read(111,*) ii,jj,Tjuly(i,j)
519!!       print*,ii,jj,Tjuly(i,j)
520!       read(112,*) ii,jj,Tann(i,j)
521!       read(113,*) ii,jj,BM(i,j)
522!       read(114,*) ii,jj,abl(i,j)
523!          if (Tjuly(i,j).lt.5.) then     
524!            acc(i,j)=BM(i,j)-abl(i,j)
525!          else
526!            BM(i,j)=.0
527!          endif
528!       end do
529!      end do
530!      close(111) ;  close(112) ; close(113); close(114)
531!forcage stationnaire     
532elseif ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
533! call n'est plus dans le main
534!call massb_anteis_forcage()
535!call ablation()
536else
537 print*,"partie en travaux climat forcage auter que sur heminord"
538 print*,"geoplace ",geoplace
539endif
540! call bla2
541! call bla3
542
543END subroutine forclim
544
545end module climat_forcage_eurasie_mod
Note: See TracBrowser for help on using the repository browser.