Ignore:
Timestamp:
Aug 24, 2016 3:47:17 PM (8 years ago)
Author:
kanani
Message:

changes in the course of urban surface model implementation

File:
1 edited

Legend:

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

    r2001 r2007  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Added support for new urban surface model (temporary modifications of
     23! SELECT CASE ( ) necessary, see variable trimvar)
    2324!
    2425! Former revisions:
     
    178179        ONLY:  radiation, radiation_data_output_3d
    179180
     181    USE urban_surface_mod,                                                     &
     182        ONLY:  nzub, nzut, urban_surface, usm_data_output_3d
     183
    180184
    181185    IMPLICIT NONE
     
    200204
    201205    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted  !<
     206
     207    CHARACTER (LEN=20) ::  trimvar  !< TRIM of output-variable string
    202208
    203209!
     
    260266
    261267    DO  WHILE ( do3d(av,if)(1:1) /= ' ' )
    262 !
     268
     269!
     270!--    Temporary solution to account for data output within the new urban
     271!--    surface model (urban_surface_mod.f90), see also SELECT CASE ( trimvar ).
    263272!--    Store the array chosen on the temporary array.
    264        resorted = .FALSE.
    265        nzb_do = nzb
    266        nzt_do = nz_do3d
     273       trimvar = TRIM( do3d(av,if) )
     274       IF ( urban_surface  .AND.  trimvar(1:3) == 'us_' )  THEN
     275          trimvar = 'usm_output'
     276          resorted = .TRUE.
     277          nzb_do   = nzub
     278          nzt_do   = nzut
     279       ELSE
     280          resorted = .FALSE.
     281          nzb_do   = nzb
     282          nzt_do   = nz_do3d
     283       ENDIF
    267284!
    268285!--    Set flag to steer output of radiation, land-surface, or user-defined
     
    273290       ALLOCATE( local_pf(nxlg:nxrg,nysg:nyng,nzb_do:nzt_do) )
    274291
    275        SELECT CASE ( TRIM( do3d(av,if) ) )
     292       SELECT CASE ( trimvar )
    276293
    277294          CASE ( 'e' )
     
    553570                to_be_resorted => w_av
    554571             ENDIF
     572!             
     573!--       Block of urban surface model outputs   
     574          CASE ( 'usm_output' )
     575             CALL usm_data_output_3d( av, do3d(av,if), found, local_pf,     &
     576                                         nzb_do, nzt_do )
    555577
    556578          CASE DEFAULT
Note: See TracChangeset for help on using the changeset viewer.