source: LMDZ6/trunk/libf/phylmd/time_phylmdz_mod.f90 @ 5308

Last change on this file since 5308 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

  • Property svn:keywords set to Id
File size: 3.5 KB
Line 
1!
2! $Id: time_phylmdz_mod.f90 5285 2024-10-28 13:33:29Z fairhead $
3!
4MODULE time_phylmdz_mod
5
6    IMPLICIT NONE
7    REAL,SAVE    :: pdtphys     ! physics time step (s)
8!$OMP THREADPRIVATE(pdtphys)
9    INTEGER,SAVE :: day_step_phy    ! number of physical steps per day
10!$OMP THREADPRIVATE(day_step_phy)
11    INTEGER,SAVE :: ndays       ! number of days to run
12!$OMP THREADPRIVATE(ndays)
13    INTEGER,SAVE :: annee_ref   ! reference year from the origin
14!$OMP THREADPRIVATE(annee_ref)
15    INTEGER,SAVE :: day_ref     ! reference year of the origin
16!$OMP THREADPRIVATE(day_ref)
17    INTEGER,SAVE :: day_ini     ! initial day of the run starting from 1st january of annee_ref
18!$OMP THREADPRIVATE(day_ini)
19    INTEGER,SAVE :: day_end     ! final day of the run starting from 1st january of annee_ref
20!$OMP THREADPRIVATE(day_end)
21    REAL,SAVE    :: start_time  ! starting time from the begining of the initial day
22!$OMP THREADPRIVATE(start_time)
23    INTEGER,SAVE :: raz_date
24!$OMP THREADPRIVATE(raz_date)
25
26    INTEGER,SAVE :: itau_phy     ! number of physiq iteration from origin
27!$OMP THREADPRIVATE(itau_phy)
28    INTEGER,SAVE :: itaufin_phy      ! final iteration (in itau_phy steps)
29!$OMP THREADPRIVATE(itaufin_phy)
30    REAL,SAVE    :: current_time ! current elapsed time in seconds from the begining of the run
31!$OMP THREADPRIVATE(current_time)
32   
33
34CONTAINS
35
36  SUBROUTINE init_time(annee_ref_, day_ref_, day_ini_, start_time_, &
37                       ndays_, pdtphys_)
38  USE ioipsl_getin_p_mod, ONLY : getin_p
39  USE phys_cal_mod, ONLY: phys_cal_init
40  USE yomcst_mod_h
41IMPLICIT NONE
42
43    INTEGER, INTENT(IN) :: annee_ref_
44    INTEGER, INTENT(IN) :: day_ref_
45    INTEGER, INTENT(IN) :: day_ini_
46    REAL,    INTENT(IN) :: start_time_
47    INTEGER, INTENT(IN) :: ndays_
48    REAL,    INTENT(IN) :: pdtphys_
49
50    annee_ref    = annee_ref_
51    day_ref      = day_ref_
52    day_ini      = day_ini_
53    start_time   = start_time_
54    ndays        = ndays_
55    pdtphys      = pdtphys_
56
57    ! Initialize module variable not inherited from dynamics
58    day_step_phy = NINT(rday/pdtphys)
59    day_end  = day_ini + ndays
60
61    raz_date = 0
62    CALL getin_p('raz_date', raz_date)
63
64    current_time=0.
65
66    CALL phys_cal_init(annee_ref,day_ref)
67
68  END SUBROUTINE init_time
69
70  SUBROUTINE init_iteration(itau_phy_)
71  IMPLICIT NONE
72    INTEGER, INTENT(IN) :: itau_phy_
73    itau_phy=itau_phy_
74    IF (raz_date==1) itau_phy=0
75
76    itaufin_phy=itau_phy+NINT(ndays/pdtphys)
77
78  END SUBROUTINE init_iteration
79
80  SUBROUTINE update_time(pdtphys_)
81  ! This subroutine updates the module saved variables.
82  USE ioipsl, ONLY : ymds2ju
83  USE phys_cal_mod, ONLY: phys_cal_update
84  USE print_control_mod, ONLY: lunout
85  USE yomcst_mod_h
86  IMPLICIT NONE
87
88  REAL,INTENT(IN) :: pdtphys_
89  REAL            :: julian_date
90  INTEGER         :: cur_day
91  REAL            :: cur_sec
92
93    ! Check if the physics timestep has changed
94    IF ( ABS( (pdtphys-pdtphys_) / ((pdtphys+pdtphys_)/2))> 10.*EPSILON(pdtphys_)) THEN
95       WRITE(lunout,*) "WARNING ! Physics time step changes from a call to the next",pdtphys_,pdtphys
96       WRITE(lunout,*) "Not sure the physics parametrizations can handle this..."
97    ENDIF
98    pdtphys=pdtphys_
99   
100    ! Update elapsed time since begining of run:
101    current_time = current_time + pdtphys
102    cur_day = int(current_time/rday)
103    cur_sec = current_time - (cur_day * rday)
104
105    ! Compute corresponding Julian date and update calendar
106    cur_day = cur_day + day_ini
107    cur_sec = cur_sec + (start_time * rday)
108    CALL ymds2ju(annee_ref,1, cur_day, cur_sec, julian_date)
109    CALL phys_cal_update(julian_date)
110   
111  END SUBROUTINE update_time
112
113END MODULE time_phylmdz_mod     
114
Note: See TracBrowser for help on using the repository browser.