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