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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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
Note: See TracChangeset for help on using the changeset viewer.