Changeset 4305 for palm/trunk


Ignore:
Timestamp:
Nov 25, 2019 11:15:40 AM (4 years ago)
Author:
suehring
Message:

urban-surface model: bugfix, consider m_liq in restart runs; remove unused variables

File:
1 edited

Legend:

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

    r4267 r4305  
    2323! Current revisions:
    2424! ------------------
    25 !
    26 !
     25! - Bugfix, include m_liq into restarts
     26! - Remove unused arrays for liquid water and saturation moisture at vertical
     27!   walls
     28!
    2729! Former revisions:
    2830! -----------------
     
    548550                                      m_liq_usm_h_2          !<
    549551
    550     TYPE(surf_type_usm), DIMENSION(:), POINTER  ::        &
    551                                       m_liq_usm_v,        &  !< liquid water reservoir (m), vertical surface elements
    552                                       m_liq_usm_v_p          !< progn. liquid water reservoir (m), vertical surface elements
    553 
    554     TYPE(surf_type_usm), DIMENSION(0:3), TARGET   ::      &
    555                                       m_liq_usm_v_1,      &  !<
    556                                       m_liq_usm_v_2          !<
    557 
    558552    TYPE(surf_type_usm), TARGET ::  tm_liq_usm_h_m      !< liquid water reservoir tendency (m), horizontal surface elements
    559     TYPE(surf_type_usm), DIMENSION(0:3), TARGET ::  tm_liq_usm_v_m      !< liquid water reservoir tendency (m),
    560                                                                         !< vertical surface elements
    561 
    562553!
    563554!-- anthropogenic heat sources
     
    647638    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_green_v, t_green_v_p
    648639    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_1, t_green_v_2
    649     TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: swc_v, swc_v_p
    650     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: swc_v_1, swc_v_2
    651 
    652640!
    653641!-- Surface and material parameters classes (surface_type)
     
    10771065           IF ( .NOT. ALLOCATED( t_green_v_2(l)%t ) )                          &           
    10781066              ALLOCATE ( t_green_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
    1079            IF ( .NOT. ALLOCATED( m_liq_usm_v_1(l)%var_usm_1d ) )               &
    1080               ALLOCATE ( m_liq_usm_v_1(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
    1081            IF ( .NOT. ALLOCATED( m_liq_usm_v_2(l)%var_usm_1d ) )               &
    1082               ALLOCATE ( m_liq_usm_v_2(l)%var_usm_1d(1:surf_usm_v(l)%ns) )
    1083            IF ( .NOT. ALLOCATED( swc_v_1(l)%t ) )                              &           
    1084               ALLOCATE ( swc_v_1(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) )
    1085            IF ( .NOT. ALLOCATED( swc_v_2(l)%t ) )                              &           
    1086               ALLOCATE ( swc_v_2(l)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(l)%ns) ) 
    10871067        ENDDO
    10881068!
     
    10941074        t_surf_window_v => t_surf_window_v_1; t_surf_window_v_p => t_surf_window_v_2
    10951075        t_surf_green_v  => t_surf_green_v_1;  t_surf_green_v_p  => t_surf_green_v_2
    1096         m_liq_usm_v     => m_liq_usm_v_1;     m_liq_usm_v_p     => m_liq_usm_v_2
    1097         swc_v           => swc_v_1;           swc_v_p           => swc_v_2
    10981076
    10991077!
     
    11101088!--    Horizontal surfaces
    11111089       ALLOCATE ( tm_liq_usm_h_m%var_usm_1d(1:surf_usm_h%ns)                   )
    1112 !
    1113 !--    Horizontal surfaces
    1114        DO  l = 0, 3
    1115           ALLOCATE ( tm_liq_usm_v_m(l)%var_usm_1d(1:surf_usm_v(l)%ns)          )
    1116        ENDDO
    1117        
     1090       tm_liq_usm_h_m%var_usm_1d = 0.0_wp
    11181091!
    11191092!--     Set inital values for prognostic quantities
     
    18191792!--                 soil water content for  iwl layer of walls and land
    18201793                    IF ( l == -1 ) THEN
    1821                     DO  m = 1, surf_usm_h%ns
    1822                        surf_usm_h%swc_av(iwl,m) =                           &
    1823                                           surf_usm_h%swc_av(iwl,m) +        &
    1824                                           swc_h(iwl,m)
    1825                     ENDDO
     1794                       DO  m = 1, surf_usm_h%ns
     1795                          surf_usm_h%swc_av(iwl,m) =                           &
     1796                                          surf_usm_h%swc_av(iwl,m) +           &
     1797                                             swc_h(iwl,m)
     1798                       ENDDO
    18261799                    ELSE
    1827                        DO  m = 1, surf_usm_v(l)%ns
    1828                           surf_usm_v(l)%swc_av(iwl,m) =                     &
    1829                                           surf_usm_v(l)%swc_av(iwl,m) +     &
    1830                                           swc_v(l)%t(iwl,m)
    1831                        ENDDO
    18321800                    ENDIF
    18331801
     
    31673135                    ENDDO
    31683136                 ELSE
    3169                     l = idsidx
    3170                     DO  m = 1, surf_usm_v(l)%ns
    3171                        i = surf_usm_v(l)%i(m)
    3172                        j = surf_usm_v(l)%j(m)
    3173                        k = surf_usm_v(l)%k(m)
    3174                        temp_pf(k,j,i) = swc_v(l)%t(iwl,m)
    3175                     ENDDO
     3137
    31763138                 ENDIF
    31773139              ELSE
     
    52845246                     t_window_v(l)%t(k,m) = ( 1.0_wp - c ) * t_surf_window_v(l)%t(m) + c * twin
    52855247                     t_green_v(l)%t(k,m) = t_surf_wall_v(l)%t(m)
    5286                      swc_v(l)%t(k,m) = 0.5_wp
    52875248                  ENDDO
    52885249               ENDDO
     
    53155276
    53165277!
    5317 !--     Adjust radiative fluxes for urban surface at model start
    5318         !CALL radiation_interaction
    5319 !--     TODO: interaction should be called once before first output,
    5320 !--     that is not yet possible.
    5321        
    5322         m_liq_usm_h_p     = m_liq_usm_h
    5323         m_liq_usm_v_p     = m_liq_usm_v
     5278!--    Set initial values for prognostic soil quantities
     5279       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
     5280          m_liq_usm_h%var_usm_1d  = 0.0_wp
     5281       ENDIF
     5282       m_liq_usm_h_p     = m_liq_usm_h
    53245283!
    53255284!--    Set initial values for prognostic quantities
    53265285!--    Horizontal surfaces
    5327        tm_liq_usm_h_m%var_usm_1d  = 0.0_wp
    5328        surf_usm_h%c_liq = 0.0_wp
    5329 
     5286       surf_usm_h%c_liq     = 0.0_wp
    53305287       surf_usm_h%qsws_liq  = 0.0_wp
    53315288       surf_usm_h%qsws_veg  = 0.0_wp
     
    53345291!--    Do the same for vertical surfaces
    53355292       DO  l = 0, 3
    5336           tm_liq_usm_v_m(l)%var_usm_1d  = 0.0_wp
    5337           surf_usm_v(l)%c_liq = 0.0_wp
    5338 
     5293          surf_usm_v(l)%c_liq     = 0.0_wp
    53395294          surf_usm_v(l)%qsws_liq  = 0.0_wp
    53405295          surf_usm_v(l)%qsws_veg  = 0.0_wp
    53415296       ENDDO
    53425297
    5343 !
    5344 !--    Set initial values for prognostic soil quantities
    5345        IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
    5346           m_liq_usm_h%var_usm_1d  = 0.0_wp
    5347 
    5348           DO  l = 0, 3
    5349              m_liq_usm_v(l)%var_usm_1d  = 0.0_wp
    5350           ENDDO
    5351        ENDIF
     5298
    53525299
    53535300        CALL cpu_log( log_point_s(78), 'usm_init', 'stop' )
     
    63596306       
    63606307       INTEGER(iwp)       ::  ns_v_on_file_usm(0:3)  !< number of vertical surface elements (urban type) on file
    6361        
     6308!
     6309!--    Note, the save attribute in the following array declaration is necessary,
     6310!--    in order to keep the number of urban surface elements on file during
     6311!--    rrd_local calls.
    63626312       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  start_index_on_file
    63636313       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  end_index_on_file
    63646314
    63656315       LOGICAL, INTENT(OUT)  ::  found
    6366 !!!    suehring: Why the SAVE attribute?       
    6367        REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_wall_h
    6368        REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_window_h
    6369        REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_green_h
    6370        REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE   ::  tmp_surf_waste_h
     6316! MS: Why are there individual temporary arrays that all have the same size?
     6317       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  tmp_surf_wall_h
     6318       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  tmp_surf_window_h
     6319       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  tmp_surf_green_h
     6320       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  tmp_surf_mliq_h
     6321       REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  tmp_surf_waste_h
    63716322       
    63726323       REAL(wp), DIMENSION(:,:), ALLOCATABLE, SAVE ::  tmp_wall_h
     
    63876338
    63886339
    6389           SELECT CASE ( restart_string(1:length) )
    6390 
    6391              CASE ( 'ns_h_on_file_usm')
    6392                 IF ( k == 1 )  THEN
    6393                    READ ( 13 ) ns_h_on_file_usm
     6340       SELECT CASE ( restart_string(1:length) )
     6341
     6342          CASE ( 'ns_h_on_file_usm')
     6343             IF ( k == 1 )  THEN
     6344                READ ( 13 ) ns_h_on_file_usm
     6345             
     6346                IF ( ALLOCATED( tmp_surf_wall_h ) ) DEALLOCATE( tmp_surf_wall_h )
     6347                IF ( ALLOCATED( tmp_wall_h ) ) DEALLOCATE( tmp_wall_h )
     6348                IF ( ALLOCATED( tmp_surf_window_h ) )                       &
     6349                   DEALLOCATE( tmp_surf_window_h )
     6350                IF ( ALLOCATED( tmp_window_h) ) DEALLOCATE( tmp_window_h )
     6351                IF ( ALLOCATED( tmp_surf_green_h) )                         &
     6352                   DEALLOCATE( tmp_surf_green_h )
     6353                IF ( ALLOCATED( tmp_green_h) ) DEALLOCATE( tmp_green_h )
     6354                IF ( ALLOCATED( tmp_surf_mliq_h) )                         &
     6355                   DEALLOCATE( tmp_surf_mliq_h )
     6356                IF ( ALLOCATED( tmp_surf_waste_h) )                         &
     6357                   DEALLOCATE( tmp_surf_waste_h )
     6358 
     6359!
     6360!--             Allocate temporary arrays for reading data on file. Note,
     6361!--             the size of allocated surface elements do not necessarily
     6362!--             need  to match the size of present surface elements on
     6363!--             current processor, as the number of processors between
     6364!--             restarts can change.
     6365                ALLOCATE( tmp_surf_wall_h(1:ns_h_on_file_usm) )
     6366                ALLOCATE( tmp_wall_h(nzb_wall:nzt_wall+1,                   &
     6367                                     1:ns_h_on_file_usm) )
     6368                ALLOCATE( tmp_surf_window_h(1:ns_h_on_file_usm) )
     6369                ALLOCATE( tmp_window_h(nzb_wall:nzt_wall+1,                 &
     6370                                       1:ns_h_on_file_usm) )
     6371                ALLOCATE( tmp_surf_green_h(1:ns_h_on_file_usm) )
     6372                ALLOCATE( tmp_green_h(nzb_wall:nzt_wall+1,                  &
     6373                                      1:ns_h_on_file_usm) )
     6374                ALLOCATE( tmp_surf_mliq_h(1:ns_h_on_file_usm) )
     6375                ALLOCATE( tmp_surf_waste_h(1:ns_h_on_file_usm) )
     6376
     6377             ENDIF
     6378
     6379          CASE ( 'ns_v_on_file_usm')
     6380             IF ( k == 1 )  THEN
     6381                READ ( 13 ) ns_v_on_file_usm
     6382
     6383                DO  l = 0, 3
     6384                   IF ( ALLOCATED( tmp_surf_wall_v(l)%t ) )                 &
     6385                      DEALLOCATE( tmp_surf_wall_v(l)%t )
     6386                   IF ( ALLOCATED( tmp_wall_v(l)%t ) )                      &
     6387                      DEALLOCATE( tmp_wall_v(l)%t )
     6388                   IF ( ALLOCATED( tmp_surf_window_v(l)%t ) )               &
     6389                      DEALLOCATE( tmp_surf_window_v(l)%t )
     6390                   IF ( ALLOCATED( tmp_window_v(l)%t ) )                    &
     6391                      DEALLOCATE( tmp_window_v(l)%t )
     6392                   IF ( ALLOCATED( tmp_surf_green_v(l)%t ) )                &
     6393                      DEALLOCATE( tmp_surf_green_v(l)%t )
     6394                   IF ( ALLOCATED( tmp_green_v(l)%t ) )                     &
     6395                      DEALLOCATE( tmp_green_v(l)%t )
     6396                   IF ( ALLOCATED( tmp_surf_waste_v(l)%t ) )                &
     6397                      DEALLOCATE( tmp_surf_waste_v(l)%t )
     6398                ENDDO
     6399
     6400!
     6401!--             Allocate temporary arrays for reading data on file. Note,
     6402!--             the size of allocated surface elements do not necessarily
     6403!--             need to match the size of present surface elements on
     6404!--             current processor, as the number of processors between
     6405!--             restarts can change.
     6406                DO  l = 0, 3
     6407                   ALLOCATE( tmp_surf_wall_v(l)%t(1:ns_v_on_file_usm(l)) )
     6408                   ALLOCATE( tmp_wall_v(l)%t(nzb_wall:nzt_wall+1,           &
     6409                                             1:ns_v_on_file_usm(l) ) )
     6410                   ALLOCATE( tmp_surf_window_v(l)%t(1:ns_v_on_file_usm(l)) )
     6411                   ALLOCATE( tmp_window_v(l)%t(nzb_wall:nzt_wall+1,         &
     6412                                               1:ns_v_on_file_usm(l) ) )
     6413                   ALLOCATE( tmp_surf_green_v(l)%t(1:ns_v_on_file_usm(l)) )
     6414                   ALLOCATE( tmp_green_v(l)%t(nzb_wall:nzt_wall+1,          &
     6415                                              1:ns_v_on_file_usm(l) ) )
     6416                   ALLOCATE( tmp_surf_waste_v(l)%t(1:ns_v_on_file_usm(l)) )
     6417                ENDDO
     6418
     6419             ENDIF   
     6420       
     6421          CASE ( 'usm_start_index_h', 'usm_start_index_v'  )   
     6422             IF ( k == 1 )  THEN
     6423
     6424                IF ( ALLOCATED( start_index_on_file ) )                     &
     6425                   DEALLOCATE( start_index_on_file )
     6426
     6427                ALLOCATE ( start_index_on_file(nys_on_file:nyn_on_file,     &
     6428                                               nxl_on_file:nxr_on_file) )
     6429
     6430                READ ( 13 )  start_index_on_file
     6431
     6432             ENDIF
     6433             
     6434          CASE ( 'usm_end_index_h', 'usm_end_index_v' )   
     6435             IF ( k == 1 )  THEN
     6436
     6437                IF ( ALLOCATED( end_index_on_file ) )                       &
     6438                   DEALLOCATE( end_index_on_file )
     6439
     6440                ALLOCATE ( end_index_on_file(nys_on_file:nyn_on_file,       &
     6441                                             nxl_on_file:nxr_on_file) )
     6442
     6443                READ ( 13 )  end_index_on_file
     6444
     6445             ENDIF
     6446       
     6447          CASE ( 't_surf_wall_h' )
     6448             IF ( k == 1 )  THEN
     6449                IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )                  &
     6450                   ALLOCATE( t_surf_wall_h_1(1:surf_usm_h%ns) )
     6451                READ ( 13 )  tmp_surf_wall_h
     6452             ENDIF             
     6453             CALL surface_restore_elements(                                 &
     6454                                     t_surf_wall_h_1, tmp_surf_wall_h,      &
     6455                                     surf_usm_h%start_index,                &
     6456                                     start_index_on_file,                   &
     6457                                     end_index_on_file,                     &
     6458                                     nxlc, nysc,                            &
     6459                                     nxlf, nxrf, nysf, nynf,                &
     6460                                     nys_on_file, nyn_on_file,              &
     6461                                     nxl_on_file,nxr_on_file )
     6462
     6463          CASE ( 't_surf_wall_v(0)' )
     6464             IF ( k == 1 )  THEN
     6465                IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%t ) )             &
     6466                   ALLOCATE( t_surf_wall_v_1(0)%t(1:surf_usm_v(0)%ns) )
     6467                READ ( 13 )  tmp_surf_wall_v(0)%t
     6468             ENDIF
     6469             CALL surface_restore_elements(                                 &
     6470                                     t_surf_wall_v_1(0)%t, tmp_surf_wall_v(0)%t,      &
     6471                                     surf_usm_v(0)%start_index,             &
     6472                                     start_index_on_file,                   &
     6473                                     end_index_on_file,                     &
     6474                                     nxlc, nysc,                            &
     6475                                     nxlf, nxrf, nysf, nynf,                &
     6476                                     nys_on_file, nyn_on_file,              &
     6477                                     nxl_on_file,nxr_on_file )
     6478                   
     6479          CASE ( 't_surf_wall_v(1)' )
     6480             IF ( k == 1 )  THEN
     6481                IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%t ) )             &
     6482                   ALLOCATE( t_surf_wall_v_1(1)%t(1:surf_usm_v(1)%ns) )
     6483                READ ( 13 )  tmp_surf_wall_v(1)%t
     6484             ENDIF
     6485             CALL surface_restore_elements(                                 &
     6486                                     t_surf_wall_v_1(1)%t, tmp_surf_wall_v(1)%t,      &
     6487                                     surf_usm_v(1)%start_index,             &
     6488                                     start_index_on_file,                   &
     6489                                     end_index_on_file,                     &
     6490                                     nxlc, nysc,                            &
     6491                                     nxlf, nxrf, nysf, nynf,                &
     6492                                     nys_on_file, nyn_on_file,              &
     6493                                     nxl_on_file,nxr_on_file )
     6494
     6495          CASE ( 't_surf_wall_v(2)' )
     6496             IF ( k == 1 )  THEN
     6497                IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%t ) )             &
     6498                   ALLOCATE( t_surf_wall_v_1(2)%t(1:surf_usm_v(2)%ns) )
     6499                READ ( 13 )  tmp_surf_wall_v(2)%t
     6500             ENDIF
     6501             CALL surface_restore_elements(                                 &
     6502                                     t_surf_wall_v_1(2)%t, tmp_surf_wall_v(2)%t,      &
     6503                                     surf_usm_v(2)%start_index,             & 
     6504                                     start_index_on_file,                   &
     6505                                     end_index_on_file,                     &
     6506                                     nxlc, nysc,                            &
     6507                                     nxlf, nxrf, nysf, nynf,                &
     6508                                     nys_on_file, nyn_on_file,              &
     6509                                     nxl_on_file,nxr_on_file )
     6510                   
     6511          CASE ( 't_surf_wall_v(3)' )
     6512             IF ( k == 1 )  THEN
     6513                IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%t ) )             &
     6514                   ALLOCATE( t_surf_wall_v_1(3)%t(1:surf_usm_v(3)%ns) )
     6515                READ ( 13 )  tmp_surf_wall_v(3)%t
     6516             ENDIF
     6517             CALL surface_restore_elements(                                 &
     6518                                     t_surf_wall_v_1(3)%t, tmp_surf_wall_v(3)%t,      &
     6519                                     surf_usm_v(3)%start_index,             &
     6520                                     start_index_on_file,                   &
     6521                                     end_index_on_file,                     &
     6522                                     nxlc, nysc,                            &
     6523                                     nxlf, nxrf, nysf, nynf,                &
     6524                                     nys_on_file, nyn_on_file,              &
     6525                                     nxl_on_file,nxr_on_file )
     6526
     6527          CASE ( 't_surf_green_h' )
     6528             IF ( k == 1 )  THEN
     6529                IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )                 &
     6530                   ALLOCATE( t_surf_green_h_1(1:surf_usm_h%ns) )
     6531                READ ( 13 )  tmp_surf_green_h
     6532             ENDIF
     6533             CALL surface_restore_elements(                                 &
     6534                                     t_surf_green_h_1, tmp_surf_green_h,    &
     6535                                     surf_usm_h%start_index,                & 
     6536                                     start_index_on_file,                   &
     6537                                     end_index_on_file,                     &
     6538                                     nxlc, nysc,                            &
     6539                                     nxlf, nxrf, nysf, nynf,                &
     6540                                     nys_on_file, nyn_on_file,              &
     6541                                     nxl_on_file,nxr_on_file )
     6542
     6543          CASE ( 't_surf_green_v(0)' )
     6544             IF ( k == 1 )  THEN
     6545                IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%t ) )            &
     6546                   ALLOCATE( t_surf_green_v_1(0)%t(1:surf_usm_v(0)%ns) )
     6547                READ ( 13 )  tmp_surf_green_v(0)%t
     6548             ENDIF
     6549             CALL surface_restore_elements(                                 &
     6550                                     t_surf_green_v_1(0)%t,                 &
     6551                                     tmp_surf_green_v(0)%t,                 &
     6552                                     surf_usm_v(0)%start_index,             &
     6553                                     start_index_on_file,                   &
     6554                                     end_index_on_file,                     &
     6555                                     nxlc, nysc,                            &
     6556                                     nxlf, nxrf, nysf, nynf,                &
     6557                                     nys_on_file, nyn_on_file,              &
     6558                                     nxl_on_file,nxr_on_file )
    63946559               
    6395                    IF ( ALLOCATED( tmp_surf_wall_h ) ) DEALLOCATE( tmp_surf_wall_h )
    6396                    IF ( ALLOCATED( tmp_wall_h ) ) DEALLOCATE( tmp_wall_h )
    6397                    IF ( ALLOCATED( tmp_surf_window_h ) )                       &
    6398                       DEALLOCATE( tmp_surf_window_h )
    6399                    IF ( ALLOCATED( tmp_window_h) ) DEALLOCATE( tmp_window_h )
    6400                    IF ( ALLOCATED( tmp_surf_green_h) )                         &
    6401                       DEALLOCATE( tmp_surf_green_h )
    6402                    IF ( ALLOCATED( tmp_green_h) ) DEALLOCATE( tmp_green_h )
    6403                    IF ( ALLOCATED( tmp_surf_waste_h) )                         &
    6404                       DEALLOCATE( tmp_surf_waste_h )
    6405  
    6406 !
    6407 !--                Allocate temporary arrays for reading data on file. Note,
    6408 !--                the size of allocated surface elements do not necessarily
    6409 !--                need  to match the size of present surface elements on
    6410 !--                current processor, as the number of processors between
    6411 !--                restarts can change.
    6412                    ALLOCATE( tmp_surf_wall_h(1:ns_h_on_file_usm) )
    6413                    ALLOCATE( tmp_wall_h(nzb_wall:nzt_wall+1,                   &
    6414                                         1:ns_h_on_file_usm) )
    6415                    ALLOCATE( tmp_surf_window_h(1:ns_h_on_file_usm) )
    6416                    ALLOCATE( tmp_window_h(nzb_wall:nzt_wall+1,                 &
    6417                                           1:ns_h_on_file_usm) )
    6418                    ALLOCATE( tmp_surf_green_h(1:ns_h_on_file_usm) )
    6419                    ALLOCATE( tmp_green_h(nzb_wall:nzt_wall+1,                  &
    6420                                          1:ns_h_on_file_usm) )
    6421                    ALLOCATE( tmp_surf_waste_h(1:ns_h_on_file_usm) )
    6422 
    6423                 ENDIF
    6424 
    6425              CASE ( 'ns_v_on_file_usm')
    6426                 IF ( k == 1 )  THEN
    6427                    READ ( 13 ) ns_v_on_file_usm
    6428 
    6429                    DO  l = 0, 3
    6430                       IF ( ALLOCATED( tmp_surf_wall_v(l)%t ) )                 &
    6431                          DEALLOCATE( tmp_surf_wall_v(l)%t )
    6432                       IF ( ALLOCATED( tmp_wall_v(l)%t ) )                      &
    6433                          DEALLOCATE( tmp_wall_v(l)%t )
    6434                       IF ( ALLOCATED( tmp_surf_window_v(l)%t ) )               &
    6435                          DEALLOCATE( tmp_surf_window_v(l)%t )
    6436                       IF ( ALLOCATED( tmp_window_v(l)%t ) )                    &
    6437                          DEALLOCATE( tmp_window_v(l)%t )
    6438                       IF ( ALLOCATED( tmp_surf_green_v(l)%t ) )                &
    6439                          DEALLOCATE( tmp_surf_green_v(l)%t )
    6440                       IF ( ALLOCATED( tmp_green_v(l)%t ) )                     &
    6441                          DEALLOCATE( tmp_green_v(l)%t )
    6442                       IF ( ALLOCATED( tmp_surf_waste_v(l)%t ) )                &
    6443                          DEALLOCATE( tmp_surf_waste_v(l)%t )
    6444                    ENDDO
    6445 
    6446 !
    6447 !--                Allocate temporary arrays for reading data on file. Note,
    6448 !--                the size of allocated surface elements do not necessarily
    6449 !--                need to match the size of present surface elements on
    6450 !--                current processor, as the number of processors between
    6451 !--                restarts can change.
    6452                    DO  l = 0, 3
    6453                       ALLOCATE( tmp_surf_wall_v(l)%t(1:ns_v_on_file_usm(l)) )
    6454                       ALLOCATE( tmp_wall_v(l)%t(nzb_wall:nzt_wall+1,           &
    6455                                                 1:ns_v_on_file_usm(l) ) )
    6456                       ALLOCATE( tmp_surf_window_v(l)%t(1:ns_v_on_file_usm(l)) )
    6457                       ALLOCATE( tmp_window_v(l)%t(nzb_wall:nzt_wall+1,         &
    6458                                                   1:ns_v_on_file_usm(l) ) )
    6459                       ALLOCATE( tmp_surf_green_v(l)%t(1:ns_v_on_file_usm(l)) )
    6460                       ALLOCATE( tmp_green_v(l)%t(nzb_wall:nzt_wall+1,          &
    6461                                                  1:ns_v_on_file_usm(l) ) )
    6462                       ALLOCATE( tmp_surf_waste_v(l)%t(1:ns_v_on_file_usm(l)) )
    6463                    ENDDO
    6464 
    6465                 ENDIF   
    6466          
    6467              CASE ( 'usm_start_index_h', 'usm_start_index_v'  )   
    6468                 IF ( k == 1 )  THEN
    6469 
    6470                    IF ( ALLOCATED( start_index_on_file ) )                     &
    6471                       DEALLOCATE( start_index_on_file )
    6472 
    6473                    ALLOCATE ( start_index_on_file(nys_on_file:nyn_on_file,     &
    6474                                                   nxl_on_file:nxr_on_file) )
    6475 
    6476                    READ ( 13 )  start_index_on_file
    6477 
    6478                 ENDIF
     6560          CASE ( 't_surf_green_v(1)' )
     6561             IF ( k == 1 )  THEN
     6562                IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%t ) )            &
     6563                   ALLOCATE( t_surf_green_v_1(1)%t(1:surf_usm_v(1)%ns) )
     6564                READ ( 13 )  tmp_surf_green_v(1)%t
     6565             ENDIF
     6566             CALL surface_restore_elements(                                 &
     6567                                     t_surf_green_v_1(1)%t,                 &
     6568                                     tmp_surf_green_v(1)%t,                 &
     6569                                     surf_usm_v(1)%start_index,             & 
     6570                                     start_index_on_file,                   &
     6571                                     end_index_on_file,                     &
     6572                                     nxlc, nysc,                            &
     6573                                     nxlf, nxrf, nysf, nynf,                &
     6574                                     nys_on_file, nyn_on_file,              &
     6575                                     nxl_on_file,nxr_on_file )
     6576
     6577          CASE ( 't_surf_green_v(2)' )
     6578             IF ( k == 1 )  THEN
     6579                IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%t ) )            &
     6580                   ALLOCATE( t_surf_green_v_1(2)%t(1:surf_usm_v(2)%ns) )
     6581                READ ( 13 )  tmp_surf_green_v(2)%t
     6582             ENDIF
     6583             CALL surface_restore_elements(                                 &
     6584                                     t_surf_green_v_1(2)%t,                 &
     6585                                     tmp_surf_green_v(2)%t,                 &
     6586                                     surf_usm_v(2)%start_index,             & 
     6587                                     start_index_on_file,                   &
     6588                                     end_index_on_file,                     &
     6589                                     nxlc, nysc,                            &
     6590                                     nxlf, nxrf, nysf, nynf,                &
     6591                                     nys_on_file, nyn_on_file,              &
     6592                                     nxl_on_file,nxr_on_file )
    64796593               
    6480              CASE ( 'usm_end_index_h', 'usm_end_index_v' )   
    6481                 IF ( k == 1 )  THEN
    6482 
    6483                    IF ( ALLOCATED( end_index_on_file ) )                       &
    6484                       DEALLOCATE( end_index_on_file )
    6485 
    6486                    ALLOCATE ( end_index_on_file(nys_on_file:nyn_on_file,       &
    6487                                                 nxl_on_file:nxr_on_file) )
    6488 
    6489                    READ ( 13 )  end_index_on_file
    6490 
    6491                 ENDIF
    6492          
    6493              CASE ( 't_surf_wall_h' )
    6494                 IF ( k == 1 )  THEN
    6495                    IF ( .NOT.  ALLOCATED( t_surf_wall_h_1 ) )                  &
    6496                       ALLOCATE( t_surf_wall_h_1(1:surf_usm_h%ns) )
    6497                    READ ( 13 )  tmp_surf_wall_h
    6498                 ENDIF             
    6499                 CALL surface_restore_elements(                                 &
    6500                                         t_surf_wall_h_1, tmp_surf_wall_h,      &
    6501                                         surf_usm_h%start_index,                &
    6502                                         start_index_on_file,                   &
    6503                                         end_index_on_file,                     &
    6504                                         nxlc, nysc,                            &
    6505                                         nxlf, nxrf, nysf, nynf,                &
    6506                                         nys_on_file, nyn_on_file,              &
    6507                                         nxl_on_file,nxr_on_file )
    6508 
    6509              CASE ( 't_surf_wall_v(0)' )
    6510                 IF ( k == 1 )  THEN
    6511                    IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%t ) )             &
    6512                       ALLOCATE( t_surf_wall_v_1(0)%t(1:surf_usm_v(0)%ns) )
    6513                    READ ( 13 )  tmp_surf_wall_v(0)%t
    6514                 ENDIF
    6515                 CALL surface_restore_elements(                                 &
    6516                                         t_surf_wall_v_1(0)%t, tmp_surf_wall_v(0)%t,      &
    6517                                         surf_usm_v(0)%start_index,             &
    6518                                         start_index_on_file,                   &
    6519                                         end_index_on_file,                     &
    6520                                         nxlc, nysc,                            &
    6521                                         nxlf, nxrf, nysf, nynf,                &
    6522                                         nys_on_file, nyn_on_file,              &
    6523                                         nxl_on_file,nxr_on_file )
    6524                      
    6525              CASE ( 't_surf_wall_v(1)' )
    6526                 IF ( k == 1 )  THEN
    6527                    IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%t ) )             &
    6528                       ALLOCATE( t_surf_wall_v_1(1)%t(1:surf_usm_v(1)%ns) )
    6529                    READ ( 13 )  tmp_surf_wall_v(1)%t
    6530                 ENDIF
    6531                 CALL surface_restore_elements(                                 &
    6532                                         t_surf_wall_v_1(1)%t, tmp_surf_wall_v(1)%t,      &
    6533                                         surf_usm_v(1)%start_index,             &
    6534                                         start_index_on_file,                   &
    6535                                         end_index_on_file,                     &
    6536                                         nxlc, nysc,                            &
    6537                                         nxlf, nxrf, nysf, nynf,                &
    6538                                         nys_on_file, nyn_on_file,              &
    6539                                         nxl_on_file,nxr_on_file )
    6540 
    6541              CASE ( 't_surf_wall_v(2)' )
    6542                 IF ( k == 1 )  THEN
    6543                    IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%t ) )             &
    6544                       ALLOCATE( t_surf_wall_v_1(2)%t(1:surf_usm_v(2)%ns) )
    6545                    READ ( 13 )  tmp_surf_wall_v(2)%t
    6546                 ENDIF
    6547                 CALL surface_restore_elements(                                 &
    6548                                         t_surf_wall_v_1(2)%t, tmp_surf_wall_v(2)%t,      &
    6549                                         surf_usm_v(2)%start_index,             & 
    6550                                         start_index_on_file,                   &
    6551                                         end_index_on_file,                     &
    6552                                         nxlc, nysc,                            &
    6553                                         nxlf, nxrf, nysf, nynf,                &
    6554                                         nys_on_file, nyn_on_file,              &
    6555                                         nxl_on_file,nxr_on_file )
    6556                      
    6557              CASE ( 't_surf_wall_v(3)' )
    6558                 IF ( k == 1 )  THEN
    6559                    IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%t ) )             &
    6560                       ALLOCATE( t_surf_wall_v_1(3)%t(1:surf_usm_v(3)%ns) )
    6561                    READ ( 13 )  tmp_surf_wall_v(3)%t
    6562                 ENDIF
    6563                 CALL surface_restore_elements(                                 &
    6564                                         t_surf_wall_v_1(3)%t, tmp_surf_wall_v(3)%t,      &
    6565                                         surf_usm_v(3)%start_index,             &
    6566                                         start_index_on_file,                   &
    6567                                         end_index_on_file,                     &
    6568                                         nxlc, nysc,                            &
    6569                                         nxlf, nxrf, nysf, nynf,                &
    6570                                         nys_on_file, nyn_on_file,              &
    6571                                         nxl_on_file,nxr_on_file )
    6572 
    6573              CASE ( 't_surf_green_h' )
    6574                 IF ( k == 1 )  THEN
    6575                    IF ( .NOT.  ALLOCATED( t_surf_green_h_1 ) )                 &
    6576                       ALLOCATE( t_surf_green_h_1(1:surf_usm_h%ns) )
    6577                    READ ( 13 )  tmp_surf_green_h
    6578                 ENDIF
    6579                 CALL surface_restore_elements(                                 &
    6580                                         t_surf_green_h_1, tmp_surf_green_h,    &
    6581                                         surf_usm_h%start_index,                & 
    6582                                         start_index_on_file,                   &
    6583                                         end_index_on_file,                     &
    6584                                         nxlc, nysc,                            &
    6585                                         nxlf, nxrf, nysf, nynf,                &
    6586                                         nys_on_file, nyn_on_file,              &
    6587                                         nxl_on_file,nxr_on_file )
    6588 
    6589              CASE ( 't_surf_green_v(0)' )
    6590                 IF ( k == 1 )  THEN
    6591                    IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%t ) )            &
    6592                       ALLOCATE( t_surf_green_v_1(0)%t(1:surf_usm_v(0)%ns) )
    6593                    READ ( 13 )  tmp_surf_green_v(0)%t
    6594                 ENDIF
    6595                 CALL surface_restore_elements(                                 &
    6596                                         t_surf_green_v_1(0)%t,                 &
    6597                                         tmp_surf_green_v(0)%t,                 &
    6598                                         surf_usm_v(0)%start_index,             &
    6599                                         start_index_on_file,                   &
    6600                                         end_index_on_file,                     &
    6601                                         nxlc, nysc,                            &
    6602                                         nxlf, nxrf, nysf, nynf,                &
    6603                                         nys_on_file, nyn_on_file,              &
    6604                                         nxl_on_file,nxr_on_file )
     6594          CASE ( 't_surf_green_v(3)' )
     6595             IF ( k == 1 )  THEN
     6596                IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%t ) )            &
     6597                   ALLOCATE( t_surf_green_v_1(3)%t(1:surf_usm_v(3)%ns) )
     6598                READ ( 13 )  tmp_surf_green_v(3)%t
     6599             ENDIF
     6600             CALL surface_restore_elements(                                 &
     6601                                     t_surf_green_v_1(3)%t,                 &
     6602                                     tmp_surf_green_v(3)%t,                 &
     6603                                     surf_usm_v(3)%start_index,             &
     6604                                     start_index_on_file,                   &
     6605                                     end_index_on_file,                     &
     6606                                     nxlc, nysc,                            &
     6607                                     nxlf, nxrf, nysf, nynf,                &
     6608                                     nys_on_file, nyn_on_file,              &
     6609                                     nxl_on_file,nxr_on_file )
     6610
     6611          CASE ( 't_surf_window_h' )
     6612             IF ( k == 1 )  THEN
     6613                IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )                &
     6614                   ALLOCATE( t_surf_window_h_1(1:surf_usm_h%ns) )
     6615                READ ( 13 )  tmp_surf_window_h
     6616             ENDIF
     6617             CALL surface_restore_elements(                                 &
     6618                                     t_surf_window_h_1,                     &
     6619                                     tmp_surf_window_h,                     &
     6620                                     surf_usm_h%start_index,                &
     6621                                     start_index_on_file,                   &
     6622                                     end_index_on_file,                     &
     6623                                     nxlc, nysc,                            &
     6624                                     nxlf, nxrf, nysf, nynf,                &
     6625                                     nys_on_file, nyn_on_file,              &
     6626                                     nxl_on_file,nxr_on_file )
     6627
     6628          CASE ( 't_surf_window_v(0)' )
     6629             IF ( k == 1 )  THEN
     6630                IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%t ) )           &
     6631                   ALLOCATE( t_surf_window_v_1(0)%t(1:surf_usm_v(0)%ns) )
     6632                READ ( 13 )  tmp_surf_window_v(0)%t
     6633             ENDIF
     6634             CALL surface_restore_elements(                                 &
     6635                                     t_surf_window_v_1(0)%t,                &
     6636                                     tmp_surf_window_v(0)%t,                &
     6637                                     surf_usm_v(0)%start_index,             &
     6638                                     start_index_on_file,                   &
     6639                                     end_index_on_file,                     &
     6640                                     nxlc, nysc,                            &
     6641                                     nxlf, nxrf, nysf, nynf,                &
     6642                                     nys_on_file, nyn_on_file,              &
     6643                                     nxl_on_file,nxr_on_file )
     6644               
     6645          CASE ( 't_surf_window_v(1)' )
     6646             IF ( k == 1 )  THEN
     6647                IF ( .NOT.  ALLOCATED( t_surf_window_v_1(1)%t ) )           &
     6648                   ALLOCATE( t_surf_window_v_1(1)%t(1:surf_usm_v(1)%ns) )
     6649                READ ( 13 )  tmp_surf_window_v(1)%t
     6650             ENDIF
     6651             CALL surface_restore_elements(                                 &
     6652                                     t_surf_window_v_1(1)%t,                &
     6653                                     tmp_surf_window_v(1)%t,                &
     6654                                     surf_usm_v(1)%start_index,             &
     6655                                     start_index_on_file,                   &
     6656                                     end_index_on_file,                     &
     6657                                     nxlc, nysc,                            &
     6658                                     nxlf, nxrf, nysf, nynf,                &
     6659                                     nys_on_file, nyn_on_file,              &
     6660                                     nxl_on_file,nxr_on_file )
     6661
     6662          CASE ( 't_surf_window_v(2)' )
     6663             IF ( k == 1 )  THEN
     6664                IF ( .NOT.  ALLOCATED( t_surf_window_v_1(2)%t ) )           &
     6665                   ALLOCATE( t_surf_window_v_1(2)%t(1:surf_usm_v(2)%ns) )
     6666                READ ( 13 )  tmp_surf_window_v(2)%t
     6667             ENDIF
     6668             CALL surface_restore_elements(                                 &
     6669                                     t_surf_window_v_1(2)%t,                &
     6670                                     tmp_surf_window_v(2)%t,                &
     6671                                     surf_usm_v(2)%start_index,             &
     6672                                     start_index_on_file,                   &
     6673                                     end_index_on_file,                     &
     6674                                     nxlc, nysc,                            &
     6675                                     nxlf, nxrf, nysf, nynf,                &
     6676                                     nys_on_file, nyn_on_file,              &
     6677                                     nxl_on_file,nxr_on_file )
     6678               
     6679          CASE ( 't_surf_window_v(3)' )
     6680             IF ( k == 1 )  THEN
     6681                IF ( .NOT.  ALLOCATED( t_surf_window_v_1(3)%t ) )           &
     6682                   ALLOCATE( t_surf_window_v_1(3)%t(1:surf_usm_v(3)%ns) )
     6683                READ ( 13 )  tmp_surf_window_v(3)%t
     6684             ENDIF
     6685             CALL surface_restore_elements(                                 &
     6686                                     t_surf_window_v_1(3)%t,                & 
     6687                                     tmp_surf_window_v(3)%t,                &
     6688                                     surf_usm_v(3)%start_index,             &
     6689                                     start_index_on_file,                   &
     6690                                     end_index_on_file,                     &
     6691                                     nxlc, nysc,                            &
     6692                                     nxlf, nxrf, nysf, nynf,                &
     6693                                     nys_on_file, nyn_on_file,              &
     6694                                     nxl_on_file,nxr_on_file )
     6695
     6696          CASE ( 'm_liq_usm_h' )
     6697             IF ( k == 1 )  THEN
     6698                IF ( .NOT.  ALLOCATED( m_liq_usm_h%var_usm_1d ) )           &
     6699                   ALLOCATE( m_liq_usm_h%var_usm_1d(1:surf_usm_h%ns) )
     6700                READ ( 13 )  tmp_surf_mliq_h
     6701             ENDIF             
     6702             CALL surface_restore_elements(                                 &
     6703                                     m_liq_usm_h%var_usm_1d,                &
     6704                                     tmp_surf_mliq_h,                       &
     6705                                     surf_usm_h%start_index,                &
     6706                                     start_index_on_file,                   &
     6707                                     end_index_on_file,                     &
     6708                                     nxlc, nysc,                            &
     6709                                     nxlf, nxrf, nysf, nynf,                &
     6710                                     nys_on_file, nyn_on_file,              &
     6711                                     nxl_on_file,nxr_on_file )
     6712
     6713          CASE ( 'waste_heat_h' )
     6714             IF ( k == 1 )  THEN
     6715                IF ( .NOT.  ALLOCATED( surf_usm_h%waste_heat ) )            &
     6716                   ALLOCATE( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
     6717                READ ( 13 )  tmp_surf_waste_h
     6718             ENDIF             
     6719             CALL surface_restore_elements(                                 &
     6720                                     surf_usm_h%waste_heat,                 &
     6721                                     tmp_surf_waste_h,                      &
     6722                                     surf_usm_h%start_index,                &
     6723                                     start_index_on_file,                   &
     6724                                     end_index_on_file,                     &
     6725                                     nxlc, nysc,                            &
     6726                                     nxlf, nxrf, nysf, nynf,                &
     6727                                     nys_on_file, nyn_on_file,              &
     6728                                     nxl_on_file,nxr_on_file )
     6729
     6730          CASE ( 'waste_heat_v(0)' )
     6731             IF ( k == 1 )  THEN
     6732                IF ( .NOT.  ALLOCATED( surf_usm_v(0)%waste_heat ) )         &
     6733                   ALLOCATE( surf_usm_v(0)%waste_heat(1:surf_usm_v(0)%ns) )
     6734                READ ( 13 )  tmp_surf_waste_v(0)%t
     6735             ENDIF
     6736             CALL surface_restore_elements(                                 &
     6737                                     surf_usm_v(0)%waste_heat,              &
     6738                                     tmp_surf_waste_v(0)%t,                 &
     6739                                     surf_usm_v(0)%start_index,             &
     6740                                     start_index_on_file,                   &
     6741                                     end_index_on_file,                     &
     6742                                     nxlc, nysc,                            &
     6743                                     nxlf, nxrf, nysf, nynf,                &
     6744                                     nys_on_file, nyn_on_file,              &
     6745                                     nxl_on_file,nxr_on_file )
    66056746                   
    6606              CASE ( 't_surf_green_v(1)' )
    6607                 IF ( k == 1 )  THEN
    6608                    IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%t ) )            &
    6609                       ALLOCATE( t_surf_green_v_1(1)%t(1:surf_usm_v(1)%ns) )
    6610                    READ ( 13 )  tmp_surf_green_v(1)%t
    6611                 ENDIF
    6612                 CALL surface_restore_elements(                                 &
    6613                                         t_surf_green_v_1(1)%t,                 &
    6614                                         tmp_surf_green_v(1)%t,                 &
    6615                                         surf_usm_v(1)%start_index,             &
    6616                                         start_index_on_file,                   &
    6617                                         end_index_on_file,                     &
    6618                                         nxlc, nysc,                            &
    6619                                         nxlf, nxrf, nysf, nynf,                &
    6620                                         nys_on_file, nyn_on_file,              &
    6621                                         nxl_on_file,nxr_on_file )
    6622 
    6623              CASE ( 't_surf_green_v(2)' )
    6624                 IF ( k == 1 )  THEN
    6625                    IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%t ) )            &
    6626                       ALLOCATE( t_surf_green_v_1(2)%t(1:surf_usm_v(2)%ns) )
    6627                    READ ( 13 )  tmp_surf_green_v(2)%t
    6628                 ENDIF
    6629                 CALL surface_restore_elements(                                 &
    6630                                         t_surf_green_v_1(2)%t,                 &
    6631                                         tmp_surf_green_v(2)%t,                 &
    6632                                         surf_usm_v(2)%start_index,             &
    6633                                         start_index_on_file,                   &
    6634                                         end_index_on_file,                     &
    6635                                         nxlc, nysc,                            &
    6636                                         nxlf, nxrf, nysf, nynf,                &
    6637                                         nys_on_file, nyn_on_file,              &
    6638                                         nxl_on_file,nxr_on_file )
     6747          CASE ( 'waste_heat_v(1)' )
     6748             IF ( k == 1 )  THEN
     6749                IF ( .NOT.  ALLOCATED( surf_usm_v(1)%waste_heat ) )         &
     6750                   ALLOCATE( surf_usm_v(1)%waste_heat(1:surf_usm_v(1)%ns) )
     6751                READ ( 13 )  tmp_surf_waste_v(1)%t
     6752             ENDIF
     6753             CALL surface_restore_elements(                                 &
     6754                                     surf_usm_v(1)%waste_heat,              &
     6755                                     tmp_surf_waste_v(1)%t,                 &
     6756                                     surf_usm_v(1)%start_index,             &
     6757                                     start_index_on_file,                   &
     6758                                     end_index_on_file,                     &
     6759                                     nxlc, nysc,                            &
     6760                                     nxlf, nxrf, nysf, nynf,                &
     6761                                     nys_on_file, nyn_on_file,              &
     6762                                     nxl_on_file,nxr_on_file )
     6763
     6764          CASE ( 'waste_heat_v(2)' )
     6765             IF ( k == 1 )  THEN
     6766                IF ( .NOT.  ALLOCATED( surf_usm_v(2)%waste_heat ) )         &
     6767                   ALLOCATE( surf_usm_v(2)%waste_heat(1:surf_usm_v(2)%ns) )
     6768                READ ( 13 )  tmp_surf_waste_v(2)%t
     6769             ENDIF
     6770             CALL surface_restore_elements(                                 &
     6771                                     surf_usm_v(2)%waste_heat,              &
     6772                                     tmp_surf_waste_v(2)%t,                 &
     6773                                     surf_usm_v(2)%start_index,             &
     6774                                     start_index_on_file,                   &
     6775                                     end_index_on_file,                     &
     6776                                     nxlc, nysc,                            &
     6777                                     nxlf, nxrf, nysf, nynf,                &
     6778                                     nys_on_file, nyn_on_file,              &
     6779                                     nxl_on_file,nxr_on_file )
    66396780                   
    6640              CASE ( 't_surf_green_v(3)' )
    6641                 IF ( k == 1 )  THEN
    6642                    IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%t ) )            &
    6643                       ALLOCATE( t_surf_green_v_1(3)%t(1:surf_usm_v(3)%ns) )
    6644                    READ ( 13 )  tmp_surf_green_v(3)%t
    6645                 ENDIF
    6646                 CALL surface_restore_elements(                                 &
    6647                                         t_surf_green_v_1(3)%t,                 &
    6648                                         tmp_surf_green_v(3)%t,                 &
    6649                                         surf_usm_v(3)%start_index,             &
    6650                                         start_index_on_file,                   &
    6651                                         end_index_on_file,                     &
    6652                                         nxlc, nysc,                            &
    6653                                         nxlf, nxrf, nysf, nynf,                &
    6654                                         nys_on_file, nyn_on_file,              &
    6655                                         nxl_on_file,nxr_on_file )
    6656 
    6657              CASE ( 't_surf_window_h' )
    6658                 IF ( k == 1 )  THEN
    6659                    IF ( .NOT.  ALLOCATED( t_surf_window_h_1 ) )                &
    6660                       ALLOCATE( t_surf_window_h_1(1:surf_usm_h%ns) )
    6661                    READ ( 13 )  tmp_surf_window_h
    6662                 ENDIF
    6663                 CALL surface_restore_elements(                                 &
    6664                                         t_surf_window_h_1,                     &
    6665                                         tmp_surf_window_h,                     &
    6666                                         surf_usm_h%start_index,                &
    6667                                         start_index_on_file,                   &
    6668                                         end_index_on_file,                     &
    6669                                         nxlc, nysc,                            &
    6670                                         nxlf, nxrf, nysf, nynf,                &
    6671                                         nys_on_file, nyn_on_file,              &
    6672                                         nxl_on_file,nxr_on_file )
    6673 
    6674              CASE ( 't_surf_window_v(0)' )
    6675                 IF ( k == 1 )  THEN
    6676                    IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%t ) )           &
    6677                       ALLOCATE( t_surf_window_v_1(0)%t(1:surf_usm_v(0)%ns) )
    6678                    READ ( 13 )  tmp_surf_window_v(0)%t
    6679                 ENDIF
    6680                 CALL surface_restore_elements(                                 &
    6681                                         t_surf_window_v_1(0)%t,                &
    6682                                         tmp_surf_window_v(0)%t,                &
    6683                                         surf_usm_v(0)%start_index,             &
    6684                                         start_index_on_file,                   &
    6685                                         end_index_on_file,                     &
    6686                                         nxlc, nysc,                            &
    6687                                         nxlf, nxrf, nysf, nynf,                &
    6688                                         nys_on_file, nyn_on_file,              &
    6689                                         nxl_on_file,nxr_on_file )
    6690                    
    6691              CASE ( 't_surf_window_v(1)' )
    6692                 IF ( k == 1 )  THEN
    6693                    IF ( .NOT.  ALLOCATED( t_surf_window_v_1(1)%t ) )           &
    6694                       ALLOCATE( t_surf_window_v_1(1)%t(1:surf_usm_v(1)%ns) )
    6695                    READ ( 13 )  tmp_surf_window_v(1)%t
    6696                 ENDIF
    6697                 CALL surface_restore_elements(                                 &
    6698                                         t_surf_window_v_1(1)%t,                &
    6699                                         tmp_surf_window_v(1)%t,                &
    6700                                         surf_usm_v(1)%start_index,             &
    6701                                         start_index_on_file,                   &
    6702                                         end_index_on_file,                     &
    6703                                         nxlc, nysc,                            &
    6704                                         nxlf, nxrf, nysf, nynf,                &
    6705                                         nys_on_file, nyn_on_file,              &
    6706                                         nxl_on_file,nxr_on_file )
    6707 
    6708              CASE ( 't_surf_window_v(2)' )
    6709                 IF ( k == 1 )  THEN
    6710                    IF ( .NOT.  ALLOCATED( t_surf_window_v_1(2)%t ) )           &
    6711                       ALLOCATE( t_surf_window_v_1(2)%t(1:surf_usm_v(2)%ns) )
    6712                    READ ( 13 )  tmp_surf_window_v(2)%t
    6713                 ENDIF
    6714                 CALL surface_restore_elements(                                 &
    6715                                         t_surf_window_v_1(2)%t,                &
    6716                                         tmp_surf_window_v(2)%t,                &
    6717                                         surf_usm_v(2)%start_index,             &
    6718                                         start_index_on_file,                   &
    6719                                         end_index_on_file,                     &
    6720                                         nxlc, nysc,                            &
    6721                                         nxlf, nxrf, nysf, nynf,                &
    6722                                         nys_on_file, nyn_on_file,              &
    6723                                         nxl_on_file,nxr_on_file )
    6724                    
    6725              CASE ( 't_surf_window_v(3)' )
    6726                 IF ( k == 1 )  THEN
    6727                    IF ( .NOT.  ALLOCATED( t_surf_window_v_1(3)%t ) )           &
    6728                       ALLOCATE( t_surf_window_v_1(3)%t(1:surf_usm_v(3)%ns) )
    6729                    READ ( 13 )  tmp_surf_window_v(3)%t
    6730                 ENDIF
    6731                 CALL surface_restore_elements(                                 &
    6732                                         t_surf_window_v_1(3)%t,                & 
    6733                                         tmp_surf_window_v(3)%t,                &
    6734                                         surf_usm_v(3)%start_index,             &
    6735                                         start_index_on_file,                   &
    6736                                         end_index_on_file,                     &
    6737                                         nxlc, nysc,                            &
    6738                                         nxlf, nxrf, nysf, nynf,                &
    6739                                         nys_on_file, nyn_on_file,              &
    6740                                         nxl_on_file,nxr_on_file )
    6741 
    6742              CASE ( 'waste_heat_h' )
    6743                 IF ( k == 1 )  THEN
    6744                    IF ( .NOT.  ALLOCATED( surf_usm_h%waste_heat ) )            &
    6745                       ALLOCATE( surf_usm_h%waste_heat(1:surf_usm_h%ns) )
    6746                    READ ( 13 )  tmp_surf_waste_h
    6747                 ENDIF             
    6748                 CALL surface_restore_elements(                                 &
    6749                                         surf_usm_h%waste_heat,                 &
    6750                                         tmp_surf_waste_h,                      &
    6751                                         surf_usm_h%start_index,                &
    6752                                         start_index_on_file,                   &
    6753                                         end_index_on_file,                     &
    6754                                         nxlc, nysc,                            &
    6755                                         nxlf, nxrf, nysf, nynf,                &
    6756                                         nys_on_file, nyn_on_file,              &
    6757                                         nxl_on_file,nxr_on_file )                 
    6758                                        
    6759              CASE ( 'waste_heat_v(0)' )
    6760                 IF ( k == 1 )  THEN
    6761                    IF ( .NOT.  ALLOCATED( surf_usm_v(0)%waste_heat ) )         &
    6762                       ALLOCATE( surf_usm_v(0)%waste_heat(1:surf_usm_v(0)%ns) )
    6763                    READ ( 13 )  tmp_surf_waste_v(0)%t
    6764                 ENDIF
    6765                 CALL surface_restore_elements(                                 &
    6766                                         surf_usm_v(0)%waste_heat,              &
    6767                                         tmp_surf_waste_v(0)%t,                 &
    6768                                         surf_usm_v(0)%start_index,             &
    6769                                         start_index_on_file,                   &
    6770                                         end_index_on_file,                     &
    6771                                         nxlc, nysc,                            &
    6772                                         nxlf, nxrf, nysf, nynf,                &
    6773                                         nys_on_file, nyn_on_file,              &
    6774                                         nxl_on_file,nxr_on_file )
    6775                      
    6776              CASE ( 'waste_heat_v(1)' )
    6777                 IF ( k == 1 )  THEN
    6778                    IF ( .NOT.  ALLOCATED( surf_usm_v(1)%waste_heat ) )         &
    6779                       ALLOCATE( surf_usm_v(1)%waste_heat(1:surf_usm_v(1)%ns) )
    6780                    READ ( 13 )  tmp_surf_waste_v(1)%t
    6781                 ENDIF
    6782                 CALL surface_restore_elements(                                 &
    6783                                         surf_usm_v(1)%waste_heat,              &
    6784                                         tmp_surf_waste_v(1)%t,                 &
    6785                                         surf_usm_v(1)%start_index,             &
    6786                                         start_index_on_file,                   &
    6787                                         end_index_on_file,                     &
    6788                                         nxlc, nysc,                            &
    6789                                         nxlf, nxrf, nysf, nynf,                &
    6790                                         nys_on_file, nyn_on_file,              &
    6791                                         nxl_on_file,nxr_on_file )
    6792 
    6793              CASE ( 'waste_heat_v(2)' )
    6794                 IF ( k == 1 )  THEN
    6795                    IF ( .NOT.  ALLOCATED( surf_usm_v(2)%waste_heat ) )         &
    6796                       ALLOCATE( surf_usm_v(2)%waste_heat(1:surf_usm_v(2)%ns) )
    6797                    READ ( 13 )  tmp_surf_waste_v(2)%t
    6798                 ENDIF
    6799                 CALL surface_restore_elements(                                 &
    6800                                         surf_usm_v(2)%waste_heat,              &
    6801                                         tmp_surf_waste_v(2)%t,                 &
    6802                                         surf_usm_v(2)%start_index,             &
    6803                                         start_index_on_file,                   &
    6804                                         end_index_on_file,                     &
    6805                                         nxlc, nysc,                            &
    6806                                         nxlf, nxrf, nysf, nynf,                &
    6807                                         nys_on_file, nyn_on_file,              &
    6808                                         nxl_on_file,nxr_on_file )
    6809                      
    6810              CASE ( 'waste_heat_v(3)' )
    6811                 IF ( k == 1 )  THEN
    6812                    IF ( .NOT.  ALLOCATED( surf_usm_v(3)%waste_heat ) )         &
    6813                       ALLOCATE( surf_usm_v(3)%waste_heat(1:surf_usm_v(3)%ns) )
    6814                    READ ( 13 )  tmp_surf_waste_v(3)%t
    6815                 ENDIF
    6816                 CALL surface_restore_elements(                                 &
    6817                                         surf_usm_v(3)%waste_heat,              &
    6818                                         tmp_surf_waste_v(3)%t,                 &
    6819                                         surf_usm_v(3)%start_index,             &
    6820                                         start_index_on_file,                   &
    6821                                         end_index_on_file,                     &
    6822                                         nxlc, nysc,                            &
    6823                                         nxlf, nxrf, nysf, nynf,                &
    6824                                         nys_on_file, nyn_on_file,              &
    6825                                         nxl_on_file,nxr_on_file )
    6826 
    6827              CASE ( 't_wall_h' )
    6828                 IF ( k == 1 )  THEN
    6829                    IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                       &
    6830                       ALLOCATE( t_wall_h_1(nzb_wall:nzt_wall+1,                &
    6831                                            1:surf_usm_h%ns) )
    6832                    READ ( 13 )  tmp_wall_h
    6833                 ENDIF
    6834                 CALL surface_restore_elements(                                 &
    6835                                         t_wall_h_1, tmp_wall_h,                &
    6836                                         surf_usm_h%start_index,                &
    6837                                         start_index_on_file,                   &
    6838                                         end_index_on_file,                     &
    6839                                         nxlc, nysc,                            &
    6840                                         nxlf, nxrf, nysf, nynf,                &
    6841                                         nys_on_file, nyn_on_file,              &
    6842                                         nxl_on_file,nxr_on_file )
    6843 
    6844              CASE ( 't_wall_v(0)' )
    6845                 IF ( k == 1 )  THEN
    6846                    IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%t ) )                  &
    6847                       ALLOCATE( t_wall_v_1(0)%t(nzb_wall:nzt_wall+1,           &
    6848                                                 1:surf_usm_v(0)%ns) )
    6849                    READ ( 13 )  tmp_wall_v(0)%t
    6850                 ENDIF
    6851                 CALL surface_restore_elements(                                 &
    6852                                         t_wall_v_1(0)%t, tmp_wall_v(0)%t,      &
    6853                                         surf_usm_v(0)%start_index,             & 
    6854                                         start_index_on_file,                   &
    6855                                         end_index_on_file,                     &
    6856                                         nxlc, nysc,                            &
    6857                                         nxlf, nxrf, nysf, nynf,                &
    6858                                         nys_on_file, nyn_on_file,              &
    6859                                         nxl_on_file,nxr_on_file )
    6860 
    6861              CASE ( 't_wall_v(1)' )
    6862                 IF ( k == 1 )  THEN
    6863                    IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%t ) )                  &
    6864                       ALLOCATE( t_wall_v_1(1)%t(nzb_wall:nzt_wall+1,           &
    6865                                                 1:surf_usm_v(1)%ns) )
    6866                    READ ( 13 )  tmp_wall_v(1)%t
    6867                 ENDIF
    6868                 CALL surface_restore_elements(                                 &
    6869                                         t_wall_v_1(1)%t, tmp_wall_v(1)%t,      &
    6870                                         surf_usm_v(1)%start_index,             & 
    6871                                         start_index_on_file,                   &
    6872                                         end_index_on_file,                     &
    6873                                         nxlc, nysc,                            &
    6874                                         nxlf, nxrf, nysf, nynf,                &
    6875                                         nys_on_file, nyn_on_file,              &
    6876                                         nxl_on_file,nxr_on_file )
    6877 
    6878              CASE ( 't_wall_v(2)' )
    6879                 IF ( k == 1 )  THEN
    6880                    IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%t ) )                  &
    6881                       ALLOCATE( t_wall_v_1(2)%t(nzb_wall:nzt_wall+1,           &
    6882                                                 1:surf_usm_v(2)%ns) )
    6883                    READ ( 13 )  tmp_wall_v(2)%t
    6884                 ENDIF
    6885                 CALL surface_restore_elements(                                 &
    6886                                         t_wall_v_1(2)%t, tmp_wall_v(2)%t,      &
    6887                                         surf_usm_v(2)%start_index,             &
    6888                                         start_index_on_file,                   &
    6889                                         end_index_on_file ,                    &
    6890                                         nxlc, nysc,                            &
    6891                                         nxlf, nxrf, nysf, nynf,                &
    6892                                         nys_on_file, nyn_on_file,              &
    6893                                         nxl_on_file,nxr_on_file )
    6894 
    6895              CASE ( 't_wall_v(3)' )
    6896                 IF ( k == 1 )  THEN
    6897                    IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%t ) )                  &
    6898                       ALLOCATE( t_wall_v_1(3)%t(nzb_wall:nzt_wall+1,           &
    6899                                                 1:surf_usm_v(3)%ns) )
    6900                    READ ( 13 )  tmp_wall_v(3)%t
    6901                 ENDIF
    6902                 CALL surface_restore_elements(                                 &
    6903                                         t_wall_v_1(3)%t, tmp_wall_v(3)%t,      &
    6904                                         surf_usm_v(3)%start_index,             &   
    6905                                         start_index_on_file,                   &
    6906                                         end_index_on_file,                     &
    6907                                         nxlc, nysc,                            &
    6908                                         nxlf, nxrf, nysf, nynf,                &
    6909                                         nys_on_file, nyn_on_file,              &
    6910                                         nxl_on_file,nxr_on_file )
    6911 
    6912              CASE ( 't_green_h' )
    6913                 IF ( k == 1 )  THEN
    6914                    IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                      &
    6915                       ALLOCATE( t_green_h_1(nzb_wall:nzt_wall+1,               &
    6916                                             1:surf_usm_h%ns) )
    6917                    READ ( 13 )  tmp_green_h
    6918                 ENDIF
    6919                 CALL surface_restore_elements(                                 &
    6920                                         t_green_h_1, tmp_green_h,              &
    6921                                         surf_usm_h%start_index,                &
    6922                                         start_index_on_file,                   &
    6923                                         end_index_on_file,                     &
    6924                                         nxlc, nysc,                            &
    6925                                         nxlf, nxrf, nysf, nynf,                &
    6926                                         nys_on_file, nyn_on_file,              &
    6927                                         nxl_on_file,nxr_on_file )
    6928 
    6929              CASE ( 't_green_v(0)' )
    6930                 IF ( k == 1 )  THEN
    6931                    IF ( .NOT.  ALLOCATED( t_green_v_1(0)%t ) )                 &
    6932                       ALLOCATE( t_green_v_1(0)%t(nzb_wall:nzt_wall+1,          &
    6933                                                  1:surf_usm_v(0)%ns) )
    6934                    READ ( 13 )  tmp_green_v(0)%t
    6935                 ENDIF
    6936                 CALL surface_restore_elements(                                 &
    6937                                         t_green_v_1(0)%t, tmp_green_v(0)%t,    &
    6938                                         surf_usm_v(0)%start_index,             &
    6939                                         start_index_on_file,                   &
    6940                                         end_index_on_file,                     &
    6941                                         nxlc, nysc,                            &
    6942                                         nxlf, nxrf, nysf, nynf,                &
    6943                                         nys_on_file, nyn_on_file,              &
    6944                                         nxl_on_file,nxr_on_file )
    6945 
    6946              CASE ( 't_green_v(1)' )
    6947                 IF ( k == 1 )  THEN
    6948                    IF ( .NOT.  ALLOCATED( t_green_v_1(1)%t ) )                 &
    6949                       ALLOCATE( t_green_v_1(1)%t(nzb_wall:nzt_wall+1,          &
    6950                                                  1:surf_usm_v(1)%ns) )
    6951                    READ ( 13 )  tmp_green_v(1)%t
    6952                 ENDIF
    6953                 CALL surface_restore_elements(                                 &
    6954                                         t_green_v_1(1)%t, tmp_green_v(1)%t,    &
    6955                                         surf_usm_v(1)%start_index,             &
    6956                                         start_index_on_file,                   &
    6957                                         end_index_on_file,                     &
    6958                                         nxlc, nysc,                            &
    6959                                         nxlf, nxrf, nysf, nynf,                &
    6960                                         nys_on_file, nyn_on_file,              &
    6961                                         nxl_on_file,nxr_on_file )
    6962 
    6963              CASE ( 't_green_v(2)' )
    6964                 IF ( k == 1 )  THEN
    6965                    IF ( .NOT.  ALLOCATED( t_green_v_1(2)%t ) )                 &
    6966                       ALLOCATE( t_green_v_1(2)%t(nzb_wall:nzt_wall+1,          &
    6967                                                  1:surf_usm_v(2)%ns) )
    6968                    READ ( 13 )  tmp_green_v(2)%t
    6969                 ENDIF
    6970                 CALL surface_restore_elements(                                 &
    6971                                         t_green_v_1(2)%t, tmp_green_v(2)%t,    &
    6972                                         surf_usm_v(2)%start_index,             &
    6973                                         start_index_on_file,                   &
    6974                                         end_index_on_file ,                    &
    6975                                         nxlc, nysc,                            &
    6976                                         nxlf, nxrf, nysf, nynf,                &
    6977                                         nys_on_file, nyn_on_file,              &
    6978                                         nxl_on_file,nxr_on_file )
    6979 
    6980              CASE ( 't_green_v(3)' )
    6981                 IF ( k == 1 )  THEN
    6982                    IF ( .NOT.  ALLOCATED( t_green_v_1(3)%t ) )                 &
    6983                       ALLOCATE( t_green_v_1(3)%t(nzb_wall:nzt_wall+1,          &
    6984                                                  1:surf_usm_v(3)%ns) )
    6985                    READ ( 13 )  tmp_green_v(3)%t
    6986                 ENDIF
    6987                 CALL surface_restore_elements(                                 &
    6988                                         t_green_v_1(3)%t, tmp_green_v(3)%t,    &
    6989                                         surf_usm_v(3)%start_index,             & 
    6990                                         start_index_on_file,                   &
    6991                                         end_index_on_file,                     &
    6992                                         nxlc, nysc,                            &
    6993                                         nxlf, nxrf, nysf, nynf,                &
    6994                                         nys_on_file, nyn_on_file,              &
    6995                                         nxl_on_file,nxr_on_file )
    6996 
    6997              CASE ( 't_window_h' )
    6998                 IF ( k == 1 )  THEN
    6999                    IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                     &
    7000                       ALLOCATE( t_window_h_1(nzb_wall:nzt_wall+1,              &
    7001                                              1:surf_usm_h%ns) )
    7002                    READ ( 13 )  tmp_window_h
    7003                 ENDIF
    7004                 CALL surface_restore_elements(                                 &
    7005                                         t_window_h_1, tmp_window_h,            &
    7006                                         surf_usm_h%start_index,                &
    7007                                         start_index_on_file,                   &
    7008                                         end_index_on_file,                     &
    7009                                         nxlc, nysc,                            &
    7010                                         nxlf, nxrf, nysf, nynf,                &
    7011                                         nys_on_file, nyn_on_file,              &
    7012                                         nxl_on_file, nxr_on_file )
    7013 
    7014              CASE ( 't_window_v(0)' )
    7015                 IF ( k == 1 )  THEN
    7016                    IF ( .NOT.  ALLOCATED( t_window_v_1(0)%t ) )                &
    7017                       ALLOCATE( t_window_v_1(0)%t(nzb_wall:nzt_wall+1,         &
    7018                                                   1:surf_usm_v(0)%ns) )
    7019                    READ ( 13 )  tmp_window_v(0)%t
    7020                 ENDIF
    7021                 CALL surface_restore_elements(                                 &
    7022                                         t_window_v_1(0)%t,                     &
    7023                                         tmp_window_v(0)%t,                     &
    7024                                         surf_usm_v(0)%start_index,             &
    7025                                         start_index_on_file,                   &
    7026                                         end_index_on_file,                     &
    7027                                         nxlc, nysc,                            &
    7028                                         nxlf, nxrf, nysf, nynf,                &
    7029                                         nys_on_file, nyn_on_file,              &
    7030                                         nxl_on_file,nxr_on_file )
    7031 
    7032              CASE ( 't_window_v(1)' )
    7033                 IF ( k == 1 )  THEN
    7034                    IF ( .NOT.  ALLOCATED( t_window_v_1(1)%t ) )                &
    7035                       ALLOCATE( t_window_v_1(1)%t(nzb_wall:nzt_wall+1,         &
    7036                                                   1:surf_usm_v(1)%ns) )
    7037                    READ ( 13 )  tmp_window_v(1)%t
    7038                 ENDIF
    7039                 CALL surface_restore_elements(                                 &
    7040                                         t_window_v_1(1)%t,                     &
    7041                                         tmp_window_v(1)%t,                     &
    7042                                         surf_usm_v(1)%start_index,             &
    7043                                         start_index_on_file,                   &
    7044                                         end_index_on_file,                     &
    7045                                         nxlc, nysc,                            &
    7046                                         nxlf, nxrf, nysf, nynf,                &
    7047                                         nys_on_file, nyn_on_file,              &
    7048                                         nxl_on_file,nxr_on_file )
    7049 
    7050              CASE ( 't_window_v(2)' )
    7051                 IF ( k == 1 )  THEN
    7052                    IF ( .NOT.  ALLOCATED( t_window_v_1(2)%t ) )                &
    7053                       ALLOCATE( t_window_v_1(2)%t(nzb_wall:nzt_wall+1,         &
    7054                                                   1:surf_usm_v(2)%ns) )
    7055                    READ ( 13 )  tmp_window_v(2)%t
    7056                 ENDIF
    7057                 CALL surface_restore_elements(                                 &
    7058                                         t_window_v_1(2)%t,                     &
    7059                                         tmp_window_v(2)%t,                     &
    7060                                         surf_usm_v(2)%start_index,             & 
    7061                                         start_index_on_file,                   &
    7062                                         end_index_on_file ,                    &
    7063                                         nxlc, nysc,                            &
    7064                                         nxlf, nxrf, nysf, nynf,                &
    7065                                         nys_on_file, nyn_on_file,              &
    7066                                         nxl_on_file,nxr_on_file )
    7067 
    7068              CASE ( 't_window_v(3)' )
    7069                 IF ( k == 1 )  THEN
    7070                    IF ( .NOT.  ALLOCATED( t_window_v_1(3)%t ) )                &
    7071                       ALLOCATE( t_window_v_1(3)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(3)%ns) )
    7072                    READ ( 13 )  tmp_window_v(3)%t
    7073                 ENDIF
    7074                 CALL surface_restore_elements(                                 &
    7075                                         t_window_v_1(3)%t,                     &
    7076                                         tmp_window_v(3)%t,                     &
    7077                                         surf_usm_v(3)%start_index,             &
    7078                                         start_index_on_file,                   &
    7079                                         end_index_on_file,                     &
    7080                                         nxlc, nysc,                            &
    7081                                         nxlf, nxrf, nysf, nynf,                &
    7082                                         nys_on_file, nyn_on_file,              &
    7083                                         nxl_on_file,nxr_on_file )
    7084 
    7085              CASE DEFAULT
    7086 
    7087                    found = .FALSE.
    7088 
    7089           END SELECT
    7090 
    7091        
     6781          CASE ( 'waste_heat_v(3)' )
     6782             IF ( k == 1 )  THEN
     6783                IF ( .NOT.  ALLOCATED( surf_usm_v(3)%waste_heat ) )         &
     6784                   ALLOCATE( surf_usm_v(3)%waste_heat(1:surf_usm_v(3)%ns) )
     6785                READ ( 13 )  tmp_surf_waste_v(3)%t
     6786             ENDIF
     6787             CALL surface_restore_elements(                                 &
     6788                                     surf_usm_v(3)%waste_heat,              &
     6789                                     tmp_surf_waste_v(3)%t,                 &
     6790                                     surf_usm_v(3)%start_index,             &
     6791                                     start_index_on_file,                   &
     6792                                     end_index_on_file,                     &
     6793                                     nxlc, nysc,                            &
     6794                                     nxlf, nxrf, nysf, nynf,                &
     6795                                     nys_on_file, nyn_on_file,              &
     6796                                     nxl_on_file,nxr_on_file )
     6797
     6798          CASE ( 't_wall_h' )
     6799             IF ( k == 1 )  THEN
     6800                IF ( .NOT.  ALLOCATED( t_wall_h_1 ) )                       &
     6801                   ALLOCATE( t_wall_h_1(nzb_wall:nzt_wall+1,                &
     6802                                        1:surf_usm_h%ns) )
     6803                READ ( 13 )  tmp_wall_h
     6804             ENDIF
     6805             CALL surface_restore_elements(                                 &
     6806                                     t_wall_h_1, tmp_wall_h,                &
     6807                                     surf_usm_h%start_index,                &
     6808                                     start_index_on_file,                   &
     6809                                     end_index_on_file,                     &
     6810                                     nxlc, nysc,                            &
     6811                                     nxlf, nxrf, nysf, nynf,                &
     6812                                     nys_on_file, nyn_on_file,              &
     6813                                     nxl_on_file,nxr_on_file )
     6814
     6815          CASE ( 't_wall_v(0)' )
     6816             IF ( k == 1 )  THEN
     6817                IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%t ) )                  &
     6818                   ALLOCATE( t_wall_v_1(0)%t(nzb_wall:nzt_wall+1,           &
     6819                                             1:surf_usm_v(0)%ns) )
     6820                READ ( 13 )  tmp_wall_v(0)%t
     6821             ENDIF
     6822             CALL surface_restore_elements(                                 &
     6823                                     t_wall_v_1(0)%t, tmp_wall_v(0)%t,      &
     6824                                     surf_usm_v(0)%start_index,             & 
     6825                                     start_index_on_file,                   &
     6826                                     end_index_on_file,                     &
     6827                                     nxlc, nysc,                            &
     6828                                     nxlf, nxrf, nysf, nynf,                &
     6829                                     nys_on_file, nyn_on_file,              &
     6830                                     nxl_on_file,nxr_on_file )
     6831
     6832          CASE ( 't_wall_v(1)' )
     6833             IF ( k == 1 )  THEN
     6834                IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%t ) )                  &
     6835                   ALLOCATE( t_wall_v_1(1)%t(nzb_wall:nzt_wall+1,           &
     6836                                             1:surf_usm_v(1)%ns) )
     6837                READ ( 13 )  tmp_wall_v(1)%t
     6838             ENDIF
     6839             CALL surface_restore_elements(                                 &
     6840                                     t_wall_v_1(1)%t, tmp_wall_v(1)%t,      &
     6841                                     surf_usm_v(1)%start_index,             & 
     6842                                     start_index_on_file,                   &
     6843                                     end_index_on_file,                     &
     6844                                     nxlc, nysc,                            &
     6845                                     nxlf, nxrf, nysf, nynf,                &
     6846                                     nys_on_file, nyn_on_file,              &
     6847                                     nxl_on_file,nxr_on_file )
     6848
     6849          CASE ( 't_wall_v(2)' )
     6850             IF ( k == 1 )  THEN
     6851                IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%t ) )                  &
     6852                   ALLOCATE( t_wall_v_1(2)%t(nzb_wall:nzt_wall+1,           &
     6853                                             1:surf_usm_v(2)%ns) )
     6854                READ ( 13 )  tmp_wall_v(2)%t
     6855             ENDIF
     6856             CALL surface_restore_elements(                                 &
     6857                                     t_wall_v_1(2)%t, tmp_wall_v(2)%t,      &
     6858                                     surf_usm_v(2)%start_index,             &
     6859                                     start_index_on_file,                   &
     6860                                     end_index_on_file ,                    &
     6861                                     nxlc, nysc,                            &
     6862                                     nxlf, nxrf, nysf, nynf,                &
     6863                                     nys_on_file, nyn_on_file,              &
     6864                                     nxl_on_file,nxr_on_file )
     6865
     6866          CASE ( 't_wall_v(3)' )
     6867             IF ( k == 1 )  THEN
     6868                IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%t ) )                  &
     6869                   ALLOCATE( t_wall_v_1(3)%t(nzb_wall:nzt_wall+1,           &
     6870                                             1:surf_usm_v(3)%ns) )
     6871                READ ( 13 )  tmp_wall_v(3)%t
     6872             ENDIF
     6873             CALL surface_restore_elements(                                 &
     6874                                     t_wall_v_1(3)%t, tmp_wall_v(3)%t,      &
     6875                                     surf_usm_v(3)%start_index,             &   
     6876                                     start_index_on_file,                   &
     6877                                     end_index_on_file,                     &
     6878                                     nxlc, nysc,                            &
     6879                                     nxlf, nxrf, nysf, nynf,                &
     6880                                     nys_on_file, nyn_on_file,              &
     6881                                     nxl_on_file,nxr_on_file )
     6882
     6883          CASE ( 't_green_h' )
     6884             IF ( k == 1 )  THEN
     6885                IF ( .NOT.  ALLOCATED( t_green_h_1 ) )                      &
     6886                   ALLOCATE( t_green_h_1(nzb_wall:nzt_wall+1,               &
     6887                                         1:surf_usm_h%ns) )
     6888                READ ( 13 )  tmp_green_h
     6889             ENDIF
     6890             CALL surface_restore_elements(                                 &
     6891                                     t_green_h_1, tmp_green_h,              &
     6892                                     surf_usm_h%start_index,                &
     6893                                     start_index_on_file,                   &
     6894                                     end_index_on_file,                     &
     6895                                     nxlc, nysc,                            &
     6896                                     nxlf, nxrf, nysf, nynf,                &
     6897                                     nys_on_file, nyn_on_file,              &
     6898                                     nxl_on_file,nxr_on_file )
     6899
     6900          CASE ( 't_green_v(0)' )
     6901             IF ( k == 1 )  THEN
     6902                IF ( .NOT.  ALLOCATED( t_green_v_1(0)%t ) )                 &
     6903                   ALLOCATE( t_green_v_1(0)%t(nzb_wall:nzt_wall+1,          &
     6904                                              1:surf_usm_v(0)%ns) )
     6905                READ ( 13 )  tmp_green_v(0)%t
     6906             ENDIF
     6907             CALL surface_restore_elements(                                 &
     6908                                     t_green_v_1(0)%t, tmp_green_v(0)%t,    &
     6909                                     surf_usm_v(0)%start_index,             &
     6910                                     start_index_on_file,                   &
     6911                                     end_index_on_file,                     &
     6912                                     nxlc, nysc,                            &
     6913                                     nxlf, nxrf, nysf, nynf,                &
     6914                                     nys_on_file, nyn_on_file,              &
     6915                                     nxl_on_file,nxr_on_file )
     6916
     6917          CASE ( 't_green_v(1)' )
     6918             IF ( k == 1 )  THEN
     6919                IF ( .NOT.  ALLOCATED( t_green_v_1(1)%t ) )                 &
     6920                   ALLOCATE( t_green_v_1(1)%t(nzb_wall:nzt_wall+1,          &
     6921                                              1:surf_usm_v(1)%ns) )
     6922                READ ( 13 )  tmp_green_v(1)%t
     6923             ENDIF
     6924             CALL surface_restore_elements(                                 &
     6925                                     t_green_v_1(1)%t, tmp_green_v(1)%t,    &
     6926                                     surf_usm_v(1)%start_index,             &
     6927                                     start_index_on_file,                   &
     6928                                     end_index_on_file,                     &
     6929                                     nxlc, nysc,                            &
     6930                                     nxlf, nxrf, nysf, nynf,                &
     6931                                     nys_on_file, nyn_on_file,              &
     6932                                     nxl_on_file,nxr_on_file )
     6933
     6934          CASE ( 't_green_v(2)' )
     6935             IF ( k == 1 )  THEN
     6936                IF ( .NOT.  ALLOCATED( t_green_v_1(2)%t ) )                 &
     6937                   ALLOCATE( t_green_v_1(2)%t(nzb_wall:nzt_wall+1,          &
     6938                                              1:surf_usm_v(2)%ns) )
     6939                READ ( 13 )  tmp_green_v(2)%t
     6940             ENDIF
     6941             CALL surface_restore_elements(                                 &
     6942                                     t_green_v_1(2)%t, tmp_green_v(2)%t,    &
     6943                                     surf_usm_v(2)%start_index,             &
     6944                                     start_index_on_file,                   &
     6945                                     end_index_on_file ,                    &
     6946                                     nxlc, nysc,                            &
     6947                                     nxlf, nxrf, nysf, nynf,                &
     6948                                     nys_on_file, nyn_on_file,              &
     6949                                     nxl_on_file,nxr_on_file )
     6950
     6951          CASE ( 't_green_v(3)' )
     6952             IF ( k == 1 )  THEN
     6953                IF ( .NOT.  ALLOCATED( t_green_v_1(3)%t ) )                 &
     6954                   ALLOCATE( t_green_v_1(3)%t(nzb_wall:nzt_wall+1,          &
     6955                                              1:surf_usm_v(3)%ns) )
     6956                READ ( 13 )  tmp_green_v(3)%t
     6957             ENDIF
     6958             CALL surface_restore_elements(                                 &
     6959                                     t_green_v_1(3)%t, tmp_green_v(3)%t,    &
     6960                                     surf_usm_v(3)%start_index,             & 
     6961                                     start_index_on_file,                   &
     6962                                     end_index_on_file,                     &
     6963                                     nxlc, nysc,                            &
     6964                                     nxlf, nxrf, nysf, nynf,                &
     6965                                     nys_on_file, nyn_on_file,              &
     6966                                     nxl_on_file,nxr_on_file )
     6967
     6968          CASE ( 't_window_h' )
     6969             IF ( k == 1 )  THEN
     6970                IF ( .NOT.  ALLOCATED( t_window_h_1 ) )                     &
     6971                   ALLOCATE( t_window_h_1(nzb_wall:nzt_wall+1,              &
     6972                                          1:surf_usm_h%ns) )
     6973                READ ( 13 )  tmp_window_h
     6974             ENDIF
     6975             CALL surface_restore_elements(                                 &
     6976                                     t_window_h_1, tmp_window_h,            &
     6977                                     surf_usm_h%start_index,                &
     6978                                     start_index_on_file,                   &
     6979                                     end_index_on_file,                     &
     6980                                     nxlc, nysc,                            &
     6981                                     nxlf, nxrf, nysf, nynf,                &
     6982                                     nys_on_file, nyn_on_file,              &
     6983                                     nxl_on_file, nxr_on_file )
     6984
     6985          CASE ( 't_window_v(0)' )
     6986             IF ( k == 1 )  THEN
     6987                IF ( .NOT.  ALLOCATED( t_window_v_1(0)%t ) )                &
     6988                   ALLOCATE( t_window_v_1(0)%t(nzb_wall:nzt_wall+1,         &
     6989                                               1:surf_usm_v(0)%ns) )
     6990                READ ( 13 )  tmp_window_v(0)%t
     6991             ENDIF
     6992             CALL surface_restore_elements(                                 &
     6993                                     t_window_v_1(0)%t,                     &
     6994                                     tmp_window_v(0)%t,                     &
     6995                                     surf_usm_v(0)%start_index,             &
     6996                                     start_index_on_file,                   &
     6997                                     end_index_on_file,                     &
     6998                                     nxlc, nysc,                            &
     6999                                     nxlf, nxrf, nysf, nynf,                &
     7000                                     nys_on_file, nyn_on_file,              &
     7001                                     nxl_on_file,nxr_on_file )
     7002
     7003          CASE ( 't_window_v(1)' )
     7004             IF ( k == 1 )  THEN
     7005                IF ( .NOT.  ALLOCATED( t_window_v_1(1)%t ) )                &
     7006                   ALLOCATE( t_window_v_1(1)%t(nzb_wall:nzt_wall+1,         &
     7007                                               1:surf_usm_v(1)%ns) )
     7008                READ ( 13 )  tmp_window_v(1)%t
     7009             ENDIF
     7010             CALL surface_restore_elements(                                 &
     7011                                     t_window_v_1(1)%t,                     &
     7012                                     tmp_window_v(1)%t,                     &
     7013                                     surf_usm_v(1)%start_index,             &
     7014                                     start_index_on_file,                   &
     7015                                     end_index_on_file,                     &
     7016                                     nxlc, nysc,                            &
     7017                                     nxlf, nxrf, nysf, nynf,                &
     7018                                     nys_on_file, nyn_on_file,              &
     7019                                     nxl_on_file,nxr_on_file )
     7020
     7021          CASE ( 't_window_v(2)' )
     7022             IF ( k == 1 )  THEN
     7023                IF ( .NOT.  ALLOCATED( t_window_v_1(2)%t ) )                &
     7024                   ALLOCATE( t_window_v_1(2)%t(nzb_wall:nzt_wall+1,         &
     7025                                               1:surf_usm_v(2)%ns) )
     7026                READ ( 13 )  tmp_window_v(2)%t
     7027             ENDIF
     7028             CALL surface_restore_elements(                                 &
     7029                                     t_window_v_1(2)%t,                     &
     7030                                     tmp_window_v(2)%t,                     &
     7031                                     surf_usm_v(2)%start_index,             & 
     7032                                     start_index_on_file,                   &
     7033                                     end_index_on_file ,                    &
     7034                                     nxlc, nysc,                            &
     7035                                     nxlf, nxrf, nysf, nynf,                &
     7036                                     nys_on_file, nyn_on_file,              &
     7037                                     nxl_on_file,nxr_on_file )
     7038
     7039          CASE ( 't_window_v(3)' )
     7040             IF ( k == 1 )  THEN
     7041                IF ( .NOT.  ALLOCATED( t_window_v_1(3)%t ) )                &
     7042                   ALLOCATE( t_window_v_1(3)%t(nzb_wall:nzt_wall+1,1:surf_usm_v(3)%ns) )
     7043                READ ( 13 )  tmp_window_v(3)%t
     7044             ENDIF
     7045             CALL surface_restore_elements(                                 &
     7046                                     t_window_v_1(3)%t,                     &
     7047                                     tmp_window_v(3)%t,                     &
     7048                                     surf_usm_v(3)%start_index,             &
     7049                                     start_index_on_file,                   &
     7050                                     end_index_on_file,                     &
     7051                                     nxlc, nysc,                            &
     7052                                     nxlf, nxrf, nysf, nynf,                &
     7053                                     nys_on_file, nyn_on_file,              &
     7054                                     nxl_on_file,nxr_on_file )
     7055
     7056          CASE DEFAULT
     7057
     7058             found = .FALSE.
     7059
     7060       END SELECT
     7061
    70927062    END SUBROUTINE usm_rrd_local
    70937063
     
    89708940        CALL wrd_write_string( 't_surf_green_h' )
    89718941        WRITE ( 14 )  t_surf_green_h
     8942
     8943        CALL wrd_write_string( 'm_liq_usm_h' )
     8944        WRITE ( 14 )  m_liq_usm_h%var_usm_1d
    89728945!
    89738946!--     Write restart data which is especially needed for the urban-surface
Note: See TracChangeset for help on using the changeset viewer.