source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/inifis_mod.F90 @ 3831

Last change on this file since 3831 was 3831, checked in by ymipsl, 9 years ago

module reorganisation for a cleaner dyn-phys interface
YM

File size: 3.9 KB
Line 
1
2! $Id: $
3MODULE inifis_mod
4
5  IMPLICIT NONE
6  ! for now constants and flags transmitted from dyn to phys are stored here
7!  REAL,SAVE    :: daysec ! length of reference day (s)
8!  REAL,SAVE    :: dtphys ! physics time step (s)
9!  INTEGER,SAVE :: day_step ! number of physical steps per day
10!  INTEGER,SAVE :: nday ! number of days to run
11!!$OMP THREADPRIVATE(daysec,dtphys,day_step,iphysiq,dayref,anneeref,nday)
12!  INTEGER,SAVE :: annee_ref ! reference year as read from start file
13!  INTEGER,SAVE :: day_ini
14!  INTEGER,SAVE :: day_end
15!!$OMP THREADPRIVATE(annee_ref,day_ini,day_end)
16!  INTEGER,SAVE :: itau_phy   ! number of physiq iteration from origin
17!  INTEGER,SAVE :: itaufin    ! final iteration
18!  REAL,SAVE    :: start_time
19!  INTEGER,SAVE :: day_ref
20!  REAL,SAVE :: jD_ref
21!!$OMP THREADPRIVATE(itau_phy,itaufin,start_time,day_ref,JD_ref)
22!  INTEGER,SAVE :: raz_date
23!  INTEGER,SAVE :: lunout=6 ! default output file identifier (6==screen)
24!  INTEGER,SAVE :: prt_level ! Output level
25!  LOGICAL,SAVE :: debug ! flag to specify if in "debug mode"
26!!$OMP THREADPRIVATE(lunout,prt_level,debug)
27
28CONTAINS
29
30  SUBROUTINE inifis(punjours, prad,pg,pr,pcpp)
31  ! Initialize physics constant and flags from dynamics
32  USE init_print_control_mod, ONLY : init_print_control
33  USE print_control_mod, ONLY : lunout
34  USE phystokenc_mod, only: init_phystokenc
35  IMPLICIT NONE
36
37  include "YOMCST.h"
38  REAL,INTENT(IN) :: punjours, prad, pg, pr, pcpp
39  CHARACTER (LEN=20) :: modname = 'inifis'
40  CHARACTER (LEN=80) :: abort_message
41
42  CALL init_print_control
43
44  ! suphel => initialize some physical constants (orbital parameters,
45  !           geoid, gravity, thermodynamical constants, etc.) in the
46  !           physics
47  CALL suphel
48
49  ! check that physical constants set in 'suphel' are coherent
50  ! with values set in the dynamics:
51  IF (rday/=punjours) THEN
52    WRITE (lunout, *) 'inifis: length of day discrepancy!!!'
53    WRITE (lunout, *) '  in the dynamics punjours=', punjours
54    WRITE (lunout, *) '   but in the physics RDAY=', rday
55    IF (abs(rday-punjours)>0.01*punjours) THEN
56        ! stop here if the relative difference is more than 1%
57      abort_message = 'length of day discrepancy'
58      CALL abort_physic(modname, abort_message, 1)
59    END IF
60  END IF
61  IF (rg/=pg) THEN
62    WRITE (lunout, *) 'inifis: gravity discrepancy !!!'
63    WRITE (lunout, *) '     in the dynamics pg=', pg
64    WRITE (lunout, *) '  but in the physics RG=', rg
65    IF (abs(rg-pg)>0.01*pg) THEN
66        ! stop here if the relative difference is more than 1%
67      abort_message = 'gravity discrepancy'
68      CALL abort_physic(modname, abort_message, 1)
69    END IF
70  END IF
71  IF (ra/=prad) THEN
72    WRITE (lunout, *) 'inifis: planet radius discrepancy !!!'
73    WRITE (lunout, *) '   in the dynamics prad=', prad
74    WRITE (lunout, *) '  but in the physics RA=', ra
75    IF (abs(ra-prad)>0.01*prad) THEN
76        ! stop here if the relative difference is more than 1%
77      abort_message = 'planet radius discrepancy'
78      CALL abort_physic(modname, abort_message, 1)
79    END IF
80  END IF
81  IF (rd/=pr) THEN
82    WRITE (lunout, *) 'inifis: reduced gas constant discrepancy !!!'
83    WRITE (lunout, *) '     in the dynamics pr=', pr
84    WRITE (lunout, *) '  but in the physics RD=', rd
85    IF (abs(rd-pr)>0.01*pr) THEN
86        ! stop here if the relative difference is more than 1%
87      abort_message = 'reduced gas constant discrepancy'
88      CALL abort_physic(modname, abort_message, 1)
89    END IF
90  END IF
91  IF (rcpd/=pcpp) THEN
92    WRITE (lunout, *) 'inifis: specific heat discrepancy !!!'
93    WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
94    WRITE (lunout, *) '  but in the physics RCPD=', rcpd
95    IF (abs(rcpd-pcpp)>0.01*pcpp) THEN
96        ! stop here if the relative difference is more than 1%
97      abort_message = 'specific heat discrepancy'
98      CALL abort_physic(modname, abort_message, 1)
99    END IF
100  END IF
101 
102  CALL init_phystokenc
103
104  END SUBROUTINE inifis
105
106END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.