source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/time_phylmdz_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: 2.6 KB
Line 
1MODULE time_phylmdz_mod
2
3    REAL,SAVE    :: pdtphys     ! physics time step (s)
4    INTEGER,SAVE :: day_step    ! number of physical steps per day
5    INTEGER,SAVE :: ndays       ! number of days to run
6    INTEGER,SAVE :: annee_ref   ! reference year from the origin
7    INTEGER,SAVE :: day_ref     ! reference year of the origin
8    INTEGER,SAVE :: day_ini     ! initial day of the run starting from 1st january of annee_ref
9    INTEGER,SAVE :: day_end     ! final day of the run starting from 1st january of annee_ref
10    REAL,SAVE    :: start_time  ! starting time from the begining of the initial day
11    INTEGER,SAVE :: raz_date
12
13    INTEGER,SAVE :: itau_phy     ! number of physiq iteration from origin
14    INTEGER,SAVE :: itaufin      ! final iteration
15    REAL,SAVE    :: current_time ! current elapsed time (s) from the begining of the run
16
17   
18
19CONTAINS
20
21  SUBROUTINE init_time(annee_ref_, day_ref_, day_ini_, start_time_, ndays_, pdtphys_)
22  USE ioipsl, ONLY : getin
23  USE phys_cal_mod, ONLY: phys_cal_init
24  IMPLICIT NONE
25  INCLUDE 'YOMCST.h'
26    INTEGER, INTENT(IN) :: annee_ref_ 
27    INTEGER, INTENT(IN) :: day_ref_   
28    INTEGER, INTENT(IN) :: day_ini_   
29    REAL,    INTENT(IN) :: start_time_
30    INTEGER, INTENT(IN) :: ndays_     
31    REAL,    INTENT(IN) :: pdtphys_   
32   
33    annee_ref    = annee_ref_
34    day_ref      = day_ref_
35    day_ini      = day_ini_
36    start_time   = start_time_
37    ndays        = ndays_
38    pdtphys      = pdtphys_
39   
40    day_step = NINT(rday/pdtphys)
41    day_end  = day_ini + ndays
42 
43    raz_date = 0
44    CALL getin('raz_date', raz_date)
45    current_time=0
46   
47    CALL phys_cal_init(annee_ref,day_ref)
48   
49  END SUBROUTINE init_time
50 
51  SUBROUTINE init_iteration(itau_phy_)
52  IMPLICIT NONE
53    INTEGER, INTENT(IN) :: itau_phy_
54    itau_phy=itau_phy_
55    IF (raz_date==1) itau_phy=0
56   
57    itaufin=itau_phy+NINT(ndays/pdtphys)
58   
59  END SUBROUTINE init_iteration
60
61  SUBROUTINE set_timestep(pdtphys_)
62  USE ioipsl, ONLY : ymds2ju
63  USE phys_cal_mod, ONLY: phys_cal_update
64  USE print_control_mod, ONLY: lunout
65  IMPLICIT NONE
66    REAL,INTENT(IN) :: pdtphys_
67    REAL            :: julian_day
68   
69   
70    IF ( ABS( (pdtphys-pdtphys_) / ((pdtphys+pdtphys_)/2))> 10.*EPSILON(pdtphys_)) THEN
71       WRITE(lunout,*) "WARNING ! Pas de temps physique varie d'un appel a l'autre",pdtphys_,pdtphys
72       WRITE(lunout,*) "Cela peu occasionner des dysfonctionnements"
73    ENDIF
74    pdtphys=pdtphys_
75    current_time=current_time+pdtphys
76    CALL ymds2ju(annee_ref,1,day_ini,start_time+current_time,julian_day)
77    CALL phys_cal_update(julian_day)
78   
79  END SUBROUTINE set_timestep
80     
81END MODULE time_phylmdz_mod     
82       
83   
Note: See TracBrowser for help on using the repository browser.