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