Ignore:
Timestamp:
Apr 15, 2015, 6:49:07 PM (10 years ago)
Author:
ymipsl
Message:

remove all dynamic dependency in LMDZ physics except for the include "dimensions.h"

YM

Location:
dynamico_lmdz/aquaplanet/LMDZ5/libf
Files:
21 added
17 deleted
93 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/misc/handle_err_m.F90

    r3809 r3814  
    3939          end if
    4040       end if
    41        call abort_gcm("NetCDF95 handle_err", "", 1)
     41       call abort_physic("NetCDF95 handle_err", "", 1)
    4242    end if
    4343
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/aaam_bud.F90

    r3809 r3814  
    123123  IF (iim+1>801 .OR. jjm+1>401) THEN
    124124    abort_message = 'Pb de dimension dans aaam_bud'
    125     CALL abort_gcm(modname, abort_message, 1)
     125    CALL abort_physic(modname, abort_message, 1)
    126126  END IF
    127127
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/aeropt.F90

    r3809 r3814  
    8181      IF (rh<0.) THEN
    8282        abort_message = 'aeropt: RH < 0 not possible'
    83         CALL abort_gcm(modname, abort_message, 1)
     83        CALL abort_physic(modname, abort_message, 1)
    8484      END IF
    8585      IF (rh>85.) rh_num = 10
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/aeropt_2bands.F90

    r3809 r3814  
    536536          A1_SSSSM_b2(klev), A2_SSSSM_b2(klev), A3_SSSSM_b2(klev),&
    537537          B1_SSSSM_b2(klev), B2_SSSSM_b2(klev), C1_SSSSM_b2(klev), C2_SSSSM_b2(klev), stat=ierr)
    538         IF (ierr /= 0) CALL abort_gcm('aeropt_2bands', 'pb in allocation 1',1)
     538        IF (ierr /= 0) CALL abort_physic('aeropt_2bands', 'pb in allocation 1',1)
    539539     END IF
    540540     
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/aeropt_5wv.F90

    r3809 r3814  
    588588          A1_SSSSM(klev), A2_SSSSM(klev), A3_SSSSM(klev),&
    589589          B1_SSSSM(klev), B2_SSSSM(klev), C1_SSSSM(klev), C2_SSSSM(klev), stat=ierr)
    590         IF (ierr /= 0) CALL abort_gcm('aeropt_5mw', 'pb in allocation 1',1)
     590        IF (ierr /= 0) CALL abort_physic('aeropt_5mw', 'pb in allocation 1',1)
    591591     END IF
    592592
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/calltherm.F90

    r3809 r3814  
    208208          else if (iflag_thermals.eq.11) then
    209209              abort_message = 'cas non prevu dans calltherm'
    210               CALL abort_gcm (modname,abort_message,1)
     210              CALL abort_physic (modname,abort_message,1)
    211211
    212212!           CALL thermcell_pluie(klon,klev,zdt  &
     
    260260         else
    261261           abort_message = 'Cas des thermiques non prevu'
    262            CALL abort_gcm (modname,abort_message,1)
     262           CALL abort_physic (modname,abort_message,1)
    263263         endif
    264264
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/carbon_cycle_mod.F90

    r3809 r3814  
    8888    USE comgeomphy
    8989    USE mod_phys_lmdz_transfert_para
    90     USE infotrac
     90    USE infotrac_phy
    9191    USE IOIPSL
    9292    USE surface_data, ONLY : ok_veget, type_ocean
     
    135135       WRITE(lunout,*) 'carbon_cycle_emis_comp = ',carbon_cycle_emis_comp
    136136       IF (carbon_cycle_emis_comp) THEN
    137           CALL abort_gcm('carbon_cycle_init', 'carbon_cycle_emis_comp option not yet implemented!!',1)
     137          CALL abort_physic('carbon_cycle_init', 'carbon_cycle_emis_comp option not yet implemented!!',1)
    138138       END IF
    139139    END IF
     
    225225          co2trac(itc)%updatefreq = 86400
    226226          ! DOES THIS WORK ???? Problematic due to implementation of the coupled fluxes...
    227           CALL abort_gcm('carbon_cycle_init','transport of total CO2 has to be implemented and tested',1)
     227          CALL abort_physic('carbon_cycle_init','transport of total CO2 has to be implemented and tested',1)
    228228       END SELECT
    229229    END DO
     
    247247    ! Allocate vector for storing fluxes to inject
    248248    ALLOCATE(dtr_add(klon,maxco2trac), stat=ierr)
    249     IF (ierr /= 0) CALL abort_gcm('carbon_cycle_init', 'pb in allocation 11',1)       
     249    IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 11',1)       
    250250   
    251251    ! Allocate variables for cumulating fluxes from ORCHIDEE
     
    253253       IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl) THEN
    254254          ALLOCATE(fco2_land_day(klon), stat=ierr)
    255           IF (ierr /= 0) CALL abort_gcm('carbon_cycle_init', 'pb in allocation 2',1)
     255          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 2',1)
    256256          fco2_land_day(1:klon) = 0.
    257257         
    258258          ALLOCATE(fco2_lu_day(klon), stat=ierr)
    259           IF (ierr /= 0) CALL abort_gcm('carbon_cycle_init', 'pb in allocation 3',1)
     259          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 3',1)
    260260          fco2_lu_day(1:klon)   = 0.
    261261       END IF
     
    267267!    IF (carbon_cycle_cpl .AND. type_ocean/='couple') THEN
    268268!       WRITE(lunout,*) 'Coupling with ocean model is needed for carbon_cycle_cpl'
    269 !       CALL abort_gcm('carbon_cycle_init', 'coupled ocean is needed for carbon_cycle_cpl',1)
     269!       CALL abort_physic('carbon_cycle_init', 'coupled ocean is needed for carbon_cycle_cpl',1)
    270270!    END IF
    271271!
    272272!    IF (carbon_cycle_cpl .AND..NOT. ok_veget) THEN
    273273!       WRITE(lunout,*) 'Coupling with surface land model ORCHDIEE is needed for carbon_cycle_cpl'
    274 !       CALL abort_gcm('carbon_cycle_init', 'ok_veget is needed for carbon_cycle_cpl',1)
     274!       CALL abort_physic('carbon_cycle_init', 'ok_veget is needed for carbon_cycle_cpl',1)
    275275!    END IF
    276276
     
    278278    teststop=0
    279279    DO it=1,teststop
    280        CALL abort_gcm('carbon_cycle_init', 'Entering loop from 1 to 0',1)
     280       CALL abort_physic('carbon_cycle_init', 'Entering loop from 1 to 0',1)
    281281    END DO
    282282
     
    284284       ! No carbon tracers found in tracer.def. It is not possible to do carbon cycle
    285285       WRITE(lunout,*) 'No carbon tracers found in tracer.def. Not ok with carbon_cycle_tr and/or carbon_cycle_cp'
    286        CALL abort_gcm('carbon_cycle_init', 'No carbon tracers found in tracer.def',1)
     286       CALL abort_physic('carbon_cycle_init', 'No carbon tracers found in tracer.def',1)
    287287    END IF
    288288   
     
    303303! - Calculate CO2 flux to send to ocean and land models (PISCES and ORCHIDEE)
    304304
    305     USE infotrac
     305    USE infotrac_phy
    306306    USE dimphy
    307307    USE mod_phys_lmdz_transfert_para
     
    370370             CASE DEFAULT
    371371                WRITE(lunout,*) 'Error with tracer ',co2trac(it)%name
    372                 CALL abort_gcm('carbon_cycle', 'No coupling implemented for this tracer',1)
     372                CALL abort_physic('carbon_cycle', 'No coupling implemented for this tracer',1)
    373373             END SELECT
    374374          ELSE
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cdrag.F90

    r3809 r3814  
    143143      WRITE(lunout,*)" The negative q1 is set to zero "
    144144!      abort_message="voir ci-dessus"
    145 !      CALL abort_gcm(modname,abort_message,1)
     145!      CALL abort_physic(modname,abort_message,1)
    146146  ENDIF
    147147  IF (ng_qsurf.GT.0) THEN
     
    150150      WRITE(lunout,*)" The negative qsurf is set to zero "
    151151!      abort_message="voir ci-dessus"
    152 !      CALL abort_gcm(modname,abort_message,1)
     152!      CALL abort_physic(modname,abort_message,1)
    153153  ENDIF
    154154
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/change_srf_frac_mod.F90

    r3809 r3814  
    109109          WRITE(lunout,*)'at point = ',MINLOC(pctsrf(:,:))
    110110          WRITE(lunout,*)'value = ',MINVAL(pctsrf(:,:))
    111           CALL abort_gcm('change_srf_frac','Negative fraction',1)
     111          CALL abort_physic('change_srf_frac','Negative fraction',1)
    112112       END IF
    113113
     
    116116          DO i= 1, klon
    117117             tmpsum = SUM(pctsrf(i,:))
    118              IF (ABS(1. - tmpsum) > 0.05) CALL abort_gcm('change_srf_frac','Total fraction not equal 1.',1)
     118             IF (ABS(1. - tmpsum) > 0.05) CALL abort_physic('change_srf_frac','Total fraction not equal 1.',1)
    119119          END DO
    120120       END IF
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/clcdrag.F90

    r3809 r3814  
    7373
    7474  abort_message='obsolete, remplace par cdrag, use at you own risk'
    75   CALL abort_gcm(modname,abort_message,1)
     75  CALL abort_physic(modname,abort_message,1)
    7676
    7777
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/climb_wind_mod.F90

    r3809 r3814  
    4444
    4545    ALLOCATE(alf1(klon), stat=ierr)
    46     IF (ierr /= 0) CALL abort_gcm(modname,'Pb in allocate alf1',1)
     46    IF (ierr /= 0) CALL abort_physic(modname,'Pb in allocate alf1',1)
    4747
    4848    ALLOCATE(alf2(klon), stat=ierr)
    49     IF (ierr /= 0) CALL abort_gcm(modname,'Pb in allocate alf2',1)
     49    IF (ierr /= 0) CALL abort_physic(modname,'Pb in allocate alf2',1)
    5050
    5151    ALLOCATE(Kcoefm(klon,klev), stat=ierr)
    52     IF (ierr /= 0) CALL abort_gcm(modname,'Pb in allocate Kcoefm',1)
     52    IF (ierr /= 0) CALL abort_physic(modname,'Pb in allocate Kcoefm',1)
    5353
    5454    ALLOCATE(Ccoef_U(klon,klev), stat=ierr)
    55     IF (ierr /= 0) CALL abort_gcm(modname,'Pb in allocate Ccoef_U',1)
     55    IF (ierr /= 0) CALL abort_physic(modname,'Pb in allocate Ccoef_U',1)
    5656
    5757    ALLOCATE(Dcoef_U(klon,klev), stat=ierr)
    58     IF (ierr /= 0) CALL abort_gcm(modname,'Pb in allocation Dcoef_U',1)
     58    IF (ierr /= 0) CALL abort_physic(modname,'Pb in allocation Dcoef_U',1)
    5959
    6060    ALLOCATE(Ccoef_V(klon,klev), stat=ierr)
    61     IF (ierr /= 0) CALL abort_gcm(modname,'Pb in allocation Ccoef_V',1)
     61    IF (ierr /= 0) CALL abort_physic(modname,'Pb in allocation Ccoef_V',1)
    6262
    6363    ALLOCATE(Dcoef_V(klon,klev), stat=ierr)
    64     IF (ierr /= 0) CALL abort_gcm(modname,'Pb in allocation Dcoef_V',1)
     64    IF (ierr /= 0) CALL abort_physic(modname,'Pb in allocation Dcoef_V',1)
    6565
    6666    ALLOCATE(Acoef_U(klon), Bcoef_U(klon), Acoef_V(klon), Bcoef_V(klon), STAT=ierr)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/coefcdrag.F90

    r3809 r3814  
    7878
    7979  abort_message='obsolete, remplace par cdrag, use at you own risk'
    80   CALL abort_gcm(modname,abort_message,1)
     80  CALL abort_physic(modname,abort_message,1)
    8181
    8282!
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/concvl.F90

    r3809 r3814  
    2929
    3030  USE dimphy
    31   USE infotrac, ONLY: nbtr
     31  USE infotrac_phy, ONLY: nbtr
    3232  USE phys_local_var_mod, ONLY: omega
    3333  IMPLICIT NONE
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/condsurf.F90

    r3809 r3814  
    66  USE mod_phys_lmdz_para
    77  USE indice_sol_mod
     8  USE temps_phy_mod
    89  IMPLICIT NONE
    910
     
    2627  ! ym#include "dimensions.h"
    2728  ! ym#include "dimphy.h"
    28   include "temps.h"
    2929  include "clesphys.h"
    3030
     
    5656  IF (jour<0 .OR. jour>(360-1)) THEN
    5757    PRINT *, 'Le jour demande n est pas correct: ', jour
    58     CALL abort_gcm('condsurf', '', 1)
     58    CALL abort_physic('condsurf', '', 1)
    5959  END IF
    6060
     
    7676    PRINT *, ' trouve pas sur les ', nannemax, ' annees a partir de '
    7777    PRINT *, ' l annee de debut', annee_ref
    78     CALL abort_gcm('condsurf', '', 1)
     78    CALL abort_physic('condsurf', '', 1)
    7979
    8080100 CONTINUE
     
    9696      WRITE (6, *) '       l an 2000 )  ,  n existe  pas !  '
    9797      WRITE (6, *) ' ierr = ', ierr
    98       CALL abort_gcm('condsurf', '', 1)
     98      CALL abort_physic('condsurf', '', 1)
    9999    END IF
    100100    ! DO k = 1, jour
     
    109109    ierr = nf_inq_varid(nid, 'BILS', nvarid)
    110110    IF (ierr/=nf_noerr) THEN
    111       CALL abort_gcm('cond_surf', 'Le champ <BILS> est absent', 1)
     111      CALL abort_physic('cond_surf', 'Le champ <BILS> est absent', 1)
    112112    END IF
    113113    PRINT *, 'debut,epais', debut, epais, 'jour,jourvrai', jour, jourvrai
     
    118118#endif
    119119    IF (ierr/=nf_noerr) THEN
    120       CALL abort_gcm('condsurf', 'Lecture echouee pour <BILS>', 1)
     120      CALL abort_physic('condsurf', 'Lecture echouee pour <BILS>', 1)
    121121    END IF
    122122    ! ENDDO !k = 1, jour
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/conema3.F90

    r3809 r3814  
    88
    99  USE dimphy
    10   USE infotrac, ONLY: nbtr
     10  USE infotrac_phy, ONLY: nbtr
    1111  IMPLICIT NONE
    1212  ! ======================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/conemav.F90

    r3809 r3814  
    88
    99  USE dimphy
    10   USE infotrac, ONLY: nbtr
     10  USE infotrac_phy, ONLY: nbtr
    1111  IMPLICIT NONE
    1212  ! ======================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/conf_phys_m.F90

    r3809 r3814  
    2727    USE phys_cal_mod
    2828    USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl
    29     USE control_mod
     29    USE control_phy_mod
    3030    USE mod_grid_phy_lmdz, only: klon_glo
    3131
     
    245245       WRITE(lunout,*)'Variable OCEAN has been replaced by the variable type_ocean.'
    246246       WRITE(lunout,*)'You have to update your parameter file physiq.def to succed running'
    247        CALL abort_gcm('conf_phys','Variable OCEAN no longer existing, use variable name type_ocean',1)
     247       CALL abort_physic('conf_phys','Variable OCEAN no longer existing, use variable name type_ocean',1)
    248248    END IF
    249249
     
    258258       WRITE(lunout,*)'ERROR! Timestep of coupling between atmosphere and ocean'
    259259       WRITE(lunout,*)'cannot be zero.'
    260        CALL abort_gcm('conf_phys','t_coupl = 0.',1)
     260       CALL abort_physic('conf_phys','t_coupl = 0.',1)
    261261    END IF
    262262
     
    20772077    IF (type_ocean=='couple' .AND. (version_ocean/='opa8' .AND. version_ocean/='nemo') ) THEN
    20782078       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid in coupled configuration'
    2079        CALL abort_gcm('conf_phys','version_ocean not valid',1)
     2079       CALL abort_physic('conf_phys','version_ocean not valid',1)
    20802080    END IF
    20812081
     
    20852085             .AND. version_ocean/='sicINT' .AND. version_ocean/='sicNO') THEN
    20862086       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid with slab ocean'
    2087        CALL abort_gcm('conf_phys','version_ocean not valid',1)
     2087       CALL abort_physic('conf_phys','version_ocean not valid',1)
    20882088    END IF
    20892089
     
    20922092    IF (ok_ade .OR. ok_aie) THEN
    20932093       IF ( flag_aerosol .EQ. 0 ) THEN
    2094           CALL abort_gcm('conf_phys','flag_aerosol=0 not compatible avec ok_ade ou ok_aie=.TRUE.',1)
     2094          CALL abort_physic('conf_phys','flag_aerosol=0 not compatible avec ok_ade ou ok_aie=.TRUE.',1)
    20952095       END IF
    20962096       IF ( .NOT. new_aod .AND.  flag_aerosol .NE. 1) THEN
    2097           CALL abort_gcm('conf_phys','new_aod=.FALSE. not compatible avec flag_aerosol=1',1)
     2097          CALL abort_physic('conf_phys','new_aod=.FALSE. not compatible avec flag_aerosol=1',1)
    20982098       END IF
    20992099    END IF
     
    21012101    ! ok_cdnc must be set to y if ok_aie is activated
    21022102    IF (ok_aie .AND. .NOT. ok_cdnc) THEN
    2103        CALL abort_gcm('conf_phys', 'ok_cdnc must be set to y if ok_aie is activated',1)
     2103       CALL abort_physic('conf_phys', 'ok_cdnc must be set to y if ok_aie is activated',1)
    21042104    ENDIF
    21052105
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/convect3.F90

    r3809 r3814  
    1616  ! #################################################################
    1717  USE dimphy
    18   USE infotrac, ONLY: nbtr
     18  USE infotrac_phy, ONLY: nbtr
    1919  IMPLICIT NONE
    2020  include "dimensions.h"
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cpl_mod.F90

    r3809 r3814  
    2424  USE oasis
    2525  USE write_field_phy
    26   USE control_mod
     26  USE control_phy_mod
    2727
    2828 
     
    102102    USE surface_data
    103103    USE indice_sol_mod
    104 
     104    USE temps_phy_mod
    105105    INCLUDE "dimensions.h"
    106     INCLUDE "temps.h"
    107106    INCLUDE "iniprint.h"
    108107
     
    204203    IF (sum_error /= 0) THEN
    205204       abort_message='Pb allocation variables couplees'
    206        CALL abort_gcm(modname,abort_message,1)
     205       CALL abort_physic(modname,abort_message,1)
    207206    ENDIF
    208207!*************************************************************************************
     
    279278    IF (carbon_cycle_cpl .AND. version_ocean=='opa8') THEN
    280279       abort_message='carbon_cycle_cpl does not work with opa8'
    281        CALL abort_gcm(modname,abort_message,1)
     280       CALL abort_physic(modname,abort_message,1)
    282281    END IF
    283282
     
    297296    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    298297    USE indice_sol_mod
    299 
    300     INCLUDE "temps.h"
     298    USE temps_phy_mod
     299   
    301300    INCLUDE "iniprint.h"
    302301    INCLUDE "YOMCST.h"
     
    668667          IF (sum_error /= 0) THEN
    669668             abort_message='Pb allocation variables couplees pour l''ecriture'
    670              CALL abort_gcm(modname,abort_message,1)
     669             CALL abort_physic(modname,abort_message,1)
    671670          ENDIF
    672671       ENDIF
     
    853852          IF (sum_error /= 0) THEN
    854853             abort_message='Pb allocation variables couplees pour l''ecriture'
    855              CALL abort_gcm(modname,abort_message,1)
     854             CALL abort_physic(modname,abort_message,1)
    856855          ENDIF
    857856       ENDIF
     
    10281027    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    10291028    USE indice_sol_mod
     1029    USE temps_phy_mod
     1030
    10301031! Some includes
    10311032!*************************************************************************************
    1032     INCLUDE "temps.h"
    10331033    INCLUDE "dimensions.h"
    10341034   
     
    12911291    IF (sum_error /= 0) THEN
    12921292       abort_message='Pb in deallocation of cpl_xxxx2D coupling variables'
    1293        CALL abort_gcm(modname,abort_message,1)
     1293       CALL abort_physic(modname,abort_message,1)
    12941294    ENDIF
    12951295   
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cv30_routines.F90

    r3809 r3814  
    813813    WRITE (lunout, *) 'strange! nn not equal to ncum: ', nn, ncum
    814814    abort_message = ''
    815     CALL abort_gcm(modname, abort_message, 1)
     815    CALL abort_physic(modname, abort_message, 1)
    816816  END IF
    817817
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cv3_inicp.F90

    r3809 r3814  
    109109      PRINT *, 'WARNING:: AREA OF MIXING PDF IS::', aire
    110110      abort_message = ''
    111       CALL abort_gcm(modname, abort_message, 1)
     111      CALL abort_physic(modname, abort_message, 1)
    112112    ELSE
    113113      PRINT *, 'Area, mean & std deviation are ::', aire, mu, sigma
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cv3_inip.F90

    r3809 r3814  
    138138      WRITE (lunout, *) 'WARNING:: AREA OF MIXING PDF IS::', aire
    139139      abort_message = ''
    140       CALL abort_gcm(modname, abort_message, 1)
     140      CALL abort_physic(modname, abort_message, 1)
    141141    ELSE
    142142      PRINT *, 'Area, mean & std deviation are ::', aire, mu, sigma
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cv3_routines.F90

    r3809 r3814  
    965965    WRITE (lunout, *) 'strange! nn not equal to ncum: ', nn, ncum
    966966    abort_message = ''
    967     CALL abort_gcm(modname, abort_message, 1)
     967    CALL abort_physic(modname, abort_message, 1)
    968968  END IF
    969969
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cv3a_compress.F90

    r3809 r3814  
    125125    PRINT *, 'WARNING nn not equal to ncum: ', nn, ncum
    126126    abort_message = ''
    127     CALL abort_gcm(modname, abort_message, 1)
     127    CALL abort_physic(modname, abort_message, 1)
    128128  END IF
    129129
     
    155155    PRINT *, 'WARNING nn not equal to ncum: ', nn, ncum
    156156    abort_message = ''
    157     CALL abort_gcm(modname, abort_message, 1)
     157    CALL abort_physic(modname, abort_message, 1)
    158158  END IF
    159159
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cv3p1_closure.F90

    r3809 r3814  
    551551        , il, alp2(il), alp(il), cin(il)
    552552      abort_message = ''
    553       CALL abort_gcm(modname, abort_message, 1)
     553      CALL abort_physic(modname, abort_message, 1)
    554554    END IF
    555555    cbmfmax(il) = sigmax*wb2(il)*100.*p(il, icb(il))/(rrd*tv(il,icb(il)))
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cv_routines.F90

    r3809 r3814  
    453453    WRITE (lunout, *) 'strange! nn not equal to ncum: ', nn, ncum
    454454    abort_message = ''
    455     CALL abort_gcm(modname, abort_message, 1)
     455    CALL abort_physic(modname, abort_message, 1)
    456456  END IF
    457457
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cva_driver.F90

    r3809 r3814  
    671671    WRITE (lunout, *) 'changer la valeur de sig2feed dans physiq.def'
    672672    abort_message = ''
    673     CALL abort_gcm(modname, abort_message, 1)
     673    CALL abort_physic(modname, abort_message, 1)
    674674  END IF
    675675
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cvltr.F90

    r3809 r3814  
    1212  USE IOIPSL
    1313  USE dimphy
    14   USE infotrac, ONLY : nbtr,tname
     14  USE infotrac_phy, ONLY : nbtr,tname
    1515  IMPLICIT NONE
    1616!=====================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cvltr_noscav.F90

    r3809 r3814  
    44SUBROUTINE cvltr_noscav(it,pdtime,da, phi, mp,wght_cvfd,paprs,pplay,x,upd,dnd,dx)
    55  USE dimphy
    6   USE infotrac, ONLY : nbtr
     6  USE infotrac_phy, ONLY : nbtr
    77  IMPLICIT NONE
    88!=====================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cvltr_scav.F90

    r3809 r3814  
    1313  USE IOIPSL
    1414  USE dimphy
    15   USE infotrac, ONLY : nbtr,tname
     15  USE infotrac_phy, ONLY : nbtr,tname
    1616  IMPLICIT NONE
    1717  !=====================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cvltr_spl.F90

    r3809 r3814  
    1313  USE IOIPSL
    1414  USE dimphy
    15   USE infotrac, ONLY : nbtr,tname
     15  USE infotrac_phy, ONLY : nbtr,tname
    1616  IMPLICIT NONE
    1717!=====================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cvltrorig.F90

    r3809 r3814  
    44SUBROUTINE cvltrorig(it,pdtime,da, phi, mp,paprs,pplay,x,upd,dnd,dx)
    55  USE dimphy
    6   USE infotrac, ONLY : nbtr
     6  USE infotrac_phy, ONLY : nbtr
    77  IMPLICIT NONE
    88!=====================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ener_conserv.F90

    r3809 r3814  
    8888   ELSE
    8989      abort_message = 'iflag_ener_conserv non prevu'
    90       CALL abort_gcm (modname,abort_message,1)
     90      CALL abort_physic (modname,abort_message,1)
    9191   ENDIF
    9292
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/fisrtilp.F90

    r3809 r3814  
    2525  !ym include "dimphy.h"
    2626  include "YOMCST.h"
    27   include "tracstoke.h"
    2827  include "fisrtilp.h"
    2928  include "nuage.h" ! JBM (3/14)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/fisrtilp_tr.F90

    r3809 r3814  
    2121  ! ym#include "dimphy.h"
    2222  include "YOMCST.h"
    23   include "tracstoke.h"
    2423  include "iniprint.h"
    2524
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/fonte_neige_mod.F90

    r3809 r3814  
    6363    IF (error /= 0) THEN
    6464       abort_message='Pb allocation run_off_lic'
    65        CALL abort_gcm(modname,abort_message,1)
     65       CALL abort_physic(modname,abort_message,1)
    6666    ENDIF
    6767    run_off_lic_0(:) = restart_runoff(:)
     
    7474    IF (error /= 0) THEN
    7575       abort_message='Pb allocation run_off_ter'
    76        CALL abort_gcm(modname,abort_message,1)
     76       CALL abort_physic(modname,abort_message,1)
    7777    ENDIF
    7878    run_off_ter(:) = 0.
     
    8181    IF (error /= 0) THEN
    8282       abort_message='Pb allocation run_off_lic'
    83        CALL abort_gcm(modname,abort_message,1)
     83       CALL abort_physic(modname,abort_message,1)
    8484    ENDIF
    8585    run_off_lic(:) = 0.
     
    8888    IF (error /= 0) THEN
    8989       abort_message='Pb allocation ffonte_global'
    90        CALL abort_gcm(modname,abort_message,1)
     90       CALL abort_physic(modname,abort_message,1)
    9191    ENDIF
    9292    ffonte_global(:,:) = 0.0
     
    9595    IF (error /= 0) THEN
    9696       abort_message='Pb allocation fqfonte_global'
    97        CALL abort_gcm(modname,abort_message,1)
     97       CALL abort_physic(modname,abort_message,1)
    9898    ENDIF
    9999    fqfonte_global(:,:) = 0.0
     
    102102    IF (error /= 0) THEN
    103103       abort_message='Pb allocation fqcalving_global'
    104        CALL abort_gcm(modname,abort_message,1)
     104       CALL abort_physic(modname,abort_message,1)
    105105    ENDIF
    106106    fqcalving_global(:,:) = 0.0
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/hgardfou.F90

    r3809 r3814  
    129129  END DO
    130130
    131 !  IF (.NOT. ok) CALL abort_gcm(modname, text, 1)
     131!  IF (.NOT. ok) CALL abort_physic(modname, text, 1)
    132132  IF (.NOT. ok) abortphy=1
    133133
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/inifis.F90

    r3809 r3814  
    6060    PRINT *, 'klev   = ', klev
    6161    abort_message = ''
    62     CALL abort_gcm(modname, abort_message, 1)
     62    CALL abort_physic(modname, abort_message, 1)
    6363  END IF
    6464
     
    6969    PRINT *, 'klon   = ', klon
    7070    abort_message = ''
    71     CALL abort_gcm(modname, abort_message, 1)
     71    CALL abort_physic(modname, abort_message, 1)
    7272  END IF
    7373
     
    7676    &                                                         &
    7777    &        et surf.def'
    78   CALL abort_gcm(modname, abort_message, 1)
     78  CALL abort_physic(modname, abort_message, 1)
    7979
    8080END SUBROUTINE inifis
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/init_be.F90

    r3809 r3814  
    66  USE dimphy
    77  USE comgeomphy
    8   USE infotrac, ONLY : nbtr
     8  USE infotrac_phy, ONLY : nbtr
    99  USE indice_sol_mod
    1010   
     
    6565! la source est maintenant définie independemment de la valeur de klev.
    6666!!! Source actuellement definie pour klev = 19 et klev >= 39
    67 !!  IF (klev /= 19 .AND. klev<39) CALL abort_gcm("init_be","Source du be7 necessite klev=19 ou klev>=39",1)
     67!!  IF (klev /= 19 .AND. klev<39) CALL abort_physic("init_be","Source du be7 necessite klev=19 ou klev>=39",1)
    6868!!!
    6969! Definition des constantes
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/init_phys_lmdz.F90

    r3809 r3814  
    22!$Header$
    33!
    4 SUBROUTINE Init_Phys_lmdz(iim,jjp1,llm,nb_proc,distrib)
     4SUBROUTINE Init_Phys_lmdz(iim,jjp1,llm,nb_proc,distrib,communicator)
    55  USE mod_phys_lmdz_para, ONLY: Init_phys_lmdz_para, klon_omp
    66  USE mod_grid_phy_lmdz, ONLY: Init_grid_phy_lmdz, nbp_lev
    77  USE dimphy, ONLY : Init_dimphy
    8   USE infotrac, ONLY : type_trac
     8  USE infotrac_phy, ONLY : type_trac
    99#ifdef REPROBUS
    1010  USE CHEM_REP, ONLY : Init_chem_rep_phys
     
    1818    INTEGER,INTENT(in) :: nb_proc
    1919    INTEGER,INTENT(in) :: distrib(0:nb_proc-1)
     20    INTEGER,INTENT(in) :: communicator
    2021
    2122
    2223    CALL Init_grid_phy_lmdz(iim,jjp1,llm)
    23     CALL Init_phys_lmdz_para(iim,jjp1,nb_proc,distrib)
     24    CALL Init_phys_lmdz_para(iim,jjp1,nb_proc,distrib,communicator)
    2425!$OMP PARALLEL
    2526    CALL Init_dimphy(klon_omp,nbp_lev)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/initphysto.F90

    r3809 r3814  
    88  USE IOIPSL
    99  USE iophy
    10   USE control_mod
     10  USE control_phy_mod
    1111  USE indice_sol_mod
    12  
     12  USE comconst_phy_mod
     13  USE temps_phy_mod
    1314  IMPLICIT NONE
    1415
     
    4041!   Declarations
    4142  INCLUDE "dimensions.h"
    42   INCLUDE "paramet.h"
    43   INCLUDE "comconst.h"
    44   INCLUDE "comgeom.h"
    45   INCLUDE "temps.h"
    46   INCLUDE "logic.h"
    4743  INCLUDE "description.h"
    48   INCLUDE "serre.h"
    4944
    5045!   Arguments
     
    7166!  Initialisations
    7267!
    73   pi = 4. * ATAN (1.)
    7468  ok_sync= .TRUE.
    7569!
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/initrrnpb.F90

    r3809 r3814  
    44SUBROUTINE  initrrnpb(ftsol,pctsrf,masktr,fshtr,hsoltr,tautr,vdeptr,scavtr)
    55  USE dimphy
    6   USE infotrac, ONLY : nbtr
     6  USE infotrac_phy, ONLY : nbtr
    77  USE traclmdz_mod, ONLY : id_rn, id_pb
    88  USE indice_sol_mod
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/interfoce_lim.F90

    r3809 r3814  
    118118        IF (ierr.NE.NF_NOERR) THEN
    119119           abort_message = 'Pb d''ouverture du fichier de conditions aux limites'
    120            CALL abort_gcm(modname,abort_message,1)
     120           CALL abort_physic(modname,abort_message,1)
    121121        ENDIF
    122122
     
    135135           IF (ierr /= NF_NOERR) THEN
    136136              abort_message = 'Le champ <FOCE> est absent'
    137               CALL abort_gcm(modname,abort_message,1)
     137              CALL abort_physic(modname,abort_message,1)
    138138           ENDIF
    139139#ifdef NC_DOUBLE
     
    144144           IF (ierr /= NF_NOERR) THEN
    145145              abort_message = 'Lecture echouee pour <FOCE>'
    146               CALL abort_gcm(modname,abort_message,1)
     146              CALL abort_physic(modname,abort_message,1)
    147147           ENDIF
    148148           !
     
    152152           IF (ierr /= NF_NOERR) THEN
    153153              abort_message = 'Le champ <FSIC> est absent'
    154               CALL abort_gcm(modname,abort_message,1)
     154              CALL abort_physic(modname,abort_message,1)
    155155           ENDIF
    156156#ifdef NC_DOUBLE
     
    161161           IF (ierr /= NF_NOERR) THEN
    162162              abort_message = 'Lecture echouee pour <FSIC>'
    163               CALL abort_gcm(modname,abort_message,1)
     163              CALL abort_physic(modname,abort_message,1)
    164164           ENDIF
    165165           !
     
    169169           IF (ierr /= NF_NOERR) THEN
    170170              abort_message = 'Le champ <FTER> est absent'
    171               CALL abort_gcm(modname,abort_message,1)
     171              CALL abort_physic(modname,abort_message,1)
    172172           ENDIF
    173173#ifdef NC_DOUBLE
     
    178178           IF (ierr /= NF_NOERR) THEN
    179179              abort_message = 'Lecture echouee pour <FTER>'
    180               CALL abort_gcm(modname,abort_message,1)
     180              CALL abort_physic(modname,abort_message,1)
    181181           ENDIF
    182182           !
     
    186186           IF (ierr /= NF_NOERR) THEN
    187187              abort_message = 'Le champ <FLIC> est absent'
    188               CALL abort_gcm(modname,abort_message,1)
     188              CALL abort_physic(modname,abort_message,1)
    189189           ENDIF
    190190#ifdef NC_DOUBLE
     
    195195           IF (ierr /= NF_NOERR) THEN
    196196              abort_message = 'Lecture echouee pour <FLIC>'
    197               CALL abort_gcm(modname,abort_message,1)
     197              CALL abort_physic(modname,abort_message,1)
    198198           ENDIF
    199199           !
     
    203203           IF (ierr /= NF_NOERR) THEN
    204204              abort_message = 'Le champ <NAT> est absent'
    205               CALL abort_gcm(modname,abort_message,1)
     205              CALL abort_physic(modname,abort_message,1)
    206206           ENDIF
    207207#ifdef NC_DOUBLE
     
    212212           IF (ierr /= NF_NOERR) THEN
    213213              abort_message = 'Lecture echouee pour <NAT>'
    214               CALL abort_gcm(modname,abort_message,1)
     214              CALL abort_physic(modname,abort_message,1)
    215215           ENDIF
    216216!
     
    237237        IF (ierr /= NF_NOERR) THEN
    238238           abort_message = 'Le champ <SST> est absent'
    239            CALL abort_gcm(modname,abort_message,1)
     239           CALL abort_physic(modname,abort_message,1)
    240240        ENDIF
    241241#ifdef NC_DOUBLE
     
    246246        IF (ierr /= NF_NOERR) THEN
    247247           abort_message = 'Lecture echouee pour <SST>'
    248            CALL abort_gcm(modname,abort_message,1)
     248           CALL abort_physic(modname,abort_message,1)
    249249        ENDIF
    250250         
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/iophy.F90

    r3809 r3814  
    451451    use phys_output_var_mod, only: type_ecri, zoutm, zdtime_moy, lev_files, &
    452452                                   nid_files, nhorim, swaero_diag, nfiles
     453    USE temps_phy_mod
    453454    IMPLICIT NONE
    454 
    455455    INCLUDE "dimensions.h"
    456     INCLUDE "temps.h"
    457456    INCLUDE "clesphys.h"
    458457
     
    507506                                   nhorim, zdtime_moy, levmin, levmax, &
    508507                                   nvertm, nfiles
     508    USE temps_phy_mod
    509509    IMPLICIT NONE
    510510
    511511    INCLUDE "dimensions.h"
    512     INCLUDE "temps.h"
    513512!    INCLUDE "indicesol.h"
    514513    INCLUDE "clesphys.h"
     
    566565    use wxios, only: wxios_add_field_to_file
    567566#endif
     567    USE temps_phy_mod
    568568    IMPLICIT NONE
    569569
    570570    INCLUDE "dimensions.h"
    571     INCLUDE "temps.h"
    572571    INCLUDE "clesphys.h"
    573572    INCLUDE "iniprint.h"
     
    653652    use wxios, only: wxios_add_field_to_file
    654653#endif
     654    USE temps_phy_mod
    655655    IMPLICIT NONE
    656656
    657657    INCLUDE "dimensions.h"
    658     INCLUDE "temps.h"
    659658    INCLUDE "clesphys.h"
    660659    INCLUDE "iniprint.h"
     
    767766
    768767
    769     IF (size(field)/=klon) CALL abort_gcm('iophy::histwrite2d','Field first DIMENSION not equal to klon',1)
     768    IF (size(field)/=klon) CALL abort_physic('iophy::histwrite2d','Field first DIMENSION not equal to klon',1)
    770769   
    771770    CALL Gather_omp(field,buffer_omp)   
     
    831830
    832831
    833     IF (size(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     832    IF (size(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
    834833    nlev=size(field,2)
    835834
     
    945944
    946945    !Et sinon on.... écrit
    947     IF (SIZE(field)/=klon) CALL abort_gcm('iophy::histwrite2d_phy','Field first DIMENSION not equal to klon',1)
     946    IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_phy','Field first DIMENSION not equal to klon',1)
    948947   
    949948    if (prt_level >= 10) then
     
    971970          endif
    972971#else
    973         CALL abort_gcm ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     972        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
    974973#endif
    975974      ELSE 
     
    10951094  ELSE
    10961095    !Et sinon on.... écrit
    1097     IF (SIZE(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     1096    IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
    10981097    nlev=SIZE(field,2)
    10991098    if (nlev.eq.klev+1) then
     
    11191118          CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
    11201119#else
    1121         CALL abort_gcm ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     1120        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
    11221121#endif
    11231122      ELSE 
     
    12161215
    12171216    !Et sinon on.... écrit
    1218     IF (SIZE(field)/=klon) CALL abort_gcm('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
     1217    IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
    12191218   
    12201219    CALL Gather_omp(field,buffer_omp)   
     
    12861285
    12871286    !Et on.... écrit
    1288     IF (SIZE(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     1287    IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
    12891288    nlev=SIZE(field,2)
    12901289
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/iostart.F90

    r3809 r3814  
    4141        write(6,*)' Pb d''ouverture du fichier '//filename
    4242        write(6,*)' ierr = ', ierr
    43         CALL ABORT_GCM("", "", 1)
     43        CALL abort_physic("", "", 1)
    4444      ENDIF
    4545    ENDIF
     
    166166      IF (.NOT. tmp_found) THEN
    167167        PRINT*, 'phyetat0: Le champ <'//field_name//'> est absent'
    168         call abort_gcm("", "", 1)
     168        call abort_physic("", "", 1)
    169169      ENDIF
    170170    ENDIF
     
    186186              IF (ierr/=NF90_NOERR) THEN
    187187                 PRINT*, 'phyetat0: Lecture echouee aussi en 2D pour <'//field_name//'>'
    188                  call abort_gcm("", "", 1)
     188                 call abort_physic("", "", 1)
    189189              ELSE
    190190                 PRINT*, 'phyetat0: La variable <'//field_name//'> lu sur surface seulement'!, selon ancien format, le reste mis a zero'
    191191              END IF
    192192           ELSE
    193               call abort_gcm("", "", 1)
     193              call abort_physic("", "", 1)
    194194           ENDIF
    195195         ENDIF
     
    282282        IF (ierr/=NF90_NOERR) THEN
    283283          PRINT*, 'phyetat0: Lecture echouee pour <'//var_name//'>'
    284           call abort_gcm("", "", 1)
     284          call abort_physic("", "", 1)
    285285        ENDIF
    286286        tmp_found=.TRUE.
     
    302302      IF (.NOT. tmp_found) THEN
    303303        PRINT*, 'phyetat0: La variable champ <'//var_name//'> est absente'
    304         call abort_gcm("", "", 1)
     304        call abort_physic("", "", 1)
    305305      ENDIF
    306306    ENDIF
     
    323323        write(6,*)' Pb d''ouverture du fichier '//filename
    324324        write(6,*)' ierr = ', ierr
    325         CALL ABORT_GCM("", "", 1)
     325        CALL abort_physic("", "", 1)
    326326      ENDIF
    327327
     
    410410      ELSE
    411411        PRINT *, "erreur phyredem : probleme de dimension"
    412         CALL ABORT_GCM("", "", 1)
     412        CALL abort_physic("", "", 1)
    413413      ENDIF
    414414         
     
    487487      IF (var_size/=length) THEN
    488488        PRINT *, "erreur phyredem : probleme de dimension"
    489         call abort_gcm("", "", 1)
     489        call abort_physic("", "", 1)
    490490      ENDIF
    491491     
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/limit_read_mod.F90

    r3809 r3814  
    195195       IF ( type_ocean /= 'couple' ) THEN
    196196          ALLOCATE(pctsrf(klon,nbsrf), sst(klon), stat=ierr)
    197           IF (ierr /= 0) CALL abort_gcm(modname, 'PB in allocating pctsrf and sst',1)
     197          IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating pctsrf and sst',1)
    198198       END IF
    199199
    200200       IF ( .NOT. ok_veget ) THEN
    201201          ALLOCATE(rugos(klon), albedo(klon), stat=ierr)
    202           IF (ierr /= 0) CALL abort_gcm(modname, 'PB in allocating rugos and albedo',1)
     202          IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating rugos and albedo',1)
    203203       END IF
    204204
     
    220220
    221221          ierr = NF90_OPEN ('limit.nc', NF90_NOWRITE, nid)
    222           IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,&
     222          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,&
    223223               'Pb d''ouverture du fichier de conditions aux limites',1)
    224224         
     
    239239! Ocean fraction
    240240             ierr = NF90_INQ_VARID(nid, 'FOCE', nvarid)
    241              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname, 'Le champ <FOCE> est absent',1)
     241             IF (ierr /= NF90_NOERR) CALL abort_physic(modname, 'Le champ <FOCE> est absent',1)
    242242             
    243243             ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_oce),start,epais)
    244              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <FOCE>' ,1)
     244             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FOCE>' ,1)
    245245!
    246246! Sea-ice fraction
    247247             ierr = NF90_INQ_VARID(nid, 'FSIC', nvarid)
    248              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <FSIC> est absent',1)
     248             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FSIC> est absent',1)
    249249
    250250             ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_sic),start,epais)
    251              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <FSIC>' ,1)
     251             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FSIC>' ,1)
    252252
    253253
     
    257257! Land fraction
    258258                ierr = NF90_INQ_VARID(nid, 'FTER', nvarid)
    259                 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <FTER> est absent',1)
     259                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FTER> est absent',1)
    260260               
    261261                ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_ter),start,epais)
    262                 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <FTER>',1)
     262                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FTER>',1)
    263263!
    264264! Continentale ice fraction
    265265                ierr = NF90_INQ_VARID(nid, 'FLIC', nvarid)
    266                 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <FLIC> est absent',1)
     266                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FLIC> est absent',1)
    267267
    268268                ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_lic),start,epais)
    269                 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <FLIC>',1)
     269                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FLIC>',1)
    270270             END IF
    271271
     
    279279
    280280             ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
    281              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <SST> est absent',1)
     281             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <SST> est absent',1)
    282282
    283283             ierr = NF90_GET_VAR(nid,nvarid,sst_glo,start,epais)
    284              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <SST>',1)
     284             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <SST>',1)
    285285         
    286286          END IF
     
    295295! Read albedo
    296296             ierr = NF90_INQ_VARID(nid, 'ALB', nvarid)
    297              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <ALB> est absent',1)
     297             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <ALB> est absent',1)
    298298
    299299             ierr = NF90_GET_VAR(nid,nvarid,alb_glo,start,epais)
    300              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <ALB>',1)
     300             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <ALB>',1)
    301301!
    302302! Read rugosity
    303303             ierr = NF90_INQ_VARID(nid, 'RUG', nvarid)
    304              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <RUG> est absent',1)
     304             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <RUG> est absent',1)
    305305
    306306             ierr = NF90_GET_VAR(nid,nvarid,rug_glo,start,epais)
    307              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <RUG>',1)
     307             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <RUG>',1)
    308308
    309309          END IF
     
    314314!****************************************************************************************
    315315          ierr = NF90_CLOSE(nid)
    316           IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1)
     316          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
    317317       ENDIF ! is_mpi_root
    318318
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/limit_slab.F90

    r3809 r3814  
    1111  IMPLICIT NONE
    1212
    13   INCLUDE "temps.h"
    1413  INCLUDE "clesphys.h"
    1514  INCLUDE "dimensions.h"
     
    113112!****************************************************************************************
    114113        ierr = NF90_CLOSE(nid)
    115         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1)
     114        IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
    116115        END IF ! Read File
    117116        IF (read_sst) THEN
     
    133132     IF (.NOT. ALLOCATED(bils_save)) THEN
    134133        ALLOCATE(bils_save(klon), diff_sst_save(klon), diff_siv_save(klon), stat=ierr)
    135         IF (ierr /= 0) CALL abort_gcm('limit_slab', 'pb in allocation',1)
     134        IF (ierr /= 0) CALL abort_physic('limit_slab', 'pb in allocation',1)
    136135     END IF
    137136
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/lsc_scav.F90

    r3809 r3814  
    99  USE mod_phys_lmdz_para
    1010  USE traclmdz_mod
    11   USE infotrac,ONLY : nbtr
     11  USE infotrac_phy,ONLY : nbtr
    1212  USE comgeomphy
    1313  USE iophy
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/mod_surf_para.F90

    r3809 r3814  
    4949
    5050  SUBROUTINE Init_surf_para(knon)
    51   USE mod_phys_lmdz_para, mpi_rank_root=>mpi_root
     51  USE mod_phys_lmdz_para
    5252#ifdef CPP_MPI
    5353  INCLUDE 'mpif.h'
     
    168168     
    169169  SUBROUTINE gather_surf_mpi_i(FieldIn,FieldOut)
    170   USE mod_phys_lmdz_para, mpi_rank_root => mpi_root
     170  USE mod_phys_lmdz_para
    171171#ifdef CPP_MPI
    172172  INCLUDE 'mpif.h'
     
    180180      CALL MPI_Gatherv(FieldIn,knon_mpi,MPI_INTEGER,                                &
    181181                       FieldOut,knon_mpi_para,knon_mpi_begin_para(:)-1,MPI_INTEGER, &
    182                        mpi_rank_root,COMM_LMDZ_PHY,ierr)
     182                       mpi_master,COMM_LMDZ_PHY,ierr)
    183183#endif
    184184    ELSE
     
    223223     
    224224  SUBROUTINE gather_surf_mpi_r(FieldIn,FieldOut)
    225   USE mod_phys_lmdz_para, mpi_rank_root => mpi_root
     225  USE mod_phys_lmdz_para
    226226#ifdef CPP_MPI
    227227  INCLUDE 'mpif.h'
     
    235235      CALL MPI_Gatherv(FieldIn,knon_mpi,MPI_REAL_LMDZ,                                 &
    236236                       FieldOut,knon_mpi_para,knon_mpi_begin_para(:)-1,MPI_REAL_LMDZ,  &
    237                        mpi_rank_root,COMM_LMDZ_PHY,ierr)           
     237                       mpi_master,COMM_LMDZ_PHY,ierr)           
    238238#endif
    239239    ELSE
     
    276276     
    277277  SUBROUTINE scatter_surf_mpi_i(FieldIn,FieldOut)
    278   USE mod_phys_lmdz_para, mpi_rank_root => mpi_root
     278  USE mod_phys_lmdz_para
    279279#ifdef CPP_MPI
    280280  INCLUDE 'mpif.h'
     
    288288      CALL MPI_Scatterv(FieldIn,knon_mpi_para,knon_mpi_begin_para(:)-1,MPI_INTEGER,   &
    289289                        FieldOut,knon_mpi,MPI_INTEGER,                                &
    290                         mpi_rank_root,COMM_LMDZ_PHY,ierr)
     290                        mpi_master,COMM_LMDZ_PHY,ierr)
    291291#endif
    292292    ELSE
     
    328328     
    329329  SUBROUTINE scatter_surf_mpi_r(FieldIn,FieldOut)
    330   USE mod_phys_lmdz_para, mpi_rank_root => mpi_root
     330  USE mod_phys_lmdz_para
    331331#ifdef CPP_MPI
    332332  INCLUDE 'mpif.h'
     
    340340      CALL MPI_Scatterv(FieldIn,knon_mpi_para,knon_mpi_begin_para(:)-1,MPI_INTEGER,   &
    341341                        FieldOut,knon_mpi,MPI_INTEGER,                                &
    342                         mpi_rank_root,COMM_LMDZ_PHY,ierr)
     342                        mpi_master,COMM_LMDZ_PHY,ierr)
    343343#endif
    344344    ELSE
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/o3_chem_m.F90

    r3809 r3814  
    2020    use dimphy, only: klon
    2121    use regr_pr_comb_coefoz_m, only: c_Mob, a4_mass, a2, r_het_interm
    22 
     22    use comconst_phy_mod
     23   
    2324    integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
    2425    real, intent(in):: gmtime ! heure de la journée en fraction de jour
     
    3940    ! Variables local to the procedure:
    4041    include "dimensions.h"
    41     include "comconst.h"
    4242    ! (for "pi")
    4343    integer k
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/o3cm.F90

    r3809 r3814  
    3232  IF (ntab>499) THEN
    3333    abort_message = 'BIG ntab'
    34     CALL abort_gcm(modname, abort_message, 1)
     34    CALL abort_physic(modname, abort_message, 1)
    3535  END IF
    3636  xincr = (bmb-amb)/real(ntab)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/oasis.F90

    r3809 r3814  
    218218       IF (ierror .NE. PRISM_Ok) THEN
    219219          abort_message=' Probleme init dans prism_init_comp '
    220           CALL abort_gcm(modname,abort_message,1)
     220          CALL abort_physic(modname,abort_message,1)
    221221       ELSE
    222222          WRITE(lunout,*) 'inicma : init psmile ok '
     
    240240    IF (ierror .NE. PRISM_Ok) THEN
    241241       abort_message=' Probleme dans prism_def_partition '
    242        CALL abort_gcm(modname,abort_message,1)
     242       CALL abort_physic(modname,abort_message,1)
    243243    ELSE
    244244       WRITE(lunout,*) 'inicma : decomposition domaine psmile ok '
     
    268268                  inforecv(jf)%name
    269269             abort_message=' Problem in call to prism_def_var_proto for fields to receive'
    270              CALL abort_gcm(modname,abort_message,1)
     270             CALL abort_physic(modname,abort_message,1)
    271271          ENDIF
    272272       ENDIF
     
    286286                  infosend(jf)%name
    287287             abort_message=' Problem in call to prism_def_var_proto for fields to send'
    288              CALL abort_gcm(modname,abort_message,1)
     288             CALL abort_physic(modname,abort_message,1)
    289289          ENDIF
    290290       ENDIF
     
    297297    IF (ierror .NE. PRISM_Ok) THEN
    298298       abort_message=' Problem in call to prism_endef_proto'
    299        CALL abort_gcm(modname,abort_message,1)
     299       CALL abort_physic(modname,abort_message,1)
    300300    ELSE
    301301       WRITE(lunout,*) 'inicma : endef psmile ok '
     
    362362              WRITE (lunout,*)  'Error with receiving filed : ', inforecv(i)%name, ktime   
    363363              abort_message=' Problem in prism_get_proto '
    364               CALL abort_gcm(modname,abort_message,1)
     364              CALL abort_physic(modname,abort_message,1)
    365365          ENDIF
    366366      ENDIF
     
    444444              WRITE (lunout,*) 'Error with sending field :', infosend(i)%name, ktime   
    445445              abort_message=' Problem in prism_put_proto '
    446               CALL abort_gcm(modname,abort_message,1)
     446              CALL abort_physic(modname,abort_message,1)
    447447          ENDIF
    448448      ENDIF
     
    459459          IF (ierror .NE. PRISM_Ok) THEN
    460460             abort_message=' Problem in prism_terminate_proto '
    461              CALL abort_gcm(modname,abort_message,1)
     461             CALL abort_physic(modname,abort_message,1)
    462462          ENDIF
    463463       ENDIF
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ocean_slab_mod.F90

    r3809 r3814  
    110110    IF (error /= 0) THEN
    111111       abort_message='Pb allocation tmp_pctsrf_slab'
    112        CALL abort_gcm(modname,abort_message,1)
     112       CALL abort_physic(modname,abort_message,1)
    113113    ENDIF
    114114    fsic(:)=0.
     
    121121!****************************************************************************************
    122122    ALLOCATE(tslab(klon,nslay), stat=error)
    123        IF (error /= 0) CALL abort_gcm &
     123       IF (error /= 0) CALL abort_physic &
    124124         (modname,'pb allocation tslab', 1)
    125125
     
    127127    IF (error /= 0) THEN
    128128       abort_message='Pb allocation slab_bils'
    129        CALL abort_gcm(modname,abort_message,1)
     129       CALL abort_physic(modname,abort_message,1)
    130130    ENDIF
    131131    slab_bils(:) = 0.0   
     
    133133    IF (error /= 0) THEN
    134134       abort_message='Pb allocation slab_bils_cum'
    135        CALL abort_gcm(modname,abort_message,1)
     135       CALL abort_physic(modname,abort_message,1)
    136136    ENDIF
    137137    bils_cum(:) = 0.0   
     
    141141        IF (error /= 0) THEN
    142142           abort_message='Pb allocation slab_bilg'
    143            CALL abort_gcm(modname,abort_message,1)
     143           CALL abort_physic(modname,abort_message,1)
    144144        ENDIF
    145145        slab_bilg(:) = 0.0   
     
    147147        IF (error /= 0) THEN
    148148           abort_message='Pb allocation slab_bilg_cum'
    149            CALL abort_gcm(modname,abort_message,1)
     149           CALL abort_physic(modname,abort_message,1)
    150150        ENDIF
    151151        bilg_cum(:) = 0.0   
     
    153153        IF (error /= 0) THEN
    154154           abort_message='Pb allocation slab_tice'
    155            CALL abort_gcm(modname,abort_message,1)
     155           CALL abort_physic(modname,abort_message,1)
    156156        ENDIF
    157157        ALLOCATE(seaice(klon), stat = error)
    158158        IF (error /= 0) THEN
    159159           abort_message='Pb allocation slab_seaice'
    160            CALL abort_gcm(modname,abort_message,1)
     160           CALL abort_physic(modname,abort_message,1)
    161161        ENDIF
    162162    END IF
     
    169169    IF (error /= 0) THEN
    170170       abort_message='Pb allocation slabh'
    171        CALL abort_gcm(modname,abort_message,1)
     171       CALL abort_physic(modname,abort_message,1)
    172172    ENDIF
    173173    slabh(1)=50.
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/orografi.F90

    r3809 r3814  
    13691369  IF (nlon/=klon .OR. nlev/=klev) THEN
    13701370    abort_message = 'pb dimension'
    1371     CALL abort_gcm(modname, abort_message, 1)
     1371    CALL abort_physic(modname, abort_message, 1)
    13721372  END IF
    13731373  zcons1 = 1./rd
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/orografi_strato.F90

    r3809 r3814  
    15581558  IF (nlon/=klon .OR. nlev/=klev) THEN
    15591559    abort_message = 'pb dimension'
    1560     CALL abort_gcm(modname, abort_message, 1)
     1560    CALL abort_physic(modname, abort_message, 1)
    15611561  END IF
    15621562  zcons1 = 1./rd
     
    18731873  PRINT *, ' DANS SUGWD nktopg=', nktopg
    18741874  PRINT *, ' DANS SUGWD nstra=', nstra
    1875   if (nstra == 0) call abort_gcm("sugwd_strato", "no level in stratosphere", 1)
     1875  if (nstra == 0) call abort_physic("sugwd_strato", "no level in stratosphere", 1)
    18761876
    18771877  gsigcr = 0.80
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/pbl_surface_mod.F90

    r3809 r3814  
    2323  USE climb_wind_mod,      ONLY : climb_wind_down, climb_wind_up
    2424  USE coef_diff_turb_mod,  ONLY : coef_diff_turb
    25   USE control_mod
     25  USE control_phy_mod
    2626
    2727
     
    7373!****************************************************************************************   
    7474    ALLOCATE(fder(klon), stat=ierr)
    75     IF (ierr /= 0) CALL abort_gcm('pbl_surface_init', 'pb in allocation',1)
     75    IF (ierr /= 0) CALL abort_physic('pbl_surface_init', 'pb in allocation',1)
    7676
    7777    ALLOCATE(snow(klon,nbsrf), stat=ierr)
    78     IF (ierr /= 0) CALL abort_gcm('pbl_surface_init', 'pb in allocation',1)
     78    IF (ierr /= 0) CALL abort_physic('pbl_surface_init', 'pb in allocation',1)
    7979
    8080    ALLOCATE(qsurf(klon,nbsrf), stat=ierr)
    81     IF (ierr /= 0) CALL abort_gcm('pbl_surface_init', 'pb in allocation',1)
     81    IF (ierr /= 0) CALL abort_physic('pbl_surface_init', 'pb in allocation',1)
    8282
    8383    ALLOCATE(ftsoil(klon,nsoilmx,nbsrf), stat=ierr)
    84     IF (ierr /= 0) CALL abort_gcm('pbl_surface_init', 'pb in allocation',1)
     84    IF (ierr /= 0) CALL abort_physic('pbl_surface_init', 'pb in allocation',1)
    8585
    8686
     
    100100      WRITE(lunout,*)"or on doit commencer par les surfaces continentales"
    101101      abort_message="voir ci-dessus"
    102       CALL abort_gcm(modname,abort_message,1)
     102      CALL abort_physic(modname,abort_message,1)
    103103    ENDIF
    104104
     
    109109      WRITE(lunout,*)' or is_oce = ',is_oce, '> is_sic = ',is_sic
    110110      abort_message='voir ci-dessus'
    111       CALL abort_gcm(modname,abort_message,1)
     111      CALL abort_physic(modname,abort_message,1)
    112112    ENDIF
    113113
     
    118118      WRITE(lunout,*)' or is_lic = ',is_lic, '> is_sic = ',is_sic
    119119      abort_message='voir ci-dessus'
    120       CALL abort_gcm(modname,abort_message,1)
     120      CALL abort_physic(modname,abort_message,1)
    121121    ENDIF
    122122
     
    130130       WRITE(lunout,*)'Option couplage pour l''ocean = ', type_ocean
    131131       abort_message='option pour l''ocean non valable'
    132        CALL abort_gcm(modname,abort_message,1)
     132       CALL abort_physic(modname,abort_message,1)
    133133    ENDIF
    134134
     
    261261    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    262262    USE indice_sol_mod
    263 
     263    USE temps_phy_mod
    264264    IMPLICIT NONE
    265265
     
    272272    INCLUDE "compbl.h"
    273273    INCLUDE "dimensions.h"
    274     INCLUDE "temps.h"
    275274    INCLUDE "flux_arp.h"
    276275!****************************************************************************************
     
    18371836          WRITE(lunout,*) 'Surface index = ', nsrf
    18381837          abort_message = 'Surface index not valid'
    1839           CALL abort_gcm(modname,abort_message,1)
     1838          CALL abort_physic(modname,abort_message,1)
    18401839       END SELECT
    18411840
     
    30493048                ! Security abort. This option has never been tested. To test, comment the following line.
    30503049!                abort_message='The fraction of the continents have changed!'
    3051 !                CALL abort_gcm(modname,abort_message,1)
     3050!                CALL abort_physic(modname,abort_message,1)
    30523051                nfois(nsrf) = nfois(nsrf) + 1
    30533052             END IF
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyaqua_mod.F90

    r3809 r3814  
    2525    USE fonte_neige_mod, ONLY: fonte_neige_init
    2626    USE phys_state_var_mod
    27     USE control_mod, ONLY: dayref, nday, iphysiq
     27    USE control_phy_mod, ONLY: dayref, nday, iphysiq
    2828    USE indice_sol_mod
    29 
     29    USE temps_phy_mod
     30    USE comconst_phy_mod
    3031    USE ioipsl
    3132    IMPLICIT NONE
     
    3435    ! #include "dimphy.h"
    3536    ! #include "YOMCST.h"
    36     include "comconst.h"
     37!    include "comconst.h"
    3738    include "clesphys.h"
    3839    include "dimsoil.h"
    39     include "temps.h"
     40!    include "temps.h"
    4041
    4142    INTEGER, INTENT (IN) :: nlon, iflag_phys
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyetat0.F90

    r3809 r3814  
    2121       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl
    2222  USE iostart, ONLY : close_startphy, get_field, get_var, open_startphy
    23   USE infotrac, only: nbtr, type_trac, tname, niadv
     23  USE infotrac_phy, only: nbtr, type_trac, tname, niadv
    2424  USE traclmdz_mod,    ONLY : traclmdz_from_restart
    2525  USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl, co2_send
    2626  USE indice_sol_mod, only: nbsrf, is_ter, epsfra, is_lic, is_oce, is_sic
    2727  USE ocean_slab_mod, ONLY: tslab, seaice, tice, ocean_slab_init
     28  USE temps_phy_mod
    2829
    2930  IMPLICIT none
     
    3637  include "dimsoil.h"
    3738  include "clesphys.h"
    38   include "temps.h"
    3939  include "thermcell.h"
    4040  include "compbl.h"
     
    211211        IF (nsrf.GT.99) THEN
    212212           PRINT*, "Trop de sous-mailles"
    213            call abort_gcm("phyetat0", "", 1)
     213           call abort_physic("phyetat0", "", 1)
    214214        ENDIF
    215215        WRITE(str2, '(i2.2)') nsrf
     
    248248        IF (isw.GT.99 .AND. nsrf.GT.99) THEN
    249249           PRINT*, "Trop de bandes SW ou sous-mailles"
    250            call abort_gcm("phyetat0", "", 1)
     250           call abort_physic("phyetat0", "", 1)
    251251        ENDIF
    252252        WRITE(str7, '(i2.2, "srf", i2.2)') isw, nsrf
     
    278278        IF (isoil.GT.99 .AND. nsrf.GT.99) THEN
    279279           PRINT*, "Trop de couches ou sous-mailles"
    280            call abort_gcm("phyetat0", "", 1)
     280           call abort_physic("phyetat0", "", 1)
    281281        ENDIF
    282282        WRITE(str7, '(i2.2, "srf", i2.2)') isoil, nsrf
     
    303303        IF (nsrf.GT.99) THEN
    304304           PRINT*, "Trop de sous-mailles"
    305            call abort_gcm("phyetat0", "", 1)
     305           call abort_physic("phyetat0", "", 1)
    306306        ENDIF
    307307        WRITE(str2, '(i2.2)') nsrf
     
    358358        IF (nsrf.GT.99) THEN
    359359           PRINT*, "Trop de sous-mailles"
    360            call abort_gcm("phyetat0", "", 1)
     360           call abort_physic("phyetat0", "", 1)
    361361        ENDIF
    362362        WRITE(str2, '(i2.2)') nsrf
     
    396396        IF (nsrf.GT.99) THEN
    397397           PRINT*, "Trop de sous-mailles"
    398            call abort_gcm("phyetat0", "", 1)
     398           call abort_physic("phyetat0", "", 1)
    399399        ENDIF
    400400        WRITE(str2, '(i2.2)') nsrf
     
    533533        IF (nsrf.GT.99) THEN
    534534           PRINT*, "Trop de sous-mailles"
    535            call abort_gcm("phyetat0", "", 1)
     535           call abort_physic("phyetat0", "", 1)
    536536        ENDIF
    537537        WRITE(str2, '(i2.2)') nsrf
     
    570570        IF (nsrf.GT.99) THEN
    571571           PRINT*, "Trop de sous-mailles"
    572            call abort_gcm("phyetat0", "", 1)
     572           call abort_physic("phyetat0", "", 1)
    573573        ENDIF
    574574        WRITE(str2, '(i2.2)') nsrf
     
    695695        IF (nsrf.GT.99) THEN
    696696           PRINT*, "Trop de sous-mailles"
    697            call abort_gcm("phyetat0", "", 1)
     697           call abort_physic("phyetat0", "", 1)
    698698        ENDIF
    699699        WRITE(str2, '(i2.2)') nsrf
     
    715715      IF (nsrf.GT.99) THEN
    716716        PRINT*, "Trop de sous-mailles"
    717         call abort_gcm("phyetat0", "", 1)
     717        call abort_physic("phyetat0", "", 1)
    718718      ENDIF
    719719      WRITE(str2,'(i2.2)') nsrf
     
    734734       IF (nsrf.GT.99) THEN
    735735         PRINT*, "Trop de sous-mailles"
    736          call abort_gcm("phyetat0", "", 1)
     736         call abort_physic("phyetat0", "", 1)
    737737       ENDIF
    738738       WRITE(str2,'(i2.2)') nsrf
     
    923923     IF (nbsrf.GT.99) THEN
    924924        WRITE(lunout,*) "Trop de sous-mailles"
    925         call abort_gcm("phyetat0", "", 1)
     925        call abort_physic("phyetat0", "", 1)
    926926     ENDIF
    927927
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phyredem.F90

    r3809 r3814  
    1111  USE iostart
    1212  USE traclmdz_mod, ONLY : traclmdz_to_restart
    13   USE infotrac
    14   USE control_mod
     13  USE infotrac_phy
     14  USE control_phy_mod
    1515  USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    1616  USE indice_sol_mod
    1717  USE surface_data
    1818  USE ocean_slab_mod, ONLY : tslab, seaice, tice, fsic
     19  USE temps_phy_mod
    1920
    2021  IMPLICIT none
     
    2627  include "dimsoil.h"
    2728  include "clesphys.h"
    28   include "temps.h"
    2929  include "thermcell.h"
    3030  include "compbl.h"
     
    133133     ELSE
    134134        PRINT*, "Trop de sous-mailles"
    135         call abort_gcm("phyredem", "", 1)
     135        call abort_physic("phyredem", "", 1)
    136136     ENDIF
    137137  ENDDO
     
    150150        ELSE
    151151           PRINT*, "Trop de couches"
    152            call abort_gcm("phyredem", "", 1)
     152           call abort_physic("phyredem", "", 1)
    153153        ENDIF
    154154     ENDDO
     
    164164        ELSE
    165165           PRINT*, "Trop de couches"
    166            call abort_gcm("phyredem", "", 1)
     166           call abort_physic("phyredem", "", 1)
    167167        ENDIF
    168168     ENDDO
     
    176176     ELSE
    177177        PRINT*, "Trop de sous-mailles"
    178         call abort_gcm("phyredem", "", 1)
     178        call abort_physic("phyredem", "", 1)
    179179     ENDIF
    180180  END DO
     
    189189     ELSE
    190190        PRINT*, "Trop de sous-mailles"
    191         call abort_gcm("phyredem", "", 1)
     191        call abort_physic("phyredem", "", 1)
    192192     ENDIF
    193193  ENDDO
     
    200200     ELSE
    201201        PRINT*, "Trop de sous-mailles"
    202         call abort_gcm("phyredem", "", 1)
     202        call abort_physic("phyredem", "", 1)
    203203     ENDIF
    204204  ENDDO
     
    227227     ELSE
    228228        PRINT*, "Trop de sous-mailles"
    229         call abort_gcm("phyredem", "", 1)
     229        call abort_physic("phyredem", "", 1)
    230230     ENDIF
    231231  ENDDO
     
    239239     ELSE
    240240        PRINT*, "Trop de sous-mailles"
    241         call abort_gcm("phyredem", "", 1)
     241        call abort_physic("phyredem", "", 1)
    242242     ENDIF
    243243  ENDDO
     
    287287        ELSE
    288288           PRINT*, "Trop de sous-mailles"
    289            call abort_gcm("phyredem", "", 1)
     289           call abort_physic("phyredem", "", 1)
    290290        ENDIF
    291291     ENDDO
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_local_var_mod.F90

    r3809 r3814  
    375375SUBROUTINE phys_local_var_init
    376376USE dimphy
    377 USE infotrac, ONLY : nbtr
     377USE infotrac_phy, ONLY : nbtr
    378378USE aero_mod
    379379USE indice_sol_mod
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_mod.F90

    r3809 r3814  
    3636    USE iophy
    3737    USE dimphy
    38     USE infotrac
     38    USE infotrac_phy
    3939    USE ioipsl
    4040    USE phys_cal_mod, only : hour
     
    4545    USE phys_output_ctrlout_mod
    4646    USE mod_grid_phy_lmdz, only: klon_glo
    47 
     47    USE temps_phy_mod
     48    Use comvert_phy_mod
    4849#ifdef CPP_XIOS
    4950    ! ug Pour les sorties XIOS
     
    5354    IMPLICIT NONE
    5455    include "dimensions.h"
    55     include "temps.h"
    5656    include "clesphys.h"
    5757    include "thermcell.h"
    58     include "comvert.h"
    5958    include "iniprint.h"
    6059
     
    523522    use ioipsl
    524523    USE phys_cal_mod
    525 
     524    USE comconst_phy_mod
     525    USE temps_phy_mod
    526526    IMPLICIT NONE
    527527
     
    531531    real                :: ttt,xxx,timestep,dayseconde,dtime
    532532    parameter (dayseconde=86400.)
    533     include "temps.h"
    534     include "comconst.h"
    535533    include "iniprint.h"
    536534
     
    540538    WRITE(lunout,*) "ipos = ", ipos
    541539    WRITE(lunout,*) "il = ", il
    542     if (ipos == 0) call abort_gcm("convers_timesteps", "bad str", 1)
     540    if (ipos == 0) call abort_physic("convers_timesteps", "bad str", 1)
    543541    read(str(1:ipos),*) ttt
    544542    WRITE(lunout,*)ttt
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_write_mod.F90

    r3809 r3814  
    2525
    2626    USE dimphy, only: klon, klev, klevp1, nslay
    27     USE control_mod, only: day_step, iphysiq
     27    USE control_phy_mod, only: day_step, iphysiq
    2828    USE phys_output_ctrlout_mod, only: o_phis, o_aire, is_ter, is_lic, is_oce, &
    2929         is_ave, is_sic, o_contfracATM, o_contfracOR, &
     
    232232    USE pbl_surface_mod, only: snow
    233233    USE indice_sol_mod, only: nbsrf
    234     USE infotrac, only: nqtot, nqo, type_trac
     234    USE infotrac_phy, only: nqtot, nqo, type_trac
    235235    USE comgeomphy, only: airephy
    236236    USE surface_data, only: type_ocean, version_ocean, ok_veget, ok_snow
     
    247247#endif
    248248    USE phys_cal_mod, only : mth_len
    249 
     249    USE temps_phy_mod
    250250
    251251    IMPLICIT NONE
    252252
    253253
    254     INCLUDE "temps.h"
    255254    INCLUDE "clesphys.h"
    256255    INCLUDE "thermcell.h"
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_state_var_mod.F90

    r3809 r3814  
    402402SUBROUTINE phys_state_var_init(read_climoz)
    403403USE dimphy
    404 USE control_mod
     404!USE control_mod
    405405USE aero_mod
    406 USE infotrac, ONLY : nbtr
     406USE infotrac_phy, ONLY : nbtr
    407407USE indice_sol_mod
    408408IMPLICIT NONE
     
    587587SUBROUTINE phys_state_var_end
    588588USE dimphy
    589 USE control_mod
     589!USE control_mod
    590590USE indice_sol_mod
    591591IMPLICIT NONE
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/physiq.F90

    r3809 r3814  
    1717  USE write_field_phy
    1818  USE dimphy
    19   USE infotrac
     19  USE infotrac_phy
    2020  USE mod_grid_phy_lmdz
    2121  USE mod_phys_lmdz_para
     
    4646  use radlwsw_m, only: radlwsw
    4747  use phyaqua_mod, only: zenang_an
    48   USE control_mod
     48  USE control_phy_mod
     49  USE temps_phy_mod
    4950#ifdef REPROBUS
    5051  USE CHEM_REP, ONLY : Init_chem_rep_xjour
     
    114115  include "dimsoil.h"
    115116  include "clesphys.h"
    116   include "temps.h"
     117!  include "temps.h"
    117118  include "iniprint.h"
    118119  include "thermcell.h"
     
    516517  EXTERNAL suphel    ! initialiser certaines constantes
    517518  EXTERNAL transp    ! transport total de l'eau et de l'energie
    518   EXTERNAL ecribina  ! ecrire le fichier binaire global
    519   EXTERNAL ecribins  ! ecrire le fichier binaire global
    520   EXTERNAL ecrirega  ! ecrire le fichier binaire regional
    521   EXTERNAL ecriregs  ! ecrire le fichier binaire regional
    522519  !IM
    523520  EXTERNAL haut2bas  !variables de haut en bas
     
    10311028     IF (iflag_con.EQ.2.AND.iflag_cld_th.GT.-1) THEN
    10321029        abort_message = 'Tiedtke needs iflag_cld_th=-2 or -1'
    1033         CALL abort_gcm (modname,abort_message,1)
     1030        CALL abort_physic (modname,abort_message,1)
    10341031     ENDIF
    10351032     !
     
    10901087             pdtphys
    10911088        abort_message='Pas physique n est pas correct '
    1092         !           call abort_gcm(modname,abort_message,1)
     1089
    10931090        dtime=pdtphys
    10941091     ENDIF
     
    10971094             klon
    10981095        abort_message='nlon et klon ne sont pas coherents'
    1099         call abort_gcm(modname,abort_message,1)
     1096        call abort_physic(modname,abort_message,1)
    11001097     ENDIF
    11011098     IF (nlev .NE. klev) THEN
     
    11031100             klev
    11041101        abort_message='nlev et klev ne sont pas coherents'
    1105         call abort_gcm(modname,abort_message,1)
     1102        call abort_physic(modname,abort_message,1)
    11061103     ENDIF
    11071104     !
     
    11101107        WRITE(lunout,*)"Au minimum 4 appels par jour si cycle diurne"
    11111108        abort_message='Nbre d appels au rayonnement insuffisant'
    1112         call abort_gcm(modname,abort_message,1)
     1109        call abort_physic(modname,abort_message,1)
    11131110     ENDIF
    11141111     WRITE(lunout,*)"Clef pour la convection, iflag_con=", iflag_con
     
    11651162           IF(nCFMIP.GT.npCFMIP) THEN
    11661163              print*,'nCFMIP > npCFMIP : augmenter npCFMIP et recompiler'
    1167               call abort_gcm("physiq", "", 1)
     1164              call abort_physic("physiq", "", 1)
    11681165           else
    11691166              print*,'physiq npCFMIP=',npCFMIP,'nCFMIP=',nCFMIP
     
    16641661        IF (read_climoz/=-1) THEN
    16651662           abort_message ='read_climoz=-1 is recommended when solarlong0=1000.'
    1666            CALL abort_gcm (modname,abort_message,1)
     1663           CALL abort_physic (modname,abort_message,1)
    16671664        ENDIF
    16681665     ELSE
     
    20472044  IF (iflag_con.EQ.1) THEN
    20482045     abort_message ='reactiver le call conlmd dans physiq.F'
    2049      CALL abort_gcm (modname,abort_message,1)
     2046     CALL abort_physic (modname,abort_message,1)
    20502047     !     CALL conlmd (dtime, paprs, pplay, t_seri, q_seri, conv_q,
    20512048     !    .             d_t_con, d_q_con,
     
    21852182           else
    21862183       abort_message ='Ne pas passer la car www non calcule'
    2187        CALL abort_gcm (modname,abort_message,1)
     2184       CALL abort_physic (modname,abort_message,1)
    21882185
    21892186!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    23512348  ELSE
    23522349     WRITE(lunout,*) "iflag_con non-prevu", iflag_con
    2353      call abort_gcm("physiq", "", 1)
     2350     call abort_physic("physiq", "", 1)
    23542351  ENDIF
    23552352
     
    30173014           IF (aerosol_couple .AND. config_inca == 'aero' ) THEN
    30183015            abort_message='config_inca=aero et rrtm=1 impossible'
    3019             call abort_gcm(modname,abort_message,1)
     3016            call abort_physic(modname,abort_message,1)
    30203017           ELSE
    30213018!
     
    30323029
    30333030              abort_message='You should compile with -rrtm if running with iflag_rrtm=1'
    3034               call abort_gcm(modname,abort_message,1)
     3031              call abort_physic(modname,abort_message,1)
    30353032#endif
    30363033              !
     
    30653062
    30663063           abort_message='You should compile with -rrtm if running with iflag_rrtm=1'
    3067            call abort_gcm(modname,abort_message,1)
     3064           call abort_physic(modname,abort_message,1)
    30683065#endif
    30693066        ENDIF
     
    32943291        IF (ok_cdnc.AND.NRADLP.NE.3) THEN
    32953292           abort_message='RRTM choix incoherent NRADLP doit etre egal a 3 pour ok_cdnc'
    3296            call abort_gcm(modname,abort_message,1)
     3293           call abort_physic(modname,abort_message,1)
    32973294        endif
    32983295#else
    32993296
    33003297        abort_message='You should compile with -rrtm if running with iflag_rrtm=1'
    3301         call abort_gcm(modname,abort_message,1)
     3298        call abort_physic(modname,abort_message,1)
    33023299#endif
    33033300     ENDIF
     
    41744171    IF (abortphy==1) THEN
    41754172       abort_message ='Plantage hgardfou'
    4176        CALL abort_gcm (modname,abort_message,1)
     4173       CALL abort_physic (modname,abort_message,1)
    41774174    ENDIF
    41784175
     
    41924189  !        "stats")          only possible in 3D runs !
    41934190
    4194 
     4191#ifdef YM_TO_DO_LATER
    41954192  IF (callstats) THEN
    41964193
     
    42374234
    42384235  ENDIF !if callstats
     4236#endif
    42394237
    42404238  IF (lafin) THEN
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phystokenc.F90

    r3809 r3814  
    99  USE ioipsl
    1010  USE dimphy
    11   USE infotrac, ONLY : nqtot
     11  USE infotrac_phy, ONLY : nqtot
    1212  USE iophy
    13   USE control_mod
     13  USE control_phy_mod
    1414  USE indice_sol_mod
     15  USE tracstoke_phy_mod
    1516 
    1617  IMPLICIT NONE
     
    2223!======================================================================
    2324  INCLUDE "dimensions.h"
    24   INCLUDE "tracstoke.h"
     25!  INCLUDE "tracstoke.h"
    2526  INCLUDE "iniprint.h"
    2627!======================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phytrac_mod.F90

    r3809 r3814  
    8989    USE phys_cal_mod, only : hour
    9090    USE dimphy
    91     USE infotrac
     91    USE infotrac_phy
    9292    USE mod_grid_phy_lmdz
    9393    USE mod_phys_lmdz_para
     
    9797    USE tracinca_mod
    9898    USE tracreprobus_mod
    99     USE control_mod
     99    USE control_phy_mod
    100100    USE indice_sol_mod
    101101
     
    107107    INCLUDE "dimensions.h"
    108108    INCLUDE "clesphys.h"
    109     INCLUDE "temps.h"
    110     INCLUDE "paramet.h"
    111109    INCLUDE "thermcell.h"
    112110    INCLUDE "iniprint.h"
     
    445443       WRITE(*,*) 'FIRST TIME IN PHYTRAC : pdtphys(sec) = ',pdtphys,'ecrit_tra (sec) = ',ecrit_tra
    446444       ALLOCATE( source(klon,nbtr), stat=ierr)
    447        IF (ierr /= 0) CALL abort_gcm('phytrac', 'pb in allocation 1',1)
     445       IF (ierr /= 0) CALL abort_physic('phytrac', 'pb in allocation 1',1)
    448446
    449447       ALLOCATE( aerosol(nbtr), stat=ierr)
    450        IF (ierr /= 0) CALL abort_gcm('phytrac', 'pb in allocation 2',1)
     448       IF (ierr /= 0) CALL abort_physic('phytrac', 'pb in allocation 2',1)
    451449
    452450
     
    503501!                ELSE
    504502!                   WRITE(lunout,*) 'pb it=', it
    505 !                   CALL abort_gcm('phytrac','pb it scavenging',1)
     503!                   CALL abort_physic('phytrac','pb it scavenging',1)
    506504!                ENDIF
    507505                !--test OB
     
    539537
    540538       IF (lessivage.AND.config_inca.EQ.'inca') THEN
    541           CALL abort_gcm('phytrac', 'lessivage=T config_inca=inca impossible',1)
     539          CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1)
    542540          STOP
    543541       ENDIF
     
    740738    ELSE
    741739       !
    742        CALL abort_gcm('iflag_vdf_trac', 'cas non prevu',1)
     740       CALL abort_physic('iflag_vdf_trac', 'cas non prevu',1)
    743741       !
    744742    END IF ! couche limite
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/radiation_AR4.F90

    r3809 r3814  
    485485  USE dimphy
    486486  USE radiation_ar4_param, ONLY: rsun, rray
    487   USE infotrac, ONLY: type_trac
     487  USE infotrac_phy, ONLY: type_trac
    488488#ifdef REPROBUS
    489489  USE chem_rep, ONLY: rsuntime, ok_suntime
     
    710710  USE dimphy
    711711  USE radiation_ar4_param, ONLY: rsun, rray
    712   USE infotrac, ONLY: type_trac
     712  USE infotrac_phy, ONLY: type_trac
    713713#ifdef REPROBUS
    714714  USE chem_rep, ONLY: rsuntime, ok_suntime
     
    23432343  USE dimphy
    23442344  USE radiation_ar4_param, ONLY: tref, rt1, raer, at, bt, oct
    2345   USE infotrac, ONLY: type_trac
     2345  USE infotrac_phy, ONLY: type_trac
    23462346#ifdef REPROBUS
    23472347  USE chem_rep, ONLY: rch42d, rn2o2d, rcfc112d, rcfc122d, ok_rtime2d
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/radio_decay.F90

    r3809 r3814  
    77!
    88  USE dimphy
    9   USE infotrac, ONLY : nbtr
     9  USE infotrac_phy, ONLY : nbtr
    1010  USE traclmdz_mod, ONLY : id_rn, id_pb
    1111  IMPLICIT NONE
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/radlwsw_m.F90

    r3809 r3814  
    4848  USE DIMPHY
    4949  USE assert_m, ONLY : assert
    50   USE infotrac, ONLY : type_trac
     50  USE infotrac_phy, ONLY : type_trac
    5151  USE write_field_phy
    5252#ifdef REPROBUS
     
    393393  IF (nb_gr*kdlon .NE. KLON) THEN
    394394      PRINT*, "kdlon mauvais:", KLON, kdlon, nb_gr
    395       call abort_gcm("radlwsw", "", 1)
     395      call abort_physic("radlwsw", "", 1)
    396396  ENDIF
    397397  IF (kflev .NE. KLEV) THEN
    398398      PRINT*, "kflev differe de KLEV, kflev, KLEV"
    399       call abort_gcm("radlwsw", "", 1)
     399      call abort_physic("radlwsw", "", 1)
    400400  ENDIF
    401401  !-------------------------------------------
     
    10251025#else
    10261026    abort_message="You should compile with -rrtm if running with iflag_rrtm=1"
    1027     call abort_gcm(modname, abort_message, 1)
     1027    call abort_physic(modname, abort_message, 1)
    10281028#endif
    10291029    ENDIF ! iflag_rrtm
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/read_map2D.F90

    r3809 r3814  
    7474      WRITE(lunout,*) 'Error in read_map2D, timestep = ', timestep
    7575
    76       CALL abort_gcm(modname, err_mess, 1)
     76      CALL abort_physic(modname, err_mess, 1)
    7777
    7878    END SUBROUTINE write_err_mess
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/read_pstoke.F90

    r3809 r3814  
    1919  USE netcdf
    2020  USE dimphy
    21   USE control_mod
     21  USE control_phy_mod
    2222  USE indice_sol_mod
    2323
     
    2626  include "netcdf.inc"
    2727  include "dimensions.h"
    28   include "paramet.h"
    29   include "comconst.h"
    30   include "comgeom.h"
    31   include "temps.h"
    32   include "ener.h"
    33   include "logic.h"
    3428  include "description.h"
    35   include "serre.h"
    36   ! ccc#include "dimphy.h"
    3729
    3830  INTEGER klono, klevo, imo, jmo
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/read_pstoke0.F90

    r3809 r3814  
    1818  USE netcdf
    1919  USE dimphy
    20   USE control_mod
     20  USE control_phy_mod
    2121  USE indice_sol_mod
    2222
     
    2525  include "netcdf.inc"
    2626  include "dimensions.h"
    27   include "paramet.h"
    28   include "comconst.h"
    29   include "comgeom.h"
    30   include "temps.h"
    31   include "ener.h"
    32   include "logic.h"
    3327  include "description.h"
    34   include "serre.h"
    35   ! ccc#include "dimphy.h"
    3628
    3729  INTEGER kon, kev, zkon, zkev
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosol.F90

    r3809 r3814  
    130130           IF (klev_src /= klev_src2) THEN
    131131              WRITE(lunout,*) 'Two aerosols files with different number of vertical levels is not allowded'
    132               CALL abort_gcm('readaersosol','Error in number of vertical levels',1)
     132              CALL abort_physic('readaersosol','Error in number of vertical levels',1)
    133133           END IF
    134134           
     
    162162  ELSE
    163163     WRITE(lunout,*)'This option is not implemented : aer_type = ', type,' name_aero=',name_aero
    164      CALL abort_gcm('readaerosol','Error : aer_type parameter not accepted',1)
     164     CALL abort_physic('readaerosol','Error : aer_type parameter not accepted',1)
    165165  END IF ! type
    166166
     
    260260          WRITE(lunout,*) 'longitudes in model :', io_lon
    261261         
    262           CALL abort_gcm('get_aero_fromfile', 'longitudes are not the same in file and model',1)
     262          CALL abort_physic('get_aero_fromfile', 'longitudes are not the same in file and model',1)
    263263       END IF
    264264
     
    283283          WRITE(lunout,*) 'latitudes in file ', TRIM(fname),' : ', lat_src     
    284284          WRITE(lunout,*) 'latitudes in model :', io_lat
    285           CALL abort_gcm('get_aero_fromfile', 'latitudes do not correspond between file and model',1)
     285          CALL abort_physic('get_aero_fromfile', 'latitudes do not correspond between file and model',1)
    286286       END IF
    287287
     
    297297          IF (ierr /= NF90_NOERR) THEN
    298298             ! Dimension PRESNIVS not found either
    299              CALL abort_gcm('get_aero_fromfile', 'dimension lev or presnivs not in file',1)
     299             CALL abort_physic('get_aero_fromfile', 'dimension lev or presnivs not in file',1)
    300300          ELSE
    301301             ! Old file found
     
    315315     ! Allocate variables depending on the number of vertical levels
    316316       ALLOCATE(varmth(iim, jjm+1, klev_src), varyear(iim, jjm+1, klev_src, 12), stat=ierr)
    317        IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 1',1)
     317       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 1',1)
    318318
    319319       ALLOCATE(pt_ap(klev_src), pt_b(klev_src), varktmp(klev_src), stat=ierr)
    320        IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 2',1)
     320       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 2',1)
    321321
    322322! 3) Read all variables from file
     
    333333!       IF (nbr_tsteps /= 12 .AND. nbr_tsteps /= 14) THEN
    334334       IF (nbr_tsteps /= 12 ) THEN
    335          CALL abort_gcm('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)',1)
     335         CALL abort_physic('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)',1)
    336336       ENDIF
    337337
     
    522522       
    523523       ALLOCATE(varyear_glo1D(klon_glo, klev_src, 12), stat=ierr)
    524        IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 3',1)
     524       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 3',1)
    525525       
    526526       ! Transform from 2D to 1D field
     
    546546    IF (.NOT. ASSOCIATED(pt_ap)) THEN  ! if pt_ap is allocated also pt_b is allocated
    547547       ALLOCATE(pt_ap(klev_src), pt_b(klev_src), stat=ierr)
    548        IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 4',1)
     548       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 4',1)
    549549    END IF
    550550    CALL bcast(pt_ap)
     
    554554    IF (ASSOCIATED(pt_year)) DEALLOCATE(pt_year)
    555555    ALLOCATE(pt_year(klon, klev_src, 12), stat=ierr)
    556     IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 5',1)
     556    IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 5',1)
    557557
    558558    ! Scatter global field to local domain at local process
     
    583583          WRITE(lunout,*) 'Error in get_aero_fromfile : ',text
    584584       END IF
    585        CALL abort_gcm('get_aero_fromfile',trim(nf90_strerror(status)),1)
     585       CALL abort_physic('get_aero_fromfile',trim(nf90_strerror(status)),1)
    586586    END IF
    587587
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosol_interp.F90

    r3809 r3814  
    2626  INCLUDE "YOMCST.h"
    2727  INCLUDE "chem.h"     
    28   INCLUDE "temps.h"     
    2928  INCLUDE "clesphys.h"
    3029  INCLUDE "iniprint.h"
    3130  INCLUDE "dimensions.h"
    32   INCLUDE "comvert.h"
    3331!
    3432! Input:
     
    150148  IF (.NOT. ALLOCATED(var_day)) THEN
    151149     ALLOCATE( var_day(klon, klev, naero_spc), stat=ierr)
    152      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 1',1)
     150     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 1',1)
    153151     ALLOCATE( pi_var_day(klon, klev, naero_spc), stat=ierr)
    154      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 2',1)
     152     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 2',1)
    155153
    156154     ALLOCATE( psurf_year(klon, 12, naero_spc), pi_psurf_year(klon, 12, naero_spc), stat=ierr)
    157      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 3',1)
     155     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 3',1)
    158156
    159157     ALLOCATE( load_year(klon, 12, naero_spc), pi_load_year(klon, 12, naero_spc), stat=ierr)
    160      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 4',1)
     158     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 4',1)
    161159
    162160     lnewday=.TRUE.
     
    209207        END IF
    210208     ELSE
    211         CALL abort_gcm('readaerosol_interp', 'this aer_type not supported',1)
     209        CALL abort_physic('readaerosol_interp', 'this aer_type not supported',1)
    212210     END IF
    213211
     
    216214     IF (.NOT. ALLOCATED(var_year)) THEN
    217215        ALLOCATE(var_year(klon, klev_src, 12, naero_spc), stat=ierr)
    218         IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 5',1)
     216        IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 5',1)
    219217     END IF
    220218     var_year(:,:,:,id_aero) = pt_tmp(:,:,:)
     
    230228        WRITE(lunout,*) 'Error! All forcing files for the same aerosol must have the same vertical dimension'
    231229        WRITE(lunout,*) 'Aerosol : ', name_aero(id_aero)
    232         CALL abort_gcm('readaerosol_interp','Differnt vertical axes in aerosol forcing files',1)
     230        CALL abort_physic('readaerosol_interp','Differnt vertical axes in aerosol forcing files',1)
    233231     END IF
    234232
    235233     IF (.NOT. ALLOCATED(pi_var_year)) THEN
    236234        ALLOCATE(pi_var_year(klon, klev_src, 12, naero_spc), stat=ierr)
    237         IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 6',1)
     235        IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 6',1)
    238236     END IF
    239237     pi_var_year(:,:,:,id_aero) = pt_tmp(:,:,:)
     
    259257        IF (  psurf_year(1,1,id_aero) /= pi_psurf_year(1,1,id_aero) ) THEN
    260258           WRITE(lunout,*) 'Warning! All forcing files for the same aerosol must have the same structure'
    261            CALL abort_gcm('readaerosol_interp', 'The aerosol files have not the same format',1)
     259           CALL abort_physic('readaerosol_interp', 'The aerosol files have not the same format',1)
    262260        END IF
    263261       
    264262        IF (klev /= klev_src) THEN
    265263           WRITE(lunout,*) 'Old format of aerosol file do not allowed vertical interpolation'
    266            CALL abort_gcm('readaerosol_interp', 'Old aerosol file not possible',1)
     264           CALL abort_physic('readaerosol_interp', 'Old aerosol file not possible',1)
    267265        END IF
    268266
     
    336334       END IF
    337335     ELSE
    338        CALL abort_gcm('readaerosol_interp', 'number of months undefined',1)
     336       CALL abort_physic('readaerosol_interp', 'number of months undefined',1)
    339337     ENDIF
    340338     if (debug) then
     
    345343     ! Time interpolation, still on vertical source grid
    346344     ALLOCATE(tmp1(klon,klev_src), tmp2(klon,klev_src),stat=ierr)
    347      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 7',1)
     345     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 7',1)
    348346
    349347     ALLOCATE(pplay_src(klon,klev_src), stat=ierr)
    350      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 8',1)
     348     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 8',1)
    351349     
    352350
     
    544542                 WRITE(lunout,*) 'stop for aerosol : ',name_aero(id_aero)
    545543                 WRITE(lunout,*) 'day1, day2, jDay = ', day1, day2, jDay
    546                  CALL abort_gcm('readaerosol_interp','Error in interpolation 1',1)
     544                 CALL abort_physic('readaerosol_interp','Error in interpolation 1',1)
    547545              END IF
    548546           END DO
     
    563561                 
    564562                 WRITE(lunout,*) 'stop for aerosol : ',name_aero(id_aero)
    565                  CALL abort_gcm('readaerosol_interp','Error in interpolation 2',1)
     563                 CALL abort_physic('readaerosol_interp','Error in interpolation 2',1)
    566564              END IF
    567565           END DO
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_climoz_m.F90

    r3809 r3814  
    7373    use netcdf, only: nf90_get_att, nf90_get_var, nf90_noerr, nf90_nowrite
    7474    use assert_m, only: assert
    75 
     75    use comconst_phy_mod, only : pi
     76    use comgeom2_phy_mod, only : rlatv
    7677    integer, intent(in):: read_climoz ! read ozone climatology
    7778    ! Allowed values are 1 and 2
     
    8485    include "dimensions.h"
    8586    ! (for "jjm")
    86     include "paramet.h"
    87     ! (for the other included files)
    88     include "comgeom2.h"
    89     ! (for "rlatv")
    90     include "comconst.h"
    91     ! (for "pi")
    9287
    9388    integer n_plev ! number of pressure levels in the input data
     
    339334         nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
    340335    use netcdf, only: nf90_clobber, nf90_float, nf90_global
    341 
     336    use comconst_phy_mod, only : pi
     337    use comgeom2_phy_mod, only : rlatu
    342338    integer, intent(in):: ncid_in, n_plev
    343339    integer, intent(out):: ncid_out, varid_plev, varid_time
     
    350346
    351347    include "dimensions.h"
    352     ! (for "jjm")
    353     include "paramet.h"
    354     ! (for the other included files)
    355     include "comgeom2.h"
    356     ! (for "rlatu")
    357     include "comconst.h"
    358     ! (for "pi")
    359348
    360349    integer ncerr
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_coefoz_m.F90

    r3809 r3814  
    4545         nf95_put_var, nf95_gw_var
    4646    use netcdf, only: nf90_nowrite, nf90_get_var
    47 
     47    use comgeom2_phy_mod, only : rlatv
     48    use comconst_phy_mod, only : pi
    4849    ! Variables local to the procedure:
    4950
    5051    include "dimensions.h"
    5152    ! (for "jjm")
    52     include "paramet.h"
    53     include "comgeom2.h"
    54     ! (for "rlatv")
    55     include "comconst.h"
    56     ! (for "pi")
    5753
    5854    integer ncid_in, ncid_out ! NetCDF IDs for input and output files
     
    251247         nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
    252248    use netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global
     249    use comgeom2_phy_mod, only : rlatu
     250    use comconst_phy_mod, only : pi
    253251
    254252    integer, intent(in):: ncid_in, varid_in(:), n_plev
     
    260258    include "dimensions.h"
    261259    ! (for "jjm")
    262     include "paramet.h"
    263     include "comgeom2.h"
    264     ! (for "rlatu")
    265     include "comconst.h"
    266     ! (for "pi")
    267260
    268261    integer ncerr
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_o3_m.F90

    r3809 r3814  
    3030    use regr1_step_av_m, only: regr1_step_av
    3131    use press_coefoz_m, only: press_in_edg
    32     use control_mod, only: dayref
     32    use control_phy_mod, only: dayref
    3333
    3434    REAL, intent(in):: p3d(:, :, :) ! pressure at layer interfaces, in Pa
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/soil.F90

    r3809 r3814  
    178178  ELSE
    179179     WRITE(lunout,*) "valeur d indice non prevue", indice
    180      call abort_gcm("soil", "", 1)
     180     call abort_physic("soil", "", 1)
    181181  ENDIF
    182182
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/surf_land_orchidee_mod.F90

    r3809 r3814  
    1818  USE comgeomphy,   ONLY : cuphy, cvphy
    1919  USE mod_grid_phy_lmdz
    20   USE mod_phys_lmdz_para, mpi_root_rank=>mpi_root
     20  USE mod_phys_lmdz_para
    2121
    2222  IMPLICIT NONE
     
    4545    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    4646    USE indice_sol_mod
    47 
     47    USE temps_phy_mod
    4848!   
    4949! Cette routine sert d'interface entre le modele atmospherique et le
     
    9898!   qsurf        air moisture at surface
    9999!
    100     INCLUDE "temps.h"
    101100    INCLUDE "YOMCST.h"
    102101    INCLUDE "iniprint.h"
     
    210209#ifndef CPP_VEGET
    211210       abort_message='Pb de coherence: ok_veget = .true. mais CPP_VEGET = .false.'
    212        CALL abort_gcm(modname,abort_message,1)
     211       CALL abort_physic(modname,abort_message,1)
    213212#endif
    214213
     
    244243          IF (error /= 0) THEN
    245244             abort_message='Pb allocation lalo'
    246              CALL abort_gcm(modname,abort_message,1)
     245             CALL abort_physic(modname,abort_message,1)
    247246          ENDIF
    248247       ENDIF
     
    251250          IF (error /= 0) THEN
    252251             abort_message='Pb allocation lon_scat'
    253              CALL abort_gcm(modname,abort_message,1)
     252             CALL abort_physic(modname,abort_message,1)
    254253          ENDIF
    255254       ENDIF
     
    258257          IF (error /= 0) THEN
    259258             abort_message='Pb allocation lat_scat'
    260              CALL abort_gcm(modname,abort_message,1)
     259             CALL abort_physic(modname,abort_message,1)
    261260          ENDIF
    262261       ENDIF
     
    298297          IF (error /= 0) THEN
    299298             abort_message='Pb allocation neighbours'
    300              CALL abort_gcm(modname,abort_message,1)
     299             CALL abort_physic(modname,abort_message,1)
    301300          ENDIF
    302301       ENDIF
     
    306305          IF (error /= 0) THEN
    307306             abort_message='Pb allocation contfrac'
    308              CALL abort_gcm(modname,abort_message,1)
     307             CALL abort_physic(modname,abort_message,1)
    309308          ENDIF
    310309       ENDIF
     
    324323          IF (error /= 0) THEN
    325324             abort_message='Pb allocation resolution'
    326              CALL abort_gcm(modname,abort_message,1)
     325             CALL abort_physic(modname,abort_message,1)
    327326          ENDIF
    328327       ENDIF
     
    336335       IF (error /= 0) THEN
    337336          abort_message='Pb allocation coastalflow'
    338           CALL abort_gcm(modname,abort_message,1)
     337          CALL abort_physic(modname,abort_message,1)
    339338       ENDIF
    340339       
     
    342341       IF (error /= 0) THEN
    343342          abort_message='Pb allocation riverflow'
    344           CALL abort_gcm(modname,abort_message,1)
     343          CALL abort_physic(modname,abort_message,1)
    345344       ENDIF
    346345!
     
    349348       IF (carbon_cycle_cpl) THEN
    350349          abort_message='carbon_cycle_cpl not yet possible with this interface of ORCHIDEE'
    351           CALL abort_gcm(modname,abort_message,1)
     350          CALL abort_physic(modname,abort_message,1)
    352351       END IF
    353352       
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/surf_land_orchidee_noopenmp_mod.F90

    r3809 r3814  
    215215       IF (carbon_cycle_cpl) THEN
    216216          abort_message='You must define preprossing key ORCH_NEW when running carbon_cycle_cpl=y'
    217           CALL abort_gcm(modname,abort_message,1)
     217          CALL abort_physic(modname,abort_message,1)
    218218       END IF
    219219#endif
     
    246246          IF (error /= 0) THEN
    247247             abort_message='Pb allocation lalo'
    248              CALL abort_gcm(modname,abort_message,1)
     248             CALL abort_physic(modname,abort_message,1)
    249249          ENDIF
    250250       ENDIF
     
    253253          IF (error /= 0) THEN
    254254             abort_message='Pb allocation lon_scat'
    255              CALL abort_gcm(modname,abort_message,1)
     255             CALL abort_physic(modname,abort_message,1)
    256256          ENDIF
    257257       ENDIF
     
    260260          IF (error /= 0) THEN
    261261             abort_message='Pb allocation lat_scat'
    262              CALL abort_gcm(modname,abort_message,1)
     262             CALL abort_physic(modname,abort_message,1)
    263263          ENDIF
    264264       ENDIF
     
    301301          IF (error /= 0) THEN
    302302             abort_message='Pb allocation neighbours'
    303              CALL abort_gcm(modname,abort_message,1)
     303             CALL abort_physic(modname,abort_message,1)
    304304          ENDIF
    305305       ENDIF
     
    309309          IF (error /= 0) THEN
    310310             abort_message='Pb allocation contfrac'
    311              CALL abort_gcm(modname,abort_message,1)
     311             CALL abort_physic(modname,abort_message,1)
    312312          ENDIF
    313313       ENDIF
     
    327327          IF (error /= 0) THEN
    328328             abort_message='Pb allocation resolution'
    329              CALL abort_gcm(modname,abort_message,1)
     329             CALL abort_physic(modname,abort_message,1)
    330330          ENDIF
    331331       ENDIF
     
    339339       IF (error /= 0) THEN
    340340          abort_message='Pb allocation coastalflow'
    341           CALL abort_gcm(modname,abort_message,1)
     341          CALL abort_physic(modname,abort_message,1)
    342342       ENDIF
    343343       
     
    345345       IF (error /= 0) THEN
    346346          abort_message='Pb allocation riverflow'
    347           CALL abort_gcm(modname,abort_message,1)
     347          CALL abort_physic(modname,abort_message,1)
    348348       ENDIF
    349349
     
    359359       IF (carbon_cycle_cpl) THEN
    360360          ALLOCATE(fco2_land_inst(klon),stat=error)
    361           IF (error /= 0)  CALL abort_gcm(modname,'Pb in allocation fco2_land_inst',1)
     361          IF (error /= 0)  CALL abort_physic(modname,'Pb in allocation fco2_land_inst',1)
    362362         
    363363          ALLOCATE(fco2_lu_inst(klon),stat=error)
    364           IF(error /=0) CALL abort_gcm(modname,'Pb in allocation fco2_lu_inst',1)
     364          IF(error /=0) CALL abort_physic(modname,'Pb in allocation fco2_lu_inst',1)
    365365       END IF
    366366
    367367       ALLOCATE(fields_cpl(klon,nb_fields_cpl), stat = error)
    368        IF (error /= 0) CALL abort_gcm(modname,'Pb in allocation fields_cpl',1)
     368       IF (error /= 0) CALL abort_physic(modname,'Pb in allocation fields_cpl',1)
    369369
    370370    ENDIF                          ! (fin debut)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/surf_landice_mod.F90

    r3809 r3814  
    209209#else
    210210       abort_message='Pb de coherence: ok_snow = .true. mais CPP_SISVAT = .false.'
    211        CALL abort_gcm(modname,abort_message,1)
     211       CALL abort_physic(modname,abort_message,1)
    212212#endif
    213213    ELSE ! ok_snow=FALSE
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell.F90

    r3809 r3814  
    766766      IF (fracd(ig,l)<0.1) THEN
    767767        abort_message = 'fracd trop petit'
    768         CALL abort_gcm(modname, abort_message, 1)
     768        CALL abort_physic(modname, abort_message, 1)
    769769
    770770      ELSE
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcellV0_main.F90

    r3809 r3814  
    465465      if (.not. (f0(1).ge.0.) ) then
    466466        abort_message = 'Dans thermcell_main f0(1).lt.0 '
    467         CALL abort_gcm (modname,abort_message,1)
     467        CALL abort_physic (modname,abort_message,1)
    468468      endif
    469469
     
    591591           zcon2(ig)=zlay(ig,nlay)-(pcon(ig)-pplay(ig,nlay))/(RG*rho(ig,nlay))/100.
    592592           abort_message = 'thermcellV0_main: les thermiques vont trop haut '
    593            CALL abort_gcm (modname,abort_message,1)
     593           CALL abort_physic (modname,abort_message,1)
    594594        endif
    595595      enddo
     
    880880                print*,'wmax_sec',wmax_sec(ig)
    881881                abort_message = 'zdenom<1.e-14'
    882                 CALL abort_gcm (modname,abort_message,1)
     882                CALL abort_physic (modname,abort_message,1)
    883883             endif
    884884             if ((zmax_sec(ig).gt.1.e-10).and.(iflag_thermals_ed.eq.0)) then
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell_dq.F90

    r3809 r3814  
    5555               print*,'entr*dt>m,1',k,entr(ig,k)*ptimestep,masse(ig,k)
    5656               abort_message = 'entr dt > m, 1st'
    57                CALL abort_gcm (modname,abort_message,1)
     57               CALL abort_physic (modname,abort_message,1)
    5858            endif
    5959         enddo
     
    196196               print*,'entr*dt>m,2',k,entr(ig,k)*ptimestep,masse(ig,k)
    197197               abort_message = 'entr dt > m, 2nd'
    198                CALL abort_gcm (modname,abort_message,1)
     198               CALL abort_physic (modname,abort_message,1)
    199199            endif
    200200         enddo
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell_flux.F90

    r3809 r3814  
    103103                    print*,'detr_star(ig,l)',detr_star(ig,l)
    104104                    abort_message = ''
    105                     CALL abort_gcm (modname,abort_message,1)
     105                    CALL abort_physic (modname,abort_message,1)
    106106               endif
    107107            endif
     
    268268               print*,'N1 ig,l,entr',ig,l,entr(ig,l)
    269269               abort_message = 'entr negatif'
    270                CALL abort_gcm (modname,abort_message,1)
     270               CALL abort_physic (modname,abort_message,1)
    271271            endif
    272272            if (detr(ig,l).gt.fm(ig,l)) then
     
    297297               print*,'fm(ig,l)',fm(ig,l)
    298298               abort_message = 'probleme dans thermcell flux'
    299                CALL abort_gcm (modname,abort_message,1)
     299               CALL abort_physic (modname,abort_message,1)
    300300            endif
    301301         enddo
     
    325325               print*,'fm(ig,l)',fm(ig,l)
    326326               abort_message = 'probleme dans thermcell flux'
    327                CALL abort_gcm (modname,abort_message,1)
     327               CALL abort_physic (modname,abort_message,1)
    328328            endif
    329329        enddo
     
    427427                         print*,'fm(ig,l)',fm(ig,l)
    428428                         abort_message = 'probleme dans thermcell_flux'
    429                          CALL abort_gcm (modname,abort_message,1)
     429                         CALL abort_physic (modname,abort_message,1)
    430430                      endif
    431431                      entr(ig,l+1)=entr(ig,l+1)-ddd
     
    511511          print*,'fm(igout,l)',fm(igout,l)
    512512          abort_message = ''
    513           CALL abort_gcm (modname,abort_message,1)
     513          CALL abort_physic (modname,abort_message,1)
    514514          endif
    515515      enddo
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell_flux2.F90

    r3809 r3814  
    109109                    abort_message = ''
    110110                    labort_gcm=.true.
    111                     CALL abort_gcm (modname,abort_message,1)
     111                    CALL abort_physic (modname,abort_message,1)
    112112               endif
    113113            endif
     
    282282            print*,'N1 ig,l,entr',igout,lout,entr(igout,lout)
    283283            abort_message = 'entr negatif'
    284             CALL abort_gcm (modname,abort_message,1)
     284            CALL abort_physic (modname,abort_message,1)
    285285         endif
    286286
     
    323323            print*,'fm(ig,l)',fm(ig,l)
    324324            abort_message = 'probleme dans thermcell flux'
    325             CALL abort_gcm (modname,abort_message,1)
     325            CALL abort_physic (modname,abort_message,1)
    326326         endif
    327327
     
    361361               print*,'fm(ig,l)',fm(ig,l)
    362362               abort_message = 'probleme dans thermcell flux'
    363                CALL abort_gcm (modname,abort_message,1)
     363               CALL abort_physic (modname,abort_message,1)
    364364        endif
    365365!    enddo
     
    479479                         print*,'fm(ig,l)',fm(ig,l)
    480480                         abort_message = 'probleme dans thermcell_flux'
    481                          CALL abort_gcm (modname,abort_message,1)
     481                         CALL abort_physic (modname,abort_message,1)
    482482      endif
    483483      endif
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell_main.F90

    r3809 r3814  
    565565      if (.not. (f0(1).ge.0.) ) then
    566566              abort_message = '.not. (f0(1).ge.0.)'
    567               CALL abort_gcm (modname,abort_message,1)
     567              CALL abort_physic (modname,abort_message,1)
    568568      endif
    569569
     
    695695      if (ierr==1) then
    696696           abort_message = 'thermcellV0_main: les thermiques vont trop haut '
    697            CALL abort_gcm (modname,abort_message,1)
     697           CALL abort_physic (modname,abort_message,1)
    698698      endif
    699699
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell_old.F90

    r3809 r3814  
    520520      IF (fracd(ig,l)<0.1) THEN
    521521        abort_message = 'fracd trop petit'
    522         CALL abort_gcm(modname, abort_message, 1)
     522        CALL abort_physic(modname, abort_message, 1)
    523523      ELSE
    524524        ! vitesse descendante "diagnostique"
     
    17471747        PRINT *, 'THERMCELL PB ig=', ig, '   l=', l
    17481748        abort_message = 'THERMCELL PB'
    1749         CALL abort_gcm(modname, abort_message, 1)
     1749        CALL abort_physic(modname, abort_message, 1)
    17501750      END IF
    17511751      ! if ((zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10).and.
     
    20512051      IF (fracd(ig,l)<0.1 .AND. (test(ig)==1)) THEN
    20522052        abort_message = 'fracd trop petit'
    2053         CALL abort_gcm(modname, abort_message, 1)
     2053        CALL abort_physic(modname, abort_message, 1)
    20542054      ELSE
    20552055        ! vitesse descendante "diagnostique"
     
    31013101      IF (fracd(ig,l)<0.1) THEN
    31023102        abort_message = 'fracd trop petit'
    3103         CALL abort_gcm(modname, abort_message, 1)
     3103        CALL abort_physic(modname, abort_message, 1)
    31043104      ELSE
    31053105        ! vitesse descendante "diagnostique"
     
    39063906      IF (fracd(ig,l)<0.1) THEN
    39073907        abort_message = 'fracd trop petit'
    3908         CALL abort_gcm(modname, abort_message, 1)
     3908        CALL abort_physic(modname, abort_message, 1)
    39093909      ELSE
    39103910        ! vitesse descendante "diagnostique"
     
    52095209      IF (fracd(ig,l)<0.1) THEN
    52105210        abort_message = 'fracd trop petit'
    5211         CALL abort_gcm(modname, abort_message, 1)
     5211        CALL abort_physic(modname, abort_message, 1)
    52125212      ELSE
    52135213        ! vitesse descendante "diagnostique"
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/tracinca_mod.F90

    r3809 r3814  
    1111    ! This subroutine initialize some control varaibles.
    1212
    13     USE infotrac
     13    USE infotrac_phy
    1414    IMPLICIT NONE
    1515   
     
    4242
    4343    USE dimphy
    44     USE infotrac
     44    USE infotrac_phy
    4545    USE vampir
    4646    USE comgeomphy
    47     USE control_mod
     47    USE control_phy_mod
    4848    USE indice_sol_mod
    4949
     
    5252   
    5353    INCLUDE "dimensions.h"
    54     INCLUDE "paramet.h"
     54!    INCLUDE "paramet.h"
    5555
    5656!==========================================================================
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/traclmdz_mod.F90

    r3809 r3814  
    6767   
    6868    USE dimphy
    69     USE infotrac
     69    USE infotrac_phy
    7070   
    7171    ! Input argument
     
    7777    ! Allocate restart variables trs
    7878    ALLOCATE( trs(klon,nbtr), stat=ierr)
    79     IF (ierr /= 0) CALL abort_gcm('traclmdz_from_restart', 'pb in allocation 1',1)
     79    IF (ierr /= 0) CALL abort_physic('traclmdz_from_restart', 'pb in allocation 1',1)
    8080   
    8181    ! Initialize trs with values read from restart file
     
    8989    ! Initialization of the tracers should be done here only for those not found in the restart file.
    9090    USE dimphy
    91     USE infotrac
     91    USE infotrac_phy
    9292    USE regr_pr_comb_coefoz_m, ONLY: alloc_coefoz
    9393    USE press_coefoz_m, ONLY: press_coefoz
     
    133133! --------------------------------------------
    134134    ALLOCATE( scavtr(nbtr), stat=ierr)
    135     IF (ierr /= 0) CALL abort_gcm('traclmdz_init', 'pb in allocation 9',1)
     135    IF (ierr /= 0) CALL abort_physic('traclmdz_init', 'pb in allocation 9',1)
    136136    scavtr(:)=1.
    137137   
    138138    ALLOCATE( radio(nbtr), stat=ierr)
    139     IF (ierr /= 0) CALL abort_gcm('traclmdz_init', 'pb in allocation 11',1)
     139    IF (ierr /= 0) CALL abort_physic('traclmdz_init', 'pb in allocation 11',1)
    140140    radio(:) = .false.    ! Par defaut pas decroissance radioactive
    141141   
    142142    ALLOCATE( masktr(klon,nbtr), stat=ierr)
    143     IF (ierr /= 0) CALL abort_gcm('traclmdz_init', 'pb in allocation 2',1)
     143    IF (ierr /= 0) CALL abort_physic('traclmdz_init', 'pb in allocation 2',1)
    144144   
    145145    ALLOCATE( fshtr(klon,nbtr), stat=ierr)
    146     IF (ierr /= 0) CALL abort_gcm('traclmdz_init', 'pb in allocation 3',1)
     146    IF (ierr /= 0) CALL abort_physic('traclmdz_init', 'pb in allocation 3',1)
    147147   
    148148    ALLOCATE( hsoltr(nbtr), stat=ierr)
    149     IF (ierr /= 0) CALL abort_gcm('traclmdz_init', 'pb in allocation 4',1)
     149    IF (ierr /= 0) CALL abort_physic('traclmdz_init', 'pb in allocation 4',1)
    150150   
    151151    ALLOCATE( tautr(nbtr), stat=ierr)
    152     IF (ierr /= 0) CALL abort_gcm('traclmdz_init', 'pb in allocation 5',1)
     152    IF (ierr /= 0) CALL abort_physic('traclmdz_init', 'pb in allocation 5',1)
    153153    tautr(:)  = 0.
    154154   
    155155    ALLOCATE( vdeptr(nbtr), stat=ierr)
    156     IF (ierr /= 0) CALL abort_gcm('traclmdz_init', 'pb in allocation 6',1)
     156    IF (ierr /= 0) CALL abort_physic('traclmdz_init', 'pb in allocation 6',1)
    157157    vdeptr(:) = 0.
    158158
     
    341341   
    342342    USE dimphy
    343     USE infotrac
     343    USE infotrac_phy
    344344    USE regr_pr_comb_coefoz_m, ONLY: regr_pr_comb_coefoz
    345345    USE o3_chem_m, ONLY: o3_chem
     
    430430!=================================================================
    431431
    432     CALL q_sat(klon*klev,t_seri,pplay,qsat)
     432    CALL q_sat_phy(klon*klev,t_seri,pplay,qsat)
    433433
    434434    IF ( id_pcsat /= 0 ) THEN
     
    624624    ! variable trs is written to restart file (restartphy.nc)
    625625    USE dimphy
    626     USE infotrac
     626    USE infotrac_phy
    627627   
    628628    REAL,DIMENSION(klon,nbtr), INTENT(OUT) :: trs_out
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/tracreprobus_mod.F90

    r3809 r3814  
    1212
    1313    USE dimphy
    14     USE infotrac
     14    USE infotrac_phy
    1515#ifdef REPROBUS
    1616    USE CHEM_REP, ONLY : pdt_rep, &  ! pas de temps reprobus
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/write_field_phy.F90

    r3809 r3814  
    1313   
    1414    IMPLICIT NONE
    15     include 'dimensions.h'
    16     include 'paramet.h'
    1715
    1816    character(len=*)   :: name
     
    2119    real,save,allocatable :: Field_tmp(:,:)
    2220    real, dimension(klon_glo,ll):: New_Field
    23     real, dimension(iim,jjp1,ll):: Field_2d
     21    real, dimension(nbp_lon,nbp_lat,ll):: Field_2d
    2422
    2523    CALL Gather(Field,New_Field)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/write_histday_seri.h

    r3809 r3814  
    5151      CALL histwrite(nid_day_seri,"ecin",itau_w, &
    5252                     zx_tmp_2d,iim*jjmp1,ndex2d)
    53 !
    54 !IM 151004 BEG
    55       IF(1.EQ.0) THEN
    56 !
    57       DO k=1, klev
    58       DO i=1, klon
    59        zx_tmp_fi3d(i,k)=u_seri(i,k)*RA*cos(pir* rlat(i))
    60       ENDDO
    61       ENDDO
    62 !
    63       CALL moyglo_pondaima(klon, klev, zx_tmp_fi3d,  &
    64            airephy, paprs, moyglo)
    65       zx_tmp_fi2d(1:klon)=moyglo
    66 !
    67       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
    68       CALL histwrite(nid_day_seri,"momang",itau_w,zx_tmp_2d, &
    69                      iim*jjmp1,ndex2d)
    70 !
    71 ! friction torque
    72 !
    73       DO i=1, klon
    74        zx_tmp_fi2d(i)=zxfluxu(i,1)*RA* cos(pir* rlat(i))
    75       ENDDO
    76 !
    77       ok_msk=.FALSE.
    78       CALL moyglo_pondaire(klon, zx_tmp_fi2d, airephy,  &
    79            ok_msk, msk, moyglo)
    80       zx_tmp_fi2d(1:klon)=moyglo
    81 !
    82       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
    83       CALL histwrite(nid_day_seri,"frictor",itau_w,zx_tmp_2d, &
    84                      iim*jjmp1,ndex2d)
    85 !
    86 ! mountain torque
    87 !
    88 !IM 190504 BEG
    89       CALL gr_fi_dyn(1,klon,iim+1,jjm+1,airephy,airedyn)
    90       CALL gr_fi_dyn(klev+1,klon,iim+1,jjm+1,paprs,padyn)
    91       CALL gr_fi_dyn(1,klon,iim+1,jjm+1,rlat,rlatdyn)
    92       mountor=0.
    93       airetot=0.
    94       DO j = 1, jjmp1
    95        DO i = 1, iim+1
    96         ij=i+(iim+1)*(j-1)
    97         zx_tmp(ij)=0.
    98         DO k = 1, klev
    99          zx_tmp(ij)=zx_tmp(ij)+dudyn(i,j,k)*airedyn(i,j)* &
    100                     (padyn(i,j,k+1)-padyn(i,j,k))/RG
    101          airetot=airetot+airedyn(i,j)
    102         ENDDO
    103 !IM 190504 mountor=mountor+zx_tmp(ij)*airedyn(i,j)*RA*
    104         mountor=mountor+zx_tmp(ij)*RA* &
    105                  cos(pir* rlatdyn(i,j))
    106        ENDDO
    107       ENDDO
    108 !IM 151004 BEG
    109       IF(itap.EQ.1) PRINT*,'airetot=',airetot,airetot/klev
    110 !IM 151004 END
    111 !IM 190504      mountor=mountor/(airetot*airetot)
    112       mountor=mountor/airetot
    113 !
    114 !IM 190504 END
    115       zx_tmp_2d(1:iim,1:jjmp1)=mountor
    116       CALL histwrite(nid_day_seri,"mountor",itau_w,zx_tmp_2d, &
    117                      iim*jjmp1,ndex2d)
    118 !
    119       ENDIF !(1.EQ.0) THEN
    120 !
    121 !
    122       CALL gr_fi_dyn(1,klon,iim+1,jjm+1,airephy,airedyn)
     53
     54
     55!#ifdef _YM_UNUSED_TO_SUPRESS_
     56!ym !
     57!ym!IM 151004 BEG
     58!ym      IF(1.EQ.0) THEN
     59!ym!
     60!ym      DO k=1, klev
     61!ym      DO i=1, klon
     62!ym       zx_tmp_fi3d(i,k)=u_seri(i,k)*RA*cos(pir* rlat(i))
     63!ym      ENDDO
     64!ym      ENDDO
     65!ym!
     66!ym      CALL moyglo_pondaima(klon, klev, zx_tmp_fi3d,  &
     67!ym           airephy, paprs, moyglo)
     68!ym      zx_tmp_fi2d(1:klon)=moyglo
     69!ym!
     70!ym      CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     71!ym      CALL histwrite(nid_day_seri,"momang",itau_w,zx_tmp_2d, &
     72!ym                     iim*jjmp1,ndex2d)
     73!ym!
     74!ym! friction torque
     75!ym!
     76!ym      DO i=1, klon
     77!ym       zx_tmp_fi2d(i)=zxfluxu(i,1)*RA* cos(pir* rlat(i))
     78!ym      ENDDO
     79!ym!
     80!ym      ok_msk=.FALSE.
     81!ym      CALL moyglo_pondaire(klon, zx_tmp_fi2d, airephy,  &
     82!ym           ok_msk, msk, moyglo)
     83!ym      zx_tmp_fi2d(1:klon)=moyglo
     84!ym!
     85!ym      CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     86!ym      CALL histwrite(nid_day_seri,"frictor",itau_w,zx_tmp_2d, &
     87!ym                     iim*jjmp1,ndex2d)
     88!ym!
     89!ym! mountain torque
     90!ym!
     91!ym!IM 190504 BEG
     92!ym      CALL gr_fi_dyn(1,klon,iim+1,jjm+1,airephy,airedyn)
     93!ym      CALL gr_fi_dyn(klev+1,klon,iim+1,jjm+1,paprs,padyn)
     94!ym      CALL gr_fi_dyn(1,klon,iim+1,jjm+1,rlat,rlatdyn)
     95!ym     
     96!ym
     97!ym      mountor=0.
     98!ym      airetot=0.
     99!ym      DO j = 1, jjmp1
     100!ym       DO i = 1, iim+1
     101!ym        ij=i+(iim+1)*(j-1)
     102!ym        zx_tmp(ij)=0.
     103!ym        DO k = 1, klev
     104!ym         zx_tmp(ij)=zx_tmp(ij)+dudyn(i,j,k)*airedyn(i,j)* &
     105!ym                    (padyn(i,j,k+1)-padyn(i,j,k))/RG
     106!ym         airetot=airetot+airedyn(i,j)
     107!ym        ENDDO
     108!ym!IM 190504 mountor=mountor+zx_tmp(ij)*airedyn(i,j)*RA*
     109!ym        mountor=mountor+zx_tmp(ij)*RA* &
     110!ym                 cos(pir* rlatdyn(i,j))
     111!ym       ENDDO
     112!ym      ENDDO
     113!ym!IM 151004 BEG
     114!ym      IF(itap.EQ.1) PRINT*,'airetot=',airetot,airetot/klev
     115!ym!IM 151004 END
     116!ym!IM 190504      mountor=mountor/(airetot*airetot)
     117!ym      mountor=mountor/airetot
     118!ym!
     119!ym!IM 190504 END
     120!ym      zx_tmp_2d(1:iim,1:jjmp1)=mountor
     121!ym      CALL histwrite(nid_day_seri,"mountor",itau_w,zx_tmp_2d, &
     122!ym                     iim*jjmp1,ndex2d)
     123!ym!
     124!ym      ENDIF !(1.EQ.0) THEN
     125!ym!
     126!ym!
     127!ym
     128!ym      CALL gr_fi_dyn(1,klon,iim+1,jjm+1,airephy,airedyn)
     129!#endif     
     130     
    123131      CALL gr_fi_ecrit(1,klon,iim,jjmp1,airephy,zx_tmp_2d)
    124132      airetot=0.
     
    133141!     ENDDO !j
    134142!
     143
     144
     145      airetot=0.
    135146      DO i=1, klon
    136147       airetot=airetot+airephy(i)
Note: See TracChangeset for help on using the changeset viewer.