Changeset 575 for trunk


Ignore:
Timestamp:
Mar 12, 2012, 2:10:08 PM (13 years ago)
Author:
emillour
Message:

Mars GCM:

correction in nirco2abs: io and ico2 should be declared as integers
Update sponge: remove posibility of specifying 'hsponge', all modes

apply to the last upper "nsponge" layers (default nsponge=3) and
sponge time scale doubles with every level, starting from top.

EM

Location:
trunk/LMDZ.MARS
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r567 r575  
    15641564>> END OF UPDATE ON PARAMETERS FOR THE THERMALS MODEL
    15651565********************************************************
     1566
     1567== 12/03/12 == EM
     1568>> correction in nirco2abs: io and ico2 should be declared as integers
     1569>> Update sponge: remove posibility of specifying 'hsponge', all modes
     1570   apply to the last upper "nsponge" layers (default nsponge=3) and
     1571   sponge time scale doubles with every level, starting from top.
     1572
  • trunk/LMDZ.MARS/deftank/run.def.32x24x25

    r38 r575  
    103103  mode_sponge= 2
    104104
    105 # Sponge:  hauteur de sponge (km)
    106   hsponge= 90
    107 
    108105# Sponge:  tetasponge (secondes)
    109   tetasponge = 50000
     106  tetasponge = 30000
    110107
    111108# some definitions for the physics, in file 'callphys.def'
  • trunk/LMDZ.MARS/deftank/run.def.32x24x32

    r38 r575  
    103103  mode_sponge= 2
    104104
    105 # Sponge:  hauteur de sponge (km)
    106   hsponge= 130
    107 
    108105# Sponge:  tetasponge (secondes)
    109   tetasponge = 50000
     106  tetasponge = 30000
    110107
    111108# some definitions for the physics, in file 'callphys.def'
  • trunk/LMDZ.MARS/deftank/run.def.64x48x25

    r38 r575  
    103103  mode_sponge= 2
    104104
    105 # Sponge:  hauteur de sponge (km)
    106   hsponge= 90
    107 
    108105# Sponge:  tetasponge (secondes)
    109   tetasponge = 50000
     106  tetasponge = 30000
    110107
    111108# some definitions for the physics, in file 'callphys.def'
  • trunk/LMDZ.MARS/deftank/run.def.64x48x32

    r38 r575  
    103103  mode_sponge= 2
    104104
    105 # Sponge:  hauteur de sponge (km)
    106   hsponge= 130
    107 
    108105# Sponge:  tetasponge (secondes)
    109   tetasponge = 50000
     106  tetasponge = 30000
    110107
    111108# some definitions for the physics, in file 'callphys.def'
  • trunk/LMDZ.MARS/deftank/run.def.64x48x50

    r38 r575  
    103103  mode_sponge= 2
    104104
    105 # Sponge:  hauteur de sponge (km)
    106   hsponge= 230
    107 
    108105# Sponge:  tetasponge (secondes)
    109106  tetasponge = 30000
  • trunk/LMDZ.MARS/libf/dyn3d/defrun_new.F

    r38 r575  
    457457
    458458        WRITE(tapeout,*) ""
    459         WRITE(tapeout,*) "Sponge:  mode0(u=v=0), mode1(u=umoy,v=0), ",
    460      & "mode2(u=umoy,v=vmoy)"
     459        WRITE(tapeout,*) "Sponge: number of layers over which",
     460     &                    " sponge extends"
     461        nsponge=3 ! default value
     462        call getin("nsponge",nsponge)
     463        WRITE(tapeout,*)" nsponge = ",nsponge
     464
     465        WRITE(tapeout,*)""
     466        WRITE(tapeout,*)"Sponge mode: (forcing is towards ..."
     467        WRITE(tapeout,*)"  over upper nsponge layers)"
     468        WRITE(tapeout,*)"  0: (h=hmean,u=v=0)"
     469        WRITE(tapeout,*)"  1: (h=hmean,u=umean,v=0)"
     470        WRITE(tapeout,*)"  2: (h=hmean,u=umean,v=vmean)"
    461471        mode_sponge=2 ! default value
    462472        call getin("mode_sponge",mode_sponge)
     
    464474
    465475        WRITE(tapeout,*) ""
    466         WRITE(tapeout,*) "Sponge:  hauteur de sponge (km)"
    467         hsponge=90.0 ! default value
    468         call getin("hsponge",hsponge)
    469         WRITE(tapeout,*)" hsponge = ",hsponge
    470 
    471         WRITE(tapeout,*) ""
    472         WRITE(tapeout,*) "Sponge:  tetasponge (secondes)"
    473         tetasponge=50000.0
     476        WRITE(tapeout,*) "Sponge: characteristice time scale tetasponge"
     477        WRITE(tapeout,*) "(seconds) at topmost layer (time scale then "
     478        WRITE(tapeout,*) " doubles with decreasing layer index)."
     479        tetasponge=30000.0
    474480        call getin("tetasponge",tetasponge)
    475481        WRITE(tapeout,*)" tetasponge = ",tetasponge
  • trunk/LMDZ.MARS/libf/dyn3d/sponge.F

    r38 r575  
    11      subroutine sponge(ucov,vcov,h,pext,dt,mode)
     2
     3! Sponge routine: Quench ucov, vcov and potential temperature near the
     4!                 top of the model
     5! Depending on 'mode' relaxation of variables is towards:
     6! mode = 0 : h -> h_mean , ucov -> 0 , vcov -> 0
     7! mode = 1 : h -> h_mean , ucov -> ucov_mean , vcov -> 0
     8! mode >= 2 : h -> h_mean , ucov -> ucov_mean , vcov -> vcov_mean
     9! Number of layer over which sponge is applied is 'nsponge' (read from def file)
     10! Time scale for quenching at top level is given by 'tetasponge' (read from
     11! def file) and doubles as level indexes decrease.
     12
    213      implicit none
    314#include "dimensions.h"
     
    718#include "comgeom2.h"
    819#include "sponge.h"
    9       real ucov(iip1,jjp1,llm),vcov(iip1,jjm,llm)
    10       real h(iip1,jjp1,llm),pext(iip1,jjp1)
    11       real dt
    12       real sig_s(llm) !sigma au milieu des couches
    13       save sig_s
     20
     21! Arguments:
     22!------------
     23      real,intent(inout) :: ucov(iip1,jjp1,llm) ! covariant zonal wind
     24      real,intent(inout) :: vcov(iip1,jjm,llm) ! covariant meridional wind
     25      real,intent(inout) :: h(iip1,jjp1,llm) ! potential temperature
     26      real,intent(in) :: pext(iip1,jjp1) ! extensive pressure
     27      real,intent(in) :: dt   ! time step
     28      integer,intent(in) :: mode  ! sponge mode
    1429
    1530c   Local:
    1631c   ------
    1732
     33      real,save :: sig_s(llm) !sigma au milieu des couches
    1834      REAL vm,um,hm,ptot(jjp1)
    19       real cst(llm)
    20       integer mode
     35      real,save :: cst(llm)
    2136
    22       INTEGER l,i,j,l0
     37      INTEGER l,i,j
     38      integer,save :: l0 ! layer down to which sponge is applied
    2339
    2440      real ssum
    2541
    2642      real echelle,zkm
    27       logical firstcall
    28       save firstcall,cst,l0
    29       data firstcall/.true./
     43      logical,save :: firstcall=.true.
     44
     45
    3046
    3147      if (firstcall) then
    32        do l=1,llm
     48
     49       ! build approximative sigma levels at midlayer
     50        do l=1,llm
    3351          sig_s(l)=((ap(l)+ap(l+1))/preff+bp(l)+bp(l+1))/2.
    34        enddo
     52        enddo
    3553
    36        IF (mode.eq.3) then
    37          l0=llm-2
    38          echelle=10.
     54        l0=llm-nsponge+1
    3955 
    40          PRINT*
    41          print*,'sponge mode',mode
    42          print*,'hsponge',hsponge
    43          print*,'tetasponge n intervient pas'
    44          print*,'Constantes de dissipations fixees comme les anglais'
    45          print*,'Coeffs pour la couche en eponge'
    46          print*,'Z (km)  tau'
    47          cst(llm)=dt/(0.5*88775)
    48          cst(llm-1)=dt/(88775)
    49          cst(l0)=dt/(2*88775)
    50          do l=l0,llm
    51             zkm=-echelle*log(sig_s(l))
    52             print*,zkm,dt/cst(l),cst(l)
    53          enddo
    54          firstcall=.false.
    55          PRINT*
    56        ELSE
    57          l0=1
    58          echelle=10.
    59  
    60          PRINT*
    61          print*,'sponge mode',mode
    62          print*,'hsponge tetasponge ',hsponge,tetasponge
    63          print*,'Coeffs pour la couche en eponge'
    64          print*,'Z (km)  tau'
    65          do l=1,llm
    66             zkm=-echelle*log(sig_s(l))
    67             cst(l)=.5*(1.+tanh((zkm-hsponge)/echelle))
    68             cst(l)= max(tetasponge*1.e-15,cst(l))
    69             print*,zkm,1./cst(l)*tetasponge,cst(l)*dt/tetasponge
    70             cst(l)=cst(l)*dt/tetasponge
    71          enddo
    72          firstcall=.false.
    73          PRINT*
    74        ENDIF
    75       endif
     56        PRINT*
     57        print*,'sponge mode',mode
     58        print*,'nsponge tetasponge ',nsponge,tetasponge
     59        print*,'Coeffs for the sponge layer'
     60        print*,'Z (km)     tau      cst'
     61        do l=llm,l0,-1
     62          ! double time scale with every level, starting from the top
     63          cst(l)=dt/(tetasponge*2**(llm-l))
     64        enddo
     65
     66        echelle=10.
     67        do l=l0,llm
     68           zkm=-echelle*log(sig_s(l))
     69           print*,zkm,dt/cst(l),cst(l)
     70        enddo
     71        PRINT*
     72
     73        firstcall=.false.
     74      endif ! of if (firstcall)
    7675
    7776c-----------------------------------------------------------------------
     
    8382      enddo
    8483 
    85 c   temperature potentielle
     84c   potential temperature
    8685      do l=l0,llm
    8786         do j=1,jjp1
     
    9897      enddo
    9998
    100 c   vent zonal
     99c   zonal wind
    101100      do l=l0,llm
    102101         do j=2,jjm
     
    116115      enddo
    117116
    118 vent meridien
     117meridional wind
    119118      do l=l0,llm
    120119         do j=1,jjm
     
    134133      enddo
    135134
    136       RETURN
    137135      end
  • trunk/LMDZ.MARS/libf/dyn3d/sponge.h

    r38 r575  
    22c INCLUDE 'sponge.h'
    33
    4       COMMON/com_sponge/callsponge,mode_sponge,hsponge,tetasponge
     4      COMMON/com_sponge_l/callsponge
     5      common/com_sponge_i/mode_sponge,nsponge
     6      common/com_sponge_r/tetasponge
    57
    6       LOGICAL   callsponge
    7       INTEGER   mode_sponge
    8       REAL   hsponge,tetasponge
     8      LOGICAL   callsponge  ! do we use a sponge on upper layers
     9      INTEGER   mode_sponge ! sponge mode
     10      INTEGER nsponge ! number of sponge layers
     11      REAL  tetasponge  ! sponge time scale (s) at topmost layer
    912c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/nirco2abs.F

    r552 r575  
    8080c   ---------------------
    8181      logical,save :: firstcall=.true.
    82       real,save :: ico2=0 ! index of "co2" tracer
    83       real,save :: io=0 ! index of "o" tracer
     82      integer,save :: ico2=0 ! index of "co2" tracer
     83      integer,save :: io=0 ! index of "o" tracer
    8484c     p0noonlte is a pressure below which non LTE effects are significant.
    8585c     REAL p0nonlte
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r566 r575  
    15211521           call wstats(ngrid,"ps","Surface pressure","Pa",2,ps)
    15221522           call wstats(ngrid,"tsurf","Surface temperature","K",2,tsurf)
    1523 c           call wstats(ngrid,"co2ice","CO2 ice cover",
    1524 c     &                "kg.m-2",2,co2ice)
    1525 c           call wstats(ngrid,"fluxsurf_lw",
    1526 c     &                "Thermal IR radiative flux to surface","W.m-2",2,
    1527 c     &                fluxsurf_lw)
    1528 c           call wstats(ngrid,"fluxsurf_sw",
    1529 c     &                "Solar radiative flux to surface","W.m-2",2,
    1530 c     &                fluxsurf_sw_tot)
    1531 c           call wstats(ngrid,"fluxtop_lw",
    1532 c     &                "Thermal IR radiative flux to space","W.m-2",2,
    1533 c     &                fluxtop_lw)
    1534 c           call wstats(ngrid,"fluxtop_sw",
    1535 c     &                "Solar radiative flux to space","W.m-2",2,
    1536 c     &                fluxtop_sw_tot)
    1537 c           call wstats(ngrid,"temp","Atmospheric temperature","K",3,zt)
    1538 c           call wstats(ngrid,"u","Zonal (East-West) wind","m.s-1",3,zu)
    1539 c           call wstats(ngrid,"v","Meridional (North-South) wind",
    1540 c     &                "m.s-1",3,zv)
     1523           call wstats(ngrid,"co2ice","CO2 ice cover",
     1524     &                "kg.m-2",2,co2ice)
     1525           call wstats(ngrid,"fluxsurf_lw",
     1526     &                "Thermal IR radiative flux to surface","W.m-2",2,
     1527     &                fluxsurf_lw)
     1528           call wstats(ngrid,"fluxsurf_sw",
     1529     &                "Solar radiative flux to surface","W.m-2",2,
     1530     &                fluxsurf_sw_tot)
     1531           call wstats(ngrid,"fluxtop_lw",
     1532     &                "Thermal IR radiative flux to space","W.m-2",2,
     1533     &                fluxtop_lw)
     1534           call wstats(ngrid,"fluxtop_sw",
     1535     &                "Solar radiative flux to space","W.m-2",2,
     1536     &                fluxtop_sw_tot)
     1537           call wstats(ngrid,"temp","Atmospheric temperature","K",3,zt)
     1538           call wstats(ngrid,"u","Zonal (East-West) wind","m.s-1",3,zu)
     1539           call wstats(ngrid,"v","Meridional (North-South) wind",
     1540     &                "m.s-1",3,zv)
    15411541c           call wstats(ngrid,"w","Vertical (down-up) wind",
    15421542c     &                "m.s-1",3,pw)
    1543 c           call wstats(ngrid,"rho","Atmospheric density","none",3,rho)
     1543           call wstats(ngrid,"rho","Atmospheric density","kg/m3",3,rho)
    15441544c           call wstats(ngrid,"pressure","Pressure","Pa",3,pplay)
    15451545c          call wstats(ngrid,"q2",
Note: See TracChangeset for help on using the changeset viewer.