Ignore:
Timestamp:
Dec 10, 2009, 10:02:56 AM (15 years ago)
Author:
Laurent Fairhead
Message:

Merged LMDZ4-dev branch changes r1241:1278 into the trunk
Running trunk and LMDZ4-dev in LMDZOR configuration on local
machine (sequential) and SX8 (4-proc) yields identical results
(restart and restartphy are identical binarily)
Log history from r1241 to r1278 is available by switching to
source:LMDZ4/branches/LMDZ4-dev-20091210

Location:
LMDZ4/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk

  • LMDZ4/trunk/libf/dyn3d/calfis.F

    r1146 r1279  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44C
    55C
    66      SUBROUTINE calfis(lafin,
    7      $                  rdayvrai,
    8      $                  heure,
     7     $                  jD_cur, jH_cur,
    98     $                  pucov,
    109     $                  pvcov,
     
    102101c    -----------
    103102      LOGICAL  lafin
    104       REAL heure
     103
    105104
    106105      REAL pvcov(iip1,jjm,llm)
     
    170169      DATA firstcal/.true./
    171170      SAVE firstcal,debut
    172       REAL rdayvrai
     171!      REAL rdayvrai
     172      REAL, intent(in):: jD_cur, jH_cur
    173173c
    174174c-----------------------------------------------------------------------
     
    177177c    --------------------
    178178c
    179 
    180       IF (ngridmx.NE.2+(jjm-1)*iim) THEN
     179c
     180      IF ( firstcal )  THEN
     181        debut = .TRUE.
     182        IF (ngridmx.NE.2+(jjm-1)*iim) THEN
    181183         PRINT*,'STOP dans calfis'
    182184         PRINT*,'La dimension ngridmx doit etre egale a 2 + (jjm-1)*iim'
     
    184186         PRINT*,ngridmx,jjm,iim
    185187         STOP
    186       ENDIF
    187 
    188 c-----------------------------------------------------------------------
    189 c   latitude, longitude et aires des mailles pour la physique:
    190 c   ----------------------------------------------------------
    191 
    192 c
    193       IF ( firstcal )  THEN
    194           debut = .TRUE.
     188        ENDIF
    195189      ELSE
    196           debut = .FALSE.
    197       ENDIF
     190        debut = .FALSE.
     191      ENDIF ! of IF (firstcal)
    198192
    199193c
     
    290284
    291285c   convergence dynamique pour les traceurs "EAU"
    292 
    293       DO iq=1,2
     286! Earth-specific treatment of first 2 tracers (water)
     287       if (planet_type=="earth") then
     288        DO iq=1,2
    294289         DO l=1,llm
    295290            pcvgq(1,l,iq)= pdq(1,1,l,iq) / pmasse(1,1,l)
     
    303298            pcvgq(ig0,l,iq)= pdq(1,jjp1,l,iq) / pmasse(1,jjp1,l)
    304299         ENDDO
    305       ENDDO
     300        ENDDO
     301       endif ! of if (planet_type=="earth")
    306302
    307303
     
    428424      ENDDO
    429425c
     426      if (planet_type=="earth") then
     427#ifdef CPP_EARTH
    430428cIM calcul PV a teta=350, 380, 405K
    431429      CALL PVtheta(ngridmx,llm,pucov,pvcov,pteta,
    432430     $           ztfi,zplay,zplev,
    433431     $           ntetaSTD,rtetaSTD,PVteta)
     432#endif
     433      endif
    434434c
    435435c On change de grille, dynamique vers physiq, pour le flux de masse verticale
     
    441441
    442442
     443      if (planet_type=="earth") then
     444#ifdef CPP_EARTH
    443445      CALL physiq (ngridmx,
    444446     .             llm,
    445447     .             debut,
    446448     .             lafin,
    447      .             rdayvrai,
    448      .             heure,
     449     .             jD_cur,
     450     .             jH_cur,
    449451     .             dtphys,
    450452     .             zplev,
     
    467469     .             pducov,
    468470     .             PVteta)
     471#endif
     472      endif !of if (planet_type=="earth")
    469473
    470474500   CONTINUE
     
    502506c   62. humidite specifique
    503507c   ---------------------
    504 
    505       DO iq=1,nqtot
    506          DO l=1,llm
    507             DO i=1,iip1
    508                pdqfi(i,1,l,iq)    = zdqfi(1,l,iq)
    509                pdqfi(i,jjp1,l,iq) = zdqfi(ngridmx,l,iq)
    510             ENDDO
    511             DO j=2,jjm
    512                ig0=1+(j-2)*iim
    513                DO i=1,iim
    514                   pdqfi(i,j,l,iq) = zdqfi(ig0+i,l,iq)
    515                ENDDO
    516                pdqfi(iip1,j,l,iq) = pdqfi(1,j,l,iq)
    517             ENDDO
    518          ENDDO
    519       ENDDO
     508! Ehouarn: removed this useless bit: was overwritten at step 63 anyways
     509!      DO iq=1,nqtot
     510!         DO l=1,llm
     511!            DO i=1,iip1
     512!               pdqfi(i,1,l,iq)    = zdqfi(1,l,iq)
     513!               pdqfi(i,jjp1,l,iq) = zdqfi(ngridmx,l,iq)
     514!            ENDDO
     515!            DO j=2,jjm
     516!               ig0=1+(j-2)*iim
     517!               DO i=1,iim
     518!                  pdqfi(i,j,l,iq) = zdqfi(ig0+i,l,iq)
     519!               ENDDO
     520!               pdqfi(iip1,j,l,iq) = pdqfi(1,j,l,iq)
     521!            ENDDO
     522!         ENDDO
     523!      ENDDO
    520524
    521525c   63. traceurs
    522526c   ------------
    523527C     initialisation des tendances
    524       pdqfi=0.
     528      pdqfi(:,:,:,:)=0.
    525529C
    526530      DO iq=1,nqtot
Note: See TracChangeset for help on using the changeset viewer.