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 moved

Legend:

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