Ignore:
Timestamp:
Sep 19, 2016 5:29:57 PM (8 years ago)
Author:
kanani
Message:

changes related to steering and formating of urban surface model

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/data_output_3d.f90

    r2008 r2011  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Flag urban_surface is now defined in module control_parameters,
     23! changed prefix for urban surface model output to "usm_",
     24! introduced control parameter varnamelength for LEN of trimvar.
    2325!
    2426! Former revisions:
     
    152154        ONLY:  cloud_physics, do3d, do3d_no, do3d_time_count, io_blocks,       &
    153155               io_group, message_string, ntdim_3d, nz_do3d, psolver,           &
    154                simulated_time, time_since_reference_point
     156               simulated_time, time_since_reference_point, urban_surface,      &
     157               varnamelength
    155158       
    156159    USE cpulog,                                                                &
     
    183186
    184187    USE urban_surface_mod,                                                     &
    185         ONLY:  nzub, nzut, urban_surface, usm_data_output_3d
     188        ONLY:  nzub, nzut, usm_data_output_3d
    186189
    187190
     
    208211    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !<
    209212
    210     CHARACTER (LEN=20) ::  trimvar  !< TRIM of output-variable string
     213    CHARACTER (LEN=varnamelength) ::  trimvar  !< TRIM of output-variable string
    211214
    212215!
     
    275278!--    Store the array chosen on the temporary array.
    276279       trimvar = TRIM( do3d(av,if) )
    277        IF ( urban_surface  .AND.  trimvar(1:3) == 'us_' )  THEN
     280       IF ( urban_surface  .AND.  trimvar(1:4) == 'usm_' )  THEN
    278281          trimvar = 'usm_output'
    279282          resorted = .TRUE.
Note: See TracChangeset for help on using the changeset viewer.