Ignore:
Timestamp:
Jul 27, 2018 1:36:03 PM (6 years ago)
Author:
suehring
Message:

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/tests/test-grid.f90

    r2718 r3182  
    2121! Current revisions:
    2222! -----------------
     23! Updated test for new PALM grid strechting
    2324!
    2425!
     
    4142 PROGRAM test_grid
    4243
    43     USE grid, ONLY :  grid_definition, init_grid_definition
     44    USE grid, ONLY :  grid_definition, init_grid_definition, dx, dy, dz
    4445    USE test_utils
    4546   
     
    4950    LOGICAL                     ::  res
    5051
    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
    5860
    5961    CALL begin_test(title, res)
    6062
    6163    ! 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
    6283    CALL init_grid_definition('palm', grid = mygrid,                           &
    6384                              xmin = 0., xmax = lx,                            &
    6485                              ymin = 0., ymax = ly,                            &
    65                               zmin = 0., zmax = lz,                            &
    6686                              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)
    8289
    8390    ! Assert coordinates match
     
    8592    res = res .AND. assert_equal(xu(1:), mygrid%xu, "xu")
    8693    res = res .AND. assert_equal(y,      mygrid%y,  "y" )
    87     res = res .AND. assert_equal(yv(1:), mygrid%yv, "yu")
     94    res = res .AND. assert_equal(yv(1:), mygrid%yv, "yv")
    8895    res = res .AND. assert_equal(z,      mygrid%z,  "z" )
    89     res = res .AND. assert_equal(zw(1:), mygrid%zw, "zu")
     96    res = res .AND. assert_equal(zw(1:), mygrid%zw, "zw")
    9097
    9198    CALL end_test(title, res)
Note: See TracChangeset for help on using the changeset viewer.