Changeset 3182 for palm/trunk/UTIL/inifor/tests
- Timestamp:
- Jul 27, 2018 1:36:03 PM (6 years ago)
- Location:
- palm/trunk/UTIL/inifor/tests
- Files:
-
- 1 added
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/UTIL/inifor/tests/test-boundaries.f90
r2718 r3182 21 21 ! Current revisions: 22 22 ! ----------------- 23 ! Updated test for new PALM grid strechting 23 24 ! 24 25 ! … … 54 55 TYPE(grid_definition) :: boundary_grid 55 56 56 REAL :: dx, dy, dz, lx, ly, lz, x(2), y(10), z(10) 57 REAL :: dx, dy, dz, lx, ly, lz, x(2), y(10) 58 REAL, TARGET :: z(10) 57 59 58 60 CALL begin_test(title, res) … … 79 81 xmin = x(i), xmax = x(i), & 80 82 ymin = 0.5 * dy, ymax = ly - 0.5 * dy, & 81 zmin = 0.5 * dz, zmax = lz - 0.5 * dz, &82 83 x0 = 0.0, y0 = 0.0, z0 = 0.0, & 83 nx = 0, ny = ny, nz = nz, &84 dx = dx, dy = dy, dz = dz )84 nx = 0, ny = ny, nz = nz, z = z) 85 85 86 86 87 ! Assert … … 103 104 TYPE(grid_definition), INTENT(INOUT) :: grid 104 105 105 DEALLOCATE( grid % x, grid % y , grid % z)106 DEALLOCATE( grid % x, grid % y ) 106 107 DEALLOCATE( grid % kk ) 107 108 DEALLOCATE( grid % w_verti ) -
palm/trunk/UTIL/inifor/tests/test-grid.f90
r2718 r3182 21 21 ! Current revisions: 22 22 ! ----------------- 23 ! Updated test for new PALM grid strechting 23 24 ! 24 25 ! … … 41 42 PROGRAM test_grid 42 43 43 USE grid, ONLY : grid_definition, init_grid_definition 44 USE grid, ONLY : grid_definition, init_grid_definition, dx, dy, dz 44 45 USE test_utils 45 46 … … 49 50 LOGICAL :: res 50 51 51 TYPE(grid_definition) :: mygrid 52 INTEGER :: i 53 INTEGER, PARAMETER :: nx = 9, ny = 19, nz = 29 54 REAL, PARAMETER :: lx = 100., ly = 200., lz = 300. 55 REAL, DIMENSION(0:nx) :: x, xu 56 REAL, DIMENSION(0:ny) :: y, yv 57 REAL, DIMENSION(0:nz) :: z, zw 52 TYPE(grid_definition) :: mygrid 53 INTEGER :: i 54 INTEGER, PARAMETER :: nx = 9, ny = 19, nz = 29 55 REAL, PARAMETER :: lx = 100., ly = 200., lz = 300. 56 REAL, DIMENSION(0:nx) :: x, xu 57 REAL, DIMENSION(0:ny) :: y, yv 58 REAL, DIMENSION(1:nz) :: z 59 REAL, DIMENSION(1:nz-1) :: zw 58 60 59 61 CALL begin_test(title, res) 60 62 61 63 ! Arange 64 dx = lx / (nx + 1) 65 DO i = 0, nx 66 xu(i) = real(i) / (nx+1) * lx 67 x(i) = 0.5*dx + xu(i) 68 END DO 69 70 dy = ly / (ny + 1) 71 DO i = 0, ny 72 yv(i) = real(i) / (ny+1) * ly 73 y(i) = 0.5*dy + yv(i) 74 END DO 75 76 dz(:) = lz / (nz + 1) 77 DO i = 1, nz 78 IF (i < nz) zw(i) = real(i) / (nz+1) * lz 79 z(i) = 0.5*dz(1) + zw(i) 80 END DO 81 82 ! Act 62 83 CALL init_grid_definition('palm', grid = mygrid, & 63 84 xmin = 0., xmax = lx, & 64 85 ymin = 0., ymax = ly, & 65 zmin = 0., zmax = lz, &66 86 x0 = 0.0, y0 = 0.0, z0 = 0.0, & 67 nx = nx, ny = ny, nz = nz) 68 69 ! Act 70 DO i = 0, nx 71 xu(i) = real(i) / (nx+1) * lx 72 x(i) = 0.5*mygrid%dx + xu(i) 73 END DO 74 DO i = 0, ny 75 yv(i) = real(i) / (ny+1) * ly 76 y(i) = 0.5*mygrid%dy + yv(i) 77 END DO 78 DO i = 0, nz 79 zw(i) = real(i) / (nz+1) * lz 80 z(i) = 0.5*mygrid%dz + zw(i) 81 END DO 87 nx = nx, ny = ny, nz = nz, & 88 z = z, zw = zw) 82 89 83 90 ! Assert coordinates match … … 85 92 res = res .AND. assert_equal(xu(1:), mygrid%xu, "xu") 86 93 res = res .AND. assert_equal(y, mygrid%y, "y" ) 87 res = res .AND. assert_equal(yv(1:), mygrid%yv, "y u")94 res = res .AND. assert_equal(yv(1:), mygrid%yv, "yv") 88 95 res = res .AND. assert_equal(z, mygrid%z, "z" ) 89 res = res .AND. assert_equal(zw(1:), mygrid%zw, "z u")96 res = res .AND. assert_equal(zw(1:), mygrid%zw, "zw") 90 97 91 98 CALL end_test(title, res) -
palm/trunk/UTIL/inifor/tests/test-input-files.f90
r2718 r3182 21 21 ! Current revisions: 22 22 ! ----------------- 23 ! 23 ! New test for negative start_hour and greater-than-one step_hour 24 ! 24 25 ! 25 26 ! Former revisions: … … 44 45 ONLY : PATH 45 46 USE grid, & 46 ONLY : input_file_list47 ONLY : get_input_file_list 47 48 USE test_utils 48 49 49 50 IMPLICIT NONE 50 51 51 CHARACTER(LEN= 50) :: title52 CHARACTER(LEN=60) :: title 52 53 CHARACTER(LEN=PATH), ALLOCATABLE, DIMENSION(:) :: file_list, ref_list 53 54 LOGICAL :: res 54 INTEGER :: i 55 INTEGER :: i 55 56 56 57 title = "input files - daylight saving to standard time" … … 70 71 71 72 ! 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)73 CALL get_input_file_list(start_date_string='2017102823', & 74 start_hour=0, end_hour=5, step_hour=1, & 75 path='./', prefix="laf", suffix='-test', & 76 file_list=file_list) 76 77 77 78 ! Assert … … 95 96 96 97 ! 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) 98 CALL get_input_file_list(start_date_string='2016022823', & 99 start_hour=0, end_hour=1, step_hour=1, & 100 path='./', prefix="laf", suffix='-test', & 101 file_list=file_list) 102 103 ! Assert 104 DO i = 1, 2 105 res = res .AND. (TRIM(ref_list(i)) .EQ. TRIM(file_list(i))) 106 END DO 107 108 DEALLOCATE( ref_list, file_list ) 109 CALL end_test(title, res) 110 111 112 113 title = "input files - negative start_hour and step_hour > 1 hour" 114 CALL begin_test(title, res) 115 116 ! Arange 117 ! ...a date range that inlcudes a leap day (29. Feb. 2016) which should be 118 ! inlcuded in UTC time stamps. 119 ALLOCATE( ref_list(4) ) 120 ref_list(1) = './laf2017102823-test.nc' 121 ref_list(2) = './laf2017102901-test.nc' 122 ref_list(3) = './laf2017102903-test.nc' 123 ref_list(4) = './laf2017102904-test.nc' 124 125 ! Act 126 CALL get_input_file_list(start_date_string='2017102901', & 127 start_hour=-2, end_hour=3, step_hour=2, & 128 path='./', prefix="laf", suffix='-test', & 129 file_list=file_list) 130 131 PRINT *, file_list 101 132 102 133 ! Assert -
palm/trunk/UTIL/inifor/tests/test-interpolation.f90
r2718 r3182 21 21 ! Current revisions: 22 22 ! ----------------- 23 ! 23 ! Updated test for new grid_definition 24 ! 24 25 ! 25 26 ! Former revisions: … … 76 77 xmin = -5.0 * TO_RADIANS, xmax = 5.5 * TO_RADIANS, & 77 78 ymin = -5.0 * TO_RADIANS, ymax = 6.5 * TO_RADIANS, & 78 zmin = 0.0, zmax = 10.0, &79 79 x0 = 0.0, y0 = 0.0, z0 = 0.0, & 80 80 nx = nlon-1, ny = nlat-1, nz = nlev-1) … … 86 86 res = assert_equal( (/cosmo_grid%lat(0), cosmo_grid % lon(0), & 87 87 cosmo_grid%lat(2), cosmo_grid % lon(2), & 88 cosmo_grid%dx*TO_DEGREES, cosmo_grid%dy*TO_DEGREES/),& 88 (cosmo_grid%lon(1) - cosmo_grid%lon(0))*TO_DEGREES, & 89 (cosmo_grid%lat(1) - cosmo_grid%lat(0))*TO_DEGREES/),& 89 90 (/-5.0 * TO_RADIANS, -5.0 * TO_RADIANS, & 90 91 6.5 * TO_RADIANS, 5.5 * TO_RADIANS, & … … 97 98 xmin = 0.0, xmax = 1.0, & 98 99 ymin = 0.0, ymax = 1.0, & 99 zmin = 0.0, zmax = 1.0, &100 100 x0 = 0.0, y0 = 0.0, z0 = 0.0, & 101 101 nx = 1, ny = 1, nz = 1) … … 127 127 ! Act 128 128 CALL find_horizontal_neighbours(cosmo_grid % lat, cosmo_grid % lon, & 129 cosmo_grid % dxi, cosmo_grid % dyi, palm_grid % clat, palm_grid % clon,&130 palm_grid % ii, palm_grid % jj)129 palm_grid % clat, palm_grid % clon, & 130 palm_grid % ii, palm_grid % jj) 131 131 132 132 ! Assert … … 178 178 ! Act 179 179 CALL find_horizontal_neighbours(cosmo_grid % lat, cosmo_grid % lon, & 180 cosmo_grid % dxi, cosmo_grid % dyi, palm_grid % clat, palm_grid % clon,&181 palm_grid % ii, palm_grid % jj)180 palm_grid % clat, palm_grid % clon, & 181 palm_grid % ii, palm_grid % jj) 182 182 183 183 CALL compute_horizontal_interp_weights(cosmo_grid % lat, cosmo_grid % lon, & 184 cosmo_grid % dxi, cosmo_grid % dyi, palm_grid % clat, & 185 palm_grid % clon, palm_grid % ii, palm_grid % jj, palm_grid % w_horiz) 184 palm_grid % clat, palm_grid % clon, & 185 palm_grid % ii, palm_grid % jj, & 186 palm_grid % w_horiz) 186 187 187 188 ! Assert -
palm/trunk/UTIL/inifor/tests/test-prototype.f90
r2718 r3182 21 21 ! Current revisions: 22 22 ! ----------------- 23 ! 23 ! Added usage hints 24 24 ! 25 25 ! Former revisions: … … 51 51 52 52 ! Arange 53 !define parameters and reference values 53 54 54 55 ! Act 56 !compute result 55 57 56 58 ! Assert 59 !res = res .AND. assert_equal(<result_array>, <reference_array>, 'description') 57 60 58 61 CALL end_test(title, res) -
palm/trunk/UTIL/inifor/tests/util.f90
r2718 r3182 21 21 ! Current revisions: 22 22 ! ----------------- 23 ! Expose error measure as parameter in assert_equal() 23 24 ! 24 25 ! … … 74 75 END SUBROUTINE end_test 75 76 76 LOGICAL FUNCTION assert_equal(a, b, msg) 77 LOGICAL FUNCTION assert_equal(a, b, msg, ratio) 78 REAL, OPTIONAL, INTENT(IN) :: ratio 77 79 REAL, DIMENSION(:), INTENT(IN) :: a, b 78 CHARACTER(LEN=*), INTENT(IN) :: msg80 CHARACTER(LEN=*), INTENT(IN) :: msg 79 81 80 assert_equal = assert(a, b, 'eq') 82 IF ( PRESENT(ratio) ) THEN 83 assert_equal = assert(a, b, 'eq', ratio) 84 ELSE 85 assert_equal = assert(a, b, 'eq') 86 END IF 87 81 88 IF (assert_equal .eqv. .TRUE.) THEN 82 89 PRINT *, "Equality assertion for ", msg, " was successful." … … 88 95 END FUNCTION assert_equal 89 96 90 LOGICAL FUNCTION assert(a, b, mode, eps)97 LOGICAL FUNCTION assert(a, b, mode, ratio) 91 98 92 99 REAL, DIMENSION(:), INTENT(IN) :: a, b 93 REAL, OPTIONAL, INTENT(IN) :: eps100 REAL, OPTIONAL, INTENT(IN) :: ratio 94 101 CHARACTER(LEN=*), INTENT(IN) :: mode 95 102 … … 98 105 99 106 max_rel_diff = 10 * EPSILON(1.0) 100 IF (PRESENT( eps)) max_rel_diff = eps107 IF (PRESENT(ratio)) max_rel_diff = ratio 101 108 102 109 SELECT CASE( TRIM(mode) )
Note: See TracChangeset
for help on using the changeset viewer.