SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
get_date_ol.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE get_date_ol(TPTIME,PTSTEP,HDATE)
7 ! #######################################################
8 !!**** *GET_DATE_OL* - gets the initial date of the simulation to write in
9 ! netcdf file
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14  !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! S. Faroux *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 06/2010
36 !-------------------------------------------------------------------------------
37 !
39 !
40 USE yomhook ,ONLY : lhook, dr_hook
41 USE parkind1 ,ONLY : jprb
42 !
43 IMPLICIT NONE
44 !
45 TYPE(date_time), INTENT(IN) :: tptime ! current date and time
46 REAL, INTENT(IN) :: ptstep
47  CHARACTER(LEN=*), INTENT(OUT) :: hdate
48 !
49 INTEGER, DIMENSION(3) :: itime, idate
50 REAL(KIND=JPRB) :: zhook_handle
51 !
52 !-------------------------------------------------------------------------------
53 !
54 !
55 IF (lhook) CALL dr_hook('GET_DATE_OL',0,zhook_handle)
56 itime(1)=floor(tptime%TIME/3600.)
57 itime(2)=floor((tptime%TIME-itime(1)*3600)/60.)
58 itime(3)=tptime%TIME-itime(1)*3600-itime(2)*60
59 !
60 IF (ptstep == floor(ptstep/86400.)*86400) THEN
61  hdate='days since '
62 ELSEIF (ptstep == floor(ptstep/3600.)*3600) THEN
63  hdate='hours since '
64 ELSEIF (ptstep == floor(ptstep/60.)*60) THEN
65  hdate='minutes since '
66 ELSE
67  hdate='seconds since '
68 ENDIF
69 !
70 idate(1) = tptime%TDATE%YEAR
71 idate(2) = tptime%TDATE%MONTH
72 idate(3) = tptime%TDATE%DAY
73 !
74  CALL write_time(idate(1),1,"-",hdate)
75  CALL write_time(idate(2),0,"-",hdate)
76  CALL write_time(idate(3),0,"",hdate)
77  CALL write_time(itime(1),1,":",hdate)
78  CALL write_time(itime(2),0,":",hdate)
79  CALL write_time(itime(3),0,"",hdate)
80 
81 IF (lhook) CALL dr_hook('GET_DATE_OL',1,zhook_handle)
82  CONTAINS
83 
84 
85 SUBROUTINE write_time(ITIME,ISPACE,HSEP,HTDATE)
86 !
87 INTEGER, INTENT(IN) :: itime
88 INTEGER, INTENT(IN) :: ispace
89  CHARACTER(LEN=*), INTENT(IN) :: hsep
90  CHARACTER(LEN=*), INTENT(INOUT) :: htdate
91  CHARACTER(LEN=10) :: ypas
92 REAL(KIND=JPRB) :: zhook_handle
93 !
94 !
95 IF (lhook) CALL dr_hook('GET_DATE_OL:WRITE_TIME',0,zhook_handle)
96 IF (itime.LT.10) THEN
97  WRITE(ypas,'(i1)') itime
98  IF (ispace==1) THEN
99  htdate=trim(htdate)//" 0"//trim(ypas)//hsep
100  ELSE
101  htdate=trim(htdate)//"0"//trim(ypas)//hsep
102  ENDIF
103 ELSE
104  IF (itime.LT.100) THEN
105  WRITE(ypas,'(i2)') itime
106  ELSE
107  WRITE(ypas,'(i4)') itime
108  ENDIF
109  IF (ispace==1) THEN
110  htdate=trim(htdate)//" "//trim(ypas)//hsep
111  ELSE
112  htdate=trim(htdate)//trim(ypas)//hsep
113  ENDIF
114 ENDIF
115 IF (lhook) CALL dr_hook('GET_DATE_OL:WRITE_TIME',1,zhook_handle)
116 !
117 !
118 END SUBROUTINE write_time
119 
120 
121 END SUBROUTINE get_date_ol
subroutine get_date_ol(TPTIME, PTSTEP, HDATE)
Definition: get_date_ol.F90:6
subroutine write_time(ITIME, ISPACE, HSEP, HTDATE)
Definition: get_date_ol.F90:85