Changeset 2311


Ignore:
Timestamp:
Jun 25, 2015, 9:45:24 AM (9 years ago)
Author:
Ehouarn Millour
Message:

Further modifications to enforce physics/dynamics separation:

  • moved iniprint.h and misc_mod back to dyn3d_common, as these should only be used by dynamics.
  • created print_control_mod in the physics to store flags prt_level, lunout, debug to be local to physics (should be used rather than iniprint.h)
  • created abort_physic.F90 , which does the same job as abort_gcm() did, but should be used instead when in physics.
  • reactivated inifis (turned it into a module, inifis_mod.F90) to initialize physical constants and print_control_mod flags.

EM

Location:
LMDZ5/trunk/libf
Files:
7 added
96 edited
3 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dynlonlat_phylonlat/phydev/iniphysiq.F90

    r2242 r2311  
    1818                        rlond, & ! longitudes
    1919                        rlatd ! latitudes
    20   USE comcstphy, ONLY: rradius, & ! planet radius (m)
    21                        rr, & ! recuced gas constant: R/molar mass of atm
    22                        rg, & ! gravity
    23                        rcpp  ! specific heat of the atmosphere
     20!  USE comcstphy, ONLY: rradius, & ! planet radius (m)
     21!                       rr, & ! recuced gas constant: R/molar mass of atm
     22!                       rg, & ! gravity
     23!                       rcpp  ! specific heat of the atmosphere
     24  USE inifis_mod, ONLY: inifis
    2425  USE phyaqua_mod, ONLY: iniaqua
    2526  IMPLICIT NONE
     
    119120
    120121!$OMP PARALLEL
     122  ! Initialize physical constants in physics:
     123  CALL inifis(prad,pg,pr,pcpp)
     124
    121125  ! Now generate local lon/lat/cu/cv/area arrays
    122126  CALL initcomgeomphy
     
    129133  rlatd(1:klon_omp) = latfi(offset+klon_omp_begin:offset+klon_omp_end)
    130134
    131   ! copy some fundamental parameters to physics
    132   rradius=prad
    133   rg=pg
    134   rr=pr
    135   rcpp=pcpp
    136 
    137 !$OMP END PARALLEL
    138 
    139135  ! Additional initializations for aquaplanets
    140 !$OMP PARALLEL
    141136  IF (iflag_phys>=100) THEN
    142137    CALL iniaqua(klon_omp,rlatd,rlond,iflag_phys)
  • LMDZ5/trunk/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90

    r2273 r2311  
    1919                        rlond, & ! longitudes
    2020                        rlatd ! latitudes
     21  USE inifis_mod, ONLY: inifis
    2122  USE phyaqua_mod, ONLY: iniaqua
    2223  IMPLICIT NONE
     
    2728  ! =======================================================================
    2829
    29   include "YOMCST.h"
    3030  include "iniprint.h"
    3131
     
    125125
    126126!$OMP PARALLEL
     127  ! Initialize physical constants in physics:
     128  CALL inifis(punjours,prad,pg,pr,pcpp)
     129 
    127130  ! Now generate local lon/lat/cu/cv/area arrays
    128131  CALL initcomgeomphy
     
    135138  rlatd(1:klon_omp) = latfi(offset+klon_omp_begin:offset+klon_omp_end)
    136139
    137     ! suphel => initialize some physical constants (orbital parameters,
    138     !           geoid, gravity, thermodynamical constants, etc.) in the
    139     !           physics
    140   CALL suphel
    141 
    142 !$OMP END PARALLEL
    143 
    144   ! check that physical constants set in 'suphel' are coherent
    145   ! with values set in the dynamics:
    146   IF (rday/=punjours) THEN
    147     WRITE (lunout, *) 'iniphysiq: length of day discrepancy!!!'
    148     WRITE (lunout, *) '  in the dynamics punjours=', punjours
    149     WRITE (lunout, *) '   but in the physics RDAY=', rday
    150     IF (abs(rday-punjours)>0.01*punjours) THEN
    151         ! stop here if the relative difference is more than 1%
    152       abort_message = 'length of day discrepancy'
    153       CALL abort_gcm(modname, abort_message, 1)
    154     END IF
    155   END IF
    156   IF (rg/=pg) THEN
    157     WRITE (lunout, *) 'iniphysiq: gravity discrepancy !!!'
    158     WRITE (lunout, *) '     in the dynamics pg=', pg
    159     WRITE (lunout, *) '  but in the physics RG=', rg
    160     IF (abs(rg-pg)>0.01*pg) THEN
    161         ! stop here if the relative difference is more than 1%
    162       abort_message = 'gravity discrepancy'
    163       CALL abort_gcm(modname, abort_message, 1)
    164     END IF
    165   END IF
    166   IF (ra/=prad) THEN
    167     WRITE (lunout, *) 'iniphysiq: planet radius discrepancy !!!'
    168     WRITE (lunout, *) '   in the dynamics prad=', prad
    169     WRITE (lunout, *) '  but in the physics RA=', ra
    170     IF (abs(ra-prad)>0.01*prad) THEN
    171         ! stop here if the relative difference is more than 1%
    172       abort_message = 'planet radius discrepancy'
    173       CALL abort_gcm(modname, abort_message, 1)
    174     END IF
    175   END IF
    176   IF (rd/=pr) THEN
    177     WRITE (lunout, *) 'iniphysiq: reduced gas constant discrepancy !!!'
    178     WRITE (lunout, *) '     in the dynamics pr=', pr
    179     WRITE (lunout, *) '  but in the physics RD=', rd
    180     IF (abs(rd-pr)>0.01*pr) THEN
    181         ! stop here if the relative difference is more than 1%
    182       abort_message = 'reduced gas constant discrepancy'
    183       CALL abort_gcm(modname, abort_message, 1)
    184     END IF
    185   END IF
    186   IF (rcpd/=pcpp) THEN
    187     WRITE (lunout, *) 'iniphysiq: specific heat discrepancy !!!'
    188     WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
    189     WRITE (lunout, *) '  but in the physics RCPD=', rcpd
    190     IF (abs(rcpd-pcpp)>0.01*pcpp) THEN
    191         ! stop here if the relative difference is more than 1%
    192       abort_message = 'specific heat discrepancy'
    193       CALL abort_gcm(modname, abort_message, 1)
    194     END IF
    195   END IF
    196 
    197   ! Additional initializations for aquaplanets
    198 !$OMP PARALLEL
     140  ! Additional initializations for aquaplanets
    199141  IF (iflag_phys>=100) THEN
    200142    CALL iniaqua(klon_omp, rlatd, rlond, iflag_phys)
  • LMDZ5/trunk/libf/phydev/iophy.F90

    r2097 r2311  
    234234    real,allocatable,dimension(:) :: fieldok
    235235
    236     IF (size(field)/=klon) CALL abort_gcm('iophy::histwrite2d','Field first dimension not equal to klon',1)
     236    IF (size(field)/=klon) CALL abort_physic('iophy::histwrite2d','Field first dimension not equal to klon',1)
    237237   
    238238    CALL Gather_omp(field,buffer_omp)   
     
    292292    real,allocatable, dimension(:,:) :: fieldok
    293293
    294     IF (size(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first dimension not equal to klon',1)
     294    IF (size(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first dimension not equal to klon',1)
    295295    nlev=size(field,2)
    296296
     
    355355    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite2d_xios ',trim(field_name)
    356356
    357     IF (SIZE(field)/=klon) CALL abort_gcm('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
     357    IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
    358358   
    359359    CALL Gather_omp(field,buffer_omp)   
     
    393393
    394394    !Et on.... écrit
    395     IF (SIZE(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     395    IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
    396396    nlev=SIZE(field,2)
    397397
  • LMDZ5/trunk/libf/phylmd/aaam_bud.F90

    r1992 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/add_phys_tend.F90

    r2235 r2311  
    1717use phys_local_var_mod
    1818use phys_state_var_mod
     19use print_control_mod, only: prt_level
    1920IMPLICIT none
    20   include "iniprint.h"
    2121  include "YOMCST.h"
    2222  include "clesphys.h"
  • LMDZ5/trunk/libf/phylmd/aeropt.F90

    r1992 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/aeropt_2bands.F90

    r2148 r2311  
    2222
    2323  INCLUDE "YOMCST.h"
    24   INCLUDE "iniprint.h"
    2524
    2625  !
     
    536535          A1_SSSSM_b2(klev), A2_SSSSM_b2(klev), A3_SSSSM_b2(klev),&
    537536          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)
     537        IF (ierr /= 0) CALL abort_physic('aeropt_2bands', 'pb in allocation 1',1)
    539538     END IF
    540539     
  • LMDZ5/trunk/libf/phylmd/aeropt_5wv.F90

    r2146 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/calbeta_clim.F90

    r2101 r2311  
    1414
    1515  USE phys_cal_mod, only: year_len
     16  USE print_control_mod, ONLY: prt_level
    1617
    1718  implicit none
     
    2425  real lat_nord,lat_sud
    2526
    26   include "iniprint.h"
    2727  !==============================================
    2828
  • LMDZ5/trunk/libf/phylmd/calltherm.F90

    r1943 r2311  
    2121      USE dimphy
    2222      USE indice_sol_mod
     23      USE print_control_mod, ONLY: prt_level,lunout
    2324
    2425      implicit none
     
    2627!#include "dimphy.h"
    2728#include "thermcell.h"
    28 #include "iniprint.h"
    2929
    3030
     
    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
  • LMDZ5/trunk/libf/phylmd/carbon_cycle_mod.F90

    r2265 r2311  
    9292    USE surface_data, ONLY : ok_veget, type_ocean
    9393    USE phys_cal_mod, ONLY : mth_len
     94    USE print_control_mod, ONLY: lunout
    9495
    9596    IMPLICIT NONE
    9697    INCLUDE "clesphys.h"
    97     INCLUDE "iniprint.h"
    9898 
    9999! Input argument
     
    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
     
    226226          co2trac(itc)%updatefreq = 86400
    227227          ! DOES THIS WORK ???? Problematic due to implementation of the coupled fluxes...
    228           CALL abort_gcm('carbon_cycle_init','transport of total CO2 has to be implemented and tested',1)
     228          CALL abort_physic('carbon_cycle_init','transport of total CO2 has to be implemented and tested',1)
    229229       END SELECT
    230230    END DO
     
    248248    ! Allocate vector for storing fluxes to inject
    249249    ALLOCATE(dtr_add(klon,maxco2trac), stat=ierr)
    250     IF (ierr /= 0) CALL abort_gcm('carbon_cycle_init', 'pb in allocation 11',1)       
     250    IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 11',1)       
    251251   
    252252    ! Allocate variables for cumulating fluxes from ORCHIDEE
     
    254254       IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl) THEN
    255255          ALLOCATE(fco2_land_day(klon), stat=ierr)
    256           IF (ierr /= 0) CALL abort_gcm('carbon_cycle_init', 'pb in allocation 2',1)
     256          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 2',1)
    257257          fco2_land_day(1:klon) = 0.
    258258         
    259259          ALLOCATE(fco2_lu_day(klon), stat=ierr)
    260           IF (ierr /= 0) CALL abort_gcm('carbon_cycle_init', 'pb in allocation 3',1)
     260          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 3',1)
    261261          fco2_lu_day(1:klon)   = 0.
    262262       END IF
     
    268268!    IF (carbon_cycle_cpl .AND. type_ocean/='couple') THEN
    269269!       WRITE(lunout,*) 'Coupling with ocean model is needed for carbon_cycle_cpl'
    270 !       CALL abort_gcm('carbon_cycle_init', 'coupled ocean is needed for carbon_cycle_cpl',1)
     270!       CALL abort_physic('carbon_cycle_init', 'coupled ocean is needed for carbon_cycle_cpl',1)
    271271!    END IF
    272272!
    273273!    IF (carbon_cycle_cpl .AND..NOT. ok_veget) THEN
    274274!       WRITE(lunout,*) 'Coupling with surface land model ORCHDIEE is needed for carbon_cycle_cpl'
    275 !       CALL abort_gcm('carbon_cycle_init', 'ok_veget is needed for carbon_cycle_cpl',1)
     275!       CALL abort_physic('carbon_cycle_init', 'ok_veget is needed for carbon_cycle_cpl',1)
    276276!    END IF
    277277
     
    279279    teststop=0
    280280    DO it=1,teststop
    281        CALL abort_gcm('carbon_cycle_init', 'Entering loop from 1 to 0',1)
     281       CALL abort_physic('carbon_cycle_init', 'Entering loop from 1 to 0',1)
    282282    END DO
    283283
     
    285285       ! No carbon tracers found in tracer.def. It is not possible to do carbon cycle
    286286       WRITE(lunout,*) 'No carbon tracers found in tracer.def. Not ok with carbon_cycle_tr and/or carbon_cycle_cp'
    287        CALL abort_gcm('carbon_cycle_init', 'No carbon tracers found in tracer.def',1)
     287       CALL abort_physic('carbon_cycle_init', 'No carbon tracers found in tracer.def',1)
    288288    END IF
    289289   
     
    311311    USE comgeomphy
    312312    USE indice_sol_mod
     313    USE print_control_mod, ONLY: lunout
    313314
    314315    IMPLICIT NONE
    315316
    316317    INCLUDE "clesphys.h"
    317     INCLUDE "iniprint.h"
    318318    INCLUDE "YOMCST.h"
    319319
     
    371371             CASE DEFAULT
    372372                WRITE(lunout,*) 'Error with tracer ',co2trac(it)%name
    373                 CALL abort_gcm('carbon_cycle', 'No coupling implemented for this tracer',1)
     373                CALL abort_physic('carbon_cycle', 'No coupling implemented for this tracer',1)
    374374             END SELECT
    375375          ELSE
  • LMDZ5/trunk/libf/phylmd/cdrag.F90

    r2278 r2311  
    99  USE dimphy
    1010  USE indice_sol_mod
     11  USE print_control_mod, ONLY: lunout
    1112  IMPLICIT NONE
    1213! ================================================================= c
     
    9899!  INCLUDE "indicesol.h"
    99100  INCLUDE "clesphys.h"
    100   INCLUDE "iniprint.h"
    101101!
    102102! Quelques constantes et options:
     
    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
  • LMDZ5/trunk/libf/phylmd/change_srf_frac_mod.F90

    r2243 r2311  
    3333    USE ocean_slab_mod, ONLY : fsic, ocean_slab_frac
    3434    USE indice_sol_mod
    35 
    36     INCLUDE "iniprint.h"
     35    USE print_control_mod, ONLY: lunout
     36   
    3737    INCLUDE "YOMCST.h"
    3838!albedo SB >>>
     
    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
  • LMDZ5/trunk/libf/phylmd/clcdrag.F90

    r2278 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/climb_wind_mod.F90

    r2159 r2311  
    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)
  • LMDZ5/trunk/libf/phylmd/cloudth.F90

    r2267 r2311  
    1919#include "YOETHF.h"
    2020#include "FCTTRE.h"
    21 #include "iniprint.h"
    2221#include "thermcell.h"
    2322
     
    284283#include "YOETHF.h"
    285284#include "FCTTRE.h"
    286 #include "iniprint.h"
    287285#include "thermcell.h"
    288286
  • LMDZ5/trunk/libf/phylmd/coef_diff_turb_mod.F90

    r2243 r2311  
    1818    USE dimphy
    1919    USE indice_sol_mod
     20    USE print_control_mod, ONLY: prt_level, lunout
    2021!
    2122! Calculate coefficients(ycoefm, ycoefh) for turbulent diffusion in the
     
    5657!****************************************************************************************
    5758    INCLUDE "clesphys.h"
    58     INCLUDE "iniprint.h"
    5959    INCLUDE "compbl.h"
    6060    INCLUDE "YOETHF.h"
     
    188188    USE dimphy
    189189    USE indice_sol_mod
     190    USE print_control_mod, ONLY: prt_level, lunout
    190191 
    191192!======================================================================
     
    211212    INCLUDE "YOMCST.h"
    212213    INCLUDE "FCTTRE.h"
    213     INCLUDE "iniprint.h"
    214214    INCLUDE "compbl.h"
    215215!
  • LMDZ5/trunk/libf/phylmd/coefcdrag.F90

    r2232 r2311  
    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!
  • LMDZ5/trunk/libf/phylmd/concvl.F90

    r2306 r2311  
    3131  USE infotrac, ONLY: nbtr
    3232  USE phys_local_var_mod, ONLY: omega
     33  USE print_control_mod, ONLY: prt_level, lunout
    3334  IMPLICIT NONE
    3435! ======================================================================
     
    215216  include "YOETHF.h"
    216217  include "FCTTRE.h"
    217   include "iniprint.h"
    218218!jyg<
    219219  include "conema3.h"
  • LMDZ5/trunk/libf/phylmd/condsurf.F90

    r1992 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/conf_phys_m.F90

    r2305 r2311  
    2929    USE control_mod
    3030    USE mod_grid_phy_lmdz, only: klon_glo
    31 
     31    USE print_control_mod, ONLY: lunout
    3232
    3333
     
    3939
    4040    include "thermcell.h"
    41     include "iniprint.h"
    4241
    4342
     
    249248       WRITE(lunout,*)'Variable OCEAN has been replaced by the variable type_ocean.'
    250249       WRITE(lunout,*)'You have to update your parameter file physiq.def to succed running'
    251        CALL abort_gcm('conf_phys','Variable OCEAN no longer existing, use variable name type_ocean',1)
     250       CALL abort_physic('conf_phys','Variable OCEAN no longer existing, use variable name type_ocean',1)
    252251    END IF
    253252
     
    262261       WRITE(lunout,*)'ERROR! Timestep of coupling between atmosphere and ocean'
    263262       WRITE(lunout,*)'cannot be zero.'
    264        CALL abort_gcm('conf_phys','t_coupl = 0.',1)
     263       CALL abort_physic('conf_phys','t_coupl = 0.',1)
    265264    END IF
    266265
     
    21152114    IF (type_ocean=='couple' .AND. (version_ocean/='opa8' .AND. version_ocean/='nemo') ) THEN
    21162115       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid in coupled configuration'
    2117        CALL abort_gcm('conf_phys','version_ocean not valid',1)
     2116       CALL abort_physic('conf_phys','version_ocean not valid',1)
    21182117    END IF
    21192118
     
    21232122             .AND. version_ocean/='sicINT' .AND. version_ocean/='sicNO') THEN
    21242123       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid with slab ocean'
    2125        CALL abort_gcm('conf_phys','version_ocean not valid',1)
     2124       CALL abort_physic('conf_phys','version_ocean not valid',1)
    21262125    END IF
    21272126
     
    21302129    IF (ok_ade .OR. ok_aie) THEN
    21312130       IF ( flag_aerosol .EQ. 0 ) THEN
    2132           CALL abort_gcm('conf_phys','flag_aerosol=0 not compatible avec ok_ade ou ok_aie=.TRUE.',1)
     2131          CALL abort_physic('conf_phys','flag_aerosol=0 not compatible avec ok_ade ou ok_aie=.TRUE.',1)
    21332132       END IF
    21342133       IF ( .NOT. new_aod .AND.  flag_aerosol .NE. 1) THEN
    2135           CALL abort_gcm('conf_phys','new_aod=.FALSE. not compatible avec flag_aerosol=1',1)
     2134          CALL abort_physic('conf_phys','new_aod=.FALSE. not compatible avec flag_aerosol=1',1)
    21362135       END IF
    21372136    END IF
     
    21392138    ! ok_cdnc must be set to y if ok_aie is activated
    21402139    IF (ok_aie .AND. .NOT. ok_cdnc) THEN
    2141        CALL abort_gcm('conf_phys', 'ok_cdnc must be set to y if ok_aie is activated',1)
     2140       CALL abort_physic('conf_phys', 'ok_cdnc must be set to y if ok_aie is activated',1)
    21422141    ENDIF
    21432142
     
    23302329
    23312330  use IOIPSL
     2331  USE print_control_mod, ONLY: lunout
    23322332  implicit none
    2333   include "iniprint.h"
    23342333  ! Configuration de l'interace atm/surf
    23352334  !
  • LMDZ5/trunk/libf/phylmd/conflx.F90

    r1992 r2311  
    992992    pdpmel, ktopm2, pmflxr, pmflxs)
    993993  USE dimphy
     994  USE print_control_mod, ONLY: prt_level
    994995  IMPLICIT NONE
    995996  ! ----------------------------------------------------------------------
     
    10021003  include "YOETHF.h"
    10031004  include "YOECUMF.h"
    1004   include "iniprint.h"
    10051005
    10061006  REAL cevapcu(klon, klev)
  • LMDZ5/trunk/libf/phylmd/cosp/cosp_output_mod.F90

    r2297 r2311  
    100100  USE ioipsl
    101101  USE phys_cal_mod
     102  USE print_control_mod, ONLY: lunout
    102103
    103104#ifdef CPP_XIOS
     
    123124!!! Variables d'entree
    124125  include "temps.h"
    125   INCLUDE 'iniprint.h'
    126126
    127127#ifdef CPP_XIOS
  • LMDZ5/trunk/libf/phylmd/cosp/cosp_output_write_mod.F90

    r2297 r2311  
    2222    USE ioipsl
    2323    USE control_mod
     24    USE print_control_mod, ONLY: lunout,prt_level
    2425
    2526#ifdef CPP_XIOS
     
    4546
    4647  include "temps.h"
    47   include "iniprint.h"
    4848
    4949  Nlevout = vgrid%Nlvgrid
     
    268268    use iophy
    269269    USE mod_phys_lmdz_para
     270    USE print_control_mod, ONLY: lunout,prt_level
    270271#ifdef CPP_XIOS
    271272  USE wxios
     
    277278    INCLUDE "temps.h"
    278279    INCLUDE "clesphys.h"
    279     include "iniprint.h"
    280280
    281281    INTEGER                          :: iff
     
    332332    use iophy
    333333    USE mod_phys_lmdz_para
     334    USE print_control_mod, ONLY: lunout,prt_level
    334335
    335336#ifdef CPP_XIOS
     
    343344    INCLUDE "temps.h"
    344345    INCLUDE "clesphys.h"
    345     include "iniprint.h"
    346346
    347347    INTEGER                        :: iff, klevs
     
    428428  USE ioipsl
    429429  use iophy
     430  USE print_control_mod, ONLY: lunout,prt_level
    430431
    431432#ifdef CPP_XIOS
     
    435436  IMPLICIT NONE
    436437  INCLUDE 'dimensions.h'
    437   INCLUDE 'iniprint.h'
    438438  INCLUDE 'clesphys.h'
    439439
     
    467467    !Et sinon on.... écrit
    468468    IF (SIZE(field)/=klon) &
    469   CALL abort_gcm('iophy::histwrite2d_cosp','Field first DIMENSION not equal to klon',1)
     469  CALL abort_physic('iophy::histwrite2d_cosp','Field first DIMENSION not equal to klon',1)
    470470
    471471    CALL Gather_omp(field,buffer_omp)
     
    517517  USE ioipsl
    518518  use iophy
     519  USE print_control_mod, ONLY: lunout,prt_level
    519520
    520521#ifdef CPP_XIOS
     
    525526  IMPLICIT NONE
    526527  INCLUDE 'dimensions.h'
    527   INCLUDE 'iniprint.h'
    528528  INCLUDE 'clesphys.h'
    529529
     
    568568    !Et sinon on.... écrit
    569569    IF (SIZE(field,1)/=klon) &
    570    CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)                                 
     570   CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)                                 
    571571    nlev=SIZE(field,2)
    572572
     
    613613    !   en utilisant les routines getin de IOIPSL 
    614614    use ioipsl
     615    USE print_control_mod, ONLY: lunout,prt_level
    615616
    616617    IMPLICIT NONE
    617     include 'iniprint.h'
    618618
    619619   CHARACTER(LEN=20)               :: nam_var, nnam_var
  • LMDZ5/trunk/libf/phylmd/cpl_mod.F90

    r2075 r2311  
    102102    USE surface_data
    103103    USE indice_sol_mod
     104    USE print_control_mod, ONLY: lunout
    104105
    105106    INCLUDE "dimensions.h"
    106107    INCLUDE "temps.h"
    107     INCLUDE "iniprint.h"
    108108
    109109! Input arguments
     
    204204    IF (sum_error /= 0) THEN
    205205       abort_message='Pb allocation variables couplees'
    206        CALL abort_gcm(modname,abort_message,1)
     206       CALL abort_physic(modname,abort_message,1)
    207207    ENDIF
    208208!*************************************************************************************
     
    279279    IF (carbon_cycle_cpl .AND. version_ocean=='opa8') THEN
    280280       abort_message='carbon_cycle_cpl does not work with opa8'
    281        CALL abort_gcm(modname,abort_message,1)
     281       CALL abort_physic(modname,abort_message,1)
    282282    END IF
    283283
     
    299299
    300300    INCLUDE "temps.h"
    301     INCLUDE "iniprint.h"
    302301    INCLUDE "YOMCST.h"
    303302    INCLUDE "dimensions.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
     
    12911290    IF (sum_error /= 0) THEN
    12921291       abort_message='Pb in deallocation of cpl_xxxx2D coupling variables'
    1293        CALL abort_gcm(modname,abort_message,1)
     1292       CALL abort_physic(modname,abort_message,1)
    12941293    ENDIF
    12951294   
  • LMDZ5/trunk/libf/phylmd/cv30_routines.F90

    r1992 r2311  
    733733    iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, buoybase, t, q, qs, u, &
    734734    v, gz, th, tra, h, lv, cpn, p, ph, tv, tp, tvp, clw, sig, w0)
     735  USE print_control_mod, ONLY: lunout
    735736  IMPLICIT NONE
    736737
    737738  include "cv30param.h"
    738   include 'iniprint.h'
    739739
    740740  ! inputs:
     
    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
  • LMDZ5/trunk/libf/phylmd/cv3_inicp.F90

    r2197 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/cv3_inip.F90

    r2195 r2311  
    3030!----------------------------------------------
    3131
     32  USE print_control_mod, ONLY: prt_level, lunout
    3233  IMPLICIT NONE
    3334
    3435  include "YOMCST2.h"
    35 
    36   include 'iniprint.h'
    3736
    3837!----------------------------------------------
     
    138137      WRITE (lunout, *) 'WARNING:: AREA OF MIXING PDF IS::', aire
    139138      abort_message = ''
    140       CALL abort_gcm(modname, abort_message, 1)
     139      CALL abort_physic(modname, abort_message, 1)
    141140    ELSE
    142141      PRINT *, 'Area, mean & std deviation are ::', aire, mu, sigma
  • LMDZ5/trunk/libf/phylmd/cv3_routines.F90

    r2306 r2311  
    891891                        h, lv, cpn, p, ph, tv, tp, tvp, clw, &
    892892                        sig, w0)
     893  USE print_control_mod, ONLY: lunout
    893894  IMPLICIT NONE
    894895
    895896  include "cv3param.h"
    896   include 'iniprint.h'
    897897
    898898!inputs:
     
    971971    WRITE (lunout, *) 'strange! nn not equal to ncum: ', nn, ncum
    972972    abort_message = ''
    973     CALL abort_gcm(modname, abort_message, 1)
     973    CALL abort_physic(modname, abort_message, 1)
    974974  END IF
    975975
  • LMDZ5/trunk/libf/phylmd/cv3a_compress.F90

    r2259 r2311  
    154154    PRINT *, 'WARNING nn not equal to ncum: ', nn, ncum
    155155    abort_message = ''
    156     CALL abort_gcm(modname, abort_message, 1)
     156    CALL abort_physic(modname, abort_message, 1)
    157157  END IF
    158158
     
    185185    PRINT *, 'WARNING nn not equal to ncum: ', nn, ncum
    186186    abort_message = ''
    187     CALL abort_gcm(modname, abort_message, 1)
     187    CALL abort_physic(modname, abort_message, 1)
    188188  END IF
    189189!
  • LMDZ5/trunk/libf/phylmd/cv3p1_closure.F90

    r2253 r2311  
    1919  ! **************************************************************
    2020
     21  USE print_control_mod, ONLY: prt_level, lunout
    2122  IMPLICIT NONE
    2223
     
    2627  include "YOMCST.h"
    2728  include "conema3.h"
    28   include "iniprint.h"
    2929
    3030  ! input:
     
    552552        , il, alp2(il), alp(il), cin(il)
    553553      abort_message = ''
    554       CALL abort_gcm(modname, abort_message, 1)
     554      CALL abort_physic(modname, abort_message, 1)
    555555    END IF
    556556    cbmfmax(il) = sigmax*wb2(il)*100.*p(il, icb(il))/(rrd*tv(il,icb(il)))
  • LMDZ5/trunk/libf/phylmd/cv_routines.F90

    r1992 r2311  
    396396    tp1, tvp1, clw1, iflag, nk, icb, cbmf, plcl, tnk, qnk, gznk, t, q, qs, u, &
    397397    v, gz, h, lv, cpn, p, ph, tv, tp, tvp, clw, dph)
     398  USE print_control_mod, ONLY: lunout
    398399  IMPLICIT NONE
    399400
     
    422423  CHARACTER (LEN=20) :: modname = 'cv_compress'
    423424  CHARACTER (LEN=80) :: abort_message
    424 
    425   include 'iniprint.h'
    426425
    427426
     
    453452    WRITE (lunout, *) 'strange! nn not equal to ncum: ', nn, ncum
    454453    abort_message = ''
    455     CALL abort_gcm(modname, abort_message, 1)
     454    CALL abort_physic(modname, abort_message, 1)
    456455  END IF
    457456
  • LMDZ5/trunk/libf/phylmd/cva_driver.F90

    r2306 r2311  
    3939
    4040  USE dimphy
     41  USE print_control_mod, ONLY: prt_level, lunout
    4142  IMPLICIT NONE
    4243
     
    161162  include "dimensions.h"
    162163!!!!!#include "dimphy.h"
    163   include 'iniprint.h'
    164164
    165165! Input
     
    690690    WRITE (lunout, *) 'changer la valeur de sig2feed dans physiq.def'
    691691    abort_message = ''
    692     CALL abort_gcm(modname, abort_message, 1)
     692    CALL abort_physic(modname, abort_message, 1)
    693693  END IF
    694694
  • LMDZ5/trunk/libf/phylmd/dyn1d/1DUTILS.h

    r2239 r2311  
    1515      use ioipsl_getincom
    1616#endif
     17      USE print_control_mod, ONLY: lunout
    1718      IMPLICIT NONE
    1819!-----------------------------------------------------------------------
     
    2728#include "fcg_gcssold.h"
    2829#include "fcg_racmo.h"
    29 #include "iniprint.h"
    3030!
    3131!
  • LMDZ5/trunk/libf/phylmd/dyn1d/lmdz1d.F90

    r2255 r2311  
    2222      USE mod_1D_cases_read
    2323      USE mod_1D_amma_read
     24      USE print_control_mod, ONLY: prt_level
    2425
    2526      implicit none
     
    2829#include "temps.h"
    2930!!#include "control.h"
    30 #include "iniprint.h"
    3131#include "clesphys.h"
    3232#include "dimsoil.h"
  • LMDZ5/trunk/libf/phylmd/ener_conserv.F90

    r2051 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/fisrtilp.F90

    r2236 r2311  
    1414  USE dimphy
    1515  USE icefrac_lsc_mod ! compute ice fraction (JBM 3/14)
     16  USE print_control_mod, ONLY: prt_level, lunout
    1617  IMPLICIT none
    1718  !======================================================================
     
    2829  include "fisrtilp.h"
    2930  include "nuage.h" ! JBM (3/14)
    30   include "iniprint.h"
    3131
    3232  !
  • LMDZ5/trunk/libf/phylmd/fisrtilp_tr.F90

    r1992 r2311  
    1010
    1111  USE dimphy
     12  USE print_control_mod, ONLY: lunout
    1213  IMPLICIT NONE
    1314  ! ======================================================================
     
    2223  include "YOMCST.h"
    2324  include "tracstoke.h"
    24   include "iniprint.h"
    2525
    2626  ! Arguments:
  • LMDZ5/trunk/libf/phylmd/fonte_neige_mod.F90

    r1907 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/grid_noro_m.F90

    r2293 r2311  
    4646!===============================================================================
    4747  USE assert_eq_m, ONLY: assert_eq
     48  USE print_control_mod, ONLY: lunout
    4849  IMPLICIT NONE
    4950!  include "dimensions.h"
    50   include "iniprint.h"
    5151  REAL, PARAMETER :: epsfra = 1.e-5
    5252!-------------------------------------------------------------------------------
     
    9494                          SIZE(zgam,2),SIZE(zthe,2),SIZE(zpic,2),SIZE(zval,2), &
    9595                          SIZE(mask,2)],TRIM(modname)//" jmar")
    96 !  IF(imar/=iim)   CALL abort_gcm(TRIM(modname),'imar/=iim'  ,1)
    97 !  IF(jmar/=jjm+1) CALL abort_gcm(TRIM(modname),'jmar/=jjm+1',1)
     96!  IF(imar/=iim)   CALL abort_physic(TRIM(modname),'imar/=iim'  ,1)
     97!  IF(jmar/=jjm+1) CALL abort_physic(TRIM(modname),'jmar/=jjm+1',1)
    9898  iext=imdp/10                                !--- OK up to 36 degrees cell
    9999  xpi = ACOS(-1.)
  • LMDZ5/trunk/libf/phylmd/hgardfou.F90

    r2235 r2311  
    55  USE phys_state_var_mod
    66  USE indice_sol_mod
     7  USE print_control_mod, ONLY: lunout
    78  IMPLICIT NONE
    89  ! ======================================================================
     
    1112  include "dimensions.h"
    1213  include "YOMCST.h"
    13   include "iniprint.h"
    1414  REAL t(klon, klev), tsol(klon, nbsrf)
    1515  CHARACTER(len=*), intent(in):: text
     
    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
  • LMDZ5/trunk/libf/phylmd/ini_wake.F90

    r2197 r2311  
    44SUBROUTINE ini_wake(wape, fip, it_wape_prescr, wape_prescr, fip_prescr, &
    55    alp_bl_prescr, ale_bl_prescr)
     6  USE print_control_mod, ONLY: lunout
    67  IMPLICIT NONE
    78  ! **************************************************************
     
    3839  ! alpbl  = Alp de PBL lue
    3940
    40   include 'iniprint.h'
    4141  ! declarations
    4242  REAL wape, fip, wape_prescr, fip_prescr
  • LMDZ5/trunk/libf/phylmd/inifis_mod.F90

    r2309 r2311  
     1! $Id$
     2MODULE inifis_mod
    13
    2 ! $Id$
     4CONTAINS
    35
    4 SUBROUTINE inifis(ngrid, nlayer, punjours, pdayref, ptimestep, plat, plon, &
    5     parea, prad, pg, pr, pcpp)
    6   USE dimphy
     6  SUBROUTINE inifis(punjours, prad, pg, pr, pcpp)
     7  ! Initialize some physical constants and settings
     8  USE print_control_mod, ONLY: init_print_control, lunout
    79  IMPLICIT NONE
    810
    9   ! =======================================================================
     11  include "YOMCST.h"
     12  REAL,INTENT(IN) :: prad, pg, pr, pcpp, punjours
    1013
    11   ! subject:
    12   ! --------
    13 
    14   ! Initialisation for the physical parametrisations of the LMD
    15   ! martian atmospheric general circulation modele.
    16 
    17   ! author: Frederic Hourdin 15 / 10 /93
    18   ! -------
    19 
    20   ! arguments:
    21   ! ----------
    22 
    23   ! input:
    24   ! ------
    25 
    26   ! ngrid                 Size of the horizontal grid.
    27   ! All internal loops are performed on that grid.
    28   ! nlayer                Number of vertical layers.
    29   ! pdayref               Day of reference for the simulation
    30   ! firstcall             True at the first call
    31   ! lastcall              True at the last call
    32   ! pday                  Number of days counted from the North. Spring
    33   ! equinoxe.
    34 
    35   ! =======================================================================
    36 
    37   ! -----------------------------------------------------------------------
    38   ! declarations:
    39   ! -------------
    40 
    41   ! ym#include "dimensions.h"
    42   ! ym#include "dimphy.h"
    43 
    44   include 'iniprint.h'
    45   REAL prad, pg, pr, pcpp, punjours
    46 
    47   INTEGER ngrid, nlayer
    48   REAL plat(ngrid), plon(ngrid), parea(klon)
    49   INTEGER pdayref
    50 
    51   REAL ptimestep
    5214  CHARACTER (LEN=20) :: modname = 'inifis'
    5315  CHARACTER (LEN=80) :: abort_message
    5416
     17  ! Initialize flags lunout, prt_level, debug
     18  CALL init_print_control
    5519
    56   IF (nlayer/=klev) THEN
    57     PRINT *, 'STOP in inifis'
    58     PRINT *, 'Probleme de dimensions :'
    59     PRINT *, 'nlayer     = ', nlayer
    60     PRINT *, 'klev   = ', klev
    61     abort_message = ''
    62     CALL abort_gcm(modname, abort_message, 1)
     20  ! suphel => initialize some physical constants (orbital parameters,
     21  !           geoid, gravity, thermodynamical constants, etc.) in the
     22  !           physics
     23  CALL suphel
     24
     25  ! check that physical constants set in 'suphel' are coherent
     26  ! with values set in the dynamics:
     27  IF (rday/=punjours) THEN
     28    WRITE (lunout, *) 'inifis: length of day discrepancy!!!'
     29    WRITE (lunout, *) '  in the dynamics punjours=', punjours
     30    WRITE (lunout, *) '   but in the physics RDAY=', rday
     31    IF (abs(rday-punjours)>0.01*punjours) THEN
     32        ! stop here if the relative difference is more than 1%
     33      abort_message = 'length of day discrepancy'
     34      CALL abort_physic(modname, abort_message, 1)
     35    END IF
     36  END IF
     37  IF (rg/=pg) THEN
     38    WRITE (lunout, *) 'inifis: gravity discrepancy !!!'
     39    WRITE (lunout, *) '     in the dynamics pg=', pg
     40    WRITE (lunout, *) '  but in the physics RG=', rg
     41    IF (abs(rg-pg)>0.01*pg) THEN
     42        ! stop here if the relative difference is more than 1%
     43      abort_message = 'gravity discrepancy'
     44      CALL abort_physic(modname, abort_message, 1)
     45    END IF
     46  END IF
     47  IF (ra/=prad) THEN
     48    WRITE (lunout, *) 'inifis: planet radius discrepancy !!!'
     49    WRITE (lunout, *) '   in the dynamics prad=', prad
     50    WRITE (lunout, *) '  but in the physics RA=', ra
     51    IF (abs(ra-prad)>0.01*prad) THEN
     52        ! stop here if the relative difference is more than 1%
     53      abort_message = 'planet radius discrepancy'
     54      CALL abort_physic(modname, abort_message, 1)
     55    END IF
     56  END IF
     57  IF (rd/=pr) THEN
     58    WRITE (lunout, *) 'inifis: reduced gas constant discrepancy !!!'
     59    WRITE (lunout, *) '     in the dynamics pr=', pr
     60    WRITE (lunout, *) '  but in the physics RD=', rd
     61    IF (abs(rd-pr)>0.01*pr) THEN
     62        ! stop here if the relative difference is more than 1%
     63      abort_message = 'reduced gas constant discrepancy'
     64      CALL abort_physic(modname, abort_message, 1)
     65    END IF
     66  END IF
     67  IF (rcpd/=pcpp) THEN
     68    WRITE (lunout, *) 'inifis: specific heat discrepancy !!!'
     69    WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
     70    WRITE (lunout, *) '  but in the physics RCPD=', rcpd
     71    IF (abs(rcpd-pcpp)>0.01*pcpp) THEN
     72        ! stop here if the relative difference is more than 1%
     73      abort_message = 'specific heat discrepancy'
     74      CALL abort_physic(modname, abort_message, 1)
     75    END IF
    6376  END IF
    6477
    65   IF (ngrid/=klon) THEN
    66     PRINT *, 'STOP in inifis'
    67     PRINT *, 'Probleme de dimensions :'
    68     PRINT *, 'ngrid     = ', ngrid
    69     PRINT *, 'klon   = ', klon
    70     abort_message = ''
    71     CALL abort_gcm(modname, abort_message, 1)
    72   END IF
    73 
    74   RETURN
    75   abort_message = 'Cette version demande les fichier rnatur.dat &
    76     &                                                         &
    77     &        et surf.def'
    78   CALL abort_gcm(modname, abort_message, 1)
    79 
    80 END SUBROUTINE inifis
     78  END SUBROUTINE inifis
     79 
     80END MODULE inifis_mod
  • LMDZ5/trunk/libf/phylmd/init_be.F90

    r1907 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/interfoce_lim.F90

    r1907 r2311  
    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         
  • LMDZ5/trunk/libf/phylmd/iophy.F90

    r2137 r2311  
    5454  IMPLICIT NONE
    5555  INCLUDE 'dimensions.h'
    56   include 'iniprint.h'
    5756    REAL,DIMENSION(klon),INTENT(IN) :: rlon
    5857    REAL,DIMENSION(klon),INTENT(IN) :: rlat
     
    571570    INCLUDE "temps.h"
    572571    INCLUDE "clesphys.h"
    573     INCLUDE "iniprint.h"
    574572
    575573    INTEGER                          :: iff
     
    650648                                   nid_files, nhorim, swaero_diag, levmin, &
    651649                                   levmax, nvertm
     650    USE print_control_mod, ONLY: prt_level,lunout
    652651#ifdef CPP_XIOS
    653652    use wxios, only: wxios_add_field_to_file
     
    658657    INCLUDE "temps.h"
    659658    INCLUDE "clesphys.h"
    660     INCLUDE "iniprint.h"
    661659
    662660    INTEGER                          :: iff
     
    728726    use ioipsl, only: getin
    729727    use phys_output_var_mod, only: nfiles
     728    USE print_control_mod, ONLY: prt_level,lunout
    730729    IMPLICIT NONE
    731 
    732     include 'iniprint.h'
    733730
    734731    CHARACTER(LEN=20)                :: nam_var
     
    750747                                jj_nb, klon_mpi
    751748  USE ioipsl, only: histwrite
     749  USE print_control_mod, ONLY: prt_level,lunout
    752750  IMPLICIT NONE
    753751  include 'dimensions.h'
    754   include 'iniprint.h'
    755752   
    756753    integer,INTENT(IN) :: nid
     
    767764
    768765
    769     IF (size(field)/=klon) CALL abort_gcm('iophy::histwrite2d','Field first DIMENSION not equal to klon',1)
     766    IF (size(field)/=klon) CALL abort_physic('iophy::histwrite2d','Field first DIMENSION not equal to klon',1)
    770767   
    771768    CALL Gather_omp(field,buffer_omp)   
     
    815812                                jj_nb, klon_mpi
    816813  use ioipsl, only: histwrite
     814  USE print_control_mod, ONLY: prt_level,lunout
    817815  IMPLICIT NONE
    818816  include 'dimensions.h'
    819   include 'iniprint.h'
    820817   
    821818    integer,INTENT(IN) :: nid
     
    831828
    832829
    833     IF (size(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     830    IF (size(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
    834831    nlev=size(field,2)
    835832
     
    889886                                 nfiles, vars_defined, clef_stations, &
    890887                                 nid_files
     888  USE print_control_mod, ONLY: prt_level,lunout
    891889#ifdef CPP_XIOS
    892890  USE xios, only: xios_send_field
     
    896894  IMPLICIT NONE
    897895  INCLUDE 'dimensions.h'
    898   INCLUDE 'iniprint.h'
    899896  include 'clesphys.h'
    900897
     
    945942
    946943    !Et sinon on.... écrit
    947     IF (SIZE(field)/=klon) CALL abort_gcm('iophy::histwrite2d_phy','Field first DIMENSION not equal to klon',1)
     944    IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_phy','Field first DIMENSION not equal to klon',1)
    948945   
    949946    if (prt_level >= 10) then
     
    971968          endif
    972969#else
    973         CALL abort_gcm ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     970        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
    974971#endif
    975972      ELSE 
     
    10521049  USE xios, only: xios_send_field
    10531050#endif
    1054 
     1051  USE print_control_mod, ONLY: prt_level,lunout
    10551052
    10561053  IMPLICIT NONE
    10571054  INCLUDE 'dimensions.h'
    1058   INCLUDE 'iniprint.h'
    10591055  include 'clesphys.h'
    10601056
     
    10951091  ELSE
    10961092    !Et sinon on.... écrit
    1097     IF (SIZE(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     1093    IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
    10981094    nlev=SIZE(field,2)
    10991095    if (nlev.eq.klev+1) then
     
    11191115          CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
    11201116#else
    1121         CALL abort_gcm ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     1117        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
    11221118#endif
    11231119      ELSE 
     
    11971193                                jj_nb, klon_mpi
    11981194  USE xios, only: xios_send_field
    1199 
     1195  USE print_control_mod, ONLY: prt_level,lunout
    12001196
    12011197  IMPLICIT NONE
    12021198  INCLUDE 'dimensions.h'
    1203   INCLUDE 'iniprint.h'
    12041199
    12051200    CHARACTER(LEN=*), INTENT(IN) :: field_name
     
    12161211
    12171212    !Et sinon on.... écrit
    1218     IF (SIZE(field)/=klon) CALL abort_gcm('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
     1213    IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1)
    12191214   
    12201215    CALL Gather_omp(field,buffer_omp)   
     
    12681263                                jj_nb, klon_mpi
    12691264  USE xios, only: xios_send_field
    1270 
     1265  USE print_control_mod, ONLY: prt_level,lunout
    12711266
    12721267  IMPLICIT NONE
    12731268  INCLUDE 'dimensions.h'
    1274   INCLUDE 'iniprint.h'
    12751269
    12761270    CHARACTER(LEN=*), INTENT(IN) :: field_name
     
    12861280
    12871281    !Et on.... écrit
    1288     IF (SIZE(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     1282    IF (SIZE(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
    12891283    nlev=SIZE(field,2)
    12901284
  • LMDZ5/trunk/libf/phylmd/iostart.F90

    r1931 r2311  
    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     
  • LMDZ5/trunk/libf/phylmd/limit_netcdf.F90

    r2302 r2311  
    2929  USE netcdf95,    ONLY: nf95_def_var, nf95_put_att, nf95_put_var
    3030  USE grid_atob_m, ONLY: grille_m, rugosite, sea_ice
     31  USE print_control_mod, ONLY: prt_level,lunout
    3132  IMPLICIT NONE
    3233!-------------------------------------------------------------------------------
     
    3435  include "dimensions.h"
    3536  include "paramet.h"
    36   include "iniprint.h"
    3737  LOGICAL,                    INTENT(IN) :: interbar ! barycentric interpolation
    3838  LOGICAL,                    INTENT(IN) :: extrap   ! SST extrapolation flag
     
    104104     WRITE(lunout,*) 'One of following files must be available : '
    105105     DO k=1,SIZE(fsic); WRITE(lunout,*) TRIM(fsic(k)); END DO
    106      CALL abort_gcm('limit_netcdf','No sea-ice file was found',1)
     106     CALL abort_physic('limit_netcdf','No sea-ice file was found',1)
    107107  END IF
    108108  CALL ncerr(NF90_CLOSE(nid),icefile)
     
    163163     WRITE(lunout,*) 'One of following files must be available : '
    164164     DO k=1,SIZE(fsst); WRITE(lunout,*) TRIM(fsst(k)); END DO
    165      CALL abort_gcm('limit_netcdf','No sst file was found',1)
     165     CALL abort_physic('limit_netcdf','No sst file was found',1)
    166166  END IF
    167167  CALL ncerr(NF90_CLOSE(nid),sstfile)
     
    277277  include "paramet.h"
    278278  include "comgeom2.h"
    279   include "iniprint.h"
    280279!-----------------------------------------------------------------------------
    281280! Arguments:
     
    574573    WRITE(mess,'(a,i3,a,i3,a)')'Unconsistent calendar: ',nd,' days/year, but ',&
    575574      nm,' months/year. Months number should divide days number.'
    576     CALL abort_gcm('mid_months',TRIM(mess),1)
     575    CALL abort_physic('mid_months',TRIM(mess),1)
    577576
    578577  ELSE
     
    626625!-------------------------------------------------------------------------------
    627626  USE netcdf, ONLY : NF90_NOERR, NF90_STRERROR
     627  USE print_control_mod, ONLY: lunout
    628628  IMPLICIT NONE
    629629!-------------------------------------------------------------------------------
     
    632632  CHARACTER(LEN=*), INTENT(IN) :: fnam
    633633!-------------------------------------------------------------------------------
    634 #include "iniprint.h"
    635634  IF(ncres/=NF90_NOERR) THEN
    636635    WRITE(lunout,*)'Problem with file '//TRIM(fnam)//' in routine limit_netcdf.'
    637     CALL abort_gcm('limit_netcdf',NF90_STRERROR(ncres),1)
     636    CALL abort_physic('limit_netcdf',NF90_STRERROR(ncres),1)
    638637  END IF
    639638
  • LMDZ5/trunk/libf/phylmd/limit_read_mod.F90

    r2209 r2311  
    151151    IMPLICIT NONE
    152152   
    153     INCLUDE "iniprint.h"
    154 
    155153! In- and ouput arguments
    156154!****************************************************************************************
     
    195193       IF ( type_ocean /= 'couple' ) THEN
    196194          ALLOCATE(pctsrf(klon,nbsrf), sst(klon), stat=ierr)
    197           IF (ierr /= 0) CALL abort_gcm(modname, 'PB in allocating pctsrf and sst',1)
     195          IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating pctsrf and sst',1)
    198196       END IF
    199197
    200198       IF ( .NOT. ok_veget ) THEN
    201199          ALLOCATE(rugos(klon), albedo(klon), stat=ierr)
    202           IF (ierr /= 0) CALL abort_gcm(modname, 'PB in allocating rugos and albedo',1)
     200          IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating rugos and albedo',1)
    203201       END IF
    204202
     
    220218
    221219          ierr = NF90_OPEN ('limit.nc', NF90_NOWRITE, nid)
    222           IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,&
     220          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,&
    223221               'Pb d''ouverture du fichier de conditions aux limites',1)
    224222         
     
    239237! Ocean fraction
    240238             ierr = NF90_INQ_VARID(nid, 'FOCE', nvarid)
    241              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname, 'Le champ <FOCE> est absent',1)
     239             IF (ierr /= NF90_NOERR) CALL abort_physic(modname, 'Le champ <FOCE> est absent',1)
    242240             
    243241             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)
     242             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FOCE>' ,1)
    245243!
    246244! Sea-ice fraction
    247245             ierr = NF90_INQ_VARID(nid, 'FSIC', nvarid)
    248              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <FSIC> est absent',1)
     246             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FSIC> est absent',1)
    249247
    250248             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)
     249             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FSIC>' ,1)
    252250
    253251
     
    257255! Land fraction
    258256                ierr = NF90_INQ_VARID(nid, 'FTER', nvarid)
    259                 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <FTER> est absent',1)
     257                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FTER> est absent',1)
    260258               
    261259                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)
     260                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FTER>',1)
    263261!
    264262! Continentale ice fraction
    265263                ierr = NF90_INQ_VARID(nid, 'FLIC', nvarid)
    266                 IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <FLIC> est absent',1)
     264                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FLIC> est absent',1)
    267265
    268266                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)
     267                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FLIC>',1)
    270268             END IF
    271269
     
    279277
    280278             ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
    281              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <SST> est absent',1)
     279             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <SST> est absent',1)
    282280
    283281             ierr = NF90_GET_VAR(nid,nvarid,sst_glo,start,epais)
    284              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <SST>',1)
     282             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <SST>',1)
    285283         
    286284          END IF
     
    295293! Read albedo
    296294             ierr = NF90_INQ_VARID(nid, 'ALB', nvarid)
    297              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <ALB> est absent',1)
     295             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <ALB> est absent',1)
    298296
    299297             ierr = NF90_GET_VAR(nid,nvarid,alb_glo,start,epais)
    300              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <ALB>',1)
     298             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <ALB>',1)
    301299!
    302300! Read rugosity
    303301             ierr = NF90_INQ_VARID(nid, 'RUG', nvarid)
    304              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Le champ <RUG> est absent',1)
     302             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <RUG> est absent',1)
    305303
    306304             ierr = NF90_GET_VAR(nid,nvarid,rug_glo,start,epais)
    307              IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Lecture echouee pour <RUG>',1)
     305             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <RUG>',1)
    308306
    309307          END IF
     
    314312!****************************************************************************************
    315313          ierr = NF90_CLOSE(nid)
    316           IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1)
     314          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
    317315       ENDIF ! is_mpi_root
    318316
  • LMDZ5/trunk/libf/phylmd/limit_slab.F90

    r2209 r2311  
    113113!****************************************************************************************
    114114        ierr = NF90_CLOSE(nid)
    115         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1)
     115        IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
    116116        END IF ! Read File
    117117        IF (read_sst) THEN
     
    133133     IF (.NOT. ALLOCATED(bils_save)) THEN
    134134        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)
     135        IF (ierr /= 0) CALL abort_physic('limit_slab', 'pb in allocation',1)
    136136     END IF
    137137
  • LMDZ5/trunk/libf/phylmd/minmaxqfi.F90

    r2098 r2311  
    44SUBROUTINE minmaxqfi(zq,qmin,qmax,comment)
    55  USE dimphy
     6  USE print_control_mod, ONLY: prt_level
    67  IMPLICIT NONE
    78
     
    1516  INTEGER                     :: i, jbad, k
    1617
    17   include "iniprint.h"
    18  
    1918  DO k = 1, klev
    2019     jbad = 0
  • LMDZ5/trunk/libf/phylmd/nonlocal.F90

    r1992 r2311  
    2121  ! ======================================================================
    2222  include "YOMCST.h"
    23   include "iniprint.h"
    2423
    2524  ! Arguments:
  • LMDZ5/trunk/libf/phylmd/o3cm.F90

    r1992 r2311  
    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)
  • LMDZ5/trunk/libf/phylmd/oasis.F90

    r2054 r2311  
    9999    USE wxios, ONLY : wxios_context_init
    100100#endif
    101 
     101    USE print_control_mod, ONLY: lunout
    102102
    103103    INCLUDE "dimensions.h"
    104     INCLUDE "iniprint.h"
    105104
    106105! Local variables
     
    218217       IF (ierror .NE. PRISM_Ok) THEN
    219218          abort_message=' Probleme init dans prism_init_comp '
    220           CALL abort_gcm(modname,abort_message,1)
     219          CALL abort_physic(modname,abort_message,1)
    221220       ELSE
    222221          WRITE(lunout,*) 'inicma : init psmile ok '
     
    240239    IF (ierror .NE. PRISM_Ok) THEN
    241240       abort_message=' Probleme dans prism_def_partition '
    242        CALL abort_gcm(modname,abort_message,1)
     241       CALL abort_physic(modname,abort_message,1)
    243242    ELSE
    244243       WRITE(lunout,*) 'inicma : decomposition domaine psmile ok '
     
    268267                  inforecv(jf)%name
    269268             abort_message=' Problem in call to prism_def_var_proto for fields to receive'
    270              CALL abort_gcm(modname,abort_message,1)
     269             CALL abort_physic(modname,abort_message,1)
    271270          ENDIF
    272271       ENDIF
     
    286285                  infosend(jf)%name
    287286             abort_message=' Problem in call to prism_def_var_proto for fields to send'
    288              CALL abort_gcm(modname,abort_message,1)
     287             CALL abort_physic(modname,abort_message,1)
    289288          ENDIF
    290289       ENDIF
     
    297296    IF (ierror .NE. PRISM_Ok) THEN
    298297       abort_message=' Problem in call to prism_endef_proto'
    299        CALL abort_gcm(modname,abort_message,1)
     298       CALL abort_physic(modname,abort_message,1)
    300299    ELSE
    301300       WRITE(lunout,*) 'inicma : endef psmile ok '
     
    320319!======================================================================
    321320!
     321    USE print_control_mod, ONLY: lunout
    322322    INCLUDE "dimensions.h"
    323     INCLUDE "iniprint.h"
    324323! Input arguments
    325324!************************************************************************************
     
    362361              WRITE (lunout,*)  'Error with receiving filed : ', inforecv(i)%name, ktime   
    363362              abort_message=' Problem in prism_get_proto '
    364               CALL abort_gcm(modname,abort_message,1)
     363              CALL abort_physic(modname,abort_message,1)
    365364          ENDIF
    366365      ENDIF
     
    382381!
    383382!
     383    USE print_control_mod, ONLY: lunout
    384384    INCLUDE "dimensions.h"
    385     INCLUDE "iniprint.h"
    386385! Input arguments
    387386!************************************************************************************
     
    444443              WRITE (lunout,*) 'Error with sending field :', infosend(i)%name, ktime   
    445444              abort_message=' Problem in prism_put_proto '
    446               CALL abort_gcm(modname,abort_message,1)
     445              CALL abort_physic(modname,abort_message,1)
    447446          ENDIF
    448447      ENDIF
     
    459458          IF (ierror .NE. PRISM_Ok) THEN
    460459             abort_message=' Problem in prism_terminate_proto '
    461              CALL abort_gcm(modname,abort_message,1)
     460             CALL abort_physic(modname,abort_message,1)
    462461          ENDIF
    463462       ENDIF
  • LMDZ5/trunk/libf/phylmd/ocean_slab_mod.F90

    r2254 r2311  
    8888    use IOIPSL
    8989
    90     INCLUDE "iniprint.h"
    9190    ! For ok_xxx vars (Ekman...)
    9291    INCLUDE "clesphys.h"
     
    110109    IF (error /= 0) THEN
    111110       abort_message='Pb allocation tmp_pctsrf_slab'
    112        CALL abort_gcm(modname,abort_message,1)
     111       CALL abort_physic(modname,abort_message,1)
    113112    ENDIF
    114113    fsic(:)=0.
     
    121120!****************************************************************************************
    122121    ALLOCATE(tslab(klon,nslay), stat=error)
    123        IF (error /= 0) CALL abort_gcm &
     122       IF (error /= 0) CALL abort_physic &
    124123         (modname,'pb allocation tslab', 1)
    125124
     
    127126    IF (error /= 0) THEN
    128127       abort_message='Pb allocation slab_bils'
    129        CALL abort_gcm(modname,abort_message,1)
     128       CALL abort_physic(modname,abort_message,1)
    130129    ENDIF
    131130    slab_bils(:) = 0.0   
     
    133132    IF (error /= 0) THEN
    134133       abort_message='Pb allocation slab_bils_cum'
    135        CALL abort_gcm(modname,abort_message,1)
     134       CALL abort_physic(modname,abort_message,1)
    136135    ENDIF
    137136    bils_cum(:) = 0.0   
     
    141140        IF (error /= 0) THEN
    142141           abort_message='Pb allocation slab_bilg'
    143            CALL abort_gcm(modname,abort_message,1)
     142           CALL abort_physic(modname,abort_message,1)
    144143        ENDIF
    145144        slab_bilg(:) = 0.0   
     
    147146        IF (error /= 0) THEN
    148147           abort_message='Pb allocation slab_bilg_cum'
    149            CALL abort_gcm(modname,abort_message,1)
     148           CALL abort_physic(modname,abort_message,1)
    150149        ENDIF
    151150        bilg_cum(:) = 0.0   
     
    153152        IF (error /= 0) THEN
    154153           abort_message='Pb allocation slab_tice'
    155            CALL abort_gcm(modname,abort_message,1)
     154           CALL abort_physic(modname,abort_message,1)
    156155        ENDIF
    157156        ALLOCATE(seaice(klon), stat = error)
    158157        IF (error /= 0) THEN
    159158           abort_message='Pb allocation slab_seaice'
    160            CALL abort_gcm(modname,abort_message,1)
     159           CALL abort_physic(modname,abort_message,1)
    161160        ENDIF
    162161    END IF
     
    169168    IF (error /= 0) THEN
    170169       abort_message='Pb allocation slabh'
    171        CALL abort_gcm(modname,abort_message,1)
     170       CALL abort_physic(modname,abort_message,1)
    172171    ENDIF
    173172    slabh(1)=50.
     
    226225    USE calcul_fluxs_mod
    227226
    228     INCLUDE "iniprint.h"
    229227    INCLUDE "clesphys.h"
    230228
  • LMDZ5/trunk/libf/phylmd/orografi.F90

    r1992 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/orografi_strato.F90

    r2048 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/pbl_surface_mod.F90

    r2307 r2311  
    4949
    5050    USE indice_sol_mod
     51    USE print_control_mod, ONLY: lunout
    5152
    5253    INCLUDE "dimsoil.h"
    53     INCLUDE "iniprint.h"
    5454 
    5555! Input variables
     
    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    USE print_control_mod, ONLY: prt_level,lunout
    263264
    264265    IMPLICIT NONE
     
    266267    INCLUDE "dimsoil.h"
    267268    INCLUDE "YOMCST.h"
    268     INCLUDE "iniprint.h"
    269269    INCLUDE "YOETHF.h"
    270270    INCLUDE "FCTTRE.h"
     
    18711871          WRITE(lunout,*) 'Surface index = ', nsrf
    18721872          abort_message = 'Surface index not valid'
    1873           CALL abort_gcm(modname,abort_message,1)
     1873          CALL abort_physic(modname,abort_message,1)
    18741874       END SELECT
    18751875
     
    30893089                ! Security abort. This option has never been tested. To test, comment the following line.
    30903090!                abort_message='The fraction of the continents have changed!'
    3091 !                CALL abort_gcm(modname,abort_message,1)
     3091!                CALL abort_physic(modname,abort_message,1)
    30923092                nfois(nsrf) = nfois(nsrf) + 1
    30933093             END IF
  • LMDZ5/trunk/libf/phylmd/phyetat0.F90

    r2265 r2311  
    223223        IF (isw.GT.99) THEN
    224224           PRINT*, "Trop de bandes SW"
    225            call abort_gcm("phyetat0", "", 1)
     225           call abort_physic("phyetat0", "", 1)
    226226        ENDIF
    227227        WRITE(str2, '(i2.2)') isw
     
    238238        IF (isoil.GT.99) THEN
    239239           PRINT*, "Trop de couches "
    240            call abort_gcm("phyetat0", "", 1)
     240           call abort_physic("phyetat0", "", 1)
    241241        ENDIF
    242242        WRITE(str2,'(i2.2)') isoil
     
    359359     IF (carbon_cycle_cpl) THEN
    360360        ALLOCATE(co2_send(klon), stat=ierr)
    361         IF (ierr /= 0) CALL abort_gcm('phyetat0', 'pb allocation co2_send', 1)
     361        IF (ierr /= 0) CALL abort_physic('phyetat0', 'pb allocation co2_send', 1)
    362362        found=phyetat0_get(1,co2_send,"co2_send","co2 send",0.)
    363363     END IF
     
    449449USE iostart, ONLY : get_field
    450450USE dimphy, only: klon
     451USE print_control_mod, ONLY: lunout
    451452
    452453IMPLICIT NONE
    453 INCLUDE "iniprint.h"
    454454
    455455LOGICAL phyetat0_get
     
    488488USE dimphy, only: klon
    489489USE indice_sol_mod, only: nbsrf
     490USE print_control_mod, ONLY: lunout
    490491
    491492IMPLICIT NONE
    492 INCLUDE "iniprint.h"
    493493
    494494LOGICAL phyetat0_srf
     
    506506     IF (nbsrf.GT.99) THEN
    507507        WRITE(lunout,*) "Trop de sous-mailles"
    508         call abort_gcm("phyetat0", "", 1)
     508        call abort_physic("phyetat0", "", 1)
    509509     ENDIF
    510510
  • LMDZ5/trunk/libf/phylmd/phyredem.F90

    r2299 r2311  
    2323  IMPLICIT none
    2424
    25   include "iniprint.h"
    2625  include "dimsoil.h"
    2726  include "clesphys.h"
     
    127126
    128127  IF(nbsrf>99) THEN
    129     PRINT*, "Trop de sous-mailles";  CALL abort_gcm("phyredem", "", 1)
     128    PRINT*, "Trop de sous-mailles";  CALL abort_physic("phyredem", "", 1)
    130129  END IF
    131130  IF(nsoilmx>99) THEN
    132     PRINT*, "Trop de sous-surfaces"; CALL abort_gcm("phyredem", "", 1)
     131    PRINT*, "Trop de sous-surfaces"; CALL abort_physic("phyredem", "", 1)
    133132  END IF
    134133  IF(nsw>99) THEN
    135     PRINT*, "Trop de bandes"; CALL abort_gcm("phyredem", "", 1)
     134    PRINT*, "Trop de bandes"; CALL abort_physic("phyredem", "", 1)
    136135  END IF
    137136
  • LMDZ5/trunk/libf/phylmd/phys_output_mod.F90

    r2167 r2311  
    4545    USE phys_output_ctrlout_mod
    4646    USE mod_grid_phy_lmdz, only: klon_glo
     47    USE print_control_mod, ONLY: prt_level,lunout
    4748
    4849#ifdef CPP_XIOS
     
    5758    include "thermcell.h"
    5859    include "comvert.h"
    59     include "iniprint.h"
    6060
    6161    ! ug Nouveaux arguments n\'ecessaires au histwrite_mod:
     
    523523    use ioipsl
    524524    USE phys_cal_mod
     525    USE print_control_mod, ONLY: lunout
    525526
    526527    IMPLICIT NONE
     
    533534    include "temps.h"
    534535    include "comconst.h"
    535     include "iniprint.h"
    536536
    537537    ipos=scan(str,'0123456789.',.TRUE.)
     
    540540    WRITE(lunout,*) "ipos = ", ipos
    541541    WRITE(lunout,*) "il = ", il
    542     if (ipos == 0) call abort_gcm("convers_timesteps", "bad str", 1)
     542    if (ipos == 0) call abort_physic("convers_timesteps", "bad str", 1)
    543543    read(str(1:ipos),*) ttt
    544544    WRITE(lunout,*)ttt
  • LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90

    r2284 r2311  
    265265    INCLUDE "YOMCST.h"
    266266    INCLUDE "dimensions.h"
    267     include "iniprint.h"
    268267
    269268    ! Input
  • LMDZ5/trunk/libf/phylmd/physiq.F90

    r2309 r2311  
    2121  USE mod_phys_lmdz_para
    2222  USE iophy
    23   USE misc_mod, mydebug=>debug
     23  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
    2424  USE vampir
    2525  USE pbl_surface_mod, ONLY : pbl_surface
     
    121121  include "clesphys.h"
    122122  include "temps.h"
    123   include "iniprint.h"
    124123  include "thermcell.h"
    125124  !======================================================================
     
    10601059     IF (iflag_con.EQ.2.AND.iflag_cld_th.GT.-1) THEN
    10611060        abort_message = 'Tiedtke needs iflag_cld_th=-2 or -1'
    1062         CALL abort_gcm (modname,abort_message,1)
     1061        CALL abort_physic (modname,abort_message,1)
    10631062     ENDIF
    10641063     !
     
    11191118             pdtphys
    11201119        abort_message='Pas physique n est pas correct '
    1121         !           call abort_gcm(modname,abort_message,1)
     1120        !           call abort_physic(modname,abort_message,1)
    11221121        dtime=pdtphys
    11231122     ENDIF
     
    11261125             klon
    11271126        abort_message='nlon et klon ne sont pas coherents'
    1128         call abort_gcm(modname,abort_message,1)
     1127        call abort_physic(modname,abort_message,1)
    11291128     ENDIF
    11301129     IF (nlev .NE. klev) THEN
     
    11321131             klev
    11331132        abort_message='nlev et klev ne sont pas coherents'
    1134         call abort_gcm(modname,abort_message,1)
     1133        call abort_physic(modname,abort_message,1)
    11351134     ENDIF
    11361135     !
     
    11391138        WRITE(lunout,*)"Au minimum 4 appels par jour si cycle diurne"
    11401139        abort_message='Nbre d appels au rayonnement insuffisant'
    1141         call abort_gcm(modname,abort_message,1)
     1140        call abort_physic(modname,abort_message,1)
    11421141     ENDIF
    11431142     WRITE(lunout,*)"Clef pour la convection, iflag_con=", iflag_con
     
    11941193           IF(nCFMIP.GT.npCFMIP) THEN
    11951194              print*,'nCFMIP > npCFMIP : augmenter npCFMIP et recompiler'
    1196               call abort_gcm("physiq", "", 1)
     1195              call abort_physic("physiq", "", 1)
    11971196           else
    11981197              print*,'physiq npCFMIP=',npCFMIP,'nCFMIP=',nCFMIP
     
    16991698        IF (read_climoz/=-1) THEN
    17001699           abort_message ='read_climoz=-1 is recommended when solarlong0=1000.'
    1701            CALL abort_gcm (modname,abort_message,1)
     1700           CALL abort_physic (modname,abort_message,1)
    17021701        ENDIF
    17031702     ELSE
     
    20962095  IF (iflag_con.EQ.1) THEN
    20972096     abort_message ='reactiver le call conlmd dans physiq.F'
    2098      CALL abort_gcm (modname,abort_message,1)
     2097     CALL abort_physic (modname,abort_message,1)
    20992098     !     CALL conlmd (dtime, paprs, pplay, t_seri, q_seri, conv_q,
    21002099     !    .             d_t_con, d_q_con,
     
    22642263           else
    22652264       abort_message ='Ne pas passer la car www non calcule'
    2266        CALL abort_gcm (modname,abort_message,1)
     2265       CALL abort_physic (modname,abort_message,1)
    22672266
    22682267!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    24562455  ELSE
    24572456     WRITE(lunout,*) "iflag_con non-prevu", iflag_con
    2458      call abort_gcm("physiq", "", 1)
     2457     call abort_physic("physiq", "", 1)
    24592458  ENDIF
    24602459
     
    31233122           IF (aerosol_couple .AND. config_inca == 'aero' ) THEN
    31243123            abort_message='config_inca=aero et rrtm=1 impossible'
    3125             call abort_gcm(modname,abort_message,1)
     3124            call abort_physic(modname,abort_message,1)
    31263125           ELSE
    31273126!
     
    31383137
    31393138              abort_message='You should compile with -rrtm if running with iflag_rrtm=1'
    3140               call abort_gcm(modname,abort_message,1)
     3139              call abort_physic(modname,abort_message,1)
    31413140#endif
    31423141              !
     
    31713170
    31723171           abort_message='You should compile with -rrtm if running with iflag_rrtm=1'
    3173            call abort_gcm(modname,abort_message,1)
     3172           call abort_physic(modname,abort_message,1)
    31743173#endif
    31753174        ENDIF
     
    34003399        IF (ok_cdnc.AND.NRADLP.NE.3) THEN
    34013400           abort_message='RRTM choix incoherent NRADLP doit etre egal a 3 pour ok_cdnc'
    3402            call abort_gcm(modname,abort_message,1)
     3401           call abort_physic(modname,abort_message,1)
    34033402        endif
    34043403#else
    34053404
    34063405        abort_message='You should compile with -rrtm if running with iflag_rrtm=1'
    3407         call abort_gcm(modname,abort_message,1)
     3406        call abort_physic(modname,abort_message,1)
    34083407#endif
    34093408     ENDIF
     
    42924291    IF (abortphy==1) THEN
    42934292       abort_message ='Plantage hgardfou'
    4294        CALL abort_gcm (modname,abort_message,1)
     4293       CALL abort_physic (modname,abort_message,1)
    42954294    ENDIF
    42964295
  • LMDZ5/trunk/libf/phylmd/phystokenc.F90

    r1907 r2311  
    1313  USE control_mod
    1414  USE indice_sol_mod
     15  USE print_control_mod, ONLY: lunout
    1516 
    1617  IMPLICIT NONE
     
    2324  INCLUDE "dimensions.h"
    2425  INCLUDE "tracstoke.h"
    25   INCLUDE "iniprint.h"
    2626!======================================================================
    2727
  • LMDZ5/trunk/libf/phylmd/phytrac_mod.F90

    r2284 r2311  
    101101
    102102    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
     103    USE print_control_mod, ONLY: lunout
    103104
    104105    IMPLICIT NONE
     
    110111    INCLUDE "paramet.h"
    111112    INCLUDE "thermcell.h"
    112     INCLUDE "iniprint.h"
    113113    !==========================================================================
    114114    !                   -- ARGUMENT DESCRIPTION --
     
    445445       WRITE(*,*) 'FIRST TIME IN PHYTRAC : pdtphys(sec) = ',pdtphys,'ecrit_tra (sec) = ',ecrit_tra
    446446       ALLOCATE( source(klon,nbtr), stat=ierr)
    447        IF (ierr /= 0) CALL abort_gcm('phytrac', 'pb in allocation 1',1)
     447       IF (ierr /= 0) CALL abort_physic('phytrac', 'pb in allocation 1',1)
    448448
    449449       ALLOCATE( aerosol(nbtr), stat=ierr)
    450        IF (ierr /= 0) CALL abort_gcm('phytrac', 'pb in allocation 2',1)
     450       IF (ierr /= 0) CALL abort_physic('phytrac', 'pb in allocation 2',1)
    451451
    452452
     
    503503!                ELSE
    504504!                   WRITE(lunout,*) 'pb it=', it
    505 !                   CALL abort_gcm('phytrac','pb it scavenging',1)
     505!                   CALL abort_physic('phytrac','pb it scavenging',1)
    506506!                ENDIF
    507507                !--test OB
     
    539539
    540540       IF (lessivage.AND.config_inca.EQ.'inca') THEN
    541           CALL abort_gcm('phytrac', 'lessivage=T config_inca=inca impossible',1)
     541          CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1)
    542542          STOP
    543543       ENDIF
     
    740740    ELSE
    741741       !
    742        CALL abort_gcm('iflag_vdf_trac', 'cas non prevu',1)
     742       CALL abort_physic('iflag_vdf_trac', 'cas non prevu',1)
    743743       !
    744744    END IF ! couche limite
  • LMDZ5/trunk/libf/phylmd/radiation_AR4.F90

    r1992 r2311  
    66    psolswai, ok_ade, ok_aie)
    77  USE dimphy
     8  USE print_control_mod, ONLY: lunout
    89  IMPLICIT NONE
    910
     
    1213  ! ym#include "raddim.h"
    1314  include "YOMCST.h"
    14   include "iniprint.h"
    1515
    1616  ! ------------------------------------------------------------------
     
    494494  ! ym#include "dimphy.h"
    495495  ! ym#include "raddim.h"i
    496   include "iniprint.h"
    497496
    498497  ! ------------------------------------------------------------------
     
    21522151    plwup, plwdn, plwup0, plwdn0)
    21532152  USE dimphy
     2153  USE print_control_mod, ONLY: lunout
    21542154  IMPLICIT NONE
    21552155  ! ym#include "dimensions.h"
     
    21582158  include "raddimlw.h"
    21592159  include "YOMCST.h"
    2160   include "iniprint.h"
    21612160
    21622161  ! -----------------------------------------------------------------------
  • LMDZ5/trunk/libf/phylmd/radlwsw_m.F90

    r2297 r2311  
    171171  include "YOMCST.h"
    172172  include "clesphys.h"
    173   include "iniprint.h"
    174173
    175174! Input arguments
     
    393392  IF (nb_gr*kdlon .NE. KLON) THEN
    394393      PRINT*, "kdlon mauvais:", KLON, kdlon, nb_gr
    395       call abort_gcm("radlwsw", "", 1)
     394      call abort_physic("radlwsw", "", 1)
    396395  ENDIF
    397396  IF (kflev .NE. KLEV) THEN
    398397      PRINT*, "kflev differe de KLEV, kflev, KLEV"
    399       call abort_gcm("radlwsw", "", 1)
     398      call abort_physic("radlwsw", "", 1)
    400399  ENDIF
    401400  !-------------------------------------------
     
    10271026#else
    10281027    abort_message="You should compile with -rrtm if running with iflag_rrtm=1"
    1029     call abort_gcm(modname, abort_message, 1)
     1028    call abort_physic(modname, abort_message, 1)
    10301029#endif
    10311030    ENDIF ! iflag_rrtm
  • LMDZ5/trunk/libf/phylmd/read_map2D.F90

    r1907 r2311  
    66  USE mod_grid_phy_lmdz
    77  USE mod_phys_lmdz_para
    8 
     8  USE print_control_mod, ONLY: lunout
    99
    1010  IMPLICIT NONE
     
    2727  REAL, DIMENSION(nbp_lon,nbp_lat) :: var_glo2D_tmp ! 2D global
    2828  REAL, DIMENSION(klon_glo)        :: var_glo1D     ! 1D global
    29   INCLUDE "iniprint.h"
    3029
    3130! Read variable from file. Done by master process MPI and master thread OpenMP
     
    6665  CONTAINS
    6766    SUBROUTINE write_err_mess(err_mess)
    68 
     67      USE print_control_mod, ONLY: lunout
     68      IMPLICIT NONE
    6969      CHARACTER(len=*), INTENT(IN) :: err_mess
    70       INCLUDE "iniprint.h"
    7170     
    7271      WRITE(lunout,*) 'Error in read_map2D, filename = ', trim(filename)
     
    7473      WRITE(lunout,*) 'Error in read_map2D, timestep = ', timestep
    7574
    76       CALL abort_gcm(modname, err_mess, 1)
     75      CALL abort_physic(modname, err_mess, 1)
    7776
    7877    END SUBROUTINE write_err_mess
  • LMDZ5/trunk/libf/phylmd/readaerosol.F90

    r1907 r2311  
    2020!****************************************************************************************
    2121  USE dimphy
     22  USE print_control_mod, ONLY: lunout
    2223
    2324  IMPLICIT NONE
    24 
    25  INCLUDE "iniprint.h"
    2625
    2726  ! Input arguments
     
    130129           IF (klev_src /= klev_src2) THEN
    131130              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)
     131              CALL abort_physic('readaersosol','Error in number of vertical levels',1)
    133132           END IF
    134133           
     
    162161  ELSE
    163162     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)
     163     CALL abort_physic('readaerosol','Error : aer_type parameter not accepted',1)
    165164  END IF ! type
    166165
     
    192191    USE mod_phys_lmdz_para
    193192    USE iophy, ONLY : io_lon, io_lat
     193    USE print_control_mod, ONLY: lunout
    194194
    195195    IMPLICIT NONE
    196196     
    197197    INCLUDE "dimensions.h"     
    198     INCLUDE "iniprint.h"
    199198
    200199! Input argumets
     
    260259          WRITE(lunout,*) 'longitudes in model :', io_lon
    261260         
    262           CALL abort_gcm('get_aero_fromfile', 'longitudes are not the same in file and model',1)
     261          CALL abort_physic('get_aero_fromfile', 'longitudes are not the same in file and model',1)
    263262       END IF
    264263
     
    283282          WRITE(lunout,*) 'latitudes in file ', TRIM(fname),' : ', lat_src     
    284283          WRITE(lunout,*) 'latitudes in model :', io_lat
    285           CALL abort_gcm('get_aero_fromfile', 'latitudes do not correspond between file and model',1)
     284          CALL abort_physic('get_aero_fromfile', 'latitudes do not correspond between file and model',1)
    286285       END IF
    287286
     
    297296          IF (ierr /= NF90_NOERR) THEN
    298297             ! Dimension PRESNIVS not found either
    299              CALL abort_gcm('get_aero_fromfile', 'dimension lev or presnivs not in file',1)
     298             CALL abort_physic('get_aero_fromfile', 'dimension lev or presnivs not in file',1)
    300299          ELSE
    301300             ! Old file found
     
    315314     ! Allocate variables depending on the number of vertical levels
    316315       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)
     316       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 1',1)
    318317
    319318       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)
     319       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 2',1)
    321320
    322321! 3) Read all variables from file
     
    333332!       IF (nbr_tsteps /= 12 .AND. nbr_tsteps /= 14) THEN
    334333       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)
     334         CALL abort_physic('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)',1)
    336335       ENDIF
    337336
     
    522521       
    523522       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)
     523       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 3',1)
    525524       
    526525       ! Transform from 2D to 1D field
     
    546545    IF (.NOT. ASSOCIATED(pt_ap)) THEN  ! if pt_ap is allocated also pt_b is allocated
    547546       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)
     547       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 4',1)
    549548    END IF
    550549    CALL bcast(pt_ap)
     
    554553    IF (ASSOCIATED(pt_year)) DEALLOCATE(pt_year)
    555554    ALLOCATE(pt_year(klon, klev_src, 12), stat=ierr)
    556     IF (ierr /= 0) CALL abort_gcm('get_aero_fromfile', 'pb in allocation 5',1)
     555    IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 5',1)
    557556
    558557    ! Scatter global field to local domain at local process
     
    572571  SUBROUTINE check_err(status,text)
    573572    USE netcdf
     573    USE print_control_mod, ONLY: lunout
    574574    IMPLICIT NONE
    575575
    576     INCLUDE "iniprint.h"
    577576    INTEGER, INTENT (IN) :: status
    578577    CHARACTER(len=*), INTENT (IN), OPTIONAL :: text
     
    583582          WRITE(lunout,*) 'Error in get_aero_fromfile : ',text
    584583       END IF
    585        CALL abort_gcm('get_aero_fromfile',trim(nf90_strerror(status)),1)
     584       CALL abort_physic('get_aero_fromfile',trim(nf90_strerror(status)),1)
    586585    END IF
    587586
  • LMDZ5/trunk/libf/phylmd/readaerosol_interp.F90

    r1907 r2311  
    2121  USE phys_cal_mod
    2222  USE pres2lev_mod
     23  USE print_control_mod, ONLY: lunout
    2324
    2425  IMPLICIT NONE
     
    2829  INCLUDE "temps.h"     
    2930  INCLUDE "clesphys.h"
    30   INCLUDE "iniprint.h"
    3131  INCLUDE "dimensions.h"
    3232  INCLUDE "comvert.h"
     
    150150  IF (.NOT. ALLOCATED(var_day)) THEN
    151151     ALLOCATE( var_day(klon, klev, naero_spc), stat=ierr)
    152      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 1',1)
     152     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 1',1)
    153153     ALLOCATE( pi_var_day(klon, klev, naero_spc), stat=ierr)
    154      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 2',1)
     154     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 2',1)
    155155
    156156     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)
     157     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 3',1)
    158158
    159159     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)
     160     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 4',1)
    161161
    162162     lnewday=.TRUE.
     
    209209        END IF
    210210     ELSE
    211         CALL abort_gcm('readaerosol_interp', 'this aer_type not supported',1)
     211        CALL abort_physic('readaerosol_interp', 'this aer_type not supported',1)
    212212     END IF
    213213
     
    216216     IF (.NOT. ALLOCATED(var_year)) THEN
    217217        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)
     218        IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 5',1)
    219219     END IF
    220220     var_year(:,:,:,id_aero) = pt_tmp(:,:,:)
     
    230230        WRITE(lunout,*) 'Error! All forcing files for the same aerosol must have the same vertical dimension'
    231231        WRITE(lunout,*) 'Aerosol : ', name_aero(id_aero)
    232         CALL abort_gcm('readaerosol_interp','Differnt vertical axes in aerosol forcing files',1)
     232        CALL abort_physic('readaerosol_interp','Differnt vertical axes in aerosol forcing files',1)
    233233     END IF
    234234
    235235     IF (.NOT. ALLOCATED(pi_var_year)) THEN
    236236        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)
     237        IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 6',1)
    238238     END IF
    239239     pi_var_year(:,:,:,id_aero) = pt_tmp(:,:,:)
     
    259259        IF (  psurf_year(1,1,id_aero) /= pi_psurf_year(1,1,id_aero) ) THEN
    260260           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)
     261           CALL abort_physic('readaerosol_interp', 'The aerosol files have not the same format',1)
    262262        END IF
    263263       
    264264        IF (klev /= klev_src) THEN
    265265           WRITE(lunout,*) 'Old format of aerosol file do not allowed vertical interpolation'
    266            CALL abort_gcm('readaerosol_interp', 'Old aerosol file not possible',1)
     266           CALL abort_physic('readaerosol_interp', 'Old aerosol file not possible',1)
    267267        END IF
    268268
     
    336336       END IF
    337337     ELSE
    338        CALL abort_gcm('readaerosol_interp', 'number of months undefined',1)
     338       CALL abort_physic('readaerosol_interp', 'number of months undefined',1)
    339339     ENDIF
    340340     if (debug) then
     
    345345     ! Time interpolation, still on vertical source grid
    346346     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)
     347     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 7',1)
    348348
    349349     ALLOCATE(pplay_src(klon,klev_src), stat=ierr)
    350      IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 8',1)
     350     IF (ierr /= 0) CALL abort_physic('readaerosol_interp', 'pb in allocation 8',1)
    351351     
    352352
     
    544544                 WRITE(lunout,*) 'stop for aerosol : ',name_aero(id_aero)
    545545                 WRITE(lunout,*) 'day1, day2, jDay = ', day1, day2, jDay
    546                  CALL abort_gcm('readaerosol_interp','Error in interpolation 1',1)
     546                 CALL abort_physic('readaerosol_interp','Error in interpolation 1',1)
    547547              END IF
    548548           END DO
     
    563563                 
    564564                 WRITE(lunout,*) 'stop for aerosol : ',name_aero(id_aero)
    565                  CALL abort_gcm('readaerosol_interp','Error in interpolation 2',1)
     565                 CALL abort_physic('readaerosol_interp','Error in interpolation 2',1)
    566566              END IF
    567567           END DO
  • LMDZ5/trunk/libf/phylmd/rrtm/aeropt_6bands_rrtm.F90

    r2231 r2311  
    2222
    2323  INCLUDE "YOMCST.h"
    24   INCLUDE "iniprint.h"
    2524  INCLUDE "clesphys.h"
    2625
  • LMDZ5/trunk/libf/phylmd/soil.F90

    r1931 r2311  
    88  USE mod_phys_lmdz_para
    99  USE indice_sol_mod
     10  USE print_control_mod, ONLY: lunout
    1011
    1112  IMPLICIT NONE
     
    5556  INCLUDE "dimsoil.h"
    5657  INCLUDE "comsoil.h"
    57   INCLUDE "iniprint.h"
    5858!-----------------------------------------------------------------------
    5959! Arguments
     
    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
  • LMDZ5/trunk/libf/phylmd/solarlong.F90

    r1992 r2311  
    22
    33  USE ioipsl
     4  USE print_control_mod, ONLY: lunout
    45
    56  IMPLICIT NONE
     
    4647  include "planete.h"
    4748  include "YOMCST.h"
    48   include 'iniprint.h'
    4949
    5050  ! arguments:
  • LMDZ5/trunk/libf/phylmd/surf_land_orchidee_mod.F90

    r2240 r2311  
    4545    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    4646    USE indice_sol_mod
    47 
     47    USE print_control_mod, ONLY: lunout
    4848!   
    4949! Cette routine sert d'interface entre le modele atmospherique et le
     
    100100    INCLUDE "temps.h"
    101101    INCLUDE "YOMCST.h"
    102     INCLUDE "iniprint.h"
    103102    INCLUDE "dimensions.h"
    104103 
     
    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       
  • LMDZ5/trunk/libf/phylmd/surf_land_orchidee_noopenmp_mod.F90

    r1958 r2311  
    102102    INCLUDE "temps.h"
    103103    INCLUDE "YOMCST.h"
    104     INCLUDE "iniprint.h"
    105104    INCLUDE "dimensions.h"
    106105 
     
    215214       IF (carbon_cycle_cpl) THEN
    216215          abort_message='You must define preprossing key ORCH_NEW when running carbon_cycle_cpl=y'
    217           CALL abort_gcm(modname,abort_message,1)
     216          CALL abort_physic(modname,abort_message,1)
    218217       END IF
    219218#endif
     
    246245          IF (error /= 0) THEN
    247246             abort_message='Pb allocation lalo'
    248              CALL abort_gcm(modname,abort_message,1)
     247             CALL abort_physic(modname,abort_message,1)
    249248          ENDIF
    250249       ENDIF
     
    253252          IF (error /= 0) THEN
    254253             abort_message='Pb allocation lon_scat'
    255              CALL abort_gcm(modname,abort_message,1)
     254             CALL abort_physic(modname,abort_message,1)
    256255          ENDIF
    257256       ENDIF
     
    260259          IF (error /= 0) THEN
    261260             abort_message='Pb allocation lat_scat'
    262              CALL abort_gcm(modname,abort_message,1)
     261             CALL abort_physic(modname,abort_message,1)
    263262          ENDIF
    264263       ENDIF
     
    301300          IF (error /= 0) THEN
    302301             abort_message='Pb allocation neighbours'
    303              CALL abort_gcm(modname,abort_message,1)
     302             CALL abort_physic(modname,abort_message,1)
    304303          ENDIF
    305304       ENDIF
     
    309308          IF (error /= 0) THEN
    310309             abort_message='Pb allocation contfrac'
    311              CALL abort_gcm(modname,abort_message,1)
     310             CALL abort_physic(modname,abort_message,1)
    312311          ENDIF
    313312       ENDIF
     
    327326          IF (error /= 0) THEN
    328327             abort_message='Pb allocation resolution'
    329              CALL abort_gcm(modname,abort_message,1)
     328             CALL abort_physic(modname,abort_message,1)
    330329          ENDIF
    331330       ENDIF
     
    339338       IF (error /= 0) THEN
    340339          abort_message='Pb allocation coastalflow'
    341           CALL abort_gcm(modname,abort_message,1)
     340          CALL abort_physic(modname,abort_message,1)
    342341       ENDIF
    343342       
     
    345344       IF (error /= 0) THEN
    346345          abort_message='Pb allocation riverflow'
    347           CALL abort_gcm(modname,abort_message,1)
     346          CALL abort_physic(modname,abort_message,1)
    348347       ENDIF
    349348
     
    359358       IF (carbon_cycle_cpl) THEN
    360359          ALLOCATE(fco2_land_inst(klon),stat=error)
    361           IF (error /= 0)  CALL abort_gcm(modname,'Pb in allocation fco2_land_inst',1)
     360          IF (error /= 0)  CALL abort_physic(modname,'Pb in allocation fco2_land_inst',1)
    362361         
    363362          ALLOCATE(fco2_lu_inst(klon),stat=error)
    364           IF(error /=0) CALL abort_gcm(modname,'Pb in allocation fco2_lu_inst',1)
     363          IF(error /=0) CALL abort_physic(modname,'Pb in allocation fco2_lu_inst',1)
    365364       END IF
    366365
    367366       ALLOCATE(fields_cpl(klon,nb_fields_cpl), stat = error)
    368        IF (error /= 0) CALL abort_gcm(modname,'Pb in allocation fields_cpl',1)
     367       IF (error /= 0) CALL abort_physic(modname,'Pb in allocation fields_cpl',1)
    369368
    370369    ENDIF                          ! (fin debut)
  • LMDZ5/trunk/libf/phylmd/surf_landice_mod.F90

    r2254 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/sw_aeroAR4.F90

    r1907 r2311  
    2222  USE dimphy
    2323  USE phys_output_mod, ONLY : swaero_diag
     24  USE print_control_mod, ONLY: lunout
    2425  IMPLICIT NONE
    2526
    2627#include "YOMCST.h"
    2728#include "clesphys.h"
    28 #include "iniprint.h"
    2929  !
    3030  !     ------------------------------------------------------------------
  • LMDZ5/trunk/libf/phylmd/test_disvert_m.F90

    r2049 r2311  
    6161          end do
    6262       end do
    63        call abort_gcm("test_disvert", "bad order of pressure values", 1)
     63       call abort_physic("test_disvert", "bad order of pressure values", 1)
    6464    end if
    6565
  • LMDZ5/trunk/libf/phylmd/thermcell.F90

    r1992 r2311  
    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
  • LMDZ5/trunk/libf/phylmd/thermcellV0_main.F90

    r1978 r2311  
    1414      USE dimphy
    1515      USE comgeomphy , ONLY:rlond,rlatd
     16      USE print_control_mod, ONLY: prt_level,lunout
    1617      IMPLICIT NONE
    1718
     
    4546      include "YOETHF.h"
    4647      include "FCTTRE.h"
    47       include "iniprint.h"
    4848
    4949!   arguments:
     
    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
     
    790790
    791791      subroutine testV0_ltherm(klon,klev,pplev,pplay,long,seuil,ztv,po,ztva,zqla,f_star,zw2,comment)
     792      USE print_control_mod, ONLY: prt_level
    792793      IMPLICIT NONE
    793       include "iniprint.h"
    794794
    795795      integer i, k, klon,klev
     
    833833!thermcell_closure: fermeture, determination de f
    834834!-------------------------------------------------------------------------
     835      USE print_control_mod, ONLY: prt_level,lunout
    835836      IMPLICIT NONE
    836837
    837       include "iniprint.h"
    838838      include "thermcell.h"
    839839      INTEGER ngrid,nlay
     
    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
     
    913913!--------------------------------------------------------------------------
    914914
     915      USE print_control_mod, ONLY: prt_level
    915916      IMPLICIT NONE
    916917
     
    918919      include "YOETHF.h"
    919920      include "FCTTRE.h"
    920       include "iniprint.h"
    921921      include "thermcell.h"
    922922
     
    17111711!thermcell_dry: calcul de zmax et wmax du thermique sec
    17121712!--------------------------------------------------------------------------
     1713       USE print_control_mod, ONLY: prt_level
    17131714       IMPLICIT NONE
    17141715      include "YOMCST.h"       
    1715       include "iniprint.h"
    17161716       INTEGER l,ig
    17171717
     
    19231923!thermcell_init: calcul du profil d alimentation du thermique
    19241924!----------------------------------------------------------------------
     1925      USE print_control_mod, ONLY: prt_level
    19251926      IMPLICIT NONE
    1926       include "iniprint.h"
    19271927      include "thermcell.h"
    19281928
  • LMDZ5/trunk/libf/phylmd/thermcell_closure.F90

    r1907 r2311  
    1717      IMPLICIT NONE
    1818
    19 #include "iniprint.h"
    2019#include "thermcell.h"
    2120INTEGER ngrid,nlay
  • LMDZ5/trunk/libf/phylmd/thermcell_dq.F90

    r1985 r2311  
    11      subroutine thermcell_dq(ngrid,nlay,impl,ptimestep,fm,entr,  &
    22     &           masse,q,dq,qa,lev_out)
     3      USE print_control_mod, ONLY: prt_level
    34      implicit none
    45
    5 #include "iniprint.h"
    66!=======================================================================
    77!
     
    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
     
    152152      subroutine thermcell_dq_o(ngrid,nlay,impl,ptimestep,fm,entr,  &
    153153     &           masse,q,dq,qa,lev_out)
     154      USE print_control_mod, ONLY: prt_level
    154155      implicit none
    155156
    156 #include "iniprint.h"
    157157!=======================================================================
    158158!
     
    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
  • LMDZ5/trunk/libf/phylmd/thermcell_dry.F90

    r1998 r2311  
    1515!--------------------------------------------------------------------------
    1616
     17       USE print_control_mod, ONLY: prt_level
    1718       IMPLICIT NONE
    1819#include "YOMCST.h"       
    19 #include "iniprint.h"
    2020       INTEGER l,ig
    2121
  • LMDZ5/trunk/libf/phylmd/thermcell_dtke.F90

    r1907 r2311  
    11      subroutine thermcell_dtke(ngrid,nlay,nsrf,ptimestep,fm0,entr0,  &
    22     &           rg,pplev,tke)
     3      USE print_control_mod, ONLY: prt_level
    34      implicit none
    45
    5 #include "iniprint.h"
    66!=======================================================================
    77!
  • LMDZ5/trunk/libf/phylmd/thermcell_dv2.F90

    r1907 r2311  
    22     &    ,fraca,larga  &
    33     &    ,u,v,du,dv,ua,va,lev_out)
     4      USE print_control_mod, ONLY: prt_level,lunout
    45      implicit none
    56
    6 #include "iniprint.h"
    77!=======================================================================
    88!
  • LMDZ5/trunk/libf/phylmd/thermcell_env.F90

    r1907 r2311  
    77!--------------------------------------------------------------
    88
     9      USE print_control_mod, ONLY: prt_level
    910      IMPLICIT NONE
    1011
     
    1213#include "YOETHF.h"
    1314#include "FCTTRE.h"     
    14 #include "iniprint.h"
    1515
    1616      INTEGER ngrid,nlay
  • LMDZ5/trunk/libf/phylmd/thermcell_flux.F90

    r1907 r2311  
    1414!---------------------------------------------------------------------------
    1515
     16      USE print_control_mod, ONLY: prt_level,lunout
    1617      IMPLICIT NONE
    17 #include "iniprint.h"
    1818     
    1919      INTEGER ig,l
     
    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
  • LMDZ5/trunk/libf/phylmd/thermcell_flux2.F90

    r1907 r2311  
    1313!---------------------------------------------------------------------------
    1414
     15      USE print_control_mod, ONLY: prt_level
    1516      IMPLICIT NONE
    16 #include "iniprint.h"
    1717#include "thermcell.h"
    1818     
     
    5050      save fomass_max,alphamax
    5151
    52       logical check_debug,labort_gcm
     52      logical check_debug,labort_physic
    5353
    5454      character (len=20) :: modname='thermcell_flux2'
     
    108108                    print*,'detr_star(ig,l)',detr_star(ig,l)
    109109                    abort_message = ''
    110                     labort_gcm=.true.
    111                     CALL abort_gcm (modname,abort_message,1)
     110                    labort_physic=.true.
     111                    CALL abort_physic (modname,abort_message,1)
    112112               endif
    113113            endif
     
    270270
    271271
    272          labort_gcm=.false.
     272         labort_physic=.false.
    273273         do ig=1,ngrid
    274274            if (entr(ig,l)<0.) then
    275                labort_gcm=.true.
     275               labort_physic=.true.
    276276               igout=ig
    277277               lout=l
     
    279279         enddo
    280280
    281          if (labort_gcm) then
     281         if (labort_physic) then
    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
     
    310310         enddo
    311311
    312          labort_gcm=.false.
     312         labort_physic=.false.
    313313         do ig=1,ngrid
    314314            if (entr(ig,l).lt.0.) then
    315                labort_gcm=.true.
     315               labort_physic=.true.
    316316               igout=ig
    317317            endif
    318318         enddo
    319          if (labort_gcm) then
     319         if (labort_physic) then
    320320            ig=igout
    321321            print*,'ig,l,lmax(ig)',ig,l,lmax(ig)
     
    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
     
    348348         enddo
    349349
    350          labort_gcm=.false.
     350         labort_physic=.false.
    351351         do ig=1,ngrid
    352352            if (detr(ig,l).lt.0.) then
    353                labort_gcm=.true.
     353               labort_physic=.true.
    354354               igout=ig
    355355            endif
    356356        enddo
    357         if (labort_gcm) then
     357        if (labort_physic) then
    358358               ig=igout
    359359               print*,'cas 2 : ig,l,lmax(ig)',ig,l,lmax(ig)
     
    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
     
    427427
    428428      if (1.eq.1) then
    429       labort_gcm=.false.
     429      labort_physic=.false.
    430430      do l=1,klev-1
    431431         do ig=1,ngrid
     
    450450                         igout=ig
    451451                         lout=l
    452                          labort_gcm=.true.
     452                         labort_physic=.true.
    453453                      endif
    454454                      entr(ig,l+1)=entr(ig,l+1)-ddd
     
    461461         enddo
    462462      enddo
    463       if (labort_gcm) then
     463      if (labort_physic) then
    464464                         ig=igout
    465465                         l=lout
     
    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
  • LMDZ5/trunk/libf/phylmd/thermcell_height.F90

    r1998 r2311  
    66!-----------------------------------------------------------------------------
    77      IMPLICIT NONE
    8 #include "iniprint.h"
    98#include "thermcell.h"
    109
  • LMDZ5/trunk/libf/phylmd/thermcell_init.F90

    r1907 r2311  
    88!thermcell_init: calcul du profil d alimentation du thermique
    99!----------------------------------------------------------------------
     10      USE print_control_mod, ONLY: lunout
    1011      IMPLICIT NONE
    11 #include "iniprint.h"
    1212#include "thermcell.h"
    1313
  • LMDZ5/trunk/libf/phylmd/thermcell_main.F90

    r2193 r2311  
    2525      USE comgeomphy , ONLY:rlond,rlatd
    2626      USE indice_sol_mod
     27      USE print_control_mod, ONLY: lunout,prt_level
    2728      IMPLICIT NONE
    2829
     
    6667#include "YOETHF.h"
    6768#include "FCTTRE.h"
    68 #include "iniprint.h"
    6969#include "thermcell.h"
    7070
     
    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
     
    10971097
    10981098      subroutine test_ltherm(klon,klev,pplev,pplay,long,seuil,ztv,po,ztva,zqla,f_star,zw2,comment)
     1099      USE print_control_mod, ONLY: prt_level
    10991100      IMPLICIT NONE
    1100 #include "iniprint.h"
    11011101
    11021102      integer i, k, klon,klev
     
    11381138      subroutine thermcell_tke_transport(ngrid,nlay,ptimestep,fm0,entr0,  &
    11391139     &           rg,pplev,therm_tke_max)
     1140      USE print_control_mod, ONLY: prt_level
    11401141      implicit none
    11411142
    1142 #include "iniprint.h"
    11431143!=======================================================================
    11441144!
  • LMDZ5/trunk/libf/phylmd/thermcell_old.F90

    r1992 r2311  
    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"
  • LMDZ5/trunk/libf/phylmd/thermcell_plume.F90

    r2267 r2311  
    1313USE IOIPSL, ONLY : getin
    1414
     15       USE print_control_mod, ONLY: prt_level
    1516       IMPLICIT NONE
    1617
     
    1819#include "YOETHF.h"
    1920#include "FCTTRE.h"
    20 #include "iniprint.h"
    2121#include "thermcell.h"
    2222
     
    811811!--------------------------------------------------------------------------
    812812
     813      USE print_control_mod, ONLY: prt_level
    813814      IMPLICIT NONE
    814815
     
    816817#include "YOETHF.h"
    817818#include "FCTTRE.h"
    818 #include "iniprint.h"
    819819#include "thermcell.h"
    820820
  • LMDZ5/trunk/libf/phylmd/traclmdz_mod.F90

    r2265 r2311  
    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
     
    9696    USE mod_phys_lmdz_para
    9797    USE indice_sol_mod
    98 
    99     INCLUDE "iniprint.h"
     98    USE print_control_mod, ONLY: lunout
     99
    100100! Input variables
    101101    REAL,DIMENSION(klon,nbsrf),INTENT(IN)     :: pctsrf ! Pourcentage de sol f(nature du sol)
     
    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
  • LMDZ5/trunk/libf/phylmd/wake.F90

    r2308 r2311  
    2323  USE dimphy
    2424  use mod_phys_lmdz_para
     25  USE print_control_mod, ONLY: prt_level
    2526  IMPLICIT NONE
    2627  ! ============================================================================
     
    116117  include "YOMCST.h"
    117118  include "cvthermo.h"
    118   include "iniprint.h"
    119119
    120120  ! Arguments en entree
  • LMDZ5/trunk/libf/phylmd/yamada4.F90

    r1992 r2311  
    55    cd, q2, km, kn, kq, ustar, iflag_pbl)
    66  USE dimphy
     7  USE print_control_mod, ONLY: prt_level
    78  IMPLICIT NONE
    8   include "iniprint.h"
    99  ! .......................................................................
    1010  ! ym#include "dimensions.h"
  • LMDZ5/trunk/libf/phylmd/yamada_c.F90

    r1907 r2311  
    66     &   ,iflag_pbl,okiophys)
    77      use dimphy
     8      USE print_control_mod, ONLY: prt_level
    89      IMPLICIT NONE
    9 #include "iniprint.h"
    1010#include "YOMCST.h"
    1111!.......................................................................
Note: See TracChangeset for help on using the changeset viewer.