LMDZ
phys_cal_mod.F90
Go to the documentation of this file.
1 ! $Id:$
3 ! This module contains information on the calendar at the current time step
4 
5  INTEGER,SAVE :: year_cur ! current year
6 !$OMP THREADPRIVATE(year_cur)
7  INTEGER,SAVE :: mth_cur ! current month
8 !$OMP THREADPRIVATE(mth_cur)
9  INTEGER,SAVE :: day_cur ! current day
10 !$OMP THREADPRIVATE(day_cur)
11  INTEGER,SAVE :: days_elapsed ! number of whole days since start of the simulation
12 !$OMP THREADPRIVATE(days_elapsed)
13  INTEGER,SAVE :: mth_len ! number of days in the current month
14 !$OMP THREADPRIVATE(mth_len)
15  INTEGER,SAVE :: year_len ! number of days in the current year
16 !$OMP THREADPRIVATE(year_len)
17  REAL,SAVE :: hour
18 !$OMP THREADPRIVATE(hour)
19  REAL,SAVE :: jd_1jan
20 !$OMP THREADPRIVATE(jD_1jan)
21  REAL,SAVE :: jh_1jan
22 !$OMP THREADPRIVATE(jH_1jan)
23  REAL,SAVE :: xjour
24 !$OMP THREADPRIVATE(xjour)
25  REAL,SAVE :: jd_cur ! jour courant a l'appel de la physique (jour julien)
26 !$OMP THREADPRIVATE(jD_cur)
27  REAL,SAVE :: jh_cur ! heure courante a l'appel de la physique (jour julien)
28 !$OMP THREADPRIVATE(jH_cur)
29  REAL,SAVE :: jd_ref ! jour du demarage de la simulation (jour julien)
30 !$OMP THREADPRIVATE(jD_ref)
31  CHARACTER (len=10) :: calend ! type of calendar to use
32  ! (can be earth_360d, earth_365d or earth_366d)
33 !$OMP THREADPRIVATE(calend)
34 
35 
36 CONTAINS
37 
38  SUBROUTINE phys_cal_init(annee_ref,day_ref)
39  USE ioipsl, ONLY: ymds2ju
40  USE ioipsl_getin_p_mod, ONLY: getin_p
41  IMPLICIT NONE
42  INTEGER,INTENT(IN) :: annee_ref
43  INTEGER,INTENT(IN) :: day_ref
44 
45  ! Find out which type of calendar we are using
46  calend = 'earth_360d' ! default
47  CALL getin_p("calend",calend)
48 
49  CALL ymds2ju(annee_ref, 1, day_ref, 0., jd_ref)
50  jd_ref=int(jd_ref)
51 
52  END SUBROUTINE phys_cal_init
53 
54  SUBROUTINE phys_cal_update(jD_cur, jH_cur)
55  ! This subroutine updates the module saved variables.
56 
57  USE ioipsl, only: ju2ymds, ymds2ju, ioget_mon_len, ioget_year_len
58 
59  REAL, INTENT(IN) :: jD_cur ! jour courant a l'appel de la physique (jour julien)
60  REAL, INTENT(IN) :: jH_cur ! heure courante a l'appel de la physique (jour julien)
61 
62  CALL ju2ymds(jd_cur+jh_cur, year_cur, mth_cur, day_cur, hour)
63  CALL ymds2ju(year_cur, 1, 1, 0., jd_1jan)
64 
65  jh_1jan = jd_1jan - int(jd_1jan)
66  jd_1jan = int(jd_1jan)
67  xjour = jd_cur - jd_1jan
68  days_elapsed = jd_cur - jd_1jan
69 
70  ! Get lenght of acutual month
71  mth_len = ioget_mon_len(year_cur,mth_cur)
72 
73  year_len = ioget_year_len(year_cur)
74 
75  END SUBROUTINE phys_cal_update
76 
77 END MODULE phys_cal_mod
78 
integer, save day_cur
Definition: phys_cal_mod.F90:9
character(len=10) calend
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL ymds2ju(annee_ref, 1, day_ref, hour, zjulian)!jyg CALL histbeg_phy("histrac"
real, save xjour
integer, save year_cur
Definition: phys_cal_mod.F90:5
real, save jd_cur
real, save jh_1jan
integer, save mth_len
real, save hour
integer, save mth_cur
Definition: phys_cal_mod.F90:7
subroutine phys_cal_update(jD_cur, jH_cur)
real, save jd_1jan
real, save jh_cur
integer, save year_len
integer, save days_elapsed
subroutine phys_cal_init(annee_ref, day_ref)
real, save jd_ref