Ignore:
Timestamp:
01/26/21 17:31:08 (3 years ago)
Author:
aquiquet
Message:

Bug correction in ablation_mod affecting Ts + a bit of cleaning

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/ablation_mod.f90

    r29 r330  
    9494  real,dimension(365) :: TT             !< air temperature yearly cycle, for PDD 
    9595!- SC- Uniquement pour pdd Tarasov 
    96   REAL, DIMENSION(nx,ny) :: pr_ice_eq, snowmelt, cpsurf 
     96  REAL, DIMENSION(nx,ny) :: pr_ice_eq, totmelt, snowmelt, cpsurf 
    9797  REAL, DIMENSION(nx,ny) :: refr2, refreezed_ice 
    9898 
     
    219219 
    220220        WHERE (PDD(:,:).LE.PDS(:,:)) 
    221            snowmelt(:,:) = Csnow_2D(:,:)*PDD(:,:) 
     221           totmelt(:,:) = Csnow_2D(:,:)*PDD(:,:) 
    222222        ELSEWHERE 
    223            snowmelt(:,:) = Csnow_2D(:,:)*PDS(:,:) + Cice_2D(:,:)*(PDD(:,:)-PDS(:,:)) 
     223           totmelt(:,:) = Csnow_2D(:,:)*PDS(:,:) + Cice_2D(:,:)*(PDD(:,:)-PDS(:,:)) 
    224224        ENDWHERE 
    225225 
    226         snowmelt(:,:) = amin1(snowmelt(:,:),ACC(:,:)) 
     226        snowmelt(:,:) = amin1(totmelt(:,:),ACC(:,:)) 
    227227 
    228228! Deux formules possibles pour la capacité calorifique (en J/kg.K): 
     
    239239!           refreezed_ice(:,:) = amin1(pr_ice_eq(:,:)+snowmelt(:,:),refr2(:,:)) 
    240240!        endwhere 
    241         SIMAX(:,:)=refreezed_ice(:,:) 
    242         PDSI(:,:)=SIMAX(:,:)/Cice_2D(:,:) 
    243         WHERE (PDD(:,:).LE.PDS(:,:))         
    244            BM(:,:)=ACC(:,:)-PDD(:,:)*Csnow_2D(:,:) + SIMAX(:,:) 
    245            SIF(:,:)=PDD(:,:)*Csnow_2D(:,:)*(1-SIMAX(:,:)) 
    246         endwhere 
    247         WHERE ((PDS(:,:).LT.PDD(:,:)).AND.(PDD(:,:).LE.PDS(:,:)+PDSI(:,:))) 
    248            BM(:,:)=SIMAX(:,:)-(PDD(:,:)-PDS(:,:))*Cice_2D(:,:) 
    249            SIF(:,:)=SIMAX(:,:) 
    250         endwhere 
    251         WHERE (PDS(:,:)+PDSI(:,:).LE.PDD(:,:)) 
    252            BM(:,:)=(PDS(:,:)+PDSI(:,:)-PDD(:,:))*Cice_2D(:,:) 
    253            SIF(:,:)=SIMAX(:,:) 
    254         endwhere 
     241 
     242        bm(:,:) = ACC(:,:)+refreezed_ice(:,:)-totmelt(:,:) 
     243        SIF(:,:)=refreezed_ice(:,:) 
    255244 
    256245     ELSE ! pdd standard reeh 
Note: See TracChangeset for help on using the changeset viewer.