Ignore:
Timestamp:
Oct 22, 2010, 11:27:25 AM (14 years ago)
Author:
Ehouarn Millour
Message:

Implemented modifications to enable running with only one tracer for planet types different from "earth". Rem: If flag 'planet_type' is set to "earth" (default behaviour) then there must be at least 2 tracers for the dynamics to function properly.

These updates do not induce any changes in model outputs with respect to previous revisions.

EM

Location:
LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/addfi_p.F

    r1146 r1446  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE addfi_p(pdt, leapf, forward,
     
    77      USE parallel
    88      USE infotrac, ONLY : nqtot
     9      USE control_mod, ONLY : planet_type
    910      IMPLICIT NONE
    1011c
     
    154155c$OMP END MASTER
    155156 
    156       DO iq = 1, 2
     157      if (planet_type=="earth") then
     158      ! earth case, special treatment for first 2 tracers (water)
     159       DO iq = 1, 2
    157160c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    158161         DO k = 1,llm
     
    163166         ENDDO
    164167c$OMP END DO NOWAIT
    165       ENDDO
    166 
    167       DO iq = 3, nqtot
     168       ENDDO
     169
     170       DO iq = 3, nqtot
    168171c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    169172         DO k = 1,llm
     
    174177         ENDDO
    175178c$OMP END DO NOWAIT
    176       ENDDO
     179       ENDDO
     180      else
     181      ! general case, treat all tracers equally)
     182       DO iq = 1, nqtot
     183c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     184         DO k = 1,llm
     185            DO j = ijb,ije
     186               pq(j,k,iq)= pq(j,k,iq) + pdqfi(j,k,iq) * pdt
     187               pq(j,k,iq)= AMAX1( pq(j,k,iq), qtestt )
     188            ENDDO
     189         ENDDO
     190c$OMP END DO NOWAIT
     191       ENDDO
     192      endif ! of if (planet_type=="earth")
    177193
    178194c$OMP MASTER
  • LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/advtrac_p.F

    r1403 r1446  
    132132ccc         CALL filtreg ( massem ,jjp1, llm,-2, 2, .TRUE., 1 )
    133133c
    134       ENDIF
     134      ENDIF ! of IF(iadvtr.EQ.0)
    135135
    136136      iadvtr   = iadvtr+1
     
    266266cym      ----> Revérifier lors de la parallélisation des autres schemas
    267267   
    268 cym          call massbar_p(massem,massebx,masseby)         
     268cym          call massbar_p(massem,massebx,masseby) 
    269269
    270270          call vlspltgen_p( q,iadv, 2., massem, wg ,
     
    452452c$OMP BARRIER
    453453
    454       ijb=ij_begin
    455       ije=ij_end
     454      if (planet_type=="earth") then
     455
     456        ijb=ij_begin
     457        ije=ij_end
    456458
    457459c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)     
    458        DO l = 1, llm
     460        DO l = 1, llm
    459461         DO ij = ijb, ije
    460462           finmasse(ij,l) =  p(ij,l) - p(ij,l+1)
    461463         ENDDO
    462        ENDDO
     464        ENDDO
    463465c$OMP END DO
    464466
    465        CALL qminimum_p( q, 2, finmasse )
     467        CALL qminimum_p( q, 2, finmasse )
    466468
    467469c------------------------------------------------------------------
     
    496498c$OMP BARRIER   
    497499          iadvtr=0
     500      endif ! of if (planet_type=="earth")
    498501       ENDIF ! if iadvtr.EQ.iapp_tracvl
    499502
  • LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/caladvtrac_p.F

    r1403 r1446  
    88     *                   flxw, pk, iapptrac)
    99      USE parallel
    10       USE infotrac
    11       USE control_mod
     10      USE infotrac, ONLY : nqtot
     11      USE control_mod, ONLY : iapp_tracvl,planet_type
    1212c
    1313      IMPLICIT NONE
     
    3030c   ----------
    3131      REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm),masse(ip1jmp1,llm)
    32       REAL p( ip1jmp1,llmp1),q( ip1jmp1,llm,nqtot),dq( ip1jmp1,llm,2 )
     32      REAL p( ip1jmp1,llmp1),q( ip1jmp1,llm,nqtot)
     33      real :: dq( ip1jmp1,llm,nqtot)
    3334      REAL teta( ip1jmp1,llm),pk( ip1jmp1,llm)
    3435      REAL               :: flxw(ip1jmp1,llm)
  • LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/gcm.F

    r1403 r1446  
    276276        endif
    277277
    278         if (planet_type.eq."earth") then
    279 #ifdef CPP_EARTH
     278!        if (planet_type.eq."earth") then
    280279! Load an Earth-format start file
    281280         CALL dynetat0("start.nc",vcov,ucov,
    282281     &              teta,q,masse,ps,phis, time_0)
    283 #else
    284         ! SW model also has Earth-format start files
    285         ! (but can be used without the CPP_EARTH directive)
    286           if (iflag_phys.eq.0) then
    287             CALL dynetat0("start.nc",vcov,ucov,
    288      &              teta,q,masse,ps,phis, time_0)
    289           endif
    290 #endif
    291         endif ! of if (planet_type.eq."earth")
     282!        endif ! of if (planet_type.eq."earth")
     283
    292284c       write(73,*) 'ucov',ucov
    293285c       write(74,*) 'vcov',vcov
     
    494486#endif
    495487
    496       if (planet_type.eq."earth") then
     488!      if (planet_type.eq."earth") then
     489! Write an Earth-format restart file
    497490        CALL dynredem0_p("restart.nc", day_end, phis)
    498       endif
     491!      endif
    499492
    500493      ecripar = .TRUE.
  • LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/infotrac.F90

    r1443 r1446  
    6565    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
    6666    INTEGER :: iq, new_iq, iiq, jq, ierr
    67  
     67
     68    character(len=*),parameter :: modname="infotrac_init"
    6869!-----------------------------------------------------------------------
    6970! Initialization :
     
    99100       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    100101       IF(ierr.EQ.0) THEN
    101           WRITE(lunout,*) 'Open traceur.def : ok'
     102          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
    102103          READ(90,*) nqtrue
    103104       ELSE
    104           WRITE(lunout,*) 'Problem in opening traceur.def'
    105           WRITE(lunout,*) 'ATTENTION using defaut values'
     105          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
     106          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
    106107          nqtrue=4 ! Defaut value
    107108       END IF
    108        ! Attention! Only for planet_type=='earth'
    109        nbtr=nqtrue-2
     109       if ( planet_type=='earth') then
     110         ! For Earth, water vapour & liquid tracers are not in the physics
     111         nbtr=nqtrue-2
     112       else
     113         ! Other planets (for now); we have the same number of tracers
     114         ! in the dynamics than in the physics
     115         nbtr=nqtrue
     116       endif
    110117    ELSE
    111118       ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
     
    113120    END IF
    114121
    115     IF (nqtrue < 2) THEN
    116        WRITE(lunout,*) 'nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
     122    IF ((planet_type=="earth").and.(nqtrue < 2)) THEN
     123       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
    117124       CALL abort_gcm('infotrac_init','Not enough tracers',1)
    118125    END IF
     
    158165          END DO
    159166          CLOSE(90) 
    160        ELSE ! Without tracer.def
     167       ELSE ! Without tracer.def, set default values (for Earth!)
     168         if ((nqtrue==4).and.(planet_type=="earth")) then
    161169          hadv(1) = 14
    162170          vadv(1) = 14
     
    171179          vadv(4) = 10
    172180          tnom_0(4) = 'PB'
     181         else
     182           ! Error message, we need a traceur.def file
     183           write(lunout,*) trim(modname),&
     184           ': Cannot set default tracer names!'
     185           write(lunout,*) trim(modname),' Make a traceur.def file!!!'
     186           CALL abort_gcm('infotrac_init','Need a traceur.def file!',1)
     187         endif ! of if (nqtrue==4)
    173188       END IF
    174189       
    175        WRITE(lunout,*) 'Valeur de traceur.def :'
    176        WRITE(lunout,*) 'nombre de traceurs ',nqtrue
     190       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
     191       WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
    177192       DO iq=1,nqtrue
    178193          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq)
     
    216231          new_iq=new_iq+10 ! 9 tracers added
    217232       ELSE
    218           WRITE(lunout,*) 'This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
     233          WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
    219234          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
    220235       END IF
     
    226241       nqtot = new_iq
    227242
    228        WRITE(lunout,*) 'The choice of advection schema for one or more tracers'
     243       WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers'
    229244       WRITE(lunout,*) 'makes it necessary to add tracers'
    230        WRITE(lunout,*) nqtrue,' is the number of true tracers'
    231        WRITE(lunout,*) nqtot, ' is the total number of tracers needed'
     245       WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers'
     246       WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed'
    232247
    233248    ELSE
     
    257272          iadv(new_iq)=11
    258273       ELSE
    259           WRITE(lunout,*)'This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
     274          WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
    260275
    261276          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1)
     
    303318
    304319
    305     WRITE(lunout,*) 'Information stored in infotrac :'
    306     WRITE(lunout,*) 'iadv  niadv tname  ttext :'
     320    WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
     321    WRITE(lunout,*) trim(modname),': iadv  niadv tname  ttext :'
    307322    DO iq=1,nqtot
    308        WRITE(lunout,*) iadv(iq),niadv(iq), tname(iq), ttext(iq)
     323       WRITE(lunout,*) iadv(iq),niadv(iq),&
     324       ' ',trim(tname(iq)),' ',trim(ttext(iq))
    309325    END DO
    310326
     
    315331    DO iq=1,nqtot
    316332       IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN
    317           WRITE(lunout,*)'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     333          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
    318334          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
    319335       ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
    320           WRITE(lunout,*)'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     336          WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
    321337          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
    322338       END IF
  • LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/iniacademic.F

    r1437 r1446  
    88      USE filtreg_mod
    99      USE infotrac, ONLY : nqtot
    10       USE control_mod
     10      USE control_mod, ONLY: day_step,planet_type
    1111#ifdef CPP_IOIPSL
    1212      USE IOIPSL
     
    9595! 1. Initializations for Earth-like case
    9696! --------------------------------------
    97       if (planet_type=="earth") then
    9897c
    9998        ! initialize planet radius, rotation rate,...
     
    128127          if (.not.read_start) then
    129128            phis(:)=0.
    130             q(:,:,1)=1.e-10
    131             q(:,:,2)=1.e-15
    132             q(:,:,3:nqtot)=0.
     129            q(:,:,:)=0
    133130            CALL sw_case_williamson91_6(vcov,ucov,teta,masse,ps)
    134131          endif
     
    138135          ! initializations for the academic case
    139136         
     137!         if (planet_type=="earth") then
     138
    140139          ! 1. local parameters
    141140          ! by convention, winter is in the southern hemisphere
     
    219218          enddo
    220219
     220
     221!         else
     222!          write(lunout,*)"iniacademic: planet types other than earth",
     223!     &                   " not implemented (yet)."
     224!          stop
     225!         endif ! of if (planet_type=="earth")
     226
    221227          ! 3. Initialize fields (if necessary)
    222228          IF (.NOT. read_start) THEN
     
    245251           
    246252            ! bulk initialization of tracers
    247             do i=1,nqtot
    248               if (i.eq.1) q(:,:,i)=1.e-10
    249               if (i.eq.2) q(:,:,i)=1.e-15
    250               if (i.gt.2) q(:,:,i)=0.
    251             enddo
     253            if (planet_type=="earth") then
     254              ! Earth: first two tracers will be water
     255              do i=1,nqtot
     256                if (i.eq.1) q(:,:,i)=1.e-10
     257                if (i.eq.2) q(:,:,i)=1.e-15
     258                if (i.gt.2) q(:,:,i)=0.
     259              enddo
     260            else
     261              q(:,:,:)=0
     262            endif ! of if (planet_type=="earth")
    252263
    253264            ! add random perturbation to temperature
     
    261272            enddo
    262273
     274            ! maintain periodicity in longitude
    263275            do l=1,llm
    264276              do ij=1,ip1jmp1,iip1
     
    267279            enddo
    268280
    269 c     PRINT *,' Appel test_period avec tetarappel '
    270 c     CALL  test_period ( ucov,vcov,tetarappel,q,p,phis )
    271 c     PRINT *,' Appel test_period avec teta '
    272 c     CALL  test_period ( ucov,vcov,teta,q,p,phis )
    273 
    274            ! initialize a traceur on one column
    275 !          j=jjp1*3/4
    276 !          i=iip1/2
    277 !          ij=(j-1)*iip1+i
    278 !          q(ij,:,3)=1.
    279 
    280281          ENDIF ! of IF (.NOT. read_start)
    281282        endif ! of if (iflag_phys.eq.2)
    282283       
    283       else
    284         write(lunout,*)"iniacademic: planet types other than earth",
    285      &                 " not implemented (yet)."
    286         stop
    287       endif ! of if (planet_type=="earth")
    288       return
    289284      END
    290285c-----------------------------------------------------------------------
  • LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/integrd_p.F

    r1403 r1446  
    66     $     dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps0,masse,phis,finvmaold)
    77      USE parallel
    8       USE control_mod
     8      USE control_mod, only : planet_type
    99      IMPLICIT NONE
    1010
     
    279279
    280280          CALL qminimum_p( q, nq, deltap )
    281          endif ! of if (planet_type.eq."earth")
    282281c
    283282c    .....  Calcul de la valeur moyenne, unique  aux poles pour  q .....
     
    337336      ENDDO
    338337c$OMP END DO NOWAIT
     338
     339      endif ! of if (planet_type.eq."earth")
     340
    339341c
    340342c
  • LMDZ5/branches/LMDZ5V1.0-dev/libf/dyn3dpar/leapfrog_p.F

    r1438 r1446  
    234234
    235235c$OMP MASTER
    236       dq=0.
     236      dq(:,:,:)=0.
    237237      CALL pression ( ip1jmp1, ap, bp, ps, p       )
    238238      CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
     
    14881488c$OMP MASTER
    14891489
    1490               if (planet_type.eq."earth") then
     1490!              if (planet_type.eq."earth") then
    14911491! Write an Earth-format restart file
    14921492                CALL dynredem1_p("restart.nc",0.0,
    14931493     &                           vcov,ucov,teta,q,masse,ps)
    1494               endif ! of if (planet_type.eq."earth")
     1494!              endif ! of if (planet_type.eq."earth")
    14951495
    14961496!              CLOSE(99)
     
    16811681
    16821682              IF(itau.EQ.itaufin) THEN
    1683                 if (planet_type.eq."earth") then
     1683!                if (planet_type.eq."earth") then
    16841684c$OMP MASTER
    16851685                   CALL dynredem1_p("restart.nc",0.0,
    16861686     .                               vcov,ucov,teta,q,masse,ps)
    16871687c$OMP END MASTER
    1688                 endif ! of if (planet_type.eq."earth")
     1688!                endif ! of if (planet_type.eq."earth")
    16891689              ENDIF ! of IF(itau.EQ.itaufin)
    16901690
Note: See TracChangeset for help on using the changeset viewer.