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/average_3d_data.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),
     24! added comments in variable declaration section
    2325!
    2426! Former revisions:
     
    107109        ONLY:  radiation, radiation_3d_data_averaging
    108110
     111    USE urban_surface_mod,                                                     &
     112        ONLY:  urban_surface, usm_average_3d_data
     113
    109114
    110115    IMPLICIT NONE
    111116
    112     INTEGER(iwp) ::  i  !<
    113     INTEGER(iwp) ::  ii !<
    114     INTEGER(iwp) ::  j  !<
    115     INTEGER(iwp) ::  k  !<
     117    INTEGER(iwp) ::  i  !< running index
     118    INTEGER(iwp) ::  ii !< running index
     119    INTEGER(iwp) ::  j  !< running index
     120    INTEGER(iwp) ::  k  !< running index
     121
     122    CHARACTER (LEN=20) ::  trimvar  !< TRIM of output-variable string
    116123
    117124
     
    127134
    128135!
     136!--    Temporary solution to account for data output within the new urban
     137!--    surface model (urban_surface_mod.f90), see also SELECT CASE ( trimvar )
     138       trimvar = TRIM( doav(ii) )
     139       IF ( urban_surface  .AND.  trimvar(1:3) == 'us_' )  THEN
     140          trimvar = 'usm_output'
     141       ENDIF
     142
     143!
    129144!--    Store the array chosen on the temporary array.
    130        SELECT CASE ( TRIM( doav(ii) ) )
     145       SELECT CASE ( trimvar )
    131146
    132147          CASE ( 'e' )
     
    399414                ENDDO
    400415             ENDDO
     416!             
     417!--       Block of urban surface model outputs   
     418          CASE ( 'usm_output' )
     419             CALL usm_average_3d_data( 'average', doav(ii) )
    401420
    402421          CASE DEFAULT
Note: See TracChangeset for help on using the changeset viewer.