Ignore:
Timestamp:
Dec 19, 2014, 4:21:08 PM (9 years ago)
Author:
acozic
Message:

There are some commits that we must not do just before holiday .... so be back to rev 2168

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d_common/infotrac.F90

    r2169 r2171  
    2929
    3030  CHARACTER(len=4),SAVE :: type_trac
    31   CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
    3231 
    3332CONTAINS
     
    6362
    6463    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
     64    CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: tracnam ! name from INCA
    6565    CHARACTER(len=3), DIMENSION(30) :: descrq
    6666    CHARACTER(len=1), DIMENSION(3)  :: txts
     
    9494       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
    9595            type_trac,' config_inca=',config_inca
    96        IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
     96       IF (config_inca/='aero' .AND. config_inca/='chem') THEN
    9797          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
    9898          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     
    172172!
    173173    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue))
    174     ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
     174    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), tracnam(nbtr))
    175175    conv_flg(:) = 1 ! convection activated for all tracers
    176176    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
     
    254254            conv_flg, &
    255255            pbl_flg,  &
    256             solsym)
     256            tracnam)
    257257#endif
    258258       tnom_0(1)='H2Ov'
     
    260260
    261261       DO iq =3,nqtrue
    262           tnom_0(iq)=solsym(iq-2)
     262          tnom_0(iq)=tracnam(iq-2)
    263263       END DO
    264264       nqo = 2
     
    394394!
    395395    DEALLOCATE(tnom_0, hadv, vadv)
    396 
     396    DEALLOCATE(tracnam)
    397397
    398398  END SUBROUTINE infotrac_init
Note: See TracChangeset for help on using the changeset viewer.