Ignore:
Timestamp:
Jul 18, 2016, 9:41:10 PM (8 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2545:2589 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3d_common/infotrac.F90

    r2408 r2594  
    8686    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv  ! index of horizontal trasport schema
    8787    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
     88
     89    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv_inca  ! index of horizontal trasport schema
     90    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv_inca  ! index of vertical trasport schema
    8891
    8992    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
     
    205208#endif       
    206209       nqtrue=nbtr+nqo
     210
     211       ALLOCATE(hadv_inca(nbtr), vadv_inca(nbtr))
     212
    207213    END IF   ! type_trac
    208214!>jyg
     
    226232!
    227233    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue),tnom_transp(nqtrue))
     234
    228235!
    229236!jyg<
     
    375382!>jyg
    376383! le module de chimie fournit les noms des traceurs
    377 ! et les schemas d'advection associes.
    378      
     384! et les schemas d'advection associes. excepte pour ceux lus
     385! dans traceur.def
     386       IF (ierr .eq. 0) then
     387          DO iq=1,nqo
     388
     389             write(*,*) 'infotrac 237: iq=',iq
     390             ! CRisi: ajout du nom du fluide transporteur
     391             ! mais rester retro compatible
     392             READ(90,'(I2,X,I2,X,A)',IOSTAT=IOstatus) hadv(iq),vadv(iq),tchaine
     393             write(lunout,*) 'iq,hadv(iq),vadv(iq)=',iq,hadv(iq),vadv(iq)
     394             write(lunout,*) 'tchaine=',trim(tchaine)
     395             write(*,*) 'infotrac 238: IOstatus=',IOstatus
     396             if (IOstatus.ne.0) then
     397                CALL abort_gcm('infotrac_init','Pb dans la lecture de traceur.def',1)
     398             endif
     399             ! Y-a-t-il 1 ou 2 noms de traceurs? -> On regarde s'il y a un
     400             ! espace ou pas au milieu de la chaine.
     401             continu=.true.
     402             nouveau_traceurdef=.false.
     403             iiq=1
     404             do while (continu)
     405                if (tchaine(iiq:iiq).eq.' ') then
     406                  nouveau_traceurdef=.true.
     407                  continu=.false.
     408                else if (iiq.lt.LEN_TRIM(tchaine)) then
     409                  iiq=iiq+1
     410                else
     411                  continu=.false.
     412                endif
     413             enddo
     414             write(*,*) 'iiq,nouveau_traceurdef=',iiq,nouveau_traceurdef
     415             if (nouveau_traceurdef) then
     416                write(lunout,*) 'C''est la nouvelle version de traceur.def'
     417                tnom_0(iq)=tchaine(1:iiq-1)
     418                tnom_transp(iq)=tchaine(iiq+1:15)
     419             else
     420                write(lunout,*) 'C''est l''ancienne version de traceur.def'
     421                write(lunout,*) 'On suppose que les traceurs sont tous d''air'
     422                tnom_0(iq)=tchaine
     423                tnom_transp(iq) = 'air'
     424             endif
     425             write(lunout,*) 'tnom_0(iq)=<',trim(tnom_0(iq)),'>'
     426             write(lunout,*) 'tnom_transp(iq)=<',trim(tnom_transp(iq)),'>'
     427
     428          END DO !DO iq=1,nqtrue
     429          CLOSE(90) 
     430       ELSE  !! if traceur.def doesn't exist
     431          tnom_0(1)='H2Ov'
     432          tnom_transp(1) = 'air'
     433          tnom_0(2)='H2Ol'
     434          tnom_transp(2) = 'air'
     435          hadv(1) = 10
     436          hadv(2) = 10
     437          vadv(1) = 10
     438          vadv(2) = 10
     439       ENDIF
     440 
    379441#ifdef INCA
    380442       CALL init_transport( &
    381             hadv, &
    382             vadv, &
     443            hadv_inca, &
     444            vadv_inca, &
    383445            conv_flg, &
    384446            pbl_flg,  &
    385447            solsym)
    386448#endif
    387        tnom_0(1)='H2Ov'
    388        tnom_transp(1) = 'air'
    389        tnom_0(2)='H2Ol'
    390        tnom_transp(2) = 'air'
    391        IF (nqo == 3) then
    392           tnom_0(3)='H2Oi'     !! jyg
    393           tnom_transp(3) = 'air'
    394        endif
     449
    395450
    396451!jyg<
    397452       DO iq = nqo+1, nqtrue
     453          hadv(iq) = hadv_inca(iq-nqo)
     454          vadv(iq) = vadv_inca(iq-nqo)
    398455          tnom_0(iq)=solsym(iq-nqo)
    399456          tnom_transp(iq) = 'air'
    400457       END DO
    401 !!       DO iq =3,nqtrue
    402 !!          tnom_0(iq)=solsym(iq-2)
    403 !!       END DO
    404 !!       nqo = 2
    405 !>jyg
    406458
    407459    END IF ! (type_trac == 'inca')
Note: See TracChangeset for help on using the changeset viewer.