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

Last change on this file since 3817 was 3817, checked in by millour, 10 years ago

Further cleanup and removal of references to iniprint.h.
Also added bench testcase 48x36x19.
EM

File size: 5.5 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 dynamical steps per day
10  INTEGER,SAVE :: iphysiq ! physics called every iphysiq dynamical step
11  INTEGER,SAVE :: dayref
12  INTEGER,SAVE :: anneeref ! reference year, ase deifined in run.def
13  INTEGER,SAVE :: nday ! number of days to run
14!$THREADPRIVATE(daysec,dtphys,day_step,iphysiq,dayref,anneeref,nday)
15  INTEGER,SAVE :: annee_ref ! reference year as read from start file
16  INTEGER,SAVE :: day_ini
17  INTEGER,SAVE :: day_end
18!$THREADPRIVATE(annee_ref,day_ini,day_end)
19  INTEGER,SAVE :: itau_phy
20  INTEGER,SAVE :: itaufin
21  REAL,SAVE :: start_time
22  INTEGER,SAVE :: day_ref
23  REAL,SAVE :: jD_ref
24!$THREADPRIVATE(itau_phy,itaufin,start_time,day_ref,JD_ref)
25  LOGICAL,SAVE :: offline
26  INTEGER,SAVE :: raz_date
27  CHARACTER(len=4),SAVE :: config_inca
28  INTEGER,SAVE :: lunout ! default output file identifier (6==screen)
29  INTEGER,SAVE :: prt_level ! Output level
30  LOGICAL,SAVE :: debug ! flag to specify if in "debug mode"
31!$THREADPRIVATE(offline,raz_date,config_inca,lunout,prt_level,debug)
32
33CONTAINS
34
35  SUBROUTINE inifis(punjours,prad,pg,pr,pcpp,ptimestep,&
36                    day_step_dyn,iphysiq_dyn,&
37                    dayref_dyn,anneeref_dyn,nday_dyn,&
38                    annee_ref_dyn,day_ini_dyn,day_end_dyn,&
39                    itau_phy_dyn,itaufin_dyn,&
40                    start_time_dyn,day_ref_dyn,jD_ref_dyn,&
41                    offline_dyn,raz_date_dyn,config_inca_dyn, &
42                    lunout_dyn,prt_level_dyn,debug_dyn)
43  ! Initialize physics constant and flags from dynamics
44  IMPLICIT NONE
45
46  include "YOMCST.h"
47  REAL,INTENT(IN) :: punjours,prad, pg, pr, pcpp
48  REAL,INTENT(IN) :: ptimestep ! physics time step (s)
49  INTEGER,INTENT(IN) :: day_step_dyn
50  INTEGER,INTENT(IN) :: iphysiq_dyn
51  INTEGER,INTENT(IN) :: dayref_dyn
52  INTEGER,INTENT(IN) :: anneeref_dyn
53  INTEGER,INTENT(IN) :: nday_dyn
54  INTEGER,INTENT(IN) :: annee_ref_dyn
55  INTEGER,INTENT(IN) :: day_ini_dyn
56  INTEGER,INTENT(IN) :: day_end_dyn
57  INTEGER,INTENT(IN) :: itau_phy_dyn
58  INTEGER,INTENT(IN) :: itaufin_dyn
59  REAL,INTENT(IN) :: start_time_dyn
60  INTEGER,INTENT(IN) :: day_ref_dyn
61  REAL,INTENT(IN) :: jD_ref_dyn
62  LOGICAL,INTENT(IN) :: offline_dyn
63  INTEGER,INTENT(IN) :: raz_date_dyn
64  CHARACTER(len=4),INTENT(IN) :: config_inca_dyn
65  INTEGER,INTENT(IN) :: lunout_dyn
66  INTEGER,INTENT(IN) :: prt_level_dyn
67  LOGICAL,INTENT(IN) :: debug_dyn
68  CHARACTER (LEN=20) :: modname = 'inifis'
69  CHARACTER (LEN=80) :: abort_message
70
71  ! Some general settings and associated flags
72  daysec=punjours
73  dtphys=ptimestep
74  day_step=day_step_dyn
75  iphysiq=iphysiq_dyn
76  dayref=dayref_dyn
77  anneeref=anneeref_dyn
78  nday=nday_dyn
79  annee_ref=annee_ref_dyn
80  day_ini=day_ini_dyn
81  day_end=day_end_dyn
82  itau_phy=itau_phy_dyn
83  itaufin=itaufin_dyn
84  start_time=start_time_dyn
85  day_ref=day_ref_dyn
86  jD_ref= jD_ref_dyn
87  offline=offline_dyn
88  raz_date=raz_date_dyn
89  config_inca=config_inca_dyn
90  lunout=lunout_dyn
91  prt_level=prt_level_dyn
92  debug=debug_dyn
93
94  ! suphel => initialize some physical constants (orbital parameters,
95  !           geoid, gravity, thermodynamical constants, etc.) in the
96  !           physics
97  CALL suphel
98
99  ! check that physical constants set in 'suphel' are coherent
100  ! with values set in the dynamics:
101  IF (rday/=punjours) THEN
102    WRITE (lunout, *) 'inifis: length of day discrepancy!!!'
103    WRITE (lunout, *) '  in the dynamics punjours=', punjours
104    WRITE (lunout, *) '   but in the physics RDAY=', rday
105    IF (abs(rday-punjours)>0.01*punjours) THEN
106        ! stop here if the relative difference is more than 1%
107      abort_message = 'length of day discrepancy'
108      CALL abort_physic(modname, abort_message, 1)
109    END IF
110  END IF
111  IF (rg/=pg) THEN
112    WRITE (lunout, *) 'inifis: gravity discrepancy !!!'
113    WRITE (lunout, *) '     in the dynamics pg=', pg
114    WRITE (lunout, *) '  but in the physics RG=', rg
115    IF (abs(rg-pg)>0.01*pg) THEN
116        ! stop here if the relative difference is more than 1%
117      abort_message = 'gravity discrepancy'
118      CALL abort_physic(modname, abort_message, 1)
119    END IF
120  END IF
121  IF (ra/=prad) THEN
122    WRITE (lunout, *) 'inifis: planet radius discrepancy !!!'
123    WRITE (lunout, *) '   in the dynamics prad=', prad
124    WRITE (lunout, *) '  but in the physics RA=', ra
125    IF (abs(ra-prad)>0.01*prad) THEN
126        ! stop here if the relative difference is more than 1%
127      abort_message = 'planet radius discrepancy'
128      CALL abort_physic(modname, abort_message, 1)
129    END IF
130  END IF
131  IF (rd/=pr) THEN
132    WRITE (lunout, *) 'inifis: reduced gas constant discrepancy !!!'
133    WRITE (lunout, *) '     in the dynamics pr=', pr
134    WRITE (lunout, *) '  but in the physics RD=', rd
135    IF (abs(rd-pr)>0.01*pr) THEN
136        ! stop here if the relative difference is more than 1%
137      abort_message = 'reduced gas constant discrepancy'
138      CALL abort_physic(modname, abort_message, 1)
139    END IF
140  END IF
141  IF (rcpd/=pcpp) THEN
142    WRITE (lunout, *) 'inifis: specific heat discrepancy !!!'
143    WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
144    WRITE (lunout, *) '  but in the physics RCPD=', rcpd
145    IF (abs(rcpd-pcpp)>0.01*pcpp) THEN
146        ! stop here if the relative difference is more than 1%
147      abort_message = 'specific heat discrepancy'
148      CALL abort_physic(modname, abort_message, 1)
149    END IF
150  END IF
151
152  END SUBROUTINE inifis
153
154END MODULE inifis_mod
Note: See TracBrowser for help on using the repository browser.