Ignore:
Timestamp:
Jan 11, 2013, 10:19:19 AM (11 years ago)
Author:
Laurent Fairhead
Message:

Version testing basée sur la r1706


Testing release based on r1706

Location:
LMDZ5/branches/testing
Files:
3 deleted
11 edited
1 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3d/calfis.F

    r1669 r1707  
    507507     .             debut_split,    !! firstcall
    508508     .             lafin_split,    !! lastcall
    509      .             float(day_ini), !! pday <-- day_ini (dans temps.h)
     509     .             jD_cur,         !! pday. see leapfrog
    510510     .             jH_cur_split,   !! ptime "fraction of day"
    511511     .             zdt_split,      !! ptimestep
  • LMDZ5/branches/testing/libf/dyn3d/comconst.h

    r1505 r1707  
    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
    24       REAL cpp   ! Cp
     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)
     25      REAL cpp   ! Specific heat Cp (J.kg-1.K-1)
    2526      REAL kappa ! kappa=R/Cp
    2627      REAL cotot
  • LMDZ5/branches/testing/libf/dyn3d/comdissnew.h

    r1319 r1707  
    1212
    1313      COMMON/comdissnew/ lstardis,nitergdiv,nitergrot,niterh,tetagdiv,  &
    14      &                   tetagrot,tetatemp,coefdis 
     14     &                   tetagrot,tetatemp,coefdis, vert_prof_dissip
    1515
    1616      LOGICAL lstardis
    1717      INTEGER nitergdiv, nitergrot, niterh
     18
     19      integer vert_prof_dissip ! vertical profile of horizontal dissipation
     20!     Allowed values:
     21!     0: rational fraction, function of pressure
     22!     1: tanh of altitude
     23
    1824      REAL     tetagdiv, tetagrot,  tetatemp, coefdis
    1925
  • LMDZ5/branches/testing/libf/dyn3d/conf_gcm.F

    r1665 r1707  
    1414#endif
    1515      USE infotrac, ONLY : type_trac
     16      use assert_m, only: assert
     17
    1618      IMPLICIT NONE
    1719c-----------------------------------------------------------------------
     
    9395      CALL getin('lunout', lunout)
    9496      IF (lunout /= 5 .and. lunout /= 6) THEN
    95         OPEN(lunout,FILE='lmdz.out')
     97        OPEN(UNIT=lunout,FILE='lmdz.out',ACTION='write',
     98     &          STATUS='unknown',FORM='formatted')
    9699      ENDIF
    97100
     
    173176
    174177!Config  Key  = nsplit_phys
    175 !Config  Desc = nombre de pas par jour
    176 !Config  Def  = 1
    177 !Config  Help = nombre de pas par jour (multiple de iperiod) (
    178 !Config          ici pour  dt = 1 min )
    179178       nsplit_phys = 1
    180179       CALL getin('nsplit_phys',nsplit_phys)
     
    625624      CALL getin('ok_dyn_ave',ok_dyn_ave)
    626625
    627 
    628626      write(lunout,*)' #########################################'
    629627      write(lunout,*)' Configuration des parametres du gcm: '
     
    635633      write(lunout,*)' day_step = ', day_step
    636634      write(lunout,*)' iperiod = ', iperiod
     635      write(lunout,*)' nsplit_phys = ', nsplit_phys
    637636      write(lunout,*)' iconser = ', iconser
    638637      write(lunout,*)' iecri = ', iecri
     
    805804!Config  Desc = sortie des transports zonaux dans la dynamique
    806805!Config  Def  = n
    807 !Config  Help =
     806!Config  Help = Permet de mettre en route le calcul des transports
    808807!Config         
    809        ok_dynzon = .FALSE.
    810        CALL getin('ok_dynzon',ok_dynzon)
     808      ok_dynzon = .FALSE.
     809      CALL getin('ok_dynzon',ok_dynzon)
    811810
    812811!Config  Key  = ok_dyn_ins
     
    838837        write(lunout,*)'STOP !!!'
    839838        write(lunout,*)'use_filtre_fft n est pas implemente dans dyn3d'
    840         STOP
     839        STOP 1
    841840      ENDIF
    842841     
     
    848847      ok_strato=.FALSE.
    849848      CALL getin('ok_strato',ok_strato)
     849
     850      vert_prof_dissip = merge(1, 0, ok_strato .and. llm==39)
     851      CALL getin('vert_prof_dissip', vert_prof_dissip)
     852      call assert(vert_prof_dissip == 0 .or. vert_prof_dissip ==  1,
     853     $     "bad value for vert_prof_dissip")
    850854
    851855!Config  Key  = ok_gradsfile
  • LMDZ5/branches/testing/libf/dyn3d/fxhyp.F

    r1403 r1707  
    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)
  • LMDZ5/branches/testing/libf/dyn3d/gcm.F

    r1665 r1707  
    405405
    406406      CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
    407      *                tetagdiv, tetagrot , tetatemp              )
     407     *                tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
    408408
    409409c-----------------------------------------------------------------------
     
    433433! Physics:
    434434#ifdef CPP_PHYS
    435          CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys ,
    436      ,                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp     )
     435         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys,
     436     &                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp,
     437     &                iflag_phys)
    437438#endif
    438439         call_iniphys=.false.
     
    457458 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    458459 302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    459 #endif
    460 
    461 #ifdef CPP_PHYS
    462 ! Create start file (startphy.nc) and boundary conditions (limit.nc)
    463 ! for the Earth verstion
    464        if (iflag_phys>=100) then
    465           call iniaqua(ngridmx,latfi,lonfi,iflag_phys)
    466        endif
    467460#endif
    468461
  • LMDZ5/branches/testing/libf/dyn3d/groupe.F

    r524 r1707  
    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 ......
  • LMDZ5/branches/testing/libf/dyn3d/inidissip.F90

    r1665 r1707  
    33!
    44SUBROUTINE inidissip ( lstardis,nitergdiv,nitergrot,niterh  , &
    5      tetagdiv,tetagrot,tetatemp             )
     5     tetagdiv,tetagrot,tetatemp, vert_prof_dissip)
    66  !=======================================================================
    77  !   initialisation de la dissipation horizontale
     
    2525  INTEGER,INTENT(in) :: nitergdiv,nitergrot,niterh
    2626  REAL,INTENT(in) :: tetagdiv,tetagrot,tetatemp
     27
     28  integer, INTENT(in):: vert_prof_dissip
     29  ! Vertical profile of horizontal dissipation
     30  ! Allowed values:
     31  ! 0: rational fraction, function of pressure
     32  ! 1: tanh of altitude
    2733
    2834! Local variables:
     
    167173  !   --------------------------------------------------
    168174
    169   if (ok_strato .and. llm==39) then
     175  if (vert_prof_dissip == 1) then
    170176     do l=1,llm
    171177        pseudoz=8.*log(preff/presnivs(l))
  • LMDZ5/branches/testing/libf/dyn3d/leapfrog.F

    r1669 r1707  
    383383           jD_cur = jD_ref + day_ini - day_ref +                        &
    384384     &          itau/day_step
     385
     386           IF (planet_type .eq."generic") THEN
     387              ! AS: we make jD_cur to be pday
     388              jD_cur = int(day_ini + itau/day_step)
     389           ENDIF
     390
    385391           jH_cur = jH_ref + start_time +                               &
    386392     &              mod(itau,day_step)/float(day_step)
  • LMDZ5/branches/testing/libf/dyn3d/paramet.h

    r792 r1707  
    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.