Ignore:
Timestamp:
Nov 13, 2012, 9:21:32 AM (12 years ago)
Author:
emillour
Message:

Common dynamics:

  • updates to keep up with LMDZ5 Earth (rev 1678) changes
  • fixed bug in leapfrog_p.F: parallel dynamics now work fine.
  • see file "DOC/chantiers/commit_importants.log" for details.

EM

Location:
trunk/LMDZ.COMMON/libf/dyn3d
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/calfis.F

    r776 r841  
    184184!      REAL rdayvrai
    185185      REAL, intent(in):: jD_cur, jH_cur
     186
     187      LOGICAL tracerdyn ! for generic/mars physics call ; possibly to get rid of
    186188c
    187189c-----------------------------------------------------------------------
     
    460462c
    461463      if (planet_type=="earth") then
    462 #ifdef CPP_EARTH
     464#ifdef CPP_PHYS
    463465! PVtheta calls tetalevel, which is in the (Earth) physics
    464466cIM calcul PV a teta=350, 380, 405K
     
    525527     .             PVteta)
    526528
     529      else if ( planet_type=="generic" ) then
     530
     531         CALL physiq (ngridmx,     !! ngrid
     532     .             llm,            !! nlayer
     533     .             nqtot,          !! nq
     534     .             tname,          !! tracer names from dynamical core (given in infotrac)
     535     .             debut_split,    !! firstcall
     536     .             lafin_split,    !! lastcall
     537     .             jD_cur,         !! pday. see leapfrog
     538     .             jH_cur_split,   !! ptime "fraction of day"
     539     .             zdt_split,      !! ptimestep
     540     .             zplev,          !! pplev
     541     .             zplay,          !! pplay
     542     .             zphi,           !! pphi
     543     .             zufi,           !! pu
     544     .             zvfi,           !! pv
     545     .             ztfi,           !! pt
     546     .             zqfi,           !! pq
     547     .             flxwfi,         !! pw !! or 0. anyway this is for diagnostic. not used in physiq.
     548     .             zdufi,          !! pdu
     549     .             zdvfi,          !! pdv
     550     .             zdtfi,          !! pdt
     551     .             zdqfi,          !! pdq
     552     .             zdpsrf,         !! pdpsrf
     553     .             tracerdyn)      !! tracerdyn <-- utilite ???
     554
    527555      else  ! a moduler pour Mars !!
    528556
  • trunk/LMDZ.COMMON/libf/dyn3d/comconst.h

    r108 r841  
    2121      REAL dtdiss ! (s) time step for the dissipation
    2222      REAL rad ! (m) radius of the planet
    23       REAL r ! Gas constant R=8.31 J.K-1.mol-1
     23      REAL r ! Reduced Gas constant r=R/mu
     24             ! with R=8.31.. J.K-1.mol-1, mu: mol mass of atmosphere (kg/mol)
    2425      REAL cpp   ! Cp
    2526      REAL kappa ! kappa=R/Cp
  • trunk/LMDZ.COMMON/libf/dyn3d/comvert.h

    r776 r841  
    11!
    2 ! $Id: comvert.h 1625 2012-05-09 13:14:48Z lguez $
     2! $Id: comvert.h 1654 2012-09-24 15:07:18Z aslmd $
    33!
    44!-----------------------------------------------------------------------
     
    77      COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm),     &
    88     &               pa,preff,nivsigs(llm),nivsig(llm+1),               &
    9      &               aps(llm),bps(llm),scaleheight
     9     &               aps(llm),bps(llm),scaleheight,pseudoalt(llm)
    1010
    1111      common/comverti/disvert_type, pressure_exner
     
    2323      real bps    ! hybrid sigma contribution at mid-layers
    2424      real scaleheight ! atmospheric (reference) scale height (km)
     25      real pseudoalt ! for planets
    2526
    2627      integer disvert_type ! type of vertical discretization:
  • trunk/LMDZ.COMMON/libf/dyn3d/disvert_noterre.F

    r127 r841  
    4646      real tt,rr,gg, prevz
    4747      real s(llm),dsig(llm)
    48       real pseudoalt(llm)
    4948
    5049      integer iz
  • trunk/LMDZ.COMMON/libf/dyn3d/dynetat0.F

    r776 r841  
    77      USE infotrac
    88      use netcdf, only: nf90_get_var
     9
     10      use control_mod, only : planet_type
     11
    912      IMPLICIT NONE
    1013
     
    5457      INTEGER ierr, nid, nvarid
    5558
     59      INTEGER idecal
     60
    5661c-----------------------------------------------------------------------
    5762
     
    7782      ENDIF
    7883
     84      !!! AS: idecal is a hack to be able to read planeto starts...
     85      !!!     .... while keeping everything OK for LMDZ EARTH
     86      if ((planet_type.eq."generic").or.(planet_type.eq."mars")) then
     87          write(lunout,*)'dynetat0 : Planeto-like start file'
     88          idecal = 4
     89          annee_ref  = 2000
     90      else
     91          write(lunout,*)'dynetat0 : Earth-like start file'
     92          idecal = 5
     93          annee_ref  = tab_cntrl(5)
     94      endif
     95
     96
    7997      im         = tab_cntrl(1)
    8098      jm         = tab_cntrl(2)
    8199      lllm       = tab_cntrl(3)
    82100      day_ref    = tab_cntrl(4)
    83       annee_ref  = tab_cntrl(5)
    84       rad        = tab_cntrl(6)
    85       omeg       = tab_cntrl(7)
    86       g          = tab_cntrl(8)
    87       cpp        = tab_cntrl(9)
    88       kappa      = tab_cntrl(10)
    89       daysec     = tab_cntrl(11)
    90       dtvr       = tab_cntrl(12)
    91       etot0      = tab_cntrl(13)
    92       ptot0      = tab_cntrl(14)
    93       ztot0      = tab_cntrl(15)
    94       stot0      = tab_cntrl(16)
    95       ang0       = tab_cntrl(17)
    96       pa         = tab_cntrl(18)
    97       preff      = tab_cntrl(19)
    98 c
    99       clon       = tab_cntrl(20)
    100       clat       = tab_cntrl(21)
    101       grossismx  = tab_cntrl(22)
    102       grossismy  = tab_cntrl(23)
    103 c
    104       IF ( tab_cntrl(24).EQ.1. )  THEN
     101      rad        = tab_cntrl(idecal+1)
     102      omeg       = tab_cntrl(idecal+2)
     103      g          = tab_cntrl(idecal+3)
     104      cpp        = tab_cntrl(idecal+4)
     105      kappa      = tab_cntrl(idecal+5)
     106      daysec     = tab_cntrl(idecal+6)
     107      dtvr       = tab_cntrl(idecal+7)
     108      etot0      = tab_cntrl(idecal+8)
     109      ptot0      = tab_cntrl(idecal+9)
     110      ztot0      = tab_cntrl(idecal+10)
     111      stot0      = tab_cntrl(idecal+11)
     112      ang0       = tab_cntrl(idecal+12)
     113      pa         = tab_cntrl(idecal+13)
     114      preff      = tab_cntrl(idecal+14)
     115c
     116      clon       = tab_cntrl(idecal+15)
     117      clat       = tab_cntrl(idecal+16)
     118      grossismx  = tab_cntrl(idecal+17)
     119      grossismy  = tab_cntrl(idecal+18)
     120c
     121      IF ( tab_cntrl(idecal+19).EQ.1. )  THEN
    105122        fxyhypb  = . TRUE .
    106123c        dzoomx   = tab_cntrl(25)
     
    111128        fxyhypb = . FALSE .
    112129        ysinus  = . FALSE .
    113         IF( tab_cntrl(27).EQ.1. ) ysinus = . TRUE.
     130        IF( tab_cntrl(idecal+22).EQ.1. ) ysinus = . TRUE.
    114131      ENDIF
    115132
     
    225242      IF (ierr .NE. NF_NOERR) THEN
    226243         write(lunout,*)"dynetat0: Le champ <temps> est absent"
    227          CALL abort
     244         write(lunout,*)"dynetat0: J essaie <Time>"
     245         ierr = NF_INQ_VARID (nid, "Time", nvarid)
     246         IF (ierr .NE. NF_NOERR) THEN
     247            write(lunout,*)"dynetat0: Le champ <Time> est absent"
     248            CALL abort
     249         ENDIF
    228250      ENDIF
    229251      ierr = nf90_get_var(nid, nvarid, time)
  • trunk/LMDZ.COMMON/libf/dyn3d/fxhyp.F

    r1 r841  
    11!
    2 ! $Id: fxhyp.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id: fxhyp.F 1674 2012-10-29 16:27:03Z emillour $
    33!
    44c
     
    6868       xzoom    = xzoomdeg * pi/180.
    6969c
     70       if (iim==1) then
     71
     72          rlonm025(1)=-pi/2.
     73          rlonv(1)=0.
     74          rlonu(1)=pi
     75          rlonp025(1)=pi/2.
     76          rlonm025(2)=rlonm025(1)+depi
     77          rlonv(2)=rlonv(1)+depi
     78          rlonu(2)=rlonu(1)+depi
     79          rlonp025(2)=rlonp025(1)+depi
     80
     81          xprimm025(:)=1.
     82          xprimv(:)=1.
     83          xprimu(:)=1.
     84          xprimp025(:)=1.
     85          champmin=depi
     86          champmax=depi
     87          return
     88
     89       endif
     90
    7091           decalx   = .75
    7192       IF( grossism.EQ.1..AND.scal180 )  THEN
     
    286307
    287308
     309
    288310       IF(ik.EQ.1.and.grossism.EQ.1.)  THEN
    289311         xvrai(1)    = xvrai(iip1)-depi
    290312         xxprim(1)   = xxprim(iip1)
    291313       ENDIF
     314
    292315       DO i = 1 , iim
    293316        xlon(i)     = xvrai(i)
  • trunk/LMDZ.COMMON/libf/dyn3d/gcm.F

    r815 r841  
    457457! Il faut une cle CPP_PHYS
    458458#ifdef CPP_PHYS
    459          CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys ,
    460      ,                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp     )
     459         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys,
     460     &                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp,
     461     &                iflag_phys)
    461462#endif
    462463         call_iniphys=.false.
     
    490491#endif
    491492
    492 #ifdef CPP_EARTH
    493 ! Create start file (startphy.nc) and boundary conditions (limit.nc)
    494 ! for the Earth verstion
    495        if (iflag_phys>=100) then
    496           call iniaqua(ngridmx,latfi,lonfi,iflag_phys)
    497        endif
    498 #endif
    499 
    500493      if (planet_type.eq."mars") then
    501494! POUR MARS, METTRE UNE FONCTION A PART, genre dynredem0_mars
  • trunk/LMDZ.COMMON/libf/dyn3d/groupe.F

    r1 r841  
    3838      integer i,j,l
    3939
    40       logical firstcall
    41       save firstcall
     40      logical firstcall,groupe_ok
     41      save firstcall,groupe_ok
    4242
    4343      data firstcall/.true./
     44      data groupe_ok/.true./
     45
     46      if (iim==1) then
     47         groupe_ok=.false.
     48      endif
    4449
    4550      if (firstcall) then
    46          if(mod(iim,2**ngroup).ne.0) stop'probleme du nombre ede point'
     51         if (groupe_ok) then
     52           if(mod(iim,2**ngroup).ne.0) stop'probleme du nombre de point'
     53         endif
    4754         firstcall=.false.
    4855      endif
     56
    4957
    5058c   Champs 1D
     
    5260      call convflu(pbaru,pbarv,llm,zconvm)
    5361
    54 c
    5562      call scopy(ijp1llm,zconvm,1,zconvmm,1)
    5663      call scopy(ijmllm,pbarv,1,pbarvm,1)
    5764
    58 c
     65      if (groupe_ok) then
    5966      call groupeun(jjp1,llm,zconvmm)
    6067      call groupeun(jjm,llm,pbarvm)
    6168
    6269c   Champs 3D
    63 
    6470      do l=1,llm
    6571         do j=2,jjm
     
    7480         enddo
    7581      enddo
     82
     83      else
     84         pbarum(:,:,:)=pbaru(:,:,:)
     85         pbarvm(:,:,:)=pbarv(:,:,:)
     86      endif
    7687
    7788c    integration de la convergence de masse de haut  en bas ......
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r776 r841  
    443443           jD_cur = jD_ref + day_ini - day_ref +                        &
    444444     &          itau/day_step
     445
     446           IF (planet_type .eq."generic") THEN
     447              ! AS: we make jD_cur to be pday
     448              jD_cur = int(day_ini + itau/day_step)
     449           ENDIF
     450
    445451           jH_cur = jH_ref + start_time +                               &
    446452     &          mod(itau,day_step)/float(day_step)
     
    471477c-jld
    472478#ifdef CPP_IOIPSL
    473 cIM : pour sortir les param. du modele dans un fis. netcdf 110106
    474          IF (first) THEN
    475 #include "ini_paramLMDZ_dyn.h"
    476           first=.false.
    477          ENDIF
    478 c
    479 #include "write_paramLMDZ_dyn.h"
     479cIM decommenter les 6 lignes suivantes pour sortir quelques parametres dynamiques de LMDZ
     480cIM uncomment next 6 lines to get some parameters for LMDZ dynamics
     481c        IF (first) THEN
     482c         first=.false.
     483c#include "ini_paramLMDZ_dyn.h"
     484c        ENDIF
     485c
     486c#include "write_paramLMDZ_dyn.h"
    480487c
    481488#endif
  • trunk/LMDZ.COMMON/libf/dyn3d/paramet.h

    r1 r841  
    1717      INTEGER jcfil,jcfllm
    1818
    19       PARAMETER( iip1= iim+1-1/iim,iip2=iim+2,iip3=iim+3                &
     19      PARAMETER( iip1= iim+1,iip2=iim+2,iip3=iim+3                       &
    2020     &    ,jjp1=jjm+1-1/jjm)
    2121      PARAMETER( llmp1 = llm+1,  llmp2 = llm+2, llmm1 = llm-1 )
Note: See TracChangeset for help on using the changeset viewer.