Changeset 3928


Ignore:
Timestamp:
Apr 23, 2019 8:58:53 PM (5 years ago)
Author:
gronemeier
Message:

change dimensions in NetCDF output files of virtual measurements; add output path to namelist

Location:
palm/trunk/UTIL/combine_virtual_measurements
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/combine_virtual_measurements/combine_virtual_measurements.f90

    r3705 r3928  
    2525! -----------------
    2626! $Id$
     27! rename subroutines
     28! remove space dimensions; add positions dimension
     29! add output path to namelist
     30!
     31! 3705 2019-01-29 19:56:39Z suehring
    2732! Initial revsion
    28 ! 
     33!
    2934! 3704 2019-01-29 19:51:41Z suehring
    3035!
     
    3742! Description:
    3843! ------------
    39 !> This routines merges binary output from virtual measurements taken from 
     44!> This routines merges binary output from virtual measurements taken from
    4045!> different subdomains and creates a NetCDF output file according to the (UC)2
    41 !> data standard. 
     46!> data standard.
    4247!------------------------------------------------------------------------------!
    4348 PROGRAM combine_virtual_measurements
    44  
    45 #if defined( __netcdf ) 
     49
     50#if defined( __netcdf )
    4651    USE NETCDF
    4752#endif
    48  
     53
    4954    IMPLICIT NONE
    50    
     55
    5156    CHARACTER(LEN=34)  ::  char_in                !< dummy string
    52     CHARACTER(LEN=4)   ::  file_suffix = '.bin'   !< string which contain the suffix indicating virtual measurement data 
     57    CHARACTER(LEN=4)   ::  file_suffix = '.bin'   !< string which contain the suffix indicating virtual measurement data
    5358    CHARACTER(LEN=30)  ::  myid_char              !< combined string indicating binary file
    54     CHARACTER(LEN=100) ::  path                   !< path to the binary data
     59    CHARACTER(LEN=100) ::  path_input             !< path to the binary input data
     60    CHARACTER(LEN=100) ::  path_output            !< path to the netcdf output files
    5561    CHARACTER(LEN=100) ::  run                    !< name of the run
    56    
     62
    5763    CHARACTER(LEN=100), DIMENSION(:),   ALLOCATABLE ::  site          !< name of the site
    5864    CHARACTER(LEN=100), DIMENSION(:),   ALLOCATABLE ::  filename      !< name of the original file
    5965    CHARACTER(LEN=100), DIMENSION(:),   ALLOCATABLE ::  feature_type  !< string indicating the type of the measurement
    6066    CHARACTER(LEN=100), DIMENSION(:),   ALLOCATABLE ::  soil_quantity !< string indicating soil measurements
    61     CHARACTER(LEN=10),  DIMENSION(:,:), ALLOCATABLE ::  variables     !< list of measured variables 
    62    
     67    CHARACTER(LEN=10),  DIMENSION(:,:), ALLOCATABLE ::  variables     !< list of measured variables
     68
    6369    CHARACTER(LEN=6), DIMENSION(5) ::  soil_quantities = (/                   & !< list of measurable soil variables
    6470                            "t_soil",                                         &
     
    6773                            "lwcs  ",                                         &
    6874                            "smp   "                    /)
    69    
     75
    7076    INTEGER, PARAMETER ::  iwp = 4                !< integer precision
    7177    INTEGER, PARAMETER ::  wp  = 8                !< float precision
    72    
     78
    7379    INTEGER(iwp) ::  cycle_number                 !< cycle number
    7480    INTEGER(iwp) ::  f                            !< running index over all binary files
    75     INTEGER(iwp) ::  file_id_in = 18              !< file unit for input binaray file   
     81    INTEGER(iwp) ::  file_id_in = 18              !< file unit for input binaray file
    7682    INTEGER(iwp) ::  l                            !< running index indicating the actual site
    7783    INTEGER(iwp) ::  n                            !< running index over all variables measured at a site
     
    7985    INTEGER(iwp) ::  nvm                          !< number of sites
    8086    INTEGER(iwp) ::  status_nc                    !< NetCDF error code, return value
    81        
     87
    8288    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ns           !< number of observation coordinates on current subdomain
    83     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ns_tot       !< total number of observation coordinates for a site 
     89    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ns_tot       !< total number of observation coordinates for a site
    8490    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ns_soil      !< number of observation coordinates for soil quantities (on current subdomain)
    8591    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ns_soil_tot  !< total number of observation coordinates for a site (for the soil)
    86     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nvar         !< number of sampled variables at a site 
     92    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nvar         !< number of sampled variables at a site
    8793!
    8894!-- NetCDF varialbes
    8995    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nc_id                 !< NetCDF file ID
    90     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_eutm               !< NetCDF dimension ID for E_UTM
    91     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_nutm               !< NetCDF dimension ID for N_UTM
    92     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_hao                !< NetCDF dimension ID for the height coordinate
    93     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_eutm_soil          !< NetCDF dimension ID for E_UTM for soil quantity
    94     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_nutm_soil          !< NetCDF dimension ID for N_UTM for soil quantity
    95     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_depth              !< NetCDF dimension ID for soil depth
     96    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_position           !< NetCDF dimension ID for vm position
     97    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_position_soil      !< NetCDF dimension ID for vm position in soil
    9698    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_time               !< NetCDF dimension ID for time
    9799    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_var_eutm           !< NetCDF variable ID for E_UTM
     
    100102    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_var_eutm_soil      !< NetCDF variable ID for E_UTM for soil quantity
    101103    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_var_nutm_soil      !< NetCDF variable ID for N_UTM for soil quantity
    102     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_var_depth          !< NetCDF variable ID for soil depth 
     104    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_var_depth          !< NetCDF variable ID for soil depth
    103105    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  id_var_time           !< NetCDF variable ID for the time coordinate
    104106    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  start_count_time      !< NetCDF start index for the time dimension
    105     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  start_count_utm       !< NetCDF start index for the UTM dimension 
     107    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  start_count_utm       !< NetCDF start index for the UTM dimension
    106108    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  start_count_utm_soil  !< NetCDF start index for the UTM dimension in the soil
    107    
     109
    108110    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  id_var              !< NetCDF variable IDs for the sampled variables at a site
    109    
     111
    110112    LOGICAL, DIMENSION(:), ALLOCATABLE ::  soil  !< flag indicating sampled soil quantities
    111    
    112     REAL(wp)                              ::  output_time    !< output time   
     113
     114    REAL(wp)                              ::  output_time    !< output time
    113115    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var            !< sampled data
    114116    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var_soil       !< sampled data of a soil varialbe
     
    121123    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  n_utm_soil     !< N_UTM coordinates where measurements were taken (soil)
    122124    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  depth          !< soil depth where measurements were taken (soil)
    123        
     125
    124126!
    125127!-- Read namelist.
     
    131133!
    132134!-- Open binary file for processor 0.
    133     OPEN ( file_id_in, FILE = TRIM( path ) // TRIM( run ) //                   &
     135    OPEN ( file_id_in, FILE = TRIM( path_input ) // TRIM( run ) //             &
    134136           TRIM( myid_char ), FORM = 'UNFORMATTED' )
    135137!
    136 !-- Reader global information, such as number of stations, their type, 
    137 !-- number of observation coordinates for each station on subdomain and 
    138 !-- total. Read number of sites. 
    139     READ( file_id_in )  char_in   
     138!-- Reader global information, such as number of stations, their type,
     139!-- number of observation coordinates for each station on subdomain and
     140!-- total. Read number of sites.
     141    READ( file_id_in )  char_in
    140142    READ( file_id_in )  nvm
    141143!
     
    147149    ALLOCATE( nvar(1:nvm)          )
    148150    ALLOCATE( origin_x_obs(1:nvm)  )
    149     ALLOCATE( origin_y_obs(1:nvm)  )   
     151    ALLOCATE( origin_y_obs(1:nvm)  )
    150152    ALLOCATE( ns(1:nvm)            )
    151153    ALLOCATE( ns_tot(1:nvm)        )
     
    153155    ALLOCATE( ns_soil_tot(1:nvm)   )
    154156    ALLOCATE( soil(1:nvm)          )
    155    
     157
    156158    ns_soil = 0
    157     ns_soil_tot = 0 
     159    ns_soil_tot = 0
    158160!
    159161!-- Allocate array with the measured variables at each station
     
    162164!-- Allocate arrays for NetCDF IDs
    163165    ALLOCATE( nc_id(1:nvm)        )
    164     ALLOCATE( id_eutm(1:nvm)      )
    165     ALLOCATE( id_nutm(1:nvm)      )
    166     ALLOCATE( id_hao(1:nvm)       )
    167     ALLOCATE( id_eutm_soil(1:nvm) )
    168     ALLOCATE( id_nutm_soil(1:nvm) )
    169     ALLOCATE( id_depth(1:nvm)     )
     166    ALLOCATE( id_position(1:nvm)      )
     167    ALLOCATE( id_position_soil(1:nvm) )
    170168    ALLOCATE( id_time(1:nvm)      )
    171169    ALLOCATE( id_var_eutm(1:nvm)  )
    172170    ALLOCATE( id_var_nutm(1:nvm)  )
    173     ALLOCATE( id_var_hao(1:nvm)   ) 
     171    ALLOCATE( id_var_hao(1:nvm)   )
    174172    ALLOCATE( id_var_eutm_soil(1:nvm) )
    175173    ALLOCATE( id_var_nutm_soil(1:nvm) )
    176     ALLOCATE( id_var_depth(1:nvm) )   
     174    ALLOCATE( id_var_depth(1:nvm) )
    177175    ALLOCATE( id_var_time(1:nvm)  )
    178176    ALLOCATE( id_var(1:50,1:nvm)  )
    179     id_var = 0   
     177    id_var = 0
    180178    nc_id  = 0
    181179!
    182 !-- Allocate arrays that contain information about the start index in the 
     180!-- Allocate arrays that contain information about the start index in the
    183181!-- dimension array, used to write binary data at the correct position in
    184 !-- the NetCDF file.   
     182!-- the NetCDF file.
    185183    ALLOCATE( start_count_utm(1:nvm) )
    186184    ALLOCATE( start_count_utm_soil(1:nvm) )
    187    
     185
    188186    ALLOCATE( start_count_time(1:nvm) )
    189187!
     
    194192!--    Read sitename
    195193       READ( file_id_in )  char_in
    196        READ( file_id_in )  site(l)   
    197 !
    198 !--    Read filename (original name where real-world data is stored) 
     194       READ( file_id_in )  site(l)
     195!
     196!--    Read filename (original name where real-world data is stored)
    199197       READ( file_id_in )  char_in
    200198       READ( file_id_in )  filename(l)
     
    210208       READ( file_id_in )  origin_y_obs(l)
    211209!
    212 !--    Read total number of observation grid points (dimension size of the 
     210!--    Read total number of observation grid points (dimension size of the
    213211!--    virtual measurement)
    214212       READ( file_id_in )  char_in
     
    219217       READ( file_id_in )  nvar(l)
    220218!
    221 !--    Read names of observed quantities 
     219!--    Read names of observed quantities
    222220       READ( file_id_in )  char_in
    223221       READ( file_id_in )  variables(1:nvar(l),l)
    224222!
    225 !--    Further dummy arguments are read (number of observation points 
    226 !--    on subdomains and its UTM coordinates). 
     223!--    Further dummy arguments are read (number of observation points
     224!--    on subdomains and its UTM coordinates).
    227225       READ( file_id_in )  char_in
    228226       READ( file_id_in )  ns(l)
    229              
     227
    230228       ALLOCATE( e_utm(1:ns(l)) )
    231229       ALLOCATE( n_utm(1:ns(l)) )
     
    234232!--    Read the local coordinate arrays
    235233       READ( file_id_in )  char_in
    236        READ( file_id_in )  e_utm 
    237      
     234       READ( file_id_in )  e_utm
     235
    238236       READ( file_id_in )  char_in
    239237       READ( file_id_in )  n_utm
     
    241239       READ( file_id_in )  char_in
    242240       READ( file_id_in )  z_ag
    243        
     241
    244242       DEALLOCATE( e_utm )
    245243       DEALLOCATE( n_utm )
    246        DEALLOCATE( z_ag  ) 
    247        
     244       DEALLOCATE( z_ag  )
     245
    248246!
    249247!--    Read flag indicating whether soil data is also present or not
    250248       READ( file_id_in )  char_in
    251249       READ( file_id_in )  char_in
    252        
     250
    253251       soil(l) = MERGE( .TRUE., .FALSE., TRIM( char_in ) == "yes" )
    254        
     252
    255253       IF ( soil(l) )  THEN
    256        
     254
    257255          READ( file_id_in )  char_in
    258256          READ( file_id_in )  ns_soil_tot(l)
    259          
     257
    260258          READ( file_id_in )  char_in
    261259          READ( file_id_in )  ns_soil(l)
    262        
     260
    263261          ALLOCATE( e_utm_soil(1:ns_soil(l)) )
    264262          ALLOCATE( n_utm_soil(1:ns_soil(l)) )
     
    267265!--       Read the local coordinate arrays
    268266          READ( file_id_in )  char_in
    269           READ( file_id_in )  e_utm_soil 
    270      
     267          READ( file_id_in )  e_utm_soil
     268
    271269          READ( file_id_in )  char_in
    272270          READ( file_id_in )  n_utm_soil
     
    274272          READ( file_id_in )  char_in
    275273          READ( file_id_in )  depth
    276        
     274
    277275          DEALLOCATE( e_utm_soil )
    278276          DEALLOCATE( n_utm_soil )
    279277          DEALLOCATE( depth      )
    280        
     278
    281279       ENDIF
    282280!
    283281!--    Create netcdf file and setup header information
    284282       CALL netcdf_create_file
    285        
     283
    286284    ENDDO
    287285!
     
    300298!
    301299!--    Open binary file for processor f.
    302        OPEN ( file_id_in, FILE = TRIM( path ) // TRIM( run ) //                &
     300       OPEN ( file_id_in, FILE = TRIM( path_input ) // TRIM( run ) //          &
    303301              TRIM( myid_char ), FORM = 'UNFORMATTED' )
    304302!
     
    306304       start_count_time = 1
    307305!
    308 !--    Reader global information, such as number of stations, their type, 
    309 !--    number of observation coordinates for each station on subdomain and 
    310 !--    total. 
    311 !--    Again, read number of sites. 
     306!--    Reader global information, such as number of stations, their type,
     307!--    number of observation coordinates for each station on subdomain and
     308!--    total.
     309!--    Again, read number of sites.
    312310       READ( file_id_in ) char_in
    313311       READ( file_id_in ) nvm
    314              
     312
    315313       DO  l = 1, nvm
    316314!
    317315!--       Read sitename
    318316          READ( file_id_in )  char_in
    319           READ( file_id_in )  site(l)   
    320 !
    321 !--       Read filename (original name where real-world data is stored) 
     317          READ( file_id_in )  site(l)
     318!
     319!--       Read filename (original name where real-world data is stored)
    322320          READ( file_id_in )  char_in
    323321          READ( file_id_in )  filename(l)
     
    333331          READ( file_id_in )  origin_y_obs(l)
    334332!
    335 !--       Read total number of observation grid points (dimension size of the 
     333!--       Read total number of observation grid points (dimension size of the
    336334!--       virtual measurement)
    337335          READ( file_id_in )  char_in
     
    342340          READ( file_id_in )  nvar(l)
    343341!
    344 !--       Read names of observed quantities 
     342!--       Read names of observed quantities
    345343          READ( file_id_in )  char_in
    346344          READ( file_id_in )  variables(1:nvar(l),l)
    347345!
    348 !--       Further dummy arguments are read (number of observation points 
    349 !--       on subdomains and its UTM coordinates). 
     346!--       Further dummy arguments are read (number of observation points
     347!--       on subdomains and its UTM coordinates).
    350348          READ( file_id_in )  char_in
    351349          READ( file_id_in )  ns(l)
    352              
     350
    353351          ALLOCATE( e_utm(1:ns(l)) )
    354352          ALLOCATE( n_utm(1:ns(l)) )
     
    357355!--       Read the local coordinate arrays
    358356          READ( file_id_in )  char_in
    359           READ( file_id_in )  e_utm 
    360      
     357          READ( file_id_in )  e_utm
     358
    361359          READ( file_id_in )  char_in
    362360          READ( file_id_in )  n_utm
    363    
    364           READ( file_id_in )  char_in
    365           READ( file_id_in )  z_ag     
     361
     362          READ( file_id_in )  char_in
     363          READ( file_id_in )  z_ag
    366364!
    367365!--       Read flag indicating whether soil data is also present or not
    368366          READ( file_id_in )  char_in
    369367          READ( file_id_in )  char_in
    370        
     368
    371369          soil(l) = MERGE( .TRUE., .FALSE., TRIM( char_in ) == "yes" )
    372        
     370
    373371          IF ( soil(l) )  THEN
    374        
     372
    375373             READ( file_id_in )  char_in
    376374             READ( file_id_in )  ns_soil_tot(l)
    377          
     375
    378376             READ( file_id_in )  char_in
    379377             READ( file_id_in )  ns_soil(l)
    380        
     378
    381379             ALLOCATE( e_utm_soil(1:ns_soil(l)) )
    382380             ALLOCATE( n_utm_soil(1:ns_soil(l)) )
     
    385383!--          Read the local coordinate arrays
    386384             READ( file_id_in )  char_in
    387              READ( file_id_in )  e_utm_soil 
    388      
     385             READ( file_id_in )  e_utm_soil
     386
    389387             READ( file_id_in )  char_in
    390388             READ( file_id_in )  n_utm_soil
    391    
     389
    392390             READ( file_id_in )  char_in
    393391             READ( file_id_in )  depth
    394        
     392
    395393          ENDIF
    396394!
    397 !--       Setup the NetCDF dimensions for the UTM coordinates
    398           CALL netcdf_define_utm_dimension
    399          
     395!--       Write the spatial coordinates to the NetCDF file
     396          CALL netcdf_write_spatial_coordinates
     397
    400398          DEALLOCATE( e_utm )
    401399          DEALLOCATE( n_utm )
    402400          DEALLOCATE( z_ag )
    403          
     401
    404402          IF ( soil(l) )  THEN
    405403             DEALLOCATE( e_utm_soil )
     
    407405             DEALLOCATE( depth      )
    408406          ENDIF
    409          
     407
    410408       ENDDO
    411409!
    412 !--    Read the actual data, starting with the identification string for the 
     410!--    Read the actual data, starting with the identification string for the
    413411!--    output time
    414        READ( file_id_in )  char_in         
     412       READ( file_id_in )  char_in
    415413       DO WHILE ( TRIM( char_in ) == 'output time')
    416        
    417           READ( file_id_in )  output_time 
     414
     415          READ( file_id_in )  output_time
    418416!
    419417!--       Loop over all sites
     
    423421             IF ( ns(l) < 1  .AND.  ns_soil(l) < 1 )  CYCLE
    424422!
    425 !--          Setup time coordinate
    426              CALL netcdf_define_time_dimension
     423!--          Write time coordinate
     424             CALL netcdf_write_time_coordinate
    427425!
    428426!--          Read the actual data, therefore, allocate appropriate array with
    429 !--          size of the subdomain coordinates. Output data immediately into 
    430 !--          NetCDF file. 
     427!--          size of the subdomain coordinates. Output data immediately into
     428!--          NetCDF file.
    431429             ALLOCATE( var(1:ns(l)) )
    432430             IF ( soil(l) )  ALLOCATE( var_soil(1:ns_soil(l)) )
    433              
     431
    434432             DO  n = 1, nvar(l)
    435433                READ( file_id_in )  variables(n,l)
     
    441439                ENDIF
    442440!
    443 !--             Write data to NetCDF file 
     441!--             Write data to NetCDF file
    444442                CALL netcdf_data_output
    445              ENDDO       
    446              
     443             ENDDO
     444
    447445             DEALLOCATE( var )
    448446             IF( ALLOCATED(var_soil) )  DEALLOCATE( var_soil )
     
    454452!--       Read next identification string
    455453          READ( file_id_in )  char_in
    456          
     454
    457455       ENDDO
    458456!
    459 !--    After data from processor f is read and output into NetCDF file, 
     457!--    After data from processor f is read and output into NetCDF file,
    460458!--    the start index of the UTM coordinate array need to be incremented
    461459       start_count_utm      = start_count_utm      + ns
     
    470468       CALL netcdf_close_file
    471469    ENDDO
    472    
     470
    473471 CONTAINS
    474  
     472
    475473!------------------------------------------------------------------------------!
    476474! Description:
     
    479477!------------------------------------------------------------------------------!
    480478    SUBROUTINE cvm_parin
    481        
     479
    482480       IMPLICIT NONE
    483        
     481
    484482       INTEGER(iwp) ::  file_id_parin = 90
    485        
    486        NAMELIST /vm/  cycle_number, num_pe, path, run
     483
     484       NAMELIST /vm/  cycle_number, num_pe, path_input, path_output, run
    487485
    488486!
     
    495493!--    Close namelist file.
    496494       CLOSE( file_id_parin )
    497        
     495
    498496    END SUBROUTINE cvm_parin
    499      
     497
    500498!------------------------------------------------------------------------------!
    501499! Description:
     
    504502!------------------------------------------------------------------------------!
    505503    SUBROUTINE create_file_string
    506        
     504
    507505       IMPLICIT NONE
    508        
     506
    509507       CHARACTER(LEN=4)   ::  char_cycle = '' !< dummy string for cycle number
    510508       CHARACTER(LEN=10)  ::  char_dum        !< dummy string for processor ID
    511        
     509
    512510!
    513511!--    Create substring for the cycle number.
     
    551549                      TRIM( char_cycle ) // file_suffix
    552550       ENDIF
    553        
     551
    554552    END SUBROUTINE create_file_string
    555    
    556    
     553
     554
    557555!------------------------------------------------------------------------------!
    558556! Description:
     
    561559!------------------------------------------------------------------------------!
    562560    SUBROUTINE netcdf_create_file
    563        
     561
    564562       IMPLICIT NONE
    565        
    566        
     563
     564
    567565       CHARACTER(LEN=5)   ::  char_cycle = ''  !< dummy string for cycle number
    568566       CHARACTER(LEN=200) ::  nc_filename = '' !< NetCDF filename
    569        
     567
    570568!
    571569!--    Create substring for the cycle number.
     
    584582          char_cycle = '.'
    585583       ENDIF
    586 #if defined( __netcdf )     
     584#if defined( __netcdf )
    587585
    588586       nc_filename = site(l)(1:LEN_TRIM(site(l))-1) // '_palm4U' //            &
     
    590588!
    591589!--    Create NetCDF file
    592        status_nc = NF90_CREATE( nc_filename(1:LEN_TRIM(nc_filename)),          &
     590       status_nc = NF90_CREATE( TRIM(path_output) //                           &
     591                                nc_filename(1:LEN_TRIM(nc_filename)),          &
    593592                                IOR( NF90_CLOBBER, NF90_NETCDF4 ), nc_id(l) )
    594593       CALL handle_error( "create file" )
     
    598597                                 TRIM( feature_type(l) ) )
    599598       CALL handle_error( "define attribue featureType" )
    600        
     599
    601600       status_nc = NF90_PUT_ATT( nc_id(l), NF90_GLOBAL, "origin_x",            &
    602601                                 origin_x_obs(l) )
    603602       CALL handle_error( "define attribue origin_x" )
    604        
     603
    605604       status_nc = NF90_PUT_ATT( nc_id(l), NF90_GLOBAL, "origin_y",            &
    606605                                 origin_y_obs(l) )
    607606       CALL handle_error( "define attribue origin_y" )
    608        
     607
    609608       status_nc = NF90_PUT_ATT( nc_id(l), NF90_GLOBAL, "site",                &
    610609                                 TRIM( site(l) ) )
     
    612611!
    613612!--    Define dimensions
    614        status_nc = NF90_DEF_DIM( nc_id(l), 'E_UTM', ns_tot(l), id_eutm(l) )
    615        CALL handle_error( "define dimension E_UTM" )
    616        
    617        status_nc = NF90_DEF_DIM( nc_id(l), 'N_UTM', ns_tot(l), id_nutm(l) )
    618        CALL handle_error( "define dimension N_UTM" )
    619        
    620        status_nc = NF90_DEF_DIM( nc_id(l), 'height_above_origin', ns_tot(l),   &
    621                                  id_hao(l) )
    622        CALL handle_error( "define dimension height_above_origin" )
    623        
     613       status_nc = NF90_DEF_DIM( nc_id(l), 'time', NF90_UNLIMITED, id_time(l) )
     614       CALL handle_error( "define dimension time" )
     615
     616       status_nc = NF90_DEF_DIM( nc_id(l), 'position', ns_tot(l),              &
     617                                 id_position(l) )
     618       CALL handle_error( "define dimension position" )
     619
    624620       IF ( soil(l) )  THEN
    625           status_nc = NF90_DEF_DIM( nc_id(l), 'E_UTM soil', ns_soil_tot(l),    &
    626                                     id_eutm_soil(l) )
    627           CALL handle_error( "define dimension E_UTM soil" )
    628          
    629           status_nc = NF90_DEF_DIM( nc_id(l), 'N_UTM soil', ns_soil_tot(l),    &
    630                                     id_nutm_soil(l) )
    631           CALL handle_error( "define dimension N_UTM soil" )
    632           status_nc = NF90_DEF_DIM( nc_id(l), 'depth', ns_soil_tot(l),         &
    633                                     id_depth(l) )
    634           CALL handle_error( "define dimension depth" )
     621          status_nc = NF90_DEF_DIM( nc_id(l), 'position_soil', ns_soil_tot(l), &
     622                                    id_position_soil(l) )
     623          CALL handle_error( "define dimension position_soil" )
    635624       ENDIF
    636        
    637        status_nc = NF90_DEF_DIM( nc_id(l), 'time', NF90_UNLIMITED, id_time(l) )
    638        CALL handle_error( "define dimension time" )     
    639 
    640 !
    641 !--    Define dimension variables
     625!
     626!--    Define coordinate variables
    642627       status_nc = NF90_DEF_VAR( nc_id(l), 'E_UTM', NF90_DOUBLE,               &
    643                                  (/ id_eutm(l) /), id_var_eutm(l) )
     628                                 (/ id_position(l) /), id_var_eutm(l) )
    644629       CALL handle_error( "define variable E_UTM" )
    645        
     630
    646631       status_nc = NF90_DEF_VAR( nc_id(l), 'N_UTM', NF90_DOUBLE,               &
    647                                  (/ id_nutm(l) /), id_var_nutm(l) )
     632                                 (/ id_position(l) /), id_var_nutm(l) )
    648633       CALL handle_error( "define variable N_UTM" )
     634
    649635       status_nc = NF90_DEF_VAR( nc_id(l), 'height_above_origin', NF90_DOUBLE, &
    650                                  (/ id_hao(l)  /), id_var_hao(l)  )
     636                                 (/ id_position(l)  /), id_var_hao(l)  )
    651637       CALL handle_error( "define variable height_above_origin" )
     638
    652639       status_nc = NF90_DEF_VAR( nc_id(l), 'time', NF90_DOUBLE,                &
    653640                                 (/ id_time(l) /), id_var_time(l) )
    654641       CALL handle_error( "define variable time" )
    655        
     642
    656643       IF ( soil(l) )  THEN
    657644          status_nc = NF90_DEF_VAR( nc_id(l), 'E_UTM soil', NF90_DOUBLE,       &
    658                                     (/ id_eutm_soil(l) /), id_var_eutm_soil(l) )
     645                                    (/ id_position_soil(l) /),                 &
     646                                    id_var_eutm_soil(l) )
    659647          CALL handle_error( "define variable E_UTM soil" )
    660          
     648
    661649          status_nc = NF90_DEF_VAR( nc_id(l), 'N_UTM soil', NF90_DOUBLE,       &
    662                                     (/ id_nutm_soil(l) /), id_var_nutm_soil(l) )
     650                                    (/ id_position_soil(l) /),                 &
     651                                    id_var_nutm_soil(l) )
    663652          CALL handle_error( "define variable N_UTM soil" )
    664          
     653
    665654          status_nc = NF90_DEF_VAR( nc_id(l), 'depth', NF90_DOUBLE,            &
    666                                     (/ id_depth(l)  /), id_var_depth(l) )
     655                                    (/ id_position_soil(l)  /),                &
     656                                    id_var_depth(l) )
    667657          CALL handle_error( "define variable depth" )
    668658       ENDIF
     
    674664             status_nc = NF90_DEF_VAR( nc_id(l), TRIM( variables(n,l) ),       &
    675665                                       NF90_DOUBLE,                            &
    676                                        (/ id_time(l), id_eutm_soil(l) /),      &
     666                                       (/ id_time(l), id_position_soil(l) /),  &
    677667                                       id_var(n,l) )
    678668             CALL handle_error( "define variable " // TRIM( variables(n,l) ) )
     
    680670             status_nc = NF90_DEF_VAR( nc_id(l), TRIM( variables(n,l) ),       &
    681671                                       NF90_DOUBLE,                            &
    682                                        (/ id_time(l), id_eutm(l) /),           &
     672                                       (/ id_time(l), id_position(l) /),       &
    683673                                       id_var(n,l) )
    684674             CALL handle_error( "define variable " // TRIM( variables(n,l) ) )
    685675          ENDIF
    686676       ENDDO
    687 #endif       
     677#endif
    688678    END SUBROUTINE netcdf_create_file
    689    
     679
    690680!------------------------------------------------------------------------------!
    691681! Description:
     
    694684!------------------------------------------------------------------------------!
    695685    SUBROUTINE netcdf_close_file
    696        
     686
    697687       IMPLICIT NONE
    698        
    699 #if defined( __netcdf )       
     688
     689#if defined( __netcdf )
    700690       status_nc = NF90_CLOSE( nc_id(l) )
    701691       CALL handle_error( "close file" )
    702 #endif   
    703        
     692#endif
     693
    704694    END SUBROUTINE netcdf_close_file
    705    
     695
    706696!------------------------------------------------------------------------------!
    707697! Description:
    708698! ------------
    709 !> This subroutine defines the UTM dimensions
    710 !------------------------------------------------------------------------------!
    711     SUBROUTINE netcdf_define_utm_dimension
    712        
     699!> This subroutine writes the spatial coordinates
     700!------------------------------------------------------------------------------!
     701    SUBROUTINE netcdf_write_spatial_coordinates
     702
    713703       IMPLICIT NONE
    714        
    715 !
    716 !--    Define dimensions
    717 #if defined( __netcdf ) 
     704
     705!
     706!--    Write coordinates
     707#if defined( __netcdf )
    718708       status_nc = NF90_PUT_VAR( nc_id(l), id_var_eutm(l), e_utm,              &
    719                                  start = (/ start_count_utm(l) /),             & 
     709                                 start = (/ start_count_utm(l) /),             &
    720710                                 count = (/ ns(l) /) )
    721711       CALL handle_error( "write variable E_UTM" )
    722        
     712
    723713       status_nc = NF90_PUT_VAR( nc_id(l), id_var_nutm(l), n_utm,              &
    724714                                 start = (/ start_count_utm(l) /),             &
    725715                                 count = (/ ns(l) /) )
    726716       CALL handle_error( "write variable N_UTM" )
    727        
     717
    728718       status_nc = NF90_PUT_VAR( nc_id(l), id_var_hao(l),  z_ag,               &
    729719                                 start = (/ start_count_utm(l) /),             &
    730720                                 count = (/ ns(l) /) )
    731721       CALL handle_error( "write variable height_above_origin" )
    732        
     722
    733723       IF ( soil(l) )  THEN
    734724          status_nc = NF90_PUT_VAR( nc_id(l), id_var_eutm_soil(l), e_utm_soil, &
    735                                  start = (/ start_count_utm_soil(l) /),        & 
     725                                 start = (/ start_count_utm_soil(l) /),        &
    736726                                 count = (/ ns_soil(l) /) )
    737727          CALL handle_error( "write variable E_UTM soil" )
    738          
     728
    739729          status_nc = NF90_PUT_VAR( nc_id(l), id_var_nutm_soil(l), n_utm_soil, &
    740730                                 start = (/ start_count_utm_soil(l) /),        &
    741731                                 count = (/ ns_soil(l) /) )
    742732          CALL handle_error( "write variable N_UTM soil" )
    743          
     733
    744734          status_nc = NF90_PUT_VAR( nc_id(l), id_var_depth(l),  depth,         &
    745735                                 start = (/ start_count_utm_soil(l) /),        &
     
    750740!--    End of NetCDF file definition
    751741       status_nc = NF90_ENDDEF( nc_id(l) )
    752 #endif       
    753     END SUBROUTINE netcdf_define_utm_dimension
    754    
     742#endif
     743END SUBROUTINE netcdf_write_spatial_coordinates
     744
    755745!------------------------------------------------------------------------------!
    756746! Description:
    757747! ------------
    758 !> This subroutine updates the unlimited time dimension.
    759 !------------------------------------------------------------------------------!
    760     SUBROUTINE netcdf_define_time_dimension
    761        
     748!> This subroutine writes another time step to the unlimited time dimension.
     749!------------------------------------------------------------------------------!
     750    SUBROUTINE netcdf_write_time_coordinate
     751
    762752       IMPLICIT NONE
    763        
    764 !
    765 !--    Define dimensions
    766 #if defined( __netcdf )   
     753
     754#if defined( __netcdf )
    767755       status_nc = NF90_PUT_VAR( nc_id(l), id_var_time(l), (/ output_time /),  &
    768756                                 start = (/ start_count_time(l) /),            &
     
    770758       CALL handle_error( "write variable time" )
    771759#endif
    772        
    773     END SUBROUTINE netcdf_define_time_dimension
    774 
    775    
     760
     761END SUBROUTINE netcdf_write_time_coordinate
     762
     763
    776764!------------------------------------------------------------------------------!
    777765! Description:
     
    780768!------------------------------------------------------------------------------!
    781769    SUBROUTINE netcdf_data_output
    782        
     770
    783771       IMPLICIT NONE
    784        
     772
    785773
    786774       IF ( soil(l)  .AND.                                                     &
     
    798786          CALL handle_error( "write variable " // TRIM( variables(n,l) ) )
    799787       ENDIF
    800        
     788
    801789    END SUBROUTINE netcdf_data_output
    802    
     790
    803791!------------------------------------------------------------------------------!
    804792! Description:
    805793! ------------
    806794!> NetCDF error handling.
    807 !------------------------------------------------------------------------------!   
     795!------------------------------------------------------------------------------!
    808796    SUBROUTINE handle_error( action )
    809797
     
    811799
    812800       CHARACTER(LEN=*) ::  action !< string indicating the current file action
    813        
    814 #if defined( __netcdf )       
     801
     802#if defined( __netcdf )
    815803       IF ( status_nc /= NF90_NOERR )  THEN
    816           PRINT*, TRIM( NF90_STRERROR( status_nc ) ) // ' -- ' // action 
     804          PRINT*, TRIM( NF90_STRERROR( status_nc ) ) // ' -- ' // action
    817805          STOP
    818806       ENDIF
     
    820808
    821809    END SUBROUTINE handle_error
    822        
     810
    823811 END PROGRAM combine_virtual_measurements
  • palm/trunk/UTIL/combine_virtual_measurements/vm_parin

    r3704 r3928  
    22!
    33!-- Number of processors of the run.
    4     num_pe = 36,
     4    num_pe = 4,
    55!
    6 !-- Path to the output binary files.
    7     path = '~/palm/current_version/JOBS/test_urban/OUTPUT/',
     6!-- Path to the binary input files.
     7    path_input = '~/palm/current_version/JOBS/test_run/OUTPUT/',
     8!
     9!-- Path to the NetCDF output files
     10    path_output = '~/palm/current_version/JOBS/test_run/OUTPUT/',
    811!
    912!-- Name of the run.
    10     run = 'test_berlin',
     13    run = 'test_run',
    1114!
    1215!-- Cycle number of the output data which should be processed
    13     cycle_number = 0, 
    14 / 
     16    cycle_number = 0,
     17/
Note: See TracChangeset for help on using the changeset viewer.