Changeset 2856


Ignore:
Timestamp:
Dec 23, 2022, 2:09:37 PM (3 years ago)
Author:
llange
Message:

PEM
CO2 glacier flows added in a module
Maximum thickness of glacier before flow is not anymore hardcoded, but computed with the value of Tcond and the slope angle.
The method is from A.Grau Galfore (LPG), inspired from Nye et al., 2000
Works for high stress regim, will be adapted to consider also low stress regim (Tco2 > 200K);
LL

Location:
trunk/LMDZ.COMMON/libf/evolution
Files:
1 added
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r2855 r2856  
    8585
    8686      use pemredem, only:  pemdem1
    87 
     87      use co2glaciers_mod,only: co2glaciers_evol
    8888!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! SOIL
    8989      use comsoil_h_PEM, only: soil_pem,ini_comsoil_h_PEM,end_comsoil_h_PEM,nsoilmx_PEM, &
     
    225225      REAL, dimension(:,:),allocatable  :: tendencies_co2_ice_phys_slope   ! physical point xslope field : Tendency of evolution of perenial co2 ice over a year
    226226      REAL, dimension(:,:),allocatable  :: tendencies_co2_ice_phys_slope_ini ! physical point x slope field x nslope: Tendency of evolution of perenial co2 ice over a year in the GCM
    227       REAL, dimension(:,:),allocatable  :: tendencies_h2o_ice_phys_slope   ! physical pointx slope  field : Tendency of evolution of perenial co2 ice over a year
    228       REAL,SAVE,ALLOCATABLE,DIMENSION(:) ::  co2_hmax                      ! Maximum height  for CO2 deposit on slopes (m)
    229       REAL, PARAMETER :: rho_co2 = 1600           ! CO2 ice density (kg/m^3)
    230       INTEGER :: iaval                            ! Index of the neighboord slope ()
     227      REAL, dimension(:,:),allocatable  :: tendencies_h2o_ice_phys_slope   ! physical pointx slope  field : Tendency of evolution of perenial co2 ice
    231228      REAL , dimension(:,:), allocatable :: flag_co2flow(:,:)   !(ngrid,nslope)          ! To flag where there is a glacier flow
    232229      REAL , dimension(:), allocatable :: flag_co2flow_mesh(:)  !(ngrid)          ! To flag where there is a glacier flow
     
    483480     PRINT*,'corresponding criterium = ',def_slope_mean(iflat)
    484481
    485 ! CO2 max thickness (for glaciers flows)
    486        allocate(co2_hmax(nslope))
    487        if(nslope.eq.7) then ! ugly way to implement that ...
    488 !        CF documentation that explain how the values are computed
    489          co2_hmax(1) = 1.5
    490          co2_hmax(7) = co2_hmax(1)
    491          co2_hmax(2) = 2.4
    492          co2_hmax(6) = co2_hmax(2)
    493          co2_hmax(3) = 5.6
    494          co2_hmax(5) = co2_hmax(3)
    495          co2_hmax(4) = 1000000.
    496      elseif(nslope.eq.1) then
    497          co2_hmax(1) = 1000000.
    498      else
    499          print *, "Nslope must be=to 1 or 7 for now!!"
    500      endif
    501482
    502483     allocate(flag_co2flow(ngrid,nslope))
     
    963944!------------------------
    964945
    965       print *, "Co2 glacier flow"
    966        DO ig = 1,ngrid
    967         DO islope = 1,nslope
    968           IF(islope.ne.iflat) THEN ! ice can be infinite on flat ground
    969 ! First: check that CO2 ice must flow (excess of ice on the slope), ice can accumulate on flat ground
    970             IF(co2ice_slope(ig,islope).ge.rho_co2*co2_hmax(islope) * &
    971                   cos(pi*def_slope_mean(islope)/180.)) THEN
    972 ! Second: determine the flatest slopes possible:
    973                 IF(islope.gt.iflat) THEN
    974                   iaval=islope-1
    975                 ELSE
    976                  iaval=islope+1
    977                 ENDIF
    978                 do while ((iaval.ne.iflat).and.  &
    979                     (subslope_dist(ig,iaval).eq.0))
    980                   IF(iaval.gt.iflat) THEN
    981                      iaval=iaval-1
    982                   ELSE
    983                      iaval=iaval+1
    984                   ENDIF
    985                 enddo
    986               co2ice_slope(ig,iaval) = co2ice_slope(ig,iaval) + &
    987                (co2ice_slope(ig,islope) - rho_co2* co2_hmax(islope) *     &
    988                cos(pi*def_slope_mean(islope)/180.)) *             &
    989                subslope_dist(ig,islope)/subslope_dist(ig,iaval) * &
    990                cos(pi*def_slope_mean(iaval)/180.) /               &
    991                cos(pi*def_slope_mean(islope)/180.)               
    992 
    993               co2ice_slope(ig,islope)=rho_co2*co2_hmax(islope) *        &
    994                cos(pi*def_slope_mean(islope)/180.)
    995 
    996               flag_co2flow(ig,islope) = 1.
    997               flag_co2flow_mesh(ig) = 1.
    998             ENDIF ! co2ice > hmax
    999           ENDIF ! iflat
    1000         ENDDO !islope
    1001        ENDDO !ig
     946      print *, "Co2 glacier flows"
     947
     948
     949
     950    call co2glaciers_evol(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,vmr_co2_pem_phys,ps_phys_timeseries,&
     951                         global_ave_press_GCM,global_ave_press_new,co2ice_slope,flag_co2flow,flag_co2flow_mesh)
     952
     953
     954
     955
    1002956
    1003957!------------------------
Note: See TracChangeset for help on using the changeset viewer.