Ignore:
Timestamp:
10/17/19 09:42:41 (5 years ago)
Author:
aquiquet
Message:

Trunk merged to iLoveclim branch at revision 286

Location:
branches/iLoveclim
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/iLoveclim

  • branches/iLoveclim/SOURCES/bilan_eau_mod.f90

    r254 r287  
    3636real :: sum_H_old 
    3737real :: diff_H 
    38 real :: alpha_flot                      ! ro/row  
     38real :: alpha_flot                      ! ro/row 
     39real :: dtt_flux   ! 1 an si dtt<1an sinon dtt_loc=dtt  
    3940 
    4041real,dimension(nx,ny) :: bm_dt,bmelt_dt 
     
    4546subroutine init_bilan_eau 
    4647 ! initialisation des variables 
    47         diff_H=0. 
    48         sum_H_old = sum(H(2:nx-1,2:ny-1),mask=ice(2:nx-1,2:ny-1)==1) 
    49         H_beau_old(:,:)=H(:,:) 
    50         tot_water(:,:)=0. 
    51         bm_dt(:,:)=0. 
    52         bmelt_dt(:,:)=0. 
    53         alpha_flot=ro/row 
    54         archimtab(:,:) = Bsoc(:,:)+H(:,:)*alpha_flot - sealevel_2d(:,:) 
    55         gr_line(:,:)=0 
    56         do j=1,ny 
    57            do i=1,nx 
    58               !afq    if ((H(i,j).gt.0.).and.(archimtab(i,j).GE.0.).and.(Bsoc(i,j).LE.sealevel_2d(i,j))) then ! grounded with ice 
    59               if ((H(i,j).gt.0.).and.(archimtab(i,j).GE.0.)) then ! grounded with ice 
    60                  if (archimtab(i-1,j).LT.0..and.Uxbar(i,j).LT.0..and..not.flot_marais(i-1,j)) gr_line(i,j)=1 
    61                  if (archimtab(i+1,j).LT.0..and.Uxbar(i+1,j).GT.0..and..not.flot_marais(i+1,j)) gr_line(i,j)=1 
    62                  if (archimtab(i,j-1).LT.0..and.Uybar(i,j).LT.0..and..not.flot_marais(i,j-1)) gr_line(i,j)=1 
    63                  if (archimtab(i,j+1).LT.0..and.Uybar(i,j+1).GT.0..and..not.flot_marais(i,j+1)) gr_line(i,j)=1 
    64               endif 
    65            enddo 
    66         enddo 
     48  diff_H=0. 
     49  sum_H_old = sum(H(2:nx-1,2:ny-1),mask=ice(2:nx-1,2:ny-1)==1) 
     50  H_beau_old(:,:)=H(:,:) 
     51  tot_water(:,:)=0. 
     52  bm_dt(:,:)=0. 
     53  bmelt_dt(:,:)=0. 
     54  alpha_flot=ro/row 
     55  archimtab(:,:) = Bsoc(:,:)+H(:,:)*alpha_flot - sealevel_2d(:,:) 
     56  gr_line(:,:)=0 
     57  do j=1,ny 
     58    do i=1,nx 
     59      !afq    if ((H(i,j).gt.0.).and.(archimtab(i,j).GE.0.).and.(Bsoc(i,j).LE.sealevel_2d(i,j))) then ! grounded with ice 
     60      if ((H(i,j).gt.0.).and.(archimtab(i,j).GE.0.)) then ! grounded with ice 
     61        if (archimtab(i-1,j).LT.0..and.Uxbar(i,j).LT.0..and..not.flot_marais(i-1,j)) gr_line(i,j)=1 
     62        if (archimtab(i+1,j).LT.0..and.Uxbar(i+1,j).GT.0..and..not.flot_marais(i+1,j)) gr_line(i,j)=1 
     63        if (archimtab(i,j-1).LT.0..and.Uybar(i,j).LT.0..and..not.flot_marais(i,j-1)) gr_line(i,j)=1 
     64        if (archimtab(i,j+1).LT.0..and.Uybar(i,j+1).GT.0..and..not.flot_marais(i,j+1)) gr_line(i,j)=1 
     65      endif 
     66    enddo 
     67  enddo 
     68  if (dtt.ge.1.) then 
     69    dtt_flux=dtt 
     70  else 
     71    dtt_flux=1. 
     72  endif 
    6773 
    6874! iLOVECLIM initialisation of water conservation related variables 
     
    135141endwhere 
    136142 
    137  
    138 !afq -- if (isynchro.eq.1) then 
    139 if ((isynchro.eq.1).or.(nt.eq.1)) then 
    140  
     143if ((isynchro.eq.1.and.(mod(abs(TIME),1.).lt.dtmin)).or.(nt.eq.1)) then 
    141144! on raisonne en bilan annuel pour simplifier : 
    142145!~      where (ice(2:nx-1,2:ny-1).eq.1) 
     
    146149!~      endwhere 
    147150!cdc pas besoin du test sur ice ici, il a ete fait avant (et le masque ice varie a chaque dt)    
    148   tot_water(2:nx-1,2:ny-1) = (Bm_dtt(2:nx-1,2:ny-1) - Bmelt_dtt(2:nx-1,2:ny-1) + calv_dtt(2:nx-1,2:ny-1) - ablbord_dtt(2:nx-1,2:ny-1)) / dtt 
     151  tot_water(2:nx-1,2:ny-1) = (Bm_dtt(2:nx-1,2:ny-1) - Bmelt_dtt(2:nx-1,2:ny-1) + calv_dtt(2:nx-1,2:ny-1) - ablbord_dtt(2:nx-1,2:ny-1)) / dtt_flux 
    149152    
    150153! bilan d'eau sur la grille : 
    151         water_bilan=sum(tot_water(:,:)) 
    152         diff_H = diff_H/dtt 
     154  water_bilan=sum(tot_water(:,:)) 
     155  diff_H = diff_H/dtt_flux 
    153156 
    154157!999 format(f0.2,1x,e15.8,1x,i10,8(1x,e15.8)) 
    155158!       write(6,999),time,sum_H,count(ice(:,:)==1),diff_H,water_bilan,sum(calv_dtt(:,:))/dtt,sum(ablbord_dtt(:,:))/dtt,sum(bmelt_dtt(:,:),mask=ice(:,:)==1)/dtt,sum(bm(:,:),mask=ice(:,:)==1),sum(Bm_dtt(:,:))/dtt,sum(bmelt_dtt(:,:))/dtt 
    156         diff_H_water_bilan(2:nx-1,2:ny-1)=tot_water(2:nx-1,2:ny-1)-diff_H_2D(2:nx-1,2:ny-1) 
     159  diff_H_water_bilan(2:nx-1,2:ny-1)=tot_water(2:nx-1,2:ny-1)-diff_H_2D(2:nx-1,2:ny-1) 
    157160 
    158161endif 
Note: See TracChangeset for help on using the changeset viewer.