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/src/io.f90

    r2718 r3182  
    2121! Current revisions:
    2222! -----------------
     23! Introduced new PALM grid stretching
     24! Updated variable names and metadata for PIDS v1.9 compatibility
     25! Improved handling of the start date string
     26! Better compatibility with older Intel compilers:
     27! - avoiding implicit array allocation with new get_netcdf_variable()
     28!   subroutine instead of function
     29! Improved command line interface:
     30! - Added configuration validation
     31! - New options to configure input file prefixes
     32! - GNU-style short and long option names
     33! - Added version and copyright output
    2334!
    24 ! 
     35!
    2536! Former revisions:
    2637! -----------------
     
    4354    USE control
    4455    USE defs,                                                                  &
    45         ONLY:  DATE, SNAME, PATH, PI, dp, TO_RADIANS, TO_DEGREES, VERSION
     56        ONLY:  DATE, SNAME, PATH, PI, dp, hp, TO_RADIANS, TO_DEGREES, VERSION
    4657    USE netcdf
    4758    USE types
    4859    USE util,                                                                  &
    49         ONLY:  reverse, str
     60        ONLY:  reverse, str, real_to_str
    5061
    5162    IMPLICIT NONE
    5263
     64    INTERFACE get_netcdf_variable
     65        MODULE PROCEDURE get_netcdf_variable_int
     66        MODULE PROCEDURE get_netcdf_variable_real
     67    END INTERFACE get_netcdf_variable
     68
     69    PRIVATE ::  get_netcdf_variable_int, get_netcdf_variable_real
     70
    5371 CONTAINS
     72
     73    SUBROUTINE get_netcdf_variable_int(in_file, in_var, buffer)
     74
     75       CHARACTER(LEN=PATH), INTENT(IN)         ::  in_file
     76       TYPE(nc_var), INTENT(INOUT)             ::  in_var
     77       INTEGER(hp), ALLOCATABLE, INTENT(INOUT) ::  buffer(:,:,:)
     78
     79       INCLUDE 'get_netcdf_variable.inc'
     80
     81    END SUBROUTINE get_netcdf_variable_int
     82
     83
     84    SUBROUTINE get_netcdf_variable_real(in_file, in_var, buffer)
     85
     86       CHARACTER(LEN=PATH), INTENT(IN)      ::  in_file
     87       TYPE(nc_var), INTENT(INOUT)          ::  in_var
     88       REAL(dp), ALLOCATABLE, INTENT(INOUT) ::  buffer(:,:,:)
     89
     90       INCLUDE 'get_netcdf_variable.inc'
     91
     92    END SUBROUTINE get_netcdf_variable_real
     93
    5494
    5595    SUBROUTINE netcdf_define_variable(var, ncid)
     
    5999
    60100        CALL check(nf90_def_var(ncid, var % name, NF90_FLOAT,       var % dimids(1:var % ndim), var % varid))
    61         CALL check(nf90_put_att(ncid, var % varid, "standard_name", var % standard_name))
    62101        CALL check(nf90_put_att(ncid, var % varid, "long_name",     var % long_name))
    63102        CALL check(nf90_put_att(ncid, var % varid, "units",         var % units))
    64         CALL check(nf90_put_att(ncid, var % varid, "lod",           var % lod))
     103        IF ( var % lod .GE. 0 )  THEN
     104           CALL check(nf90_put_att(ncid, var % varid, "lod",           var % lod))
     105        END IF
    65106        CALL check(nf90_put_att(ncid, var % varid, "source",        var % source))
    66107        CALL check(nf90_put_att(ncid, var % varid, "_FillValue",    NF90_FILL_REAL))
     
    94135!> parameters for the PALM-4U computational grid.
    95136!------------------------------------------------------------------------------!
    96     SUBROUTINE parse_command_line_arguments( start_date, hhl_file,             &
    97        soiltyp_file, static_driver_file, input_path, output_file,              &
    98        namelist_file, ug, vg, p0, z0, mode )
    99 
    100        CHARACTER(LEN=PATH), INTENT(INOUT)  ::  hhl_file, soiltyp_file,         &
    101            static_driver_file, input_path, output_file, namelist_file
    102        CHARACTER(LEN=SNAME), INTENT(INOUT) ::  mode
    103        REAL(dp), INTENT(INOUT)             ::  ug, vg, p0, z0
    104        CHARACTER(LEN=DATE), INTENT(INOUT)  ::  start_date
    105 
    106        CHARACTER(LEN=PATH)     ::  option, arg
    107        INTEGER                 ::  arg_count, i
     137    SUBROUTINE parse_command_line_arguments( cfg )
     138
     139       TYPE(inifor_config), INTENT(INOUT) ::  cfg
     140
     141       CHARACTER(LEN=PATH)                ::  option, arg
     142       INTEGER                            ::  arg_count, i
    108143
    109144       arg_count = COMMAND_ARGUMENT_COUNT()
     
    111146
    112147          ! Every option should have an argument.
    113           IF ( MOD(arg_count, 2) .NE. 0 )  THEN
    114              message = "Syntax error in command line."
    115              CALL abort('parse_command_line_arguments', message)
    116           END IF
     148          !IF ( MOD(arg_count, 2) .NE. 0 )  THEN
     149          !   message = "Syntax error in command line."
     150          !   CALL abort('parse_command_line_arguments', message)
     151          !END IF
    117152         
    118153          message = "The -clon and -clat command line options are depricated. " // &
    119154             "Please remove them form your inifor command and specify the " // &
    120155             "location of the PALM-4U origin either" // NEW_LINE(' ') // &
    121              "   - by setting the namelist parameters 'origin_lon' and 'origin_lat, or'" // NEW_LINE(' ') // &
     156             "   - by setting the namelist parameters 'longitude' and 'latitude', or" // NEW_LINE(' ') // &
    122157             "   - by providing a static driver netCDF file via the -static command-line option."
    123158
    124           ! Loop through option/argument pairs.
    125           DO i = 1, arg_count, 2
     159          i = 1
     160          DO WHILE (i .LE. arg_count)
    126161
    127162             CALL GET_COMMAND_ARGUMENT( i, option )
    128              CALL GET_COMMAND_ARGUMENT( i+1, arg )
    129163
    130164             SELECT CASE( TRIM(option) )
    131165
    132              CASE( '-date' )
    133                 start_date = TRIM(arg)
     166             CASE( '-date', '-d', '--date' )
     167                CALL get_option_argument( i, arg )
     168                cfg % start_date = TRIM(arg)
    134169
    135170             ! Elevation of the PALM-4U domain above sea level
    136              CASE( '-z0' )
    137                 READ(arg, *) z0
     171             CASE( '-z0', '-z', '--elevation' )
     172                CALL get_option_argument( i, arg )
     173                READ(arg, *) cfg % z0
    138174
    139175             ! surface pressure, at z0
    140              CASE( '-p0' )
    141                 READ(arg, *) p0
    142 
    143              ! surface pressure, at z0
    144              CASE( '-ug' )
    145                 READ(arg, *) ug
    146 
    147              ! surface pressure, at z0
    148              CASE( '-vg' )
    149                 READ(arg, *) vg
    150 
    151              ! Domain centre geographical longitude
    152              CASE( '-clon' )
     176             CASE( '-p0', '-r', '--surface-pressure' )
     177                CALL get_option_argument( i, arg )
     178                READ(arg, *) cfg % p0
     179
     180             ! geostrophic wind in x direction
     181             CASE( '-ug', '-u', '--geostrophic-u' )
     182                CALL get_option_argument( i, arg )
     183                READ(arg, *) cfg % ug
     184
     185             ! geostrophic wind in y direction
     186             CASE( '-vg', '-v', '--geostrophic-v' )
     187                CALL get_option_argument( i, arg )
     188                READ(arg, *) cfg % vg
     189
     190             ! domain centre geographical longitude and latitude
     191             CASE( '-clon', '-clat' )
    153192                CALL abort('parse_command_line_arguments', message)         
    154193                !READ(arg, *) lambda_cg
    155194                !lambda_cg = lambda_cg * TO_RADIANS
    156 
    157              ! Domain centre geographical latitude
    158              CASE( '-clat' )
    159                 CALL abort('parse_command_line_arguments', message)         
    160195                !READ(arg, *) phi_cg
    161196                !phi_cg = phi_cg * TO_RADIANS
    162197
    163              CASE( '-path' )
    164                  input_path = TRIM(arg)
    165 
    166              CASE( '-hhl' )
    167                  hhl_file = TRIM(arg)
    168 
    169              CASE( '-static' )
    170                  static_driver_file = TRIM(arg)
    171 
    172              CASE( '-soil' )
    173                  soiltyp_file = TRIM(arg)
    174 
    175              CASE( '-o' )
    176                 output_file = TRIM(arg)
    177 
    178              CASE( '-n' )
    179                 namelist_file = TRIM(arg)
    180 
    181              ! Initialization mode: 'profile' / 'volume'
    182              CASE( '-mode' )
    183                 mode = TRIM(arg)
    184 
    185                 SELECT CASE( TRIM(mode) )
    186 
    187                 CASE( 'profile' )
    188 
    189                 CASE DEFAULT
    190                    message = "Mode '" // TRIM(mode) // "' is not supported. " //&
    191                              "Currently, '-mode profile' is the only supported option. " //&
    192                              "Select this one or omit the -mode option entirely."
    193                    CALL abort( 'parse_command_line_arguments', message )
    194                 END SELECT
     198             CASE( '-path', '-p', '--path' )
     199                CALL get_option_argument( i, arg )
     200                 cfg % input_path = TRIM(arg)
     201
     202             CASE( '-hhl', '-l', '--hhl-file' )
     203                CALL get_option_argument( i, arg )
     204                 cfg % hhl_file = TRIM(arg)
     205
     206             CASE( '-static', '-t', '--static-driver' )
     207                CALL get_option_argument( i, arg )
     208                 cfg % static_driver_file = TRIM(arg)
     209
     210             CASE( '-soil', '-s', '--soil-file')
     211                CALL get_option_argument( i, arg )
     212                 cfg % soiltyp_file = TRIM(arg)
     213
     214             CASE( '--flow-prefix')
     215                CALL get_option_argument( i, arg )
     216                 cfg % flow_prefix = TRIM(arg)
     217
     218             CASE( '--radiation-prefix')
     219                CALL get_option_argument( i, arg )
     220                 cfg % radiation_prefix = TRIM(arg)
     221
     222             CASE( '--soil-prefix')
     223                CALL get_option_argument( i, arg )
     224                 cfg % soil_prefix = TRIM(arg)
     225
     226             CASE( '--soilmoisture-prefix')
     227                CALL get_option_argument( i, arg )
     228                 cfg % soilmoisture_prefix = TRIM(arg)
     229
     230             CASE( '-o', '--output' )
     231                CALL get_option_argument( i, arg )
     232                cfg % output_file = TRIM(arg)
     233
     234             CASE( '-n', '--namelist' )
     235                CALL get_option_argument( i, arg )
     236                cfg % namelist_file = TRIM(arg)
     237
     238             ! initial condition mode: 'profile' / 'volume'
     239             CASE( '-mode', '-i', '--init-mode' )
     240                CALL get_option_argument( i, arg )
     241                cfg % ic_mode = TRIM(arg)
     242
     243             ! boundary conditions / forcing mode: 'ideal' / 'real'
     244             CASE( '-f', '--forcing-mode' )
     245                CALL get_option_argument( i, arg )
     246                cfg % bc_mode = TRIM(arg)
     247
     248             CASE( '--version' )
     249                CALL print_version()
     250                STOP
     251
     252             CASE( '--help' )
     253                CALL print_version()
     254                PRINT *, ""
     255                PRINT *, "For a list of command-line options have a look at the README file."
     256                STOP
    195257
    196258             CASE DEFAULT
    197                 message = "unknown option '" // TRIM(option(2:)) // "'."
     259                message = "unknown option '" // TRIM(option) // "'."
    198260                CALL abort('parse_command_line_arguments', message)
    199261
    200262             END SELECT
     263
     264             i = i + 1
    201265
    202266          END DO
     
    210274
    211275   END SUBROUTINE parse_command_line_arguments
     276
     277   
     278   SUBROUTINE get_option_argument(i, arg)
     279      CHARACTER(LEN=PATH), INTENT(INOUT) ::  arg
     280      INTEGER, INTENT(INOUT)             ::  i
     281
     282      i = i + 1
     283      CALL GET_COMMAND_ARGUMENT(i, arg)
     284
     285   END SUBROUTINE
     286
     287
     288   SUBROUTINE validate_config(cfg)
     289      TYPE(inifor_config), INTENT(IN) ::  cfg
     290      LOGICAL                         ::  all_files_present
     291
     292      all_files_present = .TRUE.
     293      all_files_present = all_files_present .AND. file_present(cfg % hhl_file)
     294      all_files_present = all_files_present .AND. file_present(cfg % namelist_file)
     295      all_files_present = all_files_present .AND. file_present(cfg % output_file)
     296      all_files_present = all_files_present .AND. file_present(cfg % soiltyp_file)
     297
     298      ! Only check optional static driver file name, if it has been given.
     299      IF (TRIM(cfg % static_driver_file) .NE. '')  THEN
     300         all_files_present = all_files_present .AND. file_present(cfg % static_driver_file)
     301      END IF
     302
     303      IF (.NOT. all_files_present)  THEN
     304         message = "INIFOR configuration invalid; some input files are missing."
     305         CALL abort( 'validate_config', message )
     306      END IF
     307     
     308     
     309      SELECT CASE( TRIM(cfg % ic_mode) )
     310      CASE( 'profile', 'volume')
     311      CASE DEFAULT
     312         message = "Initialization mode '" // TRIM(cfg % ic_mode) //&
     313                   "' is not supported. " //&
     314                   "Please select either 'profile' or 'volume', " //&
     315                   "or omit the -i/--init-mode/-mode option entirely, which corresponds "//&
     316                   "to the latter."
     317         CALL abort( 'validate_config', message )
     318      END SELECT
     319
     320
     321      SELECT CASE( TRIM(cfg % bc_mode) )
     322      CASE( 'real', 'ideal')
     323      CASE DEFAULT
     324         message = "Forcing mode '" // TRIM(cfg % bc_mode) //&
     325                   "' is not supported. " //&
     326                   "Please select either 'real' or 'ideal', " //&
     327                   "or omit the -f/--forcing-mode option entirely, which corresponds "//&
     328                   "to the latter."
     329         CALL abort( 'validate_config', message )
     330      END SELECT
     331
     332
     333   END SUBROUTINE validate_config
     334
     335
     336   LOGICAL FUNCTION file_present(filename)
     337      CHARACTER(LEN=PATH), INTENT(IN) ::  filename
     338
     339      INQUIRE(FILE=filename, EXIST=file_present)
     340
     341      IF (.NOT. file_present)  THEN
     342         message = "The given file '" // "' does not exist."
     343         CALL report('file_present', message)
     344      END IF
     345
     346   END FUNCTION file_present
    212347
    213348
     
    222357!> writes the actual data.
    223358!------------------------------------------------------------------------------!
    224     SUBROUTINE setup_netcdf_dimensions(output_file, palm_grid)
     359   SUBROUTINE setup_netcdf_dimensions(output_file, palm_grid,                  &
     360                                      start_date_string, origin_lon, origin_lat)
    225361
    226362       TYPE(nc_file), INTENT(INOUT)      ::  output_file
    227363       TYPE(grid_definition), INTENT(IN) ::  palm_grid
    228 
    229        CHARACTER (LEN=SNAME) ::  date
     364       CHARACTER (LEN=DATE), INTENT(IN)  ::  start_date_string
     365       REAL(dp), INTENT(IN)              ::  origin_lon, origin_lat
     366
     367       CHARACTER (LEN=8)     ::  date_string
     368       CHARACTER (LEN=10)    ::  time_string
     369       CHARACTER (LEN=5)     ::  zone_string
     370       CHARACTER (LEN=SNAME) ::  history_string
    230371       INTEGER               ::  ncid, nx, ny, nz, nt, dimids(3), dimvarids(3)
    231372       REAL(dp)              ::  z0
    232373
     374       message = "Initializing PALM-4U dynamic driver file '" //               &
     375                 TRIM(output_file % name) // "' and setting up dimensions."
     376       CALL report('setup_netcdf_dimensions', message)
     377
    233378       ! Create the NetCDF file. NF90_CLOBBER selects overwrite mode.
     379#if defined( __netcdf4 )
    234380       CALL check(nf90_create(TRIM(output_file % name), OR(NF90_CLOBBER, NF90_HDF5), ncid))
     381#else
     382       CALL check(nf90_create(TRIM(output_file % name), NF90_CLOBBER, ncid))
     383#endif
    235384
    236385!
     
    238387!- Section 1: Write global NetCDF attributes
    239388!------------------------------------------------------------------------------
    240        CALL date_and_time(date)
     389       CALL date_and_time(DATE=date_string, TIME=time_string, ZONE=zone_string)
     390       history_string =                                                        &
     391           'Created on '// date_string      //                                 &
     392           ' at '       // time_string(1:2) // ':' // time_string(3:4) //      &
     393           ' (UTC'      // zone_string // ')'
     394
    241395       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'title',          'PALM input file for scenario ...'))
    242396       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'institution',    'Deutscher Wetterdienst, Offenbach'))
    243397       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'author',         'Eckhard Kadasch, eckhard.kadasch@dwd.de'))
    244        CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'history',        'Created on '//date))
     398       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'history',        TRIM(history_string)))
    245399       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'references',     '--'))
    246400       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'comment',        '--'))
    247        CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'origin_lat',     '--'))
    248        CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'origin_lon',     '--'))
     401       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'origin_lat',     TRIM(real_to_str(origin_lat*TO_DEGREES, '(F18.13)'))))
     402       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'origin_lon',     TRIM(real_to_str(origin_lon*TO_DEGREES, '(F18.13)'))))
    249403       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'inifor_version', TRIM(VERSION)))
    250404       CALL check(nf90_put_att(ncid, NF90_GLOBAL, 'palm_version',   '--'))
     
    267421          CALL check( nf90_def_dim(ncid, "x", nx+1, dimids(1)) )
    268422          CALL check( nf90_def_dim(ncid, "y", ny+1, dimids(2)) )
    269           CALL check( nf90_def_dim(ncid, "z", nz+1, dimids(3)) )
     423          CALL check( nf90_def_dim(ncid, "z", nz, dimids(3)) )
    270424          output_file % dimids_scl = dimids ! save dimids for later
    271425
     
    285439
    286440       ! overwrite third dimid with the one of depth
    287        CALL check(nf90_def_dim(ncid, "depth", SIZE(palm_grid % depths), dimids(3)) )
     441       CALL check(nf90_def_dim(ncid, "zsoil", SIZE(palm_grid % depths), dimids(3)) )
    288442       output_file % dimids_soil = dimids ! save dimids for later
    289443
    290444       ! overwrite third dimvarid with the one of depth
    291        CALL check(nf90_def_var(ncid, "depth", NF90_FLOAT, output_file % dimids_soil(3), dimvarids(3)))
     445       CALL check(nf90_def_var(ncid, "zsoil", NF90_FLOAT, output_file % dimids_soil(3), dimvarids(3)))
    292446       CALL check(nf90_put_att(ncid, dimvarids(3), "standard_name", "depth_below_land"))
    293447       CALL check(nf90_put_att(ncid, dimvarids(3), "positive", "down"))
     
    301455          CALL check(nf90_def_dim(ncid, "xu", nx, dimids(1)) )
    302456          CALL check(nf90_def_dim(ncid, "yv", ny, dimids(2)) )
    303           CALL check(nf90_def_dim(ncid, "zw", nz, dimids(3)) )
     457          CALL check(nf90_def_dim(ncid, "zw", nz-1, dimids(3)) )
    304458       output_file % dimids_vel = dimids ! save dimids for later
    305459
     
    328482       CALL check(nf90_put_att(ncid, output_file % dimvarid_time, "standard_name", "time"))
    329483       CALL check(nf90_put_att(ncid, output_file % dimvarid_time, "long_name", "time"))
    330        CALL check(nf90_put_att(ncid, output_file % dimvarid_time, "units", "seconds since..."))
     484       CALL check(nf90_put_att(ncid, output_file % dimvarid_time, "units",     &
     485                               "seconds since " // start_date_string // " UTC"))
    331486
    332487       CALL check(nf90_enddef(ncid))
     
    363518       INTEGER                              ::  i, ncid
    364519
    365        message = "Initializing PALM-4U forcing file '" // TRIM(filename) // "'."
     520       message = "Defining variables in dynamic driver '" // TRIM(filename) // "'."
    366521       CALL report('setup_netcdf_variables', message)
    367522
     
    374529
    375530          IF ( var % to_be_processed )  THEN
    376              message = "Defining variable #" // TRIM(str(i)) // " '" // TRIM(var%name) // "'."
     531             message = "  variable #" // TRIM(str(i)) // " '" // TRIM(var%name) // "'."
    377532             CALL report('setup_netcdf_variables', message)
    378533
     
    386541       CALL check(nf90_close(ncid))
    387542
    388        message = "Forcing file '" // TRIM(filename) // "' initialized successfully."
     543       message = "Dynamic driver '" // TRIM(filename) // "' initialized successfully."
    389544       CALL report('setup_netcdf_variables', message)
    390545
     
    447602
    448603          input_var => group % in_var_list(1)
    449           buffer(buf_id) % array = get_netcdf_variable( input_file, input_var ) 
     604          CALL get_netcdf_variable(input_file, input_var, buffer(buf_id) % array)
    450605          CALL report('read_input_variables', "Read accumulated " // TRIM(group % in_var_list(1) % name))
    451606
     
    472627             END IF
    473628
    474              buffer(ivar) % array = get_netcdf_variable( input_file, input_var ) 
     629             CALL get_netcdf_variable(input_file, input_var, buffer(ivar) % array)
    475630
    476631             IF ( input_var % is_upside_down )  CALL reverse(buffer(ivar) % array)
     
    545700
    546701          CALL check(nf90_get_att(ncid, NF90_GLOBAL, TRIM(attribute), attribute_value))
     702          CALL check(nf90_close(ncid))
    547703
    548704       ELSE
     
    555711
    556712    END FUNCTION get_netcdf_attribute
    557 
    558 
    559 
    560     FUNCTION get_netcdf_variable(in_file, in_var) RESULT(buffer)
    561 
    562        CHARACTER(LEN=PATH), INTENT(IN)      ::  in_file
    563        TYPE(nc_var), INTENT(INOUT)          ::  in_var
    564        REAL(dp), ALLOCATABLE                ::  buffer(:,:,:)
    565        INTEGER                              ::  i, ncid, start(3)
    566 
    567 
    568        ! Read in_var NetCDF attributes
    569        IF ( nf90_open( TRIM(in_file), NF90_NOWRITE, ncid ) .EQ. NF90_NOERR .AND. &
    570             nf90_inq_varid( ncid, in_var % name, in_var % varid ) .EQ. NF90_NOERR )  THEN
    571 
    572           CALL check(nf90_get_att(ncid, in_var % varid, "long_name", in_var % long_name))
    573           CALL check(nf90_get_att(ncid, in_var % varid, "units", in_var % units))
    574 
    575           ! Read in_var NetCDF dimensions
    576           CALL check(nf90_inquire_variable( ncid, in_var % varid,              &
    577                                             ndims  = in_var % ndim,            &
    578                                             dimids = in_var % dimids ))
    579                                        
    580           DO i = 1, in_var % ndim
    581              CALL check(nf90_inquire_dimension( ncid, in_var % dimids(i),      &
    582                                                 name = in_var % dimname(i),    &
    583                                                 len  = in_var % dimlen(i) ))
    584           END DO
    585 
    586           start = (/ 1, 1, 1 /)
    587           IF ( TRIM(in_var % name) .EQ. 'T_SO' )  THEN
    588              ! Skip depth = 0.0 for T_SO and reduce number of depths from 9 to 8
    589              in_var % dimlen(3) = in_var % dimlen(3) - 1
    590 
    591              ! Start reading from second level, e.g. depth = 0.005 instead of 0.0
    592              start(3) = 2
    593           END IF
    594 
    595           SELECT CASE(in_var % ndim)
    596 
    597           CASE (2)
    598 
    599              ALLOCATE( buffer( in_var % dimlen(1),                             &
    600                                in_var % dimlen(2),                             &
    601                                1 ) )
    602 
    603           CASE (3)
    604 
    605              ALLOCATE( buffer( in_var % dimlen(1),                             &
    606                                in_var % dimlen(2),                             &
    607                                in_var % dimlen(3) ) )
    608           CASE (4)
    609 
    610              ALLOCATE( buffer( in_var % dimlen(1),                             &
    611                                in_var % dimlen(2),                             &
    612                                in_var % dimlen(3) ) )
    613           CASE DEFAULT
    614 
    615              message = "Failed reading NetCDF variable " //                    &
    616                 TRIM(in_var % name) // " with " // TRIM(str(in_var%ndim)) //   &
    617                 " dimensions because only two- and and three-dimensional" //   &
    618                 " variables are supported."
    619              CALL abort('get_netcdf_variable', message)
    620 
    621           END SELECT
    622  CALL run_control('time', 'alloc')
    623          
    624           ! TODO: Check for matching dimensions of buffer and var
    625           CALL check(nf90_get_var( ncid, in_var % varid, buffer,               &
    626                                    start = start,                              &
    627                                    count = in_var % dimlen(1:3) ) )
    628 
    629  CALL run_control('time', 'read')
    630        ELSE
    631 
    632           message = "Failed to read '" // TRIM(in_var % name) // &
    633              "' from file '" // TRIM(in_file) // "'."
    634           CALL report('get_netcdf_variable', message)
    635 
    636        END IF
    637 
    638        CALL check(nf90_close(ncid))
    639 
    640  CALL run_control('time', 'read')
    641 
    642     END FUNCTION get_netcdf_variable
    643713
    644714
     
    657727
    658728       ! Skip time dimension for output
    659        IF ( var_is_time_dependent )  THEN
    660           ndim = var % ndim - 1
    661        ELSE
    662           ndim = var % ndim
    663        END IF
     729       ndim = var % ndim
     730       IF ( var_is_time_dependent )  ndim = var % ndim - 1
    664731
    665732       start(:)      = (/1,1,1,1/)
     
    733800                                   start=start(1:ndim+1) ) )
    734801
    735        CASE ( 'profile' )
     802       CASE ( 'constant scalar profile' )
    736803
    737804          CALL check(nf90_put_var( ncid, var%varid, array(1,1,:),              &
    738805                                   start=start(1:ndim+1),                      &
    739806                                   count=count(1:ndim) ) )
     807
     808       CASE ( 'large-scale scalar forcing', 'large-scale w forcing' )
     809
     810           message = "Doing nothing in terms of writing large-scale forings."
     811           CALL report('update_output', message)
    740812
    741813       CASE DEFAULT
Note: See TracChangeset for help on using the changeset viewer.