Ignore:
Timestamp:
05/12/21 12:07:40 (3 years ago)
Author:
dumas
Message:

climat_forcage_mod is now compatible with more than 2 GCM snapshots and ntr (number of snapshots) is now defined in param_list.dat

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/climat_forcage_mod.f90

    r250 r347  
    1919  real,dimension(:),allocatable :: spert 
    2020  real,dimension(:),allocatable :: bpert 
     21   
     22  integer :: ntr         ! nb of snapshot files now explicitely specified  
    2123 
    2224  character(len=100) :: clim_ref_file ! climat de reference 
    23   character(len=100) :: forcage_file1 ! fichier de forcage 1 (climat+topo) 
    24   character(len=100) :: forcage_file2 ! fichier de forcage 2 (climat+topo) 
     25  character(len=70), dimension(5) :: forcage_file ! fichier de forcage (climat+topo) => dimension >= ntr 
     26!  character(len=100) :: forcage_file2 ! fichier de forcage 2 (climat+topo) 
    2527 
    2628  character(len=100) :: filforc       ! nom du fichier forcage 
     
    3133 
    3234 
    33   integer,parameter :: ntr=2         ! nb of snapshot files now explicitely specified  
    34   character(len=200) :: filtr(ntr)   ! fichiers de forcage 
    35  
    36   real,dimension(ntr) :: ttr         !< date des tranches (snapshots)  
    37   real,dimension(nx,ny,ntr) :: delta, deltj, rapact 
     35 
     36!  character(len=200) :: filtr(ntr)   ! fichiers de forcage 
     37 
     38  real,dimension(:), allocatable :: ttr         !< date des tranches (snapshots)  
    3839  real,dimension(nx,ny) :: delTatime, delTjtime, rapactime 
    3940  real,dimension(nx,ny) :: Zs        !< surface topography above sea level 
     
    4950   
    5051! climat des snapshots : 
    51   real,dimension(nx,ny,12,ntr) :: t2m_ss  !< t2m monthly for every GCM snapshot  
    52   real,dimension(nx,ny,12,ntr) :: pr_ss   !< precip monthly for every GCM snapshot 
    53   real,dimension(nx,ny,ntr) :: orog_ss    !< topo for every GCM snapshot  
    54    
    55   real,dimension(nx,ny,12,ntr) :: t2m_sstopo0 !< t2m GCM snapshot on orog0 
    56   real,dimension(nx,ny,12,ntr) :: pr_sstopo0  !< pr GCM snapshot on orog0 
     52  real,dimension(:,:,:,:), allocatable :: t2m_ss  !< t2m monthly for every GCM snapshot  
     53  real,dimension(:,:,:,:), allocatable :: pr_ss   !< precip monthly for every GCM snapshot 
     54  real,dimension(:,:,:), allocatable :: orog_ss    !< topo for every GCM snapshot  
     55   
     56  real,dimension(:,:,:,:), allocatable :: t2m_sstopo0 !< t2m GCM snapshot on orog0 
     57  real,dimension(:,:,:,:), allocatable :: pr_sstopo0  !< pr GCM snapshot on orog0 
     58 
     59 
     60!~   real,dimension(nx,ny,12,ntr) :: t2m_ss  !< t2m monthly for every GCM snapshot  
     61!~   real,dimension(nx,ny,12,ntr) :: pr_ss   !< precip monthly for every GCM snapshot 
     62!~   real,dimension(nx,ny,ntr) :: orog_ss    !< topo for every GCM snapshot  
     63   
     64!~   real,dimension(nx,ny,12,ntr) :: t2m_sstopo0 !< t2m GCM snapshot on orog0 
     65!~   real,dimension(nx,ny,12,ntr) :: pr_sstopo0  !< pr GCM snapshot on orog0 
    5766   
    5867  real :: PYY                        !< constante pour calcul de la fraction solide des precips 
     
    9099  orog0(:,:)=tab2d(:,:) 
    91100   
    92   filtr(1)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file1) 
    93   filtr(2)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file2) 
     101!  filtr(1)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file1) 
     102!  filtr(2)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file2) 
    94103 
    95104! fichiers donnant l'evolution temporelle 
     
    105114! ------------------------------------------------------------- 
    106115  do k=1,ntr 
    107      write(6,*) 'Read climate file :',trim(filtr(k)) 
    108      call Read_Ncdf_var('pr',trim(filtr(k)),tab3d) 
     116     write(6,*) 'Read climate file :',trim(DIRNAMEINP)//'Snapshots-GCM/'//trim(forcage_file(k)) 
     117     call Read_Ncdf_var('pr',trim(DIRNAMEINP)//'Snapshots-GCM/'//trim(forcage_file(k)),tab3d) 
    109118     pr_ss(:,:,:,k)=tab3d(:,:,:) 
    110      call Read_Ncdf_var('tas',trim(filtr(k)),tab3d) 
     119     call Read_Ncdf_var('tas',trim(DIRNAMEINP)//'Snapshots-GCM/'//trim(forcage_file(k)),tab3d) 
    111120     t2m_ss(:,:,:,k)=tab3d(:,:,:) 
    112      call Read_Ncdf_var('orog',trim(filtr(k)),tab2d) 
     121     call Read_Ncdf_var('orog',trim(DIRNAMEINP)//'Snapshots-GCM/'//trim(forcage_file(k)),tab2d) 
    113122     orog_ss(:,:,k)=tab2d(:,:) 
    114123!~      read(num_forc,*) ttr(k) 
     
    138147!        print*,nft 
    139148  read(num_forc,*) control,nft 
    140   print*,'control',control,nft 
     149!  print*,'control :',control,nft 
    141150! determination of file size (line nb), allocation of perturbation array 
    142151 
     
    205214subroutine init_forclim 
    206215 
    207  
    208   namelist/clim_forcage/clim_ref_file,ttr,forcage_file1,forcage_file2,typerun,lapserate,rappact,filforc,pertbmb,coeft,coefbmb,r_atmvar 
     216  real,dimension(5) :: ttr_temp         !< date des tranches (snapshots)  
     217  integer :: err                  !< recuperation erreur 
     218  integer :: k 
     219   
     220  namelist/clim_forcage/clim_ref_file,ntr,ttr_temp,forcage_file,typerun,lapserate,rappact,filforc,pertbmb,coeft,coefbmb,r_atmvar 
    209221 
    210222  rewind(num_param)        ! pour revenir au debut du fichier param_list.dat 
    211223  read(num_param,clim_forcage) 
    212  
     224   
     225  if (ntr.le.size(ttr_temp,dim=1)) then 
     226   print*,'climat_forcage : we will read ',ntr,' climate snapshots' 
     227   do k=ntr+1,size(ttr_temp,dim=1) 
     228      ttr_temp(k)= ttr_temp(ntr) 
     229      forcage_file(k)=' ' 
     230   enddo 
     231  else 
     232   print*,'climat_forcage ERROR : ntr > ttr_temp size' 
     233   print*,'ttr_temp & forcage_file size must be >= ntr' 
     234   stop 
     235  end if 
     236   
    213237  write(num_rep_42,'(A)')'!___________________________________________________________'  
    214   write(num_rep_42,'(A)') '&clim_forcage                                ! nom du bloc ' 
    215   write(num_rep_42,*) 
    216   write(num_rep_42,'(A,A,A)') 'clim_ref_file = "',trim(clim_ref_file),'"' 
    217   write(num_rep_42,*) 'ttr = ', ttr 
    218   write(num_rep_42,'(A,A,A)') 'forcage_file1 = "',trim(forcage_file1),'"' 
    219   write(num_rep_42,'(A,A,A)') 'forcage_file2 = "',trim(forcage_file2),'"' 
    220   write(num_rep_42,*) 'typerun = ', typerun 
    221   write(num_rep_42,*) 'lapserate = ', lapserate 
    222   write(num_rep_42,*) 'rappact = ', rappact 
    223   write(num_rep_42,'(A,A,A)') ' filforc      = "',trim(filforc),'"' 
    224   write(num_rep_42,*) 'pertbmb = ', pertbmb 
    225   write(num_rep_42,*) 'coefT   = ', coefT 
    226   write(num_rep_42,*) 'coefbmb = ', coefbmb 
    227   write(num_rep_42,*) 'r_atmvar = ', r_atmvar 
    228   write(num_rep_42,*)'/'                             
    229   write(num_rep_42,*) 
     238  write(num_rep_42,clim_forcage) 
     239 
     240 
     241   
     242  if (.not.allocated(ttr)) THEN 
     243   allocate(ttr(ntr),stat=err) 
     244   if (err/=0) then 
     245      print *,"Erreur à l'allocation du tableau ttr",err 
     246      stop 4 
     247   end if 
     248  end if 
     249 
     250  if (.not.allocated(t2m_ss)) THEN 
     251   allocate(t2m_ss(nx,ny,12,ntr),stat=err) 
     252   if (err/=0) then 
     253      print *,"Erreur à l'allocation du tableau t2m_ss",err 
     254      stop 4 
     255   end if 
     256  end if 
     257   
     258  if (.not.allocated(pr_ss)) THEN 
     259   allocate(pr_ss(nx,ny,12,ntr),stat=err) 
     260   if (err/=0) then 
     261      print *,"Erreur à l'allocation du tableau pr_ss",err 
     262      stop 4 
     263   end if 
     264  end if 
     265   
     266  if (.not.allocated(orog_ss)) THEN 
     267   allocate(orog_ss(nx,ny,ntr),stat=err) 
     268   if (err/=0) then 
     269      print *,"Erreur à l'allocation du tableau orog_ss",err 
     270      stop 4 
     271   end if 
     272  end if  
     273   
     274  if (.not.allocated(t2m_sstopo0)) THEN 
     275   allocate(t2m_sstopo0(nx,ny,12,ntr),stat=err) 
     276   if (err/=0) then 
     277      print *,"Erreur à l'allocation du tableau t2m_sstopo0",err 
     278      stop 4 
     279   end if 
     280  end if 
     281   
     282  if (.not.allocated(pr_sstopo0)) THEN 
     283   allocate(pr_sstopo0(nx,ny,12,ntr),stat=err) 
     284   if (err/=0) then 
     285      print *,"Erreur à l'allocation du tableau pr_sstopo0",err 
     286      stop 4 
     287   end if 
     288  end if 
     289   
     290  do k=1,ntr 
     291   ttr(k)=ttr_temp(k) 
     292  enddo 
     293    
     294 
     295!~   write(num_rep_42,'(A)')'!___________________________________________________________'  
     296!~   write(num_rep_42,'(A)') '&clim_forcage                                ! nom du bloc ' 
     297!~   write(num_rep_42,*) 
     298!~   write(num_rep_42,'(A,A,A)') 'clim_ref_file = "',trim(clim_ref_file),'"' 
     299!~   write(num_rep_42,*) 'ttr = ', ttr 
     300!~ !  write(num_rep_42,'(A,A,A)') 'forcage_file= "',trim(forcage_file),'"' 
     301!~   write(num_rep_42,'(A,A,A)') 'forcage_file1 = "',trim(forcage_file1),'"' 
     302!~   write(num_rep_42,'(A,A,A)') 'forcage_file2 = "',trim(forcage_file2),'"' 
     303!~   write(num_rep_42,*) 'typerun = ', typerun 
     304!~   write(num_rep_42,*) 'lapserate = ', lapserate 
     305!~   write(num_rep_42,*) 'rappact = ', rappact 
     306!~   write(num_rep_42,'(A,A,A)') ' filforc      = "',trim(filforc),'"' 
     307!~   write(num_rep_42,*) 'pertbmb = ', pertbmb 
     308!~   write(num_rep_42,*) 'coefT   = ', coefT 
     309!~   write(num_rep_42,*) 'coefbmb = ', coefbmb 
     310!~   write(num_rep_42,*) 'r_atmvar = ', r_atmvar 
     311!~   write(num_rep_42,*)'/'                             
     312!~   write(num_rep_42,*) 
    230313 
    231314  PYY=2.*PI/50. 
     
    362445! correction d'altitude 
    363446do m=1,12  
     447  if ((itr.LT.ntr-1).and.(ntr.ge.3)) then 
     448! if the is more than 2 snapshots : time climate is mean between 2 snapshots and anomaly with snapshot ntr (ctrl)   
     449    !$OMP WORKSHARE 
     450    Tmois(:,:,m)=  (t2m_sstopo0(:,:,m,itr)*(1-coeftime) + t2m_sstopo0(:,:,m,itr+1)*coeftime) - t2m_sstopo0(:,:,m,ntr) + t2m0(:,:,m) + deltaZs(:,:) 
     451    prmois(:,:,m)= pr0(:,:,m)*((pr_sstopo0(:,:,m,itr)*(1-coeftime) + pr_sstopo0(:,:,m,itr+1)*coeftime)/ pr_sstopo0(:,:,m,ntr)) * exp(rappact*(deltaZs(:,:))) 
     452    !$OMP END WORKSHARE 
     453 
    364454! Temp et precip fonction de coeftime : 
    365   if (itr.LT.ntr) then 
     455  else if (itr.LT.ntr) then 
    366456    !$OMP WORKSHARE 
    367457    Tmois(:,:,m)=  (t2m_sstopo0(:,:,m,itr) - t2m_sstopo0(:,:,m,itr+1))*(1-coeftime) + t2m0(:,:,m) + deltaZs(:,:) 
Note: See TracChangeset for help on using the changeset viewer.