Ignore:
Timestamp:
Oct 25, 2016, 9:23:21 AM (8 years ago)
Author:
emillour
Message:

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F

    r1576 r1621  
    2121     &                            ecritphy, iphysiq
    2222      use dimradmars_mod, only: tauscaling,tauvis
    23       USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff,sig
     23      USE comvert_mod, ONLY: ap,bp,aps,bps,pa,preff,sig,
     24     &                       presnivs,pseudoalt,scaleheight
     25      USE vertical_layers_mod, ONLY: init_vertical_layers
    2426      USE logic_mod, ONLY: hybrid
    2527      use physics_distribution_mod, only: init_physics_distribution
     
    4951c=======================================================================
    5052
    51 #include "dimensions.h"
     53      include "dimensions.h"
    5254      integer, parameter :: ngrid = 1 !(2+(jjm-1)*iim - 1/jjm)
    5355      integer, parameter :: nlayer = llm
     
    5860!#include "comsoil.h"
    5961!#include "comdiurn.h"
    60 #include "callkeys.h"
     62      include "callkeys.h"
    6163!#include "comsaison.h"
    6264!#include "control.h"
    63 #include "netcdf.inc"
    64 #include "comg1d.h"
     65      include "netcdf.inc"
     66      include "comg1d.h"
    6567!#include "advtrac.h"
    6668
     
    494496     &                   (/0.,0.,0.,0./),(/0.,0.,0.,0./),
    495497     &                   cell_area)
     498! Ehouarn: init_vertial_layers called later (because disvert not called yet)
     499!      call init_vertical_layers(nlayer,preff,scaleheight,
     500!     &                      ap,bp,aps,bps,presnivs,pseudoalt)
    496501      call init_dimphy(1,nlayer) ! Initialize dimphy module
    497       call phys_state_var_init(1,llm,nq,
     502      call phys_state_var_init(1,llm,nq,tname,
    498503     .          day0,time,daysec,dtphys,rad,g,r,cpp)
    499504      call ini_fillgeom(1,latitude,longitude,(/1.0/))
     
    611616
    612617      CALL  disvert
     618      ! now that disvert has been called, initialize module vertical_layers_mod
     619      call init_vertical_layers(nlayer,preff,scaleheight,
     620     &                      ap,bp,aps,bps,presnivs,pseudoalt)
    613621
    614622      DO ilevel=1,nlevel
  • trunk/LMDZ.MARS/libf/phymars/eofdump_mod.F90

    r1543 r1621  
    8181
    8282      use geometry_mod, only: longitude, latitude
    83       use comcstfi_h, only: pi
     83      use nrtype, only: pi
    8484      use time_phylmdz_mod, only: daysec, dtphys
    85       USE comvert_mod, ONLY: aps,bps
     85      USE vertical_layers_mod, ONLY: aps,bps
    8686      use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat
    8787      implicit none
  • trunk/LMDZ.MARS/libf/phymars/inistats.F

    r1532 r1621  
    33      use statto_mod, only: istats,istime
    44      use mod_phys_lmdz_para, only : is_master
    5       USE comvert_mod, ONLY: ap,bp,aps,bps,preff,pseudoalt,presnivs
    6       USE comcstfi_h, ONLY: pi
     5      USE vertical_layers_mod, ONLY: ap,bp,aps,bps,preff,
     6     &                               pseudoalt,presnivs
     7      USE nrtype, ONLY: pi
    78      USE time_phylmdz_mod, ONLY: daysec,dtphys
    89      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
  • trunk/LMDZ.MARS/libf/phymars/initracer.F

    r1617 r1621  
    11      SUBROUTINE initracer(ngrid,nq,qsurf)
    22
    3 #ifndef MESOSCALE
    4        use infotrac, only: tname
    5 #endif
    63       use tracer_mod
    74       USE comcstfi_h
     
    5451c-----------------------------------------------------------------------
    5552
    56 ! Initialization: allocate arrays in tracer_mod
    57       allocate(mmol(nq))
    58       allocate(radius(nq))
    59       allocate(rho_q(nq))
    60       allocate(alpha_lift(nq))
    61       allocate(alpha_devil(nq))
    62       allocate(igcm_dustbin(nq))
    63       allocate(nqdust(nq))
    64 
    65 #ifndef MESOSCALE
    66       allocate(noms(nq))
    67 ! Initialization: get tracer names from the dynamics and check if we are
    68 !                 using 'old' tracer convention ('q01',q02',...)
    69 !                 or new convention (full tracer names)
    70       ! check if tracers have 'old' names
    71 
    72       count=0
    73       do iq=1,nq
    74         txt=" "
    75         write(txt,'(a1,i2.2)') 'q',iq
    76         if (txt.eq.tname(iq)) then
    77           count=count+1
    78         endif
    79       enddo ! of do iq=1,nq
    80      
    81       if (count.eq.nq) then
    82         write(*,*) "initracer: tracers seem to follow old naming ",
    83      &             "convention (q01,q02,...)"
    84         write(*,*) "you should run newstart to rename them"
    85         stop
    86       endif
    87 
    88       ! copy tracer names from dynamics
    89       do iq=1,nq
    90         noms(iq)=tname(iq)
    91         write(*,*) "initracer names : ", noms(iq)
    92       enddo
    93 #endif
    9453
    9554c------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/iniwrite.F

    r1532 r1621  
    33      use comsoil_h, only: mlayer, nsoilmx
    44      USE comcstfi_h, only: g, mugaz, omeg, rad, rcp, pi
    5       USE comvert_mod, ONLY: ap,bp,aps,bps,pseudoalt
    6       USE logic_mod, ONLY: fxyhypb,ysinus
    7       USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
     5      USE vertical_layers_mod, ONLY: ap,bp,aps,bps,pseudoalt
     6!      USE logic_mod, ONLY: fxyhypb,ysinus
     7!      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy
    88      USE time_phylmdz_mod, ONLY: hour_ini, daysec, dtphys
    9       USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
     9!      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0
    1010      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
    1111      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
     
    7575      tab_cntrl(10) = daysec
    7676      tab_cntrl(11) = dtphys
    77       tab_cntrl(12) = etot0
    78       tab_cntrl(13) = ptot0
    79       tab_cntrl(14) = ztot0
    80       tab_cntrl(15) = stot0
    81       tab_cntrl(16) = ang0
     77!      tab_cntrl(12) = etot0
     78!      tab_cntrl(13) = ptot0
     79!      tab_cntrl(14) = ztot0
     80!      tab_cntrl(15) = stot0
     81!      tab_cntrl(16) = ang0
    8282
    8383      tab_cntrl(27) = hour_ini
     
    8585c    ..........    P.Le Van  ( ajout le 8/04/96 )    .........
    8686c         .....        parametres  pour le zoom          ......   
    87       tab_cntrl(17)  = clon
    88       tab_cntrl(18)  = clat
    89       tab_cntrl(19)  = grossismx
    90       tab_cntrl(20)  = grossismy
     87!      tab_cntrl(17)  = clon
     88!      tab_cntrl(18)  = clat
     89!      tab_cntrl(19)  = grossismx
     90!      tab_cntrl(20)  = grossismy
    9191c
    9292c     .....   ajout  le 6/05/97 et le 15/10/97  .......
    9393c
    94       IF ( fxyhypb )   THEN
    95         tab_cntrl(21) = 1.
    96         tab_cntrl(22) = dzoomx
    97         tab_cntrl(23) = dzoomy
    98       ELSE
    99         tab_cntrl(21) = 0.
    100         tab_cntrl(22) = dzoomx
    101         tab_cntrl(23) = dzoomy
    102         tab_cntrl(24) = 0.
    103         IF( ysinus )  tab_cntrl(24) = 1.
    104       ENDIF
     94!      IF ( fxyhypb )   THEN
     95!        tab_cntrl(21) = 1.
     96!        tab_cntrl(22) = dzoomx
     97!        tab_cntrl(23) = dzoomy
     98!      ELSE
     99!        tab_cntrl(21) = 0.
     100!        tab_cntrl(22) = dzoomx
     101!        tab_cntrl(23) = dzoomy
     102!        tab_cntrl(24) = 0.
     103!        IF( ysinus )  tab_cntrl(24) = 1.
     104!      ENDIF
    105105
    106106c    .........................................................
  • trunk/LMDZ.MARS/libf/phymars/iostart.F90

    r1504 r1621  
    464464  USE mod_grid_phy_lmdz, only: klon_glo
    465465  USE dimphy, only: klev, klevp1
    466   USE infotrac, only: nqtot
     466  USE tracer_mod, only: nqmx
    467467  USE comsoil_h, only: nsoilmx
    468468  IMPLICIT NONE
     
    528528      ENDIF
    529529     
    530       if (nqtot.ne.0) then
    531         ierr=NF90_DEF_DIM(nid_restart,"number_of_advected_fields",nqtot,idim5)
     530      if (nqmx.ne.0) then
     531        ierr=NF90_DEF_DIM(nid_restart,"number_of_advected_fields",nqmx,idim5)
    532532      else
    533         ! pretend nqtot=1 because 0 size implies unlimited dimension for NetCDF
     533        ! pretend nqmx=1 because 0 size implies unlimited dimension for NetCDF
    534534        ierr=NF90_DEF_DIM(nid_restart,"number_of_advected_fields",1,idim5)
    535535      endif
  • trunk/LMDZ.MARS/libf/phymars/newcondens.F

    r1543 r1621  
    1212       USE comcstfi_h
    1313#ifndef MESOSCALE
    14        USE comvert_mod, ONLY: bp
     14       USE vertical_layers_mod, ONLY: bp
    1515#endif
    1616       IMPLICIT NONE
  • trunk/LMDZ.MARS/libf/phymars/phyetat0.F90

    r1525 r1621  
    33                     tauscaling)
    44!  use netcdf
    5   use infotrac, only: nqtot, tname
     5  use tracer_mod, only: noms ! tracer names
    66  use surfdat_h, only: phisfi, albedodat, z0, z0_default,&
    77                       zmea, zstd, zsig, zgam, zthe
     
    289289if (nq.ge.1) then
    290290  do iq=1,nq
    291     txt=tname(iq)
     291    txt=noms(iq)
    292292    if (txt.eq."h2o_vap") then
    293293      ! There is no surface tracer for h2o_vap;
  • trunk/LMDZ.MARS/libf/phymars/phyredem.F90

    r1543 r1621  
    1212                         alb,ith,pzmea,pzstd,pzsig,pzgam,pzthe)
    1313! create physics restart file and write time-independent variables
    14   use infotrac, only: nqtot, tname
    1514  use comsoil_h, only: inertiedat, volcapa, mlayer
    1615  use geometry_mod, only: cell_area
     
    150149  use iostart, only : open_restartphy, close_restartphy, &
    151150                      put_var, put_field
    152   use infotrac, only: nqtot, tname
     151  use tracer_mod, only: noms ! tracer names
    153152  implicit none
    154153  character(len=*),intent(in) :: filename
     
    204203  ! preliminary stuff: look for water vapour & water ice tracers (if any)
    205204  do iq=1,nq
    206     if (tname(iq).eq."h2o_vap") then
     205    if (noms(iq).eq."h2o_vap") then
    207206      i_h2o_vap=iq
    208207    endif
    209     if (tname(iq).eq."h2o_ice") then
     208    if (noms(iq).eq."h2o_ice") then
    210209      i_h2o_ice=iq
    211210    endif
     
    214213  if (nq.gt.0) then
    215214    do iq=1,nq
    216       txt=tname(iq)
     215      txt=noms(iq)
    217216      ! Exception: there is no water vapour surface tracer
    218217      if (txt.eq."h2o_vap") then
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90

    r1524 r1621  
    33CONTAINS
    44
    5       SUBROUTINE phys_state_var_init(ngrid,nlayer,nq, &
     5      SUBROUTINE phys_state_var_init(ngrid,nlayer,nq,tname, &
    66                                     day_ini,hour_ini,pdaysec,ptimestep, &
    77                                     prad,pg,pr,pcpp)
     
    4444      use turb_mod, only: ini_turb_mod
    4545      use comcstfi_h, only: pi,rad,cpp,g,r,rcp
    46       use tracer_mod, only: nqmx
     46      use tracer_mod, only: ini_tracer_mod
    4747      use time_phylmdz_mod, only: init_time
    4848
     
    5050     
    5151      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
     52      CHARACTER(len=*),INTENT(IN) :: tname(nq)
    5253      INTEGER,INTENT(IN) :: day_ini
    5354      REAL,INTENT(IN) :: hour_ini
    5455      REAL,INTENT(IN) :: pdaysec,ptimestep,prad,pg,pr,pcpp
    5556
    56       ! set dimension in tracer_mod
    57       nqmx=nq
     57      ! set dimension and allocate arrays in tracer_mod
     58      call ini_tracer_mod(nq,tname)
    5859
    5960      ! set parameters in comcstfi_h
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r1618 r1621  
    5353      use phyredem, only: physdem0, physdem1
    5454      use eofdump_mod, only: eofdump
    55       USE comvert_mod, ONLY: ap,bp,aps,bps
     55      USE vertical_layers_mod, ONLY: ap,bp,aps,bps
    5656#endif
    5757
  • trunk/LMDZ.MARS/libf/phymars/tracer_mod.F90

    r1617 r1621  
    8888!-----------------------------------------------------------------------
    8989
     90  contains
     91 
     92    subroutine ini_tracer_mod(nq,tname)
     93      implicit none
     94     
     95      integer,intent(in) :: nq ! number of tracers
     96      character(len=*),intent(in) :: tname(nq) ! tracer names
     97     
     98      integer :: iq, count
     99      character(len=20) :: txt ! to store some text
     100     
     101      ! set dimension and tracer names
     102      nqmx=nq
     103#ifndef MESOSCALE
     104      allocate(noms(nq))
     105      do iq=1,nq
     106        noms(iq)=tname(iq)
     107        write(*,*) "tracer_mod names : ", trim(noms(iq))
     108      enddo
     109     
     110      ! check if tracers have 'old' names
     111      count=0
     112      do iq=1,nq
     113        txt=" "
     114        write(txt,'(a1,i2.2)') 'q',iq
     115        if (txt.eq.tname(iq)) then
     116          count=count+1
     117        endif
     118      enddo ! of do iq=1,nq
     119     
     120      if (count.eq.nq) then
     121        write(*,*) "ini_tracer_mod: tracers seem to follow old naming ", &
     122                   "convention (q01,q02,...)"
     123        write(*,*) "you should run newstart to rename them"
     124        stop
     125      endif
     126#endif
     127           
     128      ! allocate module arrays:
     129      allocate(mmol(nq))
     130      allocate(radius(nq))
     131      allocate(rho_q(nq))
     132      allocate(alpha_lift(nq))
     133      allocate(alpha_devil(nq))
     134      allocate(igcm_dustbin(nq))
     135      allocate(nqdust(nq))
     136     
     137    end subroutine ini_tracer_mod
     138
    90139end module tracer_mod
Note: See TracChangeset for help on using the changeset viewer.