source: LMDZ6/branches/ICOLMDZISO/libf/phylmd/inifis_mod.F90 @ 5592

Last change on this file since 5592 was 5592, checked in by yann meurdesoif, 2 months ago

Update ICOLMDZISO branch.
YM

  • 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.9 KB
Line 
1! $Id: inifis_mod.F90 5592 2025-03-26 18:00:27Z ymeurdesoif $
2MODULE inifis_mod
3
4CONTAINS
5
6  SUBROUTINE inifis(punjours, prad, pg, pr, pcpp)
7  ! Initialize some physical constants and settings
8  USE init_print_control_mod, ONLY : init_print_control
9  USE print_control_mod, ONLY: lunout
10  IMPLICIT NONE
11
12  include "YOMCST.h"
13  REAL,INTENT(IN) :: prad, pg, pr, pcpp, punjours
14
15  CHARACTER (LEN=20) :: modname = 'inifis'
16  CHARACTER (LEN=80) :: abort_message
17
18  ! Initialize flags lunout, prt_level, debug
19  CALL init_print_control
20
21  ! suphel => initialize some physical constants (orbital parameters,
22  !           geoid, gravity, thermodynamical constants, etc.) in the
23  !           physics
24  CALL suphel
25
26  ! check that physical constants set in 'suphel' are coherent
27  ! with values set in the dynamics:
28  IF (rday/=punjours) THEN
29    WRITE (lunout, *) 'inifis: length of day discrepancy!!!'
30    WRITE (lunout, *) '  in the dynamics punjours=', punjours
31    WRITE (lunout, *) '   but in the physics RDAY=', rday
32    IF (abs(rday-punjours)>0.01*punjours) THEN
33        ! stop here if the relative difference is more than 1%
34      abort_message = 'length of day discrepancy'
35      CALL abort_physic(modname, abort_message, 1)
36    END IF
37  END IF
38  IF (rg/=pg) THEN
39    WRITE (lunout, *) 'inifis: gravity discrepancy !!!'
40    WRITE (lunout, *) '     in the dynamics pg=', pg
41    WRITE (lunout, *) '  but in the physics RG=', rg
42    IF (abs(rg-pg)>0.01*pg) THEN
43        ! stop here if the relative difference is more than 1%
44      abort_message = 'gravity discrepancy'
45      CALL abort_physic(modname, abort_message, 1)
46    END IF
47  END IF
48  IF (ra/=prad) THEN
49    WRITE (lunout, *) 'inifis: planet radius discrepancy !!!'
50    WRITE (lunout, *) '   in the dynamics prad=', prad
51    WRITE (lunout, *) '  but in the physics RA=', ra
52    IF (abs(ra-prad)>0.01*prad) THEN
53        ! stop here if the relative difference is more than 1%
54      abort_message = 'planet radius discrepancy'
55      CALL abort_physic(modname, abort_message, 1)
56    END IF
57  END IF
58  IF (rd/=pr) THEN
59    WRITE (lunout, *) 'inifis: reduced gas constant discrepancy !!!'
60    WRITE (lunout, *) '     in the dynamics pr=', pr
61    WRITE (lunout, *) '  but in the physics RD=', rd
62    IF (abs(rd-pr)>0.01*pr) THEN
63        ! stop here if the relative difference is more than 1%
64      abort_message = 'reduced gas constant discrepancy'
65      CALL abort_physic(modname, abort_message, 1)
66    END IF
67  END IF
68  IF (rcpd/=pcpp) THEN
69    WRITE (lunout, *) 'inifis: specific heat discrepancy !!!'
70    WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
71    WRITE (lunout, *) '  but in the physics RCPD=', rcpd
72    IF (abs(rcpd-pcpp)>0.01*pcpp) THEN
73        ! stop here if the relative difference is more than 1%
74      abort_message = 'specific heat discrepancy'
75      CALL abort_physic(modname, abort_message, 1)
76    END IF
77  END IF
78   
79    CALL init_isotopes
80   
81  END SUBROUTINE inifis
82
83
84SUBROUTINE init_isotopes
85USE infotrac_phy,ONLY : niso, nzone, ntraciso=>ntiso
86USE isotrac_mod, ONLY: iso_traceurs_init
87USE isotopes_mod, ONLY: iso_init
88USE isotopes_verif_mod, ONLY: iso_verif_init
89IMPLICIT NONE
90
91 ! C Risi: vérifier compatibilité des options isotopiques entre
92 ! dyn3dmem et physiq
93#ifdef ISO
94    write(*,*) 'ok_isotopes,ntraciso,niso=',niso>0,ntraciso,niso
95    IF(niso  <= 0) CALL abort_physic('init_isotopes','options iso incompatibles',1)
96#ifdef ISOTRAC
97    IF(nzone <= 0) CALL abort_physic('init_isotopes','options isotrac incompatibles',1)
98#else
99    IF(nzone  > 0) CALL abort_physic('init_isotopes','options isotrac incompatibles',1)
100#endif
101#else
102    if(niso   > 0) CALL abort_physic('init_isotopes','options iso incompatibles',1)
103#endif
104
105#ifdef ISO
106        ! initialisations isotopiques
107#ifdef ISOVERIF
108           write(*,*) 'ok_isotopes=',niso > 0
109#endif
110        if (niso > 0) call iso_init()
111#ifdef ISOTRAC
112IF(nzone > 0) then
113        call iso_traceurs_init()
114endif
115#endif
116#ifdef ISOVERIF
117        call iso_verif_init()
118#endif
119#endif
120
121END SUBROUTINE init_isotopes 
122
123END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.