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