Ignore:
Timestamp:
Oct 7, 2013, 6:42:03 PM (11 years ago)
Author:
slebonnois
Message:

SL: Titan runs ! see DOC/chantiers/commit_importants.log

Location:
trunk/LMDZ.COMMON/libf/dyn3d
Files:
1 added
4 edited

Legend:

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

    r1017 r1056  
    3131      USE infotrac
    3232      USE control_mod
     33      USE write_field
    3334      USE cpdet_mod, only: t2tpot,tpot2t
     35 
     36! used only for zonal averages
     37      USE moyzon_mod
    3438
    3539      IMPLICIT NONE
     
    9094#include "paramet.h"
    9195#include "temps.h"
     96#include "logic.h"
    9297
    9398      INTEGER ngridmx
     
    111116      REAL pphis(iip1,jjp1)
    112117      REAL pphi(iip1,jjp1,llm)
    113 c
     118
    114119      REAL pdvcov(iip1,jjm,llm)
    115120      REAL pducov(iip1,jjp1,llm)
     
    119124! ecrite, et que j'ai donc commente....
    120125      REAL pdq(iip1,jjp1,llm,nqtot)
    121 c
     126
    122127      REAL pps(iip1,jjp1)
    123128      REAL pp(iip1,jjp1,llmp1)
    124129      REAL ppk(iip1,jjp1,llm)
    125 c
     130
    126131c TENDENCIES in */s
    127132      REAL pdvfi(iip1,jjm,llm)
     
    139144      REAL zplev(ngridmx,llm+1),zplay(ngridmx,llm)
    140145      REAL zphi(ngridmx,llm),zphis(ngridmx)
    141 c
     146
    142147      REAL zufi(ngridmx,llm), zvfi(ngridmx,llm)
    143148      REAL ztfi(ngridmx,llm),zqfi(ngridmx,llm,nqtot)
     
    145150      REAL zteta(ngridmx,llm)
    146151      REAL zpk(ngridmx,llm)
    147 c
     152
    148153! RQ SL 13/10/10:
    149154! Ces calculs ne servent pas.
     
    151156!      REAL pcvgu(ngridmx,llm), pcvgv(ngridmx,llm)
    152157!      REAL pcvgt(ngridmx,llm), pcvgq(ngridmx,llm,2)
    153 c
     158
    154159      REAL zdufi(ngridmx,llm),zdvfi(ngridmx,llm)
    155160      REAL zdtfi(ngridmx,llm),zdqfi(ngridmx,llm,nqtot)
    156161      REAL zdpsrf(ngridmx)
    157 c
     162
    158163      REAL zdufic(ngridmx,llm),zdvfic(ngridmx,llm)
    159164      REAL zdtfic(ngridmx,llm),zdqfic(ngridmx,llm,nqtot)
     
    165170      REAL zsinbis(iim),zcosbis(iim),z1bis(iim)
    166171      REAL unskap, pksurcp
    167 c
     172      save unskap
     173
    168174cIM diagnostique PVteta, Amip2
    169175      INTEGER ntetaSTD
     
    172178      DATA rtetaSTD/350., 380., 405./ ! Earth-specific values, beware !!
    173179      REAL PVteta(ngridmx,ntetaSTD)
    174 c
     180
    175181      REAL flxw(iip1,jjp1,llm)  ! Flux de masse verticale sur la grille dynamique
    176182      REAL flxwfi(ngridmx,llm)  ! Flux de masse verticale sur la grille physiq
    177 c
    178183     
    179184      REAL SSUM
     
    186191
    187192      LOGICAL tracerdyn ! for generic/mars physics call ; possibly to get rid of
    188 c
     193
     194! For Titan only right now:
     195! to allow for 2D computation of microphys and chemistry
     196      LOGICAL,save :: flag_moyzon
     197      REAL,dimension(iip1,llm) :: tmpvar
     198      REAL,dimension(iip1,llmp1) :: tmpvarp1
     199      REAL,dimension(llm) :: tmpvarbar
     200      REAL,dimension(llmp1) :: tmpvarbarp1
     201
    189202c-----------------------------------------------------------------------
    190 c
     203
    191204c    1. Initialisations :
    192205c    --------------------
    193 c
    194 c
     206
     207
    195208      IF ( firstcal )  THEN
    196209        debut = .TRUE.
     
    203216         STOP
    204217        ENDIF
     218
     219        unskap   = 1./ kappa
     220
     221        flag_moyzon = .false.
     222        if(moyzon_ch.or.moyzon_mu) then
     223         flag_moyzon = .true.
     224        endif
     225        if (flag_moyzon) call moyzon_init
     226
     227c----------------------------------------------
     228c moyennes globales pour le profil de pression
     229        ALLOCATE(plevmoy(llm+1))
     230        ALLOCATE(playmoy(llm))
     231        ALLOCATE(tmoy(llm))
     232        ALLOCATE(tetamoy(llm))
     233        ALLOCATE(pkmoy(llm))
     234        plevmoy=0.
     235        do l=1,llmp1
     236         do i=1,iip1
     237          do j=1,jjp1
     238            plevmoy(l)=plevmoy(l)+pp(i,j,l)/(iip1*jjp1)
     239          enddo
     240         enddo
     241        enddo
     242        tetamoy=0.
     243        pkmoy=0.
     244        do l=1,llm
     245         do i=1,iip1
     246          do j=1,jjp1
     247            tetamoy(l)=tetamoy(l)+pteta(i,j,l)/(iip1*jjp1)
     248            pkmoy(l)=pkmoy(l)+ppk(i,j,l)/(iip1*jjp1)
     249          enddo
     250         enddo
     251        enddo
     252        playmoy = preff * (pkmoy/cpp) ** unskap
     253        call tpot2t(llm,tetamoy,tmoy,pkmoy)
     254c----------------------------------------------
     255c + lat index
     256      allocate(klat(ngridmx))
     257      klat=0
     258      klat(1)  = 1
     259      ig0  = 2
     260      DO j = 2,jjm
     261         do i=0,iim-1
     262          klat(ig0+i) = j
     263         enddo
     264         ig0 = ig0+iim
     265      ENDDO
     266      klat(ngridmx)  = jjp1
     267c----------------------------------------------
    205268      ELSE
    206269        debut = .FALSE.
    207270      ENDIF ! of IF (firstcal)
    208271
    209 c
    210 c
     272
    211273c-----------------------------------------------------------------------
    212274c   40. transformation des variables dynamiques en variables physiques:
     
    215277c   41. pressions au sol (en Pascals)
    216278c   ----------------------------------
    217 
    218279       
    219280      zpsrf(1) = pps(1,1)
     
    227288      zpsrf(ngridmx) = pps(1,jjp1)
    228289
    229 
    230290c   42. pression intercouches et fonction d'Exner:
    231 c
     291
    232292c   -----------------------------------------------------------------
    233293c     .... zplev  definis aux (llm +1) interfaces des couches  ....
     
    236296
    237297c    ...    Exner = cp * ( p(l) / preff ) ** kappa     ....
    238 c
    239        unskap   = 1./ kappa
    240 c
     298
    241299! ADAPTATION GCM POUR CP(T)
    242300      DO l = 1, llm
     
    266324          ENDDO
    267325        zplev( ngridmx,llmp1 ) = pp(1,jjp1,llmp1)
    268 c
    269 c
     326
     327      if (flag_moyzon) then
     328        tmpvarp1(:,:) = pp(:,1,:)
     329        call moyzon(llmp1,tmpvarp1,tmpvarbarp1)
     330        zplevbar(1,:) = tmpvarbarp1
     331        tmpvar(:,:) = ppk(:,1,:)
     332        call moyzon(llm,tmpvar,tmpvarbar)
     333        zpkbar(1,:) = tmpvarbar
     334        tmpvar(:,:) = pteta(:,1,:)
     335        call moyzon(llm,tmpvar,tmpvarbar)
     336        ztetabar(1,:) = tmpvarbar
     337        call tpot2t(llm,ztetabar(1,:),ztfibar(1,:),zpkbar(1,:))
     338        ig0 = 2
     339         do j = 2, jjm
     340          tmpvarp1(:,:) = pp(:,j,:)
     341          call moyzon(llmp1,tmpvarp1,tmpvarbarp1)
     342          zplevbar(ig0,:) = tmpvarbarp1
     343          tmpvar(:,:) = ppk(:,j,:)
     344          call moyzon(llm,tmpvar,tmpvarbar)
     345          zpkbar(ig0,:) = tmpvarbar
     346          tmpvar(:,:) = pteta(:,j,:)
     347          call moyzon(llm,tmpvar,tmpvarbar)
     348          ztetabar(ig0,:) = tmpvarbar
     349          call tpot2t(llm,ztetabar(ig0,:),ztfibar(ig0,:),zpkbar(ig0,:))
     350          ig0 = ig0+1
     351          do i=2,iim
     352            zplevbar(ig0,:) = zplevbar(ig0-1,:)
     353            zpkbar(ig0,:)   = zpkbar(ig0-1,:)
     354            ztetabar(ig0,:) = ztetabar(ig0-1,:)
     355            ztfibar(ig0,:)  = ztfibar(ig0-1,:)
     356            ig0 = ig0+1
     357          enddo
     358         enddo
     359        tmpvarp1(:,:) = pp(:,jjp1,:)
     360        call moyzon(llmp1,tmpvarp1,tmpvarbarp1)
     361        zplevbar(ngridmx,:) = tmpvarbarp1
     362        tmpvar(:,:) = ppk(:,jjp1,:)
     363        call moyzon(llm,tmpvar,tmpvarbar)
     364        zpkbar(ngridmx,:) = tmpvarbar
     365        tmpvar(:,:) = pteta(:,jjp1,:)
     366        call moyzon(llm,tmpvar,tmpvarbar)
     367        ztetabar(ngridmx,:) = tmpvarbar
     368        call tpot2t(llm,ztetabar(ngridmx,:),
     369     .                  ztfibar(ngridmx,:),zpkbar(ngridmx,:))
     370      endif
    270371
    271372c   43. temperature naturelle (en K) et pressions milieux couches .
     
    297398      ENDDO
    298399
     400      if (flag_moyzon) then
     401        zplaybar(:,:) = preff * (zpkbar(:,:)/cpp)**unskap
     402      endif
     403
    299404c   43.bis traceurs (tous intensifs)
    300405c   ---------------
    301 c
     406
    302407      DO iq=1,nqtot
    303           iiq=niadv(iq)
    304408         DO l=1,llm
    305             zqfi(1,l,iq) = pq(1,1,l,iiq)
     409            zqfi(1,l,iq) = pq(1,1,l,iq)
    306410            ig0          = 2
    307411            DO j=2,jjm
    308412               DO i = 1, iim
    309                   zqfi(ig0,l,iq)  = pq(i,j,l,iiq)
     413                  zqfi(ig0,l,iq)  = pq(i,j,l,iq)
    310414                  ig0             = ig0 + 1
    311415               ENDDO
    312416            ENDDO
    313             zqfi(ig0,l,iq) = pq(1,jjp1,l,iiq)
     417            zqfi(ig0,l,iq) = pq(1,jjp1,l,iq)
    314418         ENDDO
    315419      ENDDO  ! boucle sur traceurs
     420
     421      if (flag_moyzon) then
     422       DO iq=1,nqtot
     423! RQ: REVOIR A QUOI CA SERT... ET VERIFIER...
     424!       iiq=niadv(iq)
     425! en fait, iiq=iq...
     426! FIN RQ
     427        tmpvar(:,:) = pq(:,1,:,iq)
     428        call moyzon(llm,tmpvar,tmpvarbar)
     429        zqfibar(1,:,iq) = tmpvarbar
     430        ig0 = 2
     431         do j = 2, jjm
     432          tmpvar(:,:) = pq(:,j,:,iq)
     433          call moyzon(llm,tmpvar,tmpvarbar)
     434          zqfibar(ig0,:,iq) = tmpvarbar
     435          ig0 = ig0+1
     436          do i=2,iim
     437            zqfibar(ig0,:,iq) = zqfibar(ig0-1,:,iq)
     438            ig0 = ig0+1
     439          enddo
     440         enddo
     441        tmpvar(:,:) = pq(:,jjp1,:,iq)
     442        call moyzon(llm,tmpvar,tmpvarbar)
     443        zqfibar(ngridmx,:,iq) = tmpvarbar
     444       ENDDO ! of DO iq=1,nqtot
     445      endif
     446
     447! DEBUG
     448!     do ig0=1,ngridmx
     449!       write(*,'(6(e13.5,1x))') zqfibar(ig0,1,10),zqfi(ig0,1,10),
     450!    .                         zqfibar(ig0,llm/2,10),zqfi(ig0,llm/2,10),
     451!    .                           zqfibar(ig0,llm,10),zqfi(ig0,llm,10)
     452!     enddo
     453!     stop
    316454
    317455!-----------------
     
    349487         ENDDO
    350488      ENDDO
     489
     490      if (flag_moyzon) then
     491        tmpvar(:,1) = pphis(:,1)
     492        call moyzon(1,tmpvar(:,1),tmpvarbar(1))
     493        zphisbar(1) = tmpvarbar(1)
     494        tmpvar(:,:) = pphi(:,1,:)
     495        call moyzon(llm,tmpvar,tmpvarbar)
     496        zphibar(1,:) = tmpvarbar
     497        ig0 = 2
     498         do j = 2, jjm
     499          tmpvar(:,1) = pphis(:,j)
     500          call moyzon(1,tmpvar(:,1),tmpvarbar(1))
     501          zphisbar(ig0) = tmpvarbar(1)
     502          tmpvar(:,:) = pphi(:,j,:)
     503          call moyzon(llm,tmpvar,tmpvarbar)
     504          zphibar(ig0,:) = tmpvarbar
     505          ig0 = ig0+1
     506          do i=2,iim
     507            zphisbar(ig0)  = zphisbar(ig0-1)
     508            zphibar(ig0,:) = zphibar(ig0-1,:)
     509            ig0 = ig0+1
     510          enddo
     511         enddo
     512        tmpvar(:,1) = pphis(:,jjp1)
     513        call moyzon(1,tmpvar(:,1),tmpvarbar(1))
     514        zphisbar(ngridmx) = tmpvarbar(1)
     515        tmpvar(:,:) = pphi(:,jjp1,:)
     516        call moyzon(llm,tmpvar,tmpvarbar)
     517        zphibar(ngridmx,:) = tmpvarbar
     518      endif
    351519
    352520c   ....  Calcul de la vitesse  verticale  ( en Pa*m*s  ou Kg/s )  ....
     
    594762      enddo ! of do isplit=1,nsplit_phys
    595763
     764! ATTENTION...
     765      if (flag_moyzon.and.(nsplit_phys.ne.1)) then
     766       print*,"WARNING ! flag_moyzon + nsplit_phys"
     767       print*,"zqfibar n'est pas implemente au cours des iterations"
     768       print*,"Donc a revoir..."
     769       stop
     770      endif
     771
    596772#endif
    597773! #endif of #ifdef CPP_PHYS
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F

    r1024 r1056  
    587587      grilles_gcm_netcdf = .FALSE.
    588588      CALL getin('grilles_gcm_netcdf',grilles_gcm_netcdf)
     589
     590c----------------------------------------
     591c Parameters for zonal averages in the case of Titan
     592      moyzon_mu = .false.
     593      moyzon_ch = .false.
     594      if (planet_type=="titan") then
     595       CALL getin('moyzon_mu', moyzon_mu)
     596       CALL getin('moyzon_ch', moyzon_ch)
     597      endif
     598c----------------------------------------
    589599
    590600c----------------------------------------
     
    948958      write(lunout,*)' ok_etat0 = ', ok_etat0
    949959      write(lunout,*)' grilles_gcm_netcdf = ', grilles_gcm_netcdf
    950 c
     960      if (planet_type=="titan") then
     961       write(lunout,*)' moyzon_mu = ', moyzon_mu
     962       write(lunout,*)' moyzon_ch = ', moyzon_ch
     963      endif
     964
    951965      RETURN
    952966      END
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r1024 r1056  
    529529! #endif of #ifdef CPP_IOIPSL
    530530
     531c          call WriteField('pfi',reshape(p,(/iip1,jmp1,llmp1/)))
     532
    531533         CALL calfis( lafin , jD_cur, jH_cur,
    532534     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
     
    534536     $               flxw,
    535537     $               dufi,dvfi,dtetafi,dqfi,dpfi  )
     538
     539c          call WriteField('dufi',reshape(dufi,(/iip1,jmp1,llm/)))
     540c          call WriteField('dvfi',reshape(dvfi,(/iip1,jjm,llm/)))
     541c          call WriteField('dtetafi',reshape(dtetafi,(/iip1,jmp1,llm/)))
    536542
    537543c      ajout des tendances physiques:
  • trunk/LMDZ.COMMON/libf/dyn3d/logic.h

    r495 r1056  
    1111     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
    1212     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
    13      &  ,ok_limit,ok_etat0,grilles_gcm_netcdf,hybrid
     13     &  ,ok_limit,ok_etat0,grilles_gcm_netcdf,hybrid                    &
     14     &  ,moyzon_mu,moyzon_ch
    1415
    1516      COMMON/logici/ iflag_phys,iflag_trac
     
    2122      logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
    2223                     ! (only used if disvert_type==2)
     24      logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
    2325
    2426      integer iflag_phys,iflag_trac
Note: See TracChangeset for help on using the changeset viewer.