Changeset 2982


Ignore:
Timestamp:
Jun 21, 2023, 3:36:23 PM (20 months ago)
Author:
romain.vande
Message:

MARS PEM:
Small correction to adapt the pem to the picky gnu compiler.
RV

Location:
trunk/LMDZ.COMMON/libf/evolution
Files:
3 edited

Legend:

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

    r2980 r2982  
    106106   print*, 'Do we compute the ice table with the dynamic method?', icetable_dynamic
    107107
    108   if ((not(soil_pem)).and.((icetable_equilibrium).or.(icetable_dynamic))) then
     108  if ((.not.soil_pem).and.((icetable_equilibrium).or.(icetable_dynamic))) then
    109109       print*,'Ice table  must be used when soil_pem = T'
    110110       call abort_physic(modname,"Ice table  must be used when soil_pem = T",1)
    111111  endif
    112112
    113   if ((not(soil_pem)).and.adsorption_pem) then
     113  if ((.not.soil_pem).and.adsorption_pem) then
    114114       print*,'Adsorption must be used when soil_pem = T'
    115115       call abort_physic(modname,"Adsorption must be used when soil_pem = T",1)
    116116  endif
    117117 
    118   if ((not(soil_pem)).and.(fluxgeo.gt.0.)) then
     118  if ((.not.soil_pem).and.(fluxgeo.gt.0.)) then
    119119       print*,'Soil is not activated but Flux Geo > 0.'
    120120       call abort_physic(modname,"Soil is not activated but Flux Geo > 0.",1)
    121121  endif
    122122 
    123   if ((not(soil_pem)).and.reg_thprop_dependp) then
     123  if ((.not.soil_pem).and.reg_thprop_dependp) then
    124124     print*,'Regolith properties vary with Ps only when soil is set to true'
    125125     call abort_physic(modname,'Regolith properties vary with Ps only when soil is set to true',1)
  • trunk/LMDZ.COMMON/libf/evolution/orbit_param_criterion_mod.F90

    r2980 r2982  
    1414
    1515      SUBROUTINE orbit_param_criterion(year_iter_max)
     16#ifdef CPP_IOIPSL
     17  use IOIPSL, only: getin
     18#else
     19  ! if not using IOIPSL, we still need to use (a local version of) getin
     20  use ioipsl_getincom, only: getin
     21#endif
    1622
    1723      USE temps_mod_evol, ONLY: year_bp_ini, year_PEM, var_obl, var_ex, var_lsp
     
    109115!Constant max change case
    110116
    111         max_change_obl=0.1
     117        max_change_obl=0.5
    112118        max_change_ex=0.1
    113119        max_change_lsp=40.
     120
     121        CALL getin('max_change_obl', max_change_obl)
     122
     123        CALL getin('max_change_ex', max_change_ex)
     124
     125        CALL getin('max_change_lsp', max_change_lsp)
    114126
    115127        max_obl=obliquit+max_change_obl
     
    147159        endif
    148160
    149         max_obl_iter=999999999999
    150         max_ex_iter =999999999999
    151         max_lsp_iter=999999999999
     161        max_obl_iter=999999
     162        max_ex_iter =999999
     163        max_lsp_iter=999999
    152164
    153165!--------------------------------
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r2980 r2982  
    921921
    922922      print *, "Updating the new Tsurf"
    923       bool_sublim=0
     923      bool_sublim=.false.
    924924      Tsurfave_before_saved(:,:) = tsurf_ave(:,:)
    925925      DO ig = 1,ngrid
     
    931931                  if(initial_co2_ice(ig_loop,islope_loop).lt.0.5 .and. qsurf(ig_loop,igcm_co2,islope_loop).LT. 1E-10) then
    932932                    tsurf_ave(ig,islope)=tsurf_ave(ig_loop,islope_loop)
    933                     bool_sublim=1
     933                    bool_sublim=.true.
    934934                    exit
    935935                  endif
    936936                enddo
    937                 if (bool_sublim.eq.1) then
     937                if (bool_sublim.eqv. .true.) then
    938938                  exit
    939939                endif
     
    944944                  if(initial_co2_ice(ig_loop,islope_loop).lt.0.5 .and. qsurf(ig_loop,igcm_co2,islope_loop).LT. 1E-10) then
    945945                    tsurf_ave(ig,islope)=tsurf_ave(ig_loop,islope_loop)
    946                     bool_sublim=1
     946                    bool_sublim=.true.
    947947                    exit
    948948                  endif
    949949                enddo
    950                 if (bool_sublim.eq.1) then
     950                if (bool_sublim.eqv. .true.) then
    951951                  exit
    952952                endif
Note: See TracChangeset for help on using the changeset viewer.