Changeset 3740


Ignore:
Timestamp:
Apr 27, 2025, 4:19:12 PM (2 months ago)
Author:
emillour
Message:

Mars PCM:
Code tidying; removed unused mufract.F (mucorr.F does the job); turned
ambiguously named sig.F to sig_h2o.F90 and make it a module.
EM

Location:
trunk/LMDZ.MARS
Files:
1 deleted
9 edited
1 moved

Legend:

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

    r3739 r3740  
    48164816== 26/04/2025 == EM
    48174817Code tidying: put routines in modules, remove useless "return" statements, etc.
     4818
     4819== 27/04/2025 == EM
     4820Code tidying; removed unused mufract.F (mucorr.F does the job); turned
     4821ambiguously named sig.F to sig_h2o.F90 and make it a module.
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds_mod.F

    r3739 r3740  
    2121      use microphys_h, only: mco2, vo1, mh2o, mhdo, molco2, molhdo, To
    2222      use nuclea_mod, only: nuclea
     23      use sig_h2o_mod, only: sig_h2o
    2324      use growthrate_mod, only: growthrate
    2425      use write_output_mod, only: write_output
     
    9192      REAL*8 n_aer(nbin_cld) ! number conc. of particle/each size bin
    9293      REAL*8 m_aer(nbin_cld) ! mass mixing ratio of particle/each size bin
    93 
    94       REAL*8 sig      ! Water-ice/air surface tension  (N.m)
    95       EXTERNAL sig
    9694
    9795      REAL dN,dM
     
    405403c       saturation at equilibrium
    406404c       rice should not be too small, otherwise seq value is not valid
    407         seq  = exp(2.*sig(zt(ig,l))*mh2o / (rho_ice*rgp*zt(ig,l)*
     405        seq  = exp(2.*sig_h2o(zt(ig,l))*mh2o / (rho_ice*rgp*zt(ig,l)*
    408406     &             max(rice(ig,l),1.e-7)))
    409407       
  • trunk/LMDZ.MARS/libf/phymars/mucorr.F

    r38 r3740  
     1      MODULE mucorr_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE mucorr(npts,pdeclin, plat, pmu, pfract,phaut,prad)
    28      IMPLICIT NONE
     
    410c=======================================================================
    511c
    6 c   Calcul of equivalent solar angle and and fraction of day whithout
     12c   Compute equivalent solar angle and fraction of day whithout
    713c   diurnal cycle.
    814c
     
    1420c         npts             number of points
    1521c         pdeclin          solar declinaison
    16 c         plat(npts)        latitude
    17 c         phaut            hauteur typique de l'atmosphere
    18 c         prad             rayon planetaire
     22c         plat(npts)       latitude
     23c         phaut            thickness of atmosphere
     24c         prad             planet radius
    1925c
    2026c      Output :
    2127c      --------
    22 c         pmu(npts)          equivalent cosinus of the solar angle
     28c         pmu(npts)          equivalent cosine of the solar angle
    2329c         pfract(npts)       fractionnal day
    2430c
     
    3238c     Arguments :
    3339c     -----------
    34       INTEGER npts
    35       REAL plat(npts),pmu(npts), pfract(npts)
    36       REAL phaut,prad,pdeclin
     40      INTEGER,INTENT(IN) :: npts
     41      REAL,INTENT(IN) :: plat(npts)
     42      REAL,INTENT(IN) :: phaut,prad,pdeclin
     43      REAL,INTENT(OUT) :: pmu(npts), pfract(npts)
    3744c
    3845c     Local variables :
     
    5158      sz = sin (z)
    5259
    53       DO 20 j = 1, npts
     60      DO j = 1, npts
    5461
    5562         phi = plat(j)
     
    8693         IF (pmu(j).eq.0.) pfract(j) = 0.
    8794
    88    20 CONTINUE
     95      ENDDO
    8996
    9097c-----------------------------------------------------------------------
     
    93100
    94101      alph=phaut/prad
    95       DO 30 j=1,npts
     102      DO j=1,npts
    96103c !!!!!!
    97104         pmu(j)=sqrt(1224.*pmu(j)*pmu(j)+1.)/35.
    98105c    $          (sqrt(alph*alph*pmu(j)*pmu(j)+2.*alph+1.)-alph*pmu(j))
    99 30    CONTINUE
     106      ENDDO
    100107
    101       RETURN
    102       END
     108      END SUBROUTINE mucorr
     109
     110      END MODULE mucorr_mod
  • trunk/LMDZ.MARS/libf/phymars/nirco2abs.F

    r3726 r3740  
    1010       use tracer_mod, only: igcm_co2, igcm_o
    1111       use comgeomfi_h, only: sinlon, coslon, sinlat, coslat
     12       use solang_mod, only: solang
    1213       USE comcstfi_h, ONLY: pi
    1314       USE time_phylmdz_mod, ONLY: daysec
  • trunk/LMDZ.MARS/libf/phymars/nuclea.F

    r3726 r3740  
    1010      use microphys_h, only: desorp, kbz, nus, rgp, surfdif, vo1
    1111      use callkeys_mod, only: temp_dependent_m, cloud_adapt_ts
     12      use sig_h2o_mod, only: sig_h2o
    1213      implicit none
    1314*                                                     *
     
    3334c     Local variables
    3435      DOUBLE PRECISION nh2o
    35       DOUBLE PRECISION sig      ! Water-ice/air surface tension  (N.m)
    36       external sig
    3736      DOUBLE PRECISION rstar    ! Radius of the critical germ (m)
    3837      DOUBLE PRECISION gstar    ! # of molecules forming a critical embryo
     
    118117
    119118        nh2o   = ph2o / kbz / temp
    120         rstar  = 2. * sig(temp) * vo1 / (rgp*temp*log(sat))
     119        rstar  = 2. * sig_h2o(temp) * vo1 / (rgp*temp*log(sat))
    121120        gstar  = 4. * nav * pi * (rstar * rstar * rstar) / (3.*vo1)
    122121       
     
    140139          endif
    141140
    142           fistar = (4./3.*pi) * sig(temp) * (rstar * rstar) *
     141          fistar = (4./3.*pi) * sig_h2o(temp) * (rstar * rstar) *
    143142     &             zefshape
    144143          deltaf = (2.*desorp-surfdif-fistar)/
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r3727 r3740  
    6161     &                       mu0, fract, local_time
    6262      use solarlong_mod, only: solarlong
     63      use solang_mod, only: solang
     64      use mucorr_mod, only: mucorr
    6365      use nirdata_mod, only: NIR_leedat
    6466      use nirco2abs_mod, only: nirco2abs
  • trunk/LMDZ.MARS/libf/phymars/sig_h2o.F90

    r3739 r3740  
    1 *********************************************************
    2       double precision function sig(t)
    3       implicit none
    4 *    this function computes the surface tension (N.m)   *
    5 *   between water ice and air as a function of temp.    *
    6 *********************************************************
     1module sig_h2o_mod
     2     
     3implicit none
     4     
     5contains
     6     
     7!********************************************************
     8  double precision function sig_h2o(t)
     9  implicit none
     10! this function computes the surface tension (N.m)   *
     11! between water ice and air as a function of temp.    *
     12!********************************************************
    713
    8       real t
     14   real,intent(in) :: t
    915
    10       sig = (141. - 0.15 * dble(t)) * 1.e-3
     16   sig_h2o = (141. - 0.15 * dble(t)) * 1.e-3
    1117
    12       return
    13       end
     18   end function sig_h2o
     19     
     20end module sig_h2o_mod
    1421
  • trunk/LMDZ.MARS/libf/phymars/solang.F

    r38 r3740  
     1      MODULE solang_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      subroutine solang ( kgrid,psilon,pcolon,psilat,pcolat,
    28     &                    ptim1,ptim2,ptim3,pmu0,pfract )
     
    6571C             ---------
    6672C
    67       INTEGER kgrid
    68       REAL ptim1,ptim2,ptim3
    69       REAL psilon(kgrid),pcolon(kgrid),pmu0(kgrid),pfract(kgrid)
    70       REAL psilat(kgrid), pcolat(kgrid)
     73      INTEGER,INTENT(IN) :: kgrid
     74      REAL,INTENT(IN) :: ptim1,ptim2,ptim3
     75      REAL,INTENT(IN) :: psilon(kgrid),pcolon(kgrid)
     76      REAL,INTENT(IN) :: psilat(kgrid), pcolat(kgrid)
     77      REAL,INTENT(OUT) :: pmu0(kgrid),pfract(kgrid)
    7178C
    7279      INTEGER jl
     
    8188C             --------------
    8289C
    83  100  CONTINUE
     90
    8491C
    8592      DO jl=1,kgrid
     
    111118      ENDDO
    112119C
    113       RETURN
    114       END
     120
     121      END SUBROUTINE solang
     122     
     123      END MODULE solang_mod
  • trunk/LMDZ.MARS/libf/phymars/swr_toon.F

    r3727 r3740  
    1414      use yomlw_h, only: nlaylte
    1515      use callkeys_mod, only: rayleigh
     16      use swrayleigh_mod, only: swrayleigh
    1617     
    1718      IMPLICIT NONE
  • trunk/LMDZ.MARS/libf/phymars/swrayleigh.F

    r2616 r3740  
     1      MODULE swrayleigh_mod
     2
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE swrayleigh(kdlon,knu,ppsol,prmu,prayl)
    2        USE comcstfi_h                                                   
     8
    39       IMPLICIT NONE
    410c=======================================================================
     
    3137c    Input/Output
    3238c    ------------
    33       INTEGER kdlon, knu
     39      INTEGER,INTENT(IN) :: kdlon, knu
    3440
    35       real ppsol(kdlon),prmu(kdlon),prayl(kdlon)
     41      real,intent(in) :: ppsol(kdlon),prmu(kdlon)
     42      real,intent(out) :: prayl(kdlon)
    3643c
    3744c    Local variables :
     
    8390      END DO
    8491
     92      END SUBROUTINE swrayleigh
    8593
    86       return
    87       end
    88 
     94      END MODULE swrayleigh_mod
Note: See TracChangeset for help on using the changeset viewer.