Ignore:
Timestamp:
02/22/23 16:28:12 (15 months ago)
Author:
dumas
Message:

ablation_mod.f90 : SMB can be computed using ITM with pdd_type=3

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/climat_forcage_mod.f90

    r347 r366  
    66! possibilite d'utiliser autant de snapshots que l'on veut (ntr) 
    77! fichiers de forcage, Snapshot et valeurs de lapse rate definis dans fichier param 
    8   use module3d_phy,only:nx,ny,sealevel,sealevel_2d,S,Tmois,Tann,Tjuly,acc,num_forc,num_param,num_rep_42,tafor,coefbmshelf,PI,ro,time,dirforcage,dirnameinp 
     8  use module3d_phy,only:nx,ny,sealevel,sealevel_2d,S,Tmois,Tann,Tjuly,acc,swmois,prmois,num_forc,num_param,num_rep_42,tafor,coefbmshelf,PI,ro,time,dirforcage,dirnameinp 
    99  use netcdf 
    1010  use io_netcdf_grisli 
     
    2323 
    2424  character(len=100) :: clim_ref_file ! climat de reference 
    25   character(len=70), dimension(5) :: forcage_file ! fichier de forcage (climat+topo) => dimension >= ntr 
     25  character(len=100), dimension(12) :: forcage_file ! fichier de forcage (climat+topo) => dimension >= ntr 
    2626!  character(len=100) :: forcage_file2 ! fichier de forcage 2 (climat+topo) 
    2727 
     
    3232  real    :: r_atmvar              !< a ratio to account fast atmos variability between the 2 snapshots (in %: 0=>no fast var,1=>only fast var) 
    3333 
    34  
    35  
    3634!  character(len=200) :: filtr(ntr)   ! fichiers de forcage 
    3735 
     
    4341                     ! 2 for steady state using snap 2 ... 
    4442                     ! 0 for transient 
     43 
     44  integer :: smbcomp ! 0 for PDD 
     45                     ! 1 for ITM 
    4546   
    4647! variables pour climato mensuelle :   
    4748  real,dimension(nx,ny,12) :: t2m0   !< initial monthly air temperature (climato) 
     49  real,dimension(nx,ny,12) :: sw0   !< initial monthly downward SW radiations at the surface (climato) 
    4850  real,dimension(nx,ny,12) :: pr0    !< initial monthly precip (climato) 
    4951  real,dimension(nx,ny) :: orog0     !< topo de la climato 
     
    5153! climat des snapshots : 
    5254  real,dimension(:,:,:,:), allocatable :: t2m_ss  !< t2m monthly for every GCM snapshot  
     55  real,dimension(:,:,:,:), allocatable :: sw_ss  !< sw radiations monthly for every GCM snapshot 
    5356  real,dimension(:,:,:,:), allocatable :: pr_ss   !< precip monthly for every GCM snapshot 
    5457  real,dimension(:,:,:), allocatable :: orog_ss    !< topo for every GCM snapshot  
    5558   
    5659  real,dimension(:,:,:,:), allocatable :: t2m_sstopo0 !< t2m GCM snapshot on orog0 
     60  real,dimension(:,:,:,:), allocatable :: sw_sstopo0  !< sw GCM snapshot on orog0 
    5761  real,dimension(:,:,:,:), allocatable :: pr_sstopo0  !< pr GCM snapshot on orog0 
    58  
    5962 
    6063!~   real,dimension(nx,ny,12,ntr) :: t2m_ss  !< t2m monthly for every GCM snapshot  
     
    141144  enddo 
    142145 
     146  if (smbcomp .EQ. 1) then 
     147     ! lecture du climat de reference : climato mensuelle 
     148     call Read_Ncdf_var('rsds',trim(DIRNAMEINP)//TRIM(clim_ref_file),tab3d) 
     149     sw0(:,:,:)=tab3d(:,:,:) 
     150 
     151     ! lecture des fichiers snapshots pour n'importe quel geoplace 
     152     do k=1,ntr 
     153        call Read_Ncdf_var('rsds',trim(DIRNAMEINP)//'Snapshots-GCM/'//trim(forcage_file(k)),tab3d) 
     154        sw_ss(:,:,:,k)=tab3d(:,:,:) 
     155     end do 
     156 
     157     ! calcul de sw sur la topo des obs : 
     158     do m=1,12 
     159        do k=1,ntr 
     160           !sw_sstopo0(:,:,m,k)=sw_ss(:,:,m,k) 
     161           sw_sstopo0(:,:,m,k)=sw_ss(:,:,m,k)+sw_ss(:,:,m,k)*0.00006*(orog0(:,:)-orog_ss(:,:,k)) ! Adapted from Robinson et al., 2011 
     162        enddo 
     163     enddo 
     164 
     165  end if 
    143166 
    144167! lecture des fichiers d'evolution pour tout geoplace 
     
    214237subroutine init_forclim 
    215238 
    216   real,dimension(5) :: ttr_temp         !< date des tranches (snapshots)  
     239  real,dimension(12) :: ttr_temp         !< date des tranches (snapshots)  
    217240  integer :: err                  !< recuperation erreur 
    218241  integer :: k 
    219242   
    220   namelist/clim_forcage/clim_ref_file,ntr,ttr_temp,forcage_file,typerun,lapserate,rappact,filforc,pertbmb,coeft,coefbmb,r_atmvar 
     243  namelist/clim_forcage/clim_ref_file,ntr,ttr_temp,forcage_file,typerun,lapserate,rappact,filforc,pertbmb,coeft,coefbmb,r_atmvar,smbcomp 
    221244 
    222245  rewind(num_param)        ! pour revenir au debut du fichier param_list.dat 
     
    255278   end if 
    256279  end if 
     280 
     281  if (.not.allocated(sw_ss)) THEN 
     282   allocate(sw_ss(nx,ny,12,ntr),stat=err) 
     283   if (err/=0) then 
     284      print *,"Erreur à l'allocation du tableau t2m_ss",err 
     285      stop 4 
     286   end if 
     287  end if 
    257288   
    258289  if (.not.allocated(pr_ss)) THEN 
     
    274305  if (.not.allocated(t2m_sstopo0)) THEN 
    275306   allocate(t2m_sstopo0(nx,ny,12,ntr),stat=err) 
     307   if (err/=0) then 
     308      print *,"Erreur à l'allocation du tableau t2m_sstopo0",err 
     309      stop 4 
     310   end if 
     311  end if 
     312 
     313  if (.not.allocated(sw_sstopo0)) THEN 
     314   allocate(sw_sstopo0(nx,ny,12,ntr),stat=err) 
    276315   if (err/=0) then 
    277316      print *,"Erreur à l'allocation du tableau t2m_sstopo0",err 
     
    333372  real :: TEMP                       !< calcul du nbr de jour < psolid 
    334373  real,dimension(nx,ny) :: deltaZs   ! diff temp par rapport a topo orog0  
    335   real,dimension(nx,ny,12) :: prmois ! precip sur topo Zs 
    336    
    337374  real (kind=kind(0.d0)) ::  timeloc 
    338375   
     
    451488    prmois(:,:,m)= pr0(:,:,m)*((pr_sstopo0(:,:,m,itr)*(1-coeftime) + pr_sstopo0(:,:,m,itr+1)*coeftime)/ pr_sstopo0(:,:,m,ntr)) * exp(rappact*(deltaZs(:,:))) 
    452489    !$OMP END WORKSHARE 
    453  
    454490! Temp et precip fonction de coeftime : 
    455491  else if (itr.LT.ntr) then 
     
    466502enddo  
    467503 
    468  
     504if (smbcomp .EQ. 1) then 
     505   ! correction d'altitude 
     506   do m=1,12  
     507      if ((itr.LT.ntr-1).and.(ntr.ge.3)) then 
     508         ! if the is more than 2 snapshots : time climate is mean between 2 snapshots and anomaly with snapshot ntr (ctrl)   
     509         !$OMP WORKSHARE 
     510         swmois(:,:,m)= (sw_sstopo0(:,:,m,itr)*(1-coeftime) + sw_sstopo0(:,:,m,itr+1)*coeftime) - sw_sstopo0(:,:,m,ntr) + sw0(:,:,m)+sw0(:,:,m)*0.00006*(Zs(:,:)-orog0(:,:)) 
     511         !$OMP END WORKSHARE 
     512      ! Temp et precip fonction de coeftime : 
     513      elseif (itr.LT.ntr) then 
     514         !$OMP WORKSHARE 
     515         swmois(:,:,m)= (sw_sstopo0(:,:,m,itr) - sw_sstopo0(:,:,m,itr+1))*(1-coeftime) + sw0(:,:,m)+sw0(:,:,m)*0.00006*(Zs(:,:)-orog0(:,:)) 
     516         !$OMP END WORKSHARE 
     517      else ! itr=ntr (time>tsnapmax) 
     518         !$OMP WORKSHARE 
     519         !swmois(:,:,m) = sw0(:,:,m) 
     520         swmois(:,:,m) = sw0(:,:,m)+sw0(:,:,m)*0.00006*(Zs(:,:)-orog0(:,:)) 
     521         !$OMP END WORKSHARE 
     522      endif 
     523   enddo 
     524end if 
    469525 
    470526  !$OMP WORKSHARE 
     
    472528  Tjuly=Tmois(:,:,7) 
    473529   
    474  
    475  
    476530 
    477531! calcul de l'accumulation de neige : 
Note: See TracChangeset for help on using the changeset viewer.