source: LMDZ6/branches/Amaury_dev/libf/phylmd/inifis_mod.F90 @ 5157

Last change on this file since 5157 was 5144, checked in by abarral, 8 weeks ago

Put YOMCST.h into modules

  • 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: 3.0 KB
Line 
1! $Id: inifis_mod.F90 5144 2024-07-29 21:01:04Z abarral $
2MODULE inifis_mod
3
4CONTAINS
5
6  SUBROUTINE inifis(punjours, prad, pg, pr, pcpp)
7    ! Initialize some physical constants and settings
8    USE lmdz_init_print_control, ONLY: init_print_control
9    USE lmdz_print_control, ONLY: lunout
10    USE lmdz_abort_physic, ONLY: abort_physic
11    USE lmdz_yomcst
12
13    IMPLICIT NONE
14
15    REAL, INTENT(IN) :: prad, pg, pr, pcpp, punjours
16
17    CHARACTER (LEN = 20) :: modname = 'inifis'
18    CHARACTER (LEN = 80) :: abort_message
19
20    ! Initialize flags lunout, prt_level, debug
21    CALL init_print_control
22
23    ! suphel => initialize some physical constants (orbital parameters,
24    !           geoid, gravity, thermodynamical constants, etc.) in the
25    !           physics
26    CALL suphel
27
28    ! check that physical constants set in 'suphel' are coherent
29    ! with values set in the dynamics:
30    IF (rday/=punjours) THEN
31      WRITE (lunout, *) 'inifis: length of day discrepancy!!!'
32      WRITE (lunout, *) '  in the dynamics punjours=', punjours
33      WRITE (lunout, *) '   but in the physics RDAY=', rday
34      IF (abs(rday - punjours)>0.01 * punjours) THEN
35        ! stop here if the relative difference is more than 1%
36        abort_message = 'length of day discrepancy'
37        CALL abort_physic(modname, abort_message, 1)
38      END IF
39    END IF
40    IF (rg/=pg) THEN
41      WRITE (lunout, *) 'inifis: gravity discrepancy !!!'
42      WRITE (lunout, *) '     in the dynamics pg=', pg
43      WRITE (lunout, *) '  but in the physics RG=', rg
44      IF (abs(rg - pg)>0.01 * pg) THEN
45        ! stop here if the relative difference is more than 1%
46        abort_message = 'gravity discrepancy'
47        CALL abort_physic(modname, abort_message, 1)
48      END IF
49    END IF
50    IF (ra/=prad) THEN
51      WRITE (lunout, *) 'inifis: planet radius discrepancy !!!'
52      WRITE (lunout, *) '   in the dynamics prad=', prad
53      WRITE (lunout, *) '  but in the physics RA=', ra
54      IF (abs(ra - prad)>0.01 * prad) THEN
55        ! stop here if the relative difference is more than 1%
56        abort_message = 'planet radius discrepancy'
57        CALL abort_physic(modname, abort_message, 1)
58      END IF
59    END IF
60    IF (rd/=pr) THEN
61      WRITE (lunout, *) 'inifis: reduced gas constant discrepancy !!!'
62      WRITE (lunout, *) '     in the dynamics pr=', pr
63      WRITE (lunout, *) '  but in the physics RD=', rd
64      IF (abs(rd - pr)>0.01 * pr) THEN
65        ! stop here if the relative difference is more than 1%
66        abort_message = 'reduced gas constant discrepancy'
67        CALL abort_physic(modname, abort_message, 1)
68      END IF
69    END IF
70    IF (rcpd/=pcpp) THEN
71      WRITE (lunout, *) 'inifis: specific heat discrepancy !!!'
72      WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
73      WRITE (lunout, *) '  but in the physics RCPD=', rcpd
74      IF (abs(rcpd - pcpp)>0.01 * pcpp) THEN
75        ! stop here if the relative difference is more than 1%
76        abort_message = 'specific heat discrepancy'
77        CALL abort_physic(modname, abort_message, 1)
78      END IF
79    END IF
80
81  END SUBROUTINE inifis
82
83END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.