source: trunk/LMDZ.COMMON/libf/evolution/glaciers_mod.F90 @ 3595

Last change on this file since 3595 was 3591, checked in by jbclement, 2 days ago

PEM:

  • Making allocation/deallocation systematically and more efficient in the main program.
  • Some cleanings (variables deletion, more adapted type/dimension, etc).

JBC

File size: 11.3 KB
RevLine 
[3149]1MODULE glaciers_mod
[2995]2
[3149]3implicit none
4
[3161]5! Flags for ice management
[3308]6logical :: h2oice_flow  ! True by default, to compute H2O ice flow. Read in "run_PEM.def"
7logical :: co2ice_flow  ! True by default, to compute CO2 ice flow. Read in "run_PEM.def"
[3161]8logical :: metam_h2oice ! False by default, to compute H2O ice metamorphism. Read in "run_PEM.def"
9logical :: metam_co2ice ! False by default, to compute CO2 ice metamorphism. Read in "run_PEM.def"
10
11! Thresholds for ice management
[3553]12real :: inf_h2oice_threshold   ! To consider the amount of H2O ice as an infinite reservoir [kg.m-2]
13real :: metam_h2oice_threshold ! To consider frost is becoming perennial H2O ice [kg.m-2]
14real :: metam_co2ice_threshold ! To consider frost is becoming perennial CO2 ice [kg.m-2]
[3161]15
[3553]16real, parameter :: rho_co2ice = 1650. ! Density of CO2 ice [kg.m-3]
17real, parameter :: rho_h2oice = 920.  ! Density of H2O ice [kg.m-3]
18
[3149]19!=======================================================================
[2995]20contains
[3149]21!=======================================================================
[2995]22
[3591]23SUBROUTINE flow_co2glaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,vmr_co2_PEM,ps_PCM,ps_avg_global_ini,ps_avg_global,co2ice,flag_co2flow)
[2995]24
25!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
26!!!
27!!! Purpose: Main for CO2 glaciers evolution: compute maximum thickness, and do
28!!!          the ice transfer
[3532]29!!!
30!!!
[2995]31!!! Author: LL
32!!!
33!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
34
[3149]35implicit none
[2995]36
[3591]37! Inputs
38!-------
[3527]39integer,                           intent(in) :: timelen, ngrid, nslope, iflat ! number of time sample, physical points, subslopes, index of the flat subslope
[3571]40real,    dimension(ngrid,nslope),  intent(in) :: subslope_dist                 ! Grid points x Slopes: Distribution of the subgrid slopes
41real,    dimension(ngrid),         intent(in) :: def_slope_mean                ! Grid points: values of the sub grid slope angles
42real,    dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM                   ! Grid points x Time field : VMR of co2 in the first layer [mol/mol]
43real,    dimension(ngrid,timelen), intent(in) :: ps_PCM                        ! Grid points x Time field: surface pressure given by the PCM [Pa]
44real,                              intent(in) :: ps_avg_global_ini             ! Global averaged surface pressure at the beginning [Pa]
45real,                              intent(in) :: ps_avg_global                 ! Global averaged surface pressure during the PEM iteration [Pa]
[3591]46! Ouputs
47!-------
48real, dimension(ngrid,nslope), intent(inout) :: co2ice ! Grid points x Slope field: co2 ice on the subgrid slopes [kg/m^2]
49integer(kind=1), dimension(ngrid,nslope), intent(out) :: flag_co2flow ! Flag to see if there is flow on the subgrid slopes
[3532]50! Local
[3527]51!------
52real, dimension(ngrid,nslope) :: Tcond ! Physical field: CO2 condensation temperature [K]
[3571]53real, dimension(ngrid,nslope) :: hmax  ! Grid points x Slope field: maximum thickness for co2  glacier before flow
[2995]54
[3345]55write(*,*) "Flow of CO2 glaciers"
[3571]56call computeTcondCO2(timelen,ngrid,nslope,vmr_co2_PEM,ps_PCM,ps_avg_global_ini,ps_avg_global,Tcond)
[3149]57call compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tcond,"co2",hmax)
[3591]58call transfer_ice_duringflow(ngrid,nslope,iflat,subslope_dist,def_slope_mean,hmax,Tcond,co2ice,flag_co2flow)
[2995]59
[3149]60END SUBROUTINE flow_co2glaciers
[2995]61
[3149]62!=======================================================================
[2995]63
[3591]64SUBROUTINE flow_h2oglaciers(ngrid,nslope,iflat,subslope_dist,def_slope_mean,Tice,h2oice,flag_h2oflow)
[2995]65
66!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
67!!!
68!!! Purpose: Main for H2O glaciers evolution: compute maximum thickness, and do
69!!!          the ice transfer
[3532]70!!!
71!!!
[2995]72!!! Author: LL
73!!!
74!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
75
[3149]76implicit none
[2995]77
78! arguments
79! ---------
80
[3591]81! Inputs
82! ------
[3571]83integer,                       intent(in) :: ngrid, nslope, iflat ! number of time sample, physical points, subslopes, index of the flat subslope
84real, dimension(ngrid,nslope), intent(in) :: subslope_dist  ! Grid points x Slopes : Distribution of the subgrid slopes
[3527]85real, dimension(ngrid),        intent(in) :: def_slope_mean ! Slopes: values of the sub grid slope angles
86real, dimension(ngrid,nslope), intent(in) :: Tice           ! Ice Temperature [K]
[3591]87! Outputs
88!--------
89real, dimension(ngrid,nslope), intent(inout) :: h2oice ! Grid points x Slope field: co2 ice on the subgrid slopes [kg/m^2]
90integer(kind=1), dimension(ngrid,nslope), intent(out) :: flag_h2oflow ! Flag to see if there is flow on the subgrid slopes
[3532]91! Local
[3591]92! -----
[3571]93real, dimension(ngrid,nslope) :: hmax ! Grid points x Slope field: maximum thickness for co2  glacier before flow
[2995]94
[3149]95write(*,*) "Flow of H2O glaciers"
96call compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tice,"h2o",hmax)
[3591]97call transfer_ice_duringflow(ngrid,nslope,iflat,subslope_dist,def_slope_mean,hmax,Tice,h2oice,flag_h2oflow)
[2995]98
[3149]99END SUBROUTINE flow_h2oglaciers
[2995]100
[3149]101!=======================================================================
[2995]102
[3149]103SUBROUTINE compute_hmaxglaciers(ngrid,nslope,iflat,def_slope_mean,Tice,name_ice,hmax)
[2995]104
[3527]105use ice_table_mod, only: rho_ice
[3076]106use abort_pem_mod, only: abort_pem
[3082]107#ifndef CPP_STD
108    use comcstfi_h,   only: pi, g
109#else
110    use comcstfi_mod, only: pi, g
111#endif
[2995]112
113!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
114!!!
[3527]115!!! Purpose: Compute the maximum thickness of CO2 and H2O glaciers given a slope angle before initating flow
[3532]116!!!
[3591]117!!! Author: LL, based on  work by A.Grau Galofre (LPG) and Isaac Smith (JGR Planets 2022)
[2995]118!!!
119!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
120
[3149]121implicit none
[2995]122
123! Inputs
[3527]124! ------
125integer,                       intent(in) :: ngrid, nslope  ! # of grid points and subslopes
126integer,                       intent(in) :: iflat          ! index of the flat subslope
127real, dimension(nslope),       intent(in) :: def_slope_mean ! Slope field: Values of the subgrid slope angles [deg]
128real, dimension(ngrid,nslope), intent(in) :: Tice           ! Physical field:  ice temperature [K]
129character(3),                  intent(in) :: name_ice       ! Nature of ice
[2995]130! Outputs
[3527]131! -------
132real, dimension(ngrid,nslope), intent(out) :: hmax ! Physical grid x Slope field: maximum  thickness before flaw [m]
[2995]133! Local
[3527]134! -----
135real    :: tau_d      ! characteristic basal drag, understood as the stress that an ice mass flowing under its weight balanced by viscosity. Value obtained from I.Smith
136integer :: ig, islope ! loop variables
137real    :: slo_angle
[2995]138
[3527]139select case (trim(adjustl(name_ice)))
140    case('h2o')
141        tau_d = 1.e5
142    case('co2')
[2995]143        tau_d = 5.e3
[3527]144    case default
145        call abort_pem("compute_hmaxglaciers","Type of ice not known!",1)
146end select
[2995]147
[3527]148do ig = 1,ngrid
149    do islope = 1,nslope
150        if (islope == iflat) then
[2995]151            hmax(ig,islope) = 1.e8
[3527]152        else
[2995]153            slo_angle = abs(def_slope_mean(islope)*pi/180.)
[3527]154            hmax(ig,islope) = tau_d/(rho_ice(Tice(ig,islope),name_ice)*g*slo_angle)
155        endif
156    enddo
157enddo
158
[3149]159END SUBROUTINE compute_hmaxglaciers
[2995]160
[3149]161!=======================================================================
[2995]162
[3591]163SUBROUTINE transfer_ice_duringflow(ngrid,nslope,iflat,subslope_dist,def_slope_mean,hmax,Tice,qice,flag_flow)
[2995]164!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
165!!!
166!!! Purpose: Transfer the excess of ice from one subslope to another
167!!!          No transfer between mesh at the time
168!!! Author: LL
169!!!
170!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
171
[3527]172use ice_table_mod, only: rho_ice
[3076]173use abort_pem_mod, only: abort_pem
[3082]174#ifndef CPP_STD
175    use comcstfi_h,   only: pi
176#else
177    use comcstfi_mod, only: pi
178#endif
[2995]179
180implicit none
181
182! Inputs
[3527]183!-------
184integer,                       intent(in) :: ngrid, nslope  ! # of physical points and subslope
185integer,                       intent(in) :: iflat          ! index of the flat subslope
186real, dimension(ngrid,nslope), intent(in) :: subslope_dist  ! Distribution of the subgrid slopes within the mesh
187real, dimension(nslope),       intent(in) :: def_slope_mean ! values of the subgrid slopes
188real, dimension(ngrid,nslope), intent(in) :: hmax           ! maximum height of the  glaciers before initiating flow [m]
189real, dimension(ngrid,nslope), intent(in) :: Tice           ! Ice temperature[K]
[2995]190! Outputs
[3527]191!--------
[3591]192real, dimension(ngrid,nslope), intent(inout) :: qice ! CO2 in the subslope [kg/m^2]
193integer(kind=1), dimension(ngrid,nslope), intent(out) :: flag_flow ! Flag to see if there is flow on the subgrid slopes
[2995]194! Local
[3527]195!------
196integer :: ig, islope ! loop
197integer :: iaval      ! ice will be transfered here
[2995]198
[3591]199flag_flow = 0
200
[3527]201do ig = 1,ngrid
202    do islope = 1,nslope
203        if (islope /= iflat) then ! ice can be infinite on flat ground
[2995]204! First: check that CO2 ice must flow (excess of ice on the slope), ice can accumulate infinitely  on flat ground
[3527]205            if (qice(ig,islope) >= rho_ice(Tice(ig,islope),'h2o')*hmax(ig,islope)*cos(pi*def_slope_mean(islope)/180.)) then
[2995]206! Second: determine the flatest slopes possible:
[3527]207                if (islope > iflat) then
208                    iaval=islope-1
209                else
210                    iaval = islope + 1
211                endif
212                do while (iaval /= iflat .and. subslope_dist(ig,iaval) == 0)
213                    if (iaval > iflat) then
214                        iaval = iaval - 1
215                    else
216                        iaval = iaval + 1
217                    endif
[2995]218                enddo
[3527]219                qice(ig,iaval) = qice(ig,iaval) + (qice(ig,islope) - rho_ice(Tice(ig,islope),'h2o')*hmax(ig,islope)*cos(pi*def_slope_mean(islope)/180.)) &
220                               *subslope_dist(ig,islope)/subslope_dist(ig,iaval)*cos(pi*def_slope_mean(iaval)/180.)/cos(pi*def_slope_mean(islope)/180.)
[2995]221
[3527]222                qice(ig,islope) = rho_ice(Tice(ig,islope),'h2o')*hmax(ig,islope)*cos(pi*def_slope_mean(islope)/180.)
[3591]223                flag_flow(ig,islope) = 1
[3527]224            endif ! co2ice > hmax
225        endif ! iflat
[3532]226    enddo !islope
[3527]227enddo !ig
[2995]228
[3149]229END SUBROUTINE
[2995]230
[3149]231!=======================================================================
232
[3571]233SUBROUTINE computeTcondCO2(timelen,ngrid,nslope,vmr_co2_PEM,ps_PCM,ps_avg_global_ini,ps_avg_global,Tcond)
[2995]234!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
235!!!
236!!! Purpose: Compute CO2 condensation temperature
237!!!
238!!! Author: LL
239!!!
240!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[3532]241
[3571]242use constants_marspem_mod, only: alpha_clap_co2, beta_clap_co2
[2995]243
[3532]244implicit none
[2995]245
246! arguments:
247! ----------
248
249! INPUT
[3149]250integer,                        intent(in) :: timelen, ngrid, nslope ! # of timesample, physical points, subslopes
[3571]251real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM            ! Grid points x times field: VMR of CO2 in the first layer [mol/mol]
252real, dimension(ngrid,timelen), intent(in) :: ps_PCM                 ! Grid points x times field: surface pressure in the PCM [Pa]
253real,                           intent(in) :: ps_avg_global_ini      ! Global averaged surfacepressure in the PCM [Pa]
254real,                           intent(in) :: ps_avg_global          ! Global averaged surface pressure computed during the PEM iteration
[3149]255
[2995]256! OUTPUT
[3571]257real, dimension(ngrid,nslope), intent(out) :: Tcond ! Grid points: condensation temperature of CO2, yearly averaged
[2995]258
259! LOCAL
[3149]260integer :: ig, it ! For loop
[2995]261
[3149]262do ig = 1,ngrid
[3571]263    Tcond(ig,:) = 0
[3149]264    do it = 1,timelen
[3571]265        Tcond(ig,:) = Tcond(ig,:) + beta_clap_co2/(alpha_clap_co2 - log(vmr_co2_PEM(ig,it)*ps_PCM(ig,it)*ps_avg_global_ini/ps_avg_global/100))
[3149]266    enddo
[3571]267    Tcond(ig,:) = Tcond(ig,:)/timelen
[3149]268enddo
[2995]269
[3149]270END SUBROUTINE computeTcondCO2
[2995]271
[3149]272END MODULE glaciers_mod
Note: See TracBrowser for help on using the repository browser.