Changeset 3739 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Apr 26, 2025, 8:20:13 PM (7 weeks ago)
Author:
emillour
Message:

Mars PCM:
Code tidying: put routines in modules, remove useless "return" statements, etc.
EM

Location:
trunk/LMDZ.MARS
Files:
17 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/changelog.txt

    r3737 r3739  
    48134813- When atmospheric water profile is monitored, ice value is not put to 0 anymore.
    48144814- The user can now prescribe a specific atmospheric water profile with a file "profile_def_h2o_vap".
     4815
     4816== 26/04/2025 == EM
     4817Code tidying: put routines in modules, remove useless "return" statements, etc.
  • trunk/LMDZ.MARS/libf/phymars/call_dayperi.F

    r3040 r3739  
     1      module call_dayperi_mod
     2     
     3      implicit none
     4     
     5      contains
     6     
    17c *******************************************************
    28      subroutine call_dayperi(Lsperi,e_elips,dayperi,year_day)
     
    4349     &     -x2*sin(Lsperi)/(1+e_elips*cos(Lsperi)) )
    4450       if (dayperi < 0) dayperi=dayperi+year_day
    45        return
    4651
    47        end
     52       end subroutine call_dayperi
     53       
     54       end module call_dayperi_mod
  • trunk/LMDZ.MARS/libf/phymars/co2cloud.F90

    • Property svn:executable deleted
  • trunk/LMDZ.MARS/libf/phymars/co2condens_mod.F

    r3726 r3739  
    3939      USE paleoclimate_mod, ONLY: paleoclimate
    4040      use callkeys_mod, only: caps, co2clouds
     41      use co2snow_mod, only: co2snow
    4142
    4243       IMPLICIT NONE
  • trunk/LMDZ.MARS/libf/phymars/co2sat.F

    • Property svn:executable deleted
    r2362 r3739  
    3838c===== END
    3939c=======================================================================
    40       RETURN
    4140      END
    4241
  • trunk/LMDZ.MARS/libf/phymars/co2snow.F

    r3726 r3739  
     1      MODULE co2snow_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
    16c=======================================================================
    27c     Program for simulate the impact of the CO2 snow fall on
     
    138143c END
    139144c=======================================================================
    140       return
    141       end
     145      end subroutine co2snow
     146
     147      END MODULE co2snow_mod
  • trunk/LMDZ.MARS/libf/phymars/drag_noro_mod.F90

    r2642 r3739  
    4141      REAL, intent(in):: pvar(ndomainsz)                ! sub-grid scale standard deviation
    4242      REAL, intent(in):: psig(ndomainsz)                ! sub-grid scale standard slope
    43       REAL, intent(in):: pgam(ndomainsz)                ! sub-grid scale standard anisotropy
     43      REAL, intent(inout):: pgam(ndomainsz)             ! sub-grid scale standard anisotropy
    4444      REAL, intent(in):: pthe(ndomainsz)                ! sub-grid scale principal axes angle
    4545      REAL, intent(in):: u(ndomainsz,nlayer)            ! Zonal wind at full levels(m/s)
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/init_testphys1d_mod.F90

    r3737 r3739  
    4646use co2condens_mod,           only: CO2cond_ps
    4747use callkeys_mod, only: water, photochem, callthermos
     48use call_dayperi_mod, only: call_dayperi
    4849! Mostly for XIOS outputs:
    4950use mod_const_mpi,            only: COMM_LMDZ
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds_mod.F

    r3726 r3739  
    624624     
    625625      ENDIF ! endif test_flag
    626 !!!!!!!!!!!!!! TESTS OUTPUTS TESTS OUTPUTS TESTS OUTPUTS TESTS OUTPUTS
    627 !!!!!!!!!!!!!! TESTS OUTPUTS TESTS OUTPUTS TESTS OUTPUTS TESTS OUTPUTS
    628 !!!!!!!!!!!!!! TESTS OUTPUTS TESTS OUTPUTS TESTS OUTPUTS TESTS OUTPUTS
    629 
    630       return
    631 
    632      
    633      
     626
    634627     
    635628cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc     
  • trunk/LMDZ.MARS/libf/phymars/improvedco2clouds_mod.F90

    • Property svn:executable deleted
  • trunk/LMDZ.MARS/libf/phymars/massflowrateco2.F90

    • Property svn:executable deleted
    r3008 r3739  
    528528  visco = 0.0266958 * sqrt(M2*T) / ( sigma**2. * RGCS )  !!! microPa.s
    529529
    530   return
    531530!======================================================================================================================!
    532531! END =================================================================================================================!
  • trunk/LMDZ.MARS/libf/phymars/nucleaco2.F90

    • Property svn:executable deleted
  • trunk/LMDZ.MARS/libf/phymars/orodrag_mod.F90

    r2651 r3739  
    3939      USE comcstfi_h, ONLY: g, cpp
    4040      USE yoegwd_h, ONLY: gkwake
     41      USE orosetup_mod, ONLY: orosetup
    4142     
    4243      implicit none
     
    5758      REAL, intent(in):: pvar(ndomainsz)       ! Sub-grid scale standard deviation
    5859      REAL, intent(in):: psig(ndomainsz)       ! Sub-grid scale slope
    59       REAL, intent(in):: pgam(ndomainsz)       ! Sub-grid scale anisotropy
     60      REAL, intent(inout):: pgam(ndomainsz)       ! Sub-grid scale anisotropy
    6061      REAL, intent(in):: pthe(ndomainsz)       ! Sub-grid scale principal axes angle
    6162      REAL, intent(in):: zgeom(ndomainsz,nlayer)     ! Geopotential height of full levels
  • trunk/LMDZ.MARS/libf/phymars/orosetup.F90

    r2651 r3739  
     1MODULE orosetup_mod
     2
     3IMPLICIT NONE
     4
     5CONTAINS
     6
    17SUBROUTINE OROSETUP( ngrid, nlayer, ktest, pplev, pplay, pu, pv, pt, zgeom, &
    28            pvar,pthe, pgam,                                       &
     
    113119! 1. INITIALIZATION
    114120!--------------------------------------------------------------------------------
    115 ! 100  CONTINUE  ! continue tag without source, maybe need delete in future
    116121
    117122      !* 1.1 COMPUTATIONAL CONSTANTS
    118123      kidia=1
    119124      kfdia=ngrid
    120 ! 110  CONTINUE  ! continue tag without source, maybe need delete in future
    121125      ILEVM1=nlayer-1
    122126      ILEVM2=nlayer-2
     
    129133! 2. Compute all the critical levels and the coeffecients of anisotropy
    130134!-----------------------------------------------------------------------------------------------------
    131 ! 200  CONTINUE ! continue tag without source, maybe need delete in future
     135
    132136      ! 2.1 Define low level wind, project winds in plane of low level wind,
    133137      ! determine sector in which to take the variance and set indicator for critical levels.
     
    209213      enddo     
    210214
    211 ! 210  CONTINUE ! continue tag without source, maybe need delete in future
    212215      ! Initialize various arrays for the following computes
    213216      DO JL=kidia,kfdia
     
    329332
    330333      ! 2.2 Brunt-vaisala frequency and density at half levels
    331  220  CONTINUE ! continue tag without source, maybe need delete in future
    332334 
    333335      DO JK=ilevh,nlayer
     
    366368
    367369      ! 2.3 Mean flow richardson number and critical height for proude layer   
    368 ! 230  CONTINUE ! continue tag without source, maybe need delete in future
    369370
    370371      DO JK=2,nlayer
     
    471472      end DO
    472473
    473 ! 260  CONTINUE  ! continue tag without source, maybe need delete in future
    474 
    475   RETURN
    476 END
     474END SUBROUTINE OROSETUP
     475
     476END MODULE orosetup_mod
  • trunk/LMDZ.MARS/libf/phymars/tcondwater.F90

    r1711 r3739  
    1 SUBROUTINE tcondwater(nbpts,p,q,tcond)
     1module tcondwater_mod
     2
     3implicit none
     4
     5contains
     6
     7subroutine tcondwater(ngrid,nlay,p,q,tcond)
    28IMPLICIT NONE
    39
     
    713!--------------------------------------------------i
    814
    9 integer, intent(in) :: nbpts
    10 real, intent(in), dimension(nbpts):: p,q
    11 real, intent(out), dimension(nbpts):: tcond
     15integer, intent(in) :: ngrid, nlay
     16real, intent(in) :: p(ngrid,nlay) ! pressure (Pa)
     17real, intent(in) :: q(ngrid,nlay) ! water mass mixing ratio (kg/kg_air)
     18real, intent(out):: tcond(ngrid,nlay) ! condensation temeprature (K)
    1219
    13 real, dimension(nbpts):: res
    1420real:: x
    15 integer:: i
    16 
    17 do i=1,nbpts
     21integer:: i,j
     22do i=1,ngrid
     23 do j=1,nlay
    1824   !write(*,*) "i en cours", i, "sur nbpts=", nbpts
    1925   !write(*,*) "q(i)",q(i),"p(i)",p(i)
    20    x=alog10(MAX(q(i),1e-16)*p(i)/(100.*0.41)) ! max pour erreur q<=0
     26   x=alog10(MAX(q(i,j),1e-16)*p(i,j)/(100.*0.41)) ! max pour erreur q<=0
    2127   ! attention change le 0.41 de place le 10 juin 2014 car priorites
    2228   ! fortran dans watersat.F
     
    2632   !        + 2.12411064e-04*x**6+1.64642075e-05*x**7+9.22615632e-07*x**8
    2733   !        + 3.18958825e-08*x**9+5.00656720e-10*x**10 degre 10: trop!
    28    res(i) = 2.52846556e+02+ 2.39229653e+01*x+ 2.21333897e+00*x**2  &
     34   tcond(i,j) = 2.52846556e+02+ 2.39229653e+01*x+ 2.21333897e+00*x**2  &
    2935                + 1.79977992e-01*x**3+ 1.00068175e-02*x**4+2.55145012e-04*x**5
    3036   !write(*,*) "rex(x) tcondwater AP14! :) :) :) :P", res(i)
     37 enddo
    3138enddo
    3239
    33 tcond=res
     40end subroutine tcondwater
    3441
    35 return
    36 end
     42end module tcondwater_mod
    3743!polynome de degre 5 pas 0.0001
    3844!polynomial coefs [  2.52846556e+02   2.39229653e+01   2.21333897e+00
  • trunk/LMDZ.MARS/libf/phymars/thermcell_dqup.F90

    • Property svn:executable deleted
  • trunk/LMDZ.MARS/libf/phymars/watercloud_mod.F

    r3726 r3739  
    2020      USE improvedclouds_mod, ONLY: improvedclouds
    2121      USE watersat_mod, ONLY: watersat
     22      USE tcondwater_mod, ONLY: tcondwater
    2223      use tracer_mod, only: nqmx, igcm_h2o_vap, igcm_h2o_ice,
    2324     &                      igcm_hdo_vap, igcm_hdo_ice,
     
    244245         zqvap=zqclf(:,:,igcm_h2o_vap)
    245246         zqice=zqclf(:,:,igcm_h2o_ice)
    246          CALL tcondwater(ngrid*nlay,pplay,zqvap+zqice,tcond)
     247         CALL tcondwater(ngrid,nlay,pplay,zqvap+zqice,tcond)
    247248         DO l=1,nlay
    248249           DO ig=1,ngrid
Note: See TracChangeset for help on using the changeset viewer.