source: palm/trunk/UTIL/inifor/tests/test-input-files.f90 @ 2796

Last change on this file since 2796 was 2718, checked in by maronga, 6 years ago

deleting of deprecated files; headers updated where needed

  • Property svn:keywords set to Id
File size: 3.7 KB
Line 
1!> @file tests/test-input-files.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2017-2018 Leibniz Universitaet Hannover
18! Copyright 2017-2018 Deutscher Wetterdienst Offenbach
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: test-input-files.f90 2718 2018-01-02 08:49:38Z suehring $
28! Initial revision
29!
30!
31!
32! Authors:
33! --------
34! @author Eckhard Kadasch
35!
36! Description:
37! ------------
38!> This program tests INIFOR's timestamping used for generating input file
39!> names.
40!------------------------------------------------------------------------------!
41 PROGRAM test_input_files
42
43    USE defs,                                                                  &
44        ONLY :  PATH
45    USE grid,                                                                  & 
46        ONLY :  input_file_list
47    USE test_utils
48   
49    IMPLICIT NONE
50
51    CHARACTER(LEN=50)                              ::  title
52    CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) ::  file_list, ref_list
53    LOGICAL                                        ::  res
54    INTEGER                                        ::  i     
55
56    title = "input files - daylight saving to standard time"
57    CALL begin_test(title, res)
58
59    ! Arange
60    ! ...a date range that inlcudes a shift from daylight saving time to
61    ! standard time (29.10.2017). Since all time stamps in COSMO-DE input files
62    ! are in UTC, this should not the naming cadence.
63    ALLOCATE( ref_list(6) )
64    ref_list(1)  = './laf2017102823-test.nc'
65    ref_list(2)  = './laf2017102900-test.nc'
66    ref_list(3)  = './laf2017102901-test.nc'
67    ref_list(4)  = './laf2017102902-test.nc'
68    ref_list(5)  = './laf2017102903-test.nc'
69    ref_list(6)  = './laf2017102904-test.nc'
70
71    ! Act
72    CALL input_file_list(start_date_string='2017102823',                       &
73                         start_hour=0, end_hour=5, step_hour=1,                &
74                         path='./', prefix="laf", suffix='-test',              &
75                         file_list=file_list)
76
77    ! Assert
78    DO i = 1, 6
79       res = res .AND. (TRIM(ref_list(i)) .EQ. TRIM(file_list(i)))
80    END DO
81
82    DEALLOCATE( ref_list, file_list )
83    CALL end_test(title, res)
84
85
86    title = "input files - leap day"
87    CALL begin_test(title, res)
88
89    ! Arange
90    ! ...a date range that inlcudes a leap day (29. Feb. 2016) which should be
91    ! inlcuded in UTC time stamps.
92    ALLOCATE( ref_list(2) )
93    ref_list(1)  = './laf2016022823-test.nc'
94    ref_list(2)  = './laf2016022900-test.nc'
95
96    ! Act
97    CALL input_file_list(start_date_string='2016022823',                       &
98                         start_hour=0, end_hour=1, step_hour=1,                &
99                         path='./', prefix="laf", suffix='-test',              &
100                         file_list=file_list)
101
102    ! Assert
103    DO i = 1, 2
104       res = res .AND. (TRIM(ref_list(i)) .EQ. TRIM(file_list(i)))
105    END DO
106
107    DEALLOCATE( ref_list, file_list )
108    CALL end_test(title, res)
109
110 END PROGRAM test_input_files
Note: See TracBrowser for help on using the repository browser.