source: LMDZ6/branches/Ocean_skin/libf/phylmd/inifis_mod.F90 @ 3428

Last change on this file since 3428 was 2311, checked in by Ehouarn Millour, 9 years ago

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

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.8 KB
Line 
1! $Id: inifis_mod.F90 2311 2015-06-25 07:45:24Z lguez $
2MODULE inifis_mod
3
4CONTAINS
5
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
9  IMPLICIT NONE
10
11  include "YOMCST.h"
12  REAL,INTENT(IN) :: prad, pg, pr, pcpp, punjours
13
14  CHARACTER (LEN=20) :: modname = 'inifis'
15  CHARACTER (LEN=80) :: abort_message
16
17  ! Initialize flags lunout, prt_level, debug
18  CALL init_print_control
19
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
76  END IF
77
78  END SUBROUTINE inifis
79 
80END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.