Ignore:
Timestamp:
Dec 14, 2015, 11:43:09 AM (9 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2298:2396 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/phytrac_mod.F90

    r2298 r2408  
    8989    USE phys_cal_mod, only : hour
    9090    USE dimphy
    91     USE infotrac
     91    USE infotrac_phy, ONLY: nbtr, type_trac, conv_flg, solsym, pbl_flg
    9292    USE mod_grid_phy_lmdz
    9393    USE mod_phys_lmdz_para
    94     USE comgeomphy
    9594    USE iophy
    9695    USE traclmdz_mod
    9796    USE tracinca_mod
    9897    USE tracreprobus_mod
    99     USE control_mod
    10098    USE indice_sol_mod
    10199
    102100    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
     101    USE print_control_mod, ONLY: lunout
     102    USE aero_mod, ONLY : naero_grp
    103103
    104104    IMPLICIT NONE
    105105
    106106    INCLUDE "YOMCST.h"
    107     INCLUDE "dimensions.h"
    108107    INCLUDE "clesphys.h"
    109     INCLUDE "temps.h"
    110     INCLUDE "paramet.h"
    111108    INCLUDE "thermcell.h"
    112     INCLUDE "iniprint.h"
    113109    !==========================================================================
    114110    !                   -- ARGUMENT DESCRIPTION --
     
    173169    LOGICAL,INTENT(IN)                       :: aerosol_couple
    174170    REAL,DIMENSION(klon,klev),INTENT(IN)     :: flxmass_w
    175     REAL,DIMENSION(klon,klev,9,2),INTENT(IN) :: tau_aero
    176     REAL,DIMENSION(klon,klev,9,2),INTENT(IN) :: piz_aero
    177     REAL,DIMENSION(klon,klev,9,2),INTENT(IN) :: cg_aero
    178     CHARACTER(len=4),DIMENSION(9),INTENT(IN) :: rfname
     171    REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: tau_aero
     172    REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: piz_aero
     173    REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: cg_aero
     174    CHARACTER(len=4),DIMENSION(naero_grp),INTENT(IN) :: rfname
    179175    REAL,DIMENSION(klon,klev,2),INTENT(IN)   :: ccm
    180176    !... K.Emanuel
     
    445441       WRITE(*,*) 'FIRST TIME IN PHYTRAC : pdtphys(sec) = ',pdtphys,'ecrit_tra (sec) = ',ecrit_tra
    446442       ALLOCATE( source(klon,nbtr), stat=ierr)
    447        IF (ierr /= 0) CALL abort_gcm('phytrac', 'pb in allocation 1',1)
     443       IF (ierr /= 0) CALL abort_physic('phytrac', 'pb in allocation 1',1)
    448444
    449445       ALLOCATE( aerosol(nbtr), stat=ierr)
    450        IF (ierr /= 0) CALL abort_gcm('phytrac', 'pb in allocation 2',1)
     446       IF (ierr /= 0) CALL abort_physic('phytrac', 'pb in allocation 2',1)
    451447
    452448
     
    503499!                ELSE
    504500!                   WRITE(lunout,*) 'pb it=', it
    505 !                   CALL abort_gcm('phytrac','pb it scavenging',1)
     501!                   CALL abort_physic('phytrac','pb it scavenging',1)
    506502!                ENDIF
    507503                !--test OB
     
    539535
    540536       IF (lessivage.AND.config_inca.EQ.'inca') THEN
    541           CALL abort_gcm('phytrac', 'lessivage=T config_inca=inca impossible',1)
     537          CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1)
    542538          STOP
    543539       ENDIF
     
    740736    ELSE
    741737       !
    742        CALL abort_gcm('iflag_vdf_trac', 'cas non prevu',1)
     738       CALL abort_physic('iflag_vdf_trac', 'cas non prevu',1)
    743739       !
    744740    END IF ! couche limite
Note: See TracChangeset for help on using the changeset viewer.