Changeset 3095


Ignore:
Timestamp:
Oct 22, 2023, 3:50:26 PM (14 months ago)
Author:
emillour
Message:

Mars PCM:
Some code tidying:
Made pi in module comcstfi_h a parameter (and not a variable recomputed at
various points by various routines) and added module routine init_comcstfi_h
to cleanly initialize module variables.
Moved iniorbit.F to be a module routine of planete_h since it initializes
(some of ) the module variables it contains.
EM

Location:
trunk/LMDZ.MARS
Files:
1 deleted
7 edited

Legend:

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

    r3094 r3095  
    42724272clauses in saved module variables in comcstfi_h.F90 and planete_h.F90.
    42734273Prettyfied solarlong.F and made it a module. Likewise for conf_phys.F
     4274
     4275Some code tidying:
     4276Made pi in module comcstfi_h a parameter (and not a variable recomputed at
     4277various points by various routines) and added module routine init_comcstfi_h
     4278to cleanly initialize module variables.
     4279Moved iniorbit.F to be a module routine of planete_h since it initializes
     4280(some of ) the module variables it contains.
  • trunk/LMDZ.MARS/libf/phymars/comcstfi_h.F90

    r3094 r3095  
    1       MODULE comcstfi_h
    2       IMPLICIT NONE
     1MODULE comcstfi_h
     2IMPLICIT NONE
    33
    4       REAL,SAVE :: pi ! something like 3.14159
    5       REAL,SAVE :: rad ! radius of the planet (m)
    6       REAL,SAVE :: g ! gravity (m/s2)
    7 !$OMP THREADPRIVATE(pi,rad,g)
    8       REAL,SAVE :: r ! reduced gas constant (r=8.314511/(mugaz/1000.0))
    9       REAL,SAVE :: cpp ! Cp of the atmosphere
    10       REAL,SAVE :: rcp ! r/cpp
     4REAL,PARAMETER :: pi=acos(-1.d0) ! something like 3.14159
     5REAL,SAVE :: rad ! radius of the planet (m)
     6REAL,SAVE :: g ! gravity (m/s2)
     7!$OMP THREADPRIVATE(rad,g)
     8REAL,SAVE :: r ! reduced gas constant (r=8.314511/(mugaz/1000.0))
     9REAL,SAVE :: cpp ! Cp of the atmosphere
     10REAL,SAVE :: rcp ! r/cpp
    1111!$OMP THREADPRIVATE(r,cpp,rcp)
    12       REAL,SAVE :: mugaz ! molar mass of the atmosphere (g/mol)
    13       REAL,SAVE :: omeg ! planet rotation rate (rad/s)
     12REAL,SAVE :: mugaz ! molar mass of the atmosphere (g/mol)
     13REAL,SAVE :: omeg ! planet rotation rate (rad/s)
    1414!$OMP THREADPRIVATE(mugaz,omeg)
    15      
    16       END MODULE comcstfi_h
     15
     16! NB: Ideally all module variables should be "protected"...
     17
     18CONTAINS
     19
     20SUBROUTINE init_comcstfi_h(prad,pcpp,pg,pr)
     21IMPLICIT NONE
     22
     23REAL,INTENT(IN) :: prad
     24REAL,INTENT(IN) :: pcpp
     25REAL,INTENT(IN) :: pg
     26REAL,INTENT(IN) :: pr
     27
     28  rad=prad
     29  cpp=pcpp
     30  g=pg
     31  r=pr
     32  rcp=r/cpp
     33
     34END SUBROUTINE init_comcstfi_h
     35
     36END MODULE comcstfi_h
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/init_testphys1d_mod.F90

    r3094 r3095  
    169169! Prescribed constants to be set here
    170170!------------------------------------------------------
    171 pi = 2.*asin(1.)
    172171
    173172! Mars planetary constants
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90

    r2994 r3095  
    4545      use conc_mod, only: ini_conc_mod,end_conc_mod
    4646      use turb_mod, only: ini_turb_mod,end_turb_mod
    47       use comcstfi_h, only: pi,rad,cpp,g,r,rcp
     47      use comcstfi_h, only: init_comcstfi_h
    4848      use tracer_mod, only: ini_tracer_mod,end_tracer_mod
    4949      use time_phylmdz_mod, only: init_time
     
    109109     
    110110      ! set parameters in comcstfi_h
    111       pi=2.*asin(1.)
    112       rad=prad
    113       cpp=pcpp
    114       g=pg
    115       r=pr
    116       rcp=r/cpp
     111      call init_comcstfi_h(prad,pcpp,pg,pr)
    117112
    118113      ! Initialize some "temporal and calendar" related variables
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r3094 r3095  
    8080      use planete_h, only: aphelie, periheli, year_day, peri_day,
    8181     &                     obliquit
     82      use planete_h, only: iniorbit
    8283      USE comcstfi_h, only: r, cpp, mugaz, g, rcp, pi, rad
    8384      USE calldrag_noro_mod, ONLY: calldrag_noro
  • trunk/LMDZ.MARS/libf/phymars/planete_h.F90

    r3094 r3095  
    1       MODULE planete_h
    2       IMPLICIT NONE
     1MODULE planete_h
     2IMPLICIT NONE
    33
    4       REAL,SAVE :: aphelie   ! Aphelion, in Mkm
    5       REAL,SAVE :: periheli  ! Perihelion, in Mkm
    6       REAL,SAVE :: year_day  ! Number of days in the year
     4REAL,SAVE :: aphelie   ! Aphelion, in Mkm
     5REAL,SAVE :: periheli  ! Perihelion, in Mkm
     6REAL,SAVE :: year_day  ! Number of days in the year
    77!$OMP THREADPRIVATE(aphelie,periheli,year_day)
    8       REAL,SAVE :: peri_day  ! Date of perihelion, in days
    9       REAL,SAVE :: obliquit  ! Obliquity of the planet, in degrees
    10       REAL,SAVE :: lmixmin
     8REAL,SAVE :: peri_day  ! Date of perihelion, in days
     9REAL,SAVE :: obliquit  ! Obliquity of the planet, in degrees
     10REAL,SAVE :: lmixmin
    1111!$OMP THREADPRIVATE(peri_day,obliquit,lmixmin)
    12       REAL,SAVE :: emin_turb
    13       REAL,SAVE :: coefvis
    14       REAL,SAVE :: coefir
     12REAL,SAVE :: emin_turb
     13REAL,SAVE :: coefvis
     14REAL,SAVE :: coefir
    1515!$OMP THREADPRIVATE(emin_turb,coefvis,coefir)
    16       REAL,SAVE :: lsperi    ! Solar longitude of the perihelion, angle in rad
    17       REAL,SAVE :: e_elips   ! Orbit eccentricity
    18       REAL,SAVE :: p_elips   ! Ellipse semi-latus rectum
    19       REAL,SAVE :: unitastr  ! Astronomical unit AU, in Mkm
    20 !$OMP THREADPRIVATE(lsperi,e_elips,p_elips,unitastr)
     16REAL,SAVE :: lsperi    ! Solar longitude of the perihelion, angle in rad
     17REAL,SAVE :: e_elips   ! Orbit eccentricity
     18REAL,SAVE :: p_elips   ! Ellipse semi-latus rectum
     19!$OMP THREADPRIVATE(lsperi,e_elips,p_elips)
     20REAL,PARAMETER :: unitastr=149.597927 ! Astronomical unit AU, in Mkm
    2121
    22       END MODULE planete_h
     22! NB: Ideally all module variables should be "protected"...
     23
     24CONTAINS
     25     
     26  SUBROUTINE iniorbit(paphelie,pperiheli,pyear_day,pperi_day,pobliq)
     27  use comcstfi_h, only: pi
     28  IMPLICIT NONE
     29  ! initialize orbital parameters
     30 
     31  REAL,INTENT(IN) :: paphelie,pperiheli,pyear_day,pperi_day,pobliq
     32
     33  CHARACTER(LEN=8),PARAMETER :: myname="iniorbit"
     34  REAL :: zxref,zanom,zz,zx0,zdx
     35  INTEGER :: iter
     36
     37  ! copy over input values
     38  aphelie =paphelie
     39  periheli=pperiheli
     40  year_day=pyear_day
     41  obliquit=pobliq
     42  peri_day=pperi_day
     43 
     44  write(*,*)myname,': Perihelion in Mkm  ',periheli
     45  write(*,*)myname,': Aphelion  in Mkm  ',aphelie
     46  write(*,*)myname,': Obliquity in degrees  :',obliquit
     47     
     48  ! compute orbit geometrical parameters
     49  e_elips=(aphelie-periheli)/(periheli+aphelie)
     50  p_elips=0.5*(periheli+aphelie)*(1-e_elips*e_elips)/unitastr
     51     
     52  write(*,*)myname,': e_elips',e_elips
     53  write(*,*)myname,': p_elips',p_elips
     54     
     55  !  compute mean anomaly zanom
     56
     57  zz=(year_day-pperi_day)/year_day
     58  zanom=2.*pi*(zz-nint(zz))
     59  zxref=abs(zanom)
     60  write(*,*)myname,': zanom  ',zanom
     61
     62  ! solve equation  zx0 - e * sin (zx0) = zxref for eccentric anomaly zx0
     63  ! using Newton method
     64
     65  zx0=zxref+e_elips*sin(zxref)
     66  DO iter=1,100
     67    zdx=-(zx0-e_elips*sin(zx0)-zxref)/(1.-e_elips*cos(zx0))
     68    if(abs(zdx).le.(1.e-12)) exit
     69    zx0=zx0+zdx
     70  ENDDO
     71
     72  zx0=zx0+zdx
     73  if(zanom.lt.0.) zx0=-zx0
     74  write(*,*)myname,': zx0   ',zx0
     75
     76  lsperi=-2.*atan(sqrt((1.+e_elips)/(1.-e_elips))*tan(zx0/2.))
     77  lsperi = modulo(lsperi,2.*pi)
     78  write(*,*)myname,': Perihelion solar long. Ls (deg)=', &
     79                          lsperi*180./pi
     80
     81  END SUBROUTINE iniorbit
     82
     83END MODULE planete_h
  • trunk/LMDZ.MARS/libf/phymars/solarlong.F

    r3094 r3095  
    3535
    3636      zz=(pday-peri_day)/year_day
    37       pi=2.*asin(1.)
    3837      zanom=2.*pi*(zz-nint(zz))
    3938      xref=abs(zanom)
Note: See TracChangeset for help on using the changeset viewer.