Ignore:
Timestamp:
Jan 21, 2021 5:59:25 PM (3 years ago)
Author:
suehring
Message:

Bugfix in indoor model: consider previous indoor temperature during restarts; Further bugfix in mpi-io restart mechanism for the waste-heat flux from buildings

File:
1 edited

Legend:

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

    r4843 r4850  
    2727! -----------------
    2828! $Id$
     29! - Add restart data for previous indoor temperature
     30! - Bugfix in mpi-io restart mechanism for waste-heat flux
     31!
     32! 4843 2021-01-15 15:22:11Z raasch
    2933! local namelist parameter added to switch off the module although the respective module namelist
    3034! appears in the namelist file
     
    325329!> Further work:
    326330!> -------------
    327 !> @todo Revise sorting of building_pars
    328331!> @todo Revise initialization when building_pars / building_surface_pars are provided -
    329332!>       intialization is not consistent to building_pars
    330333!> @todo Revise flux conversion in energy-balance solver
    331334!> @todo Check divisions in wtend (etc.) calculations for possible division by zero, e.g. in case
    332 !> fraq(0,m) + fraq(1,m) = 0?!
     335!>       fraq(0,m) + fraq(1,m) = 0?!
    333336!> @todo Use unit 90 for OPEN/CLOSE of input files (FK)
    334337!--------------------------------------------------------------------------------------------------!
     
    10121015    IF ( indoor_model )  THEN
    10131016       DO  l = 0, 1
     1017          ALLOCATE ( surf_usm_h(l)%t_prev(1:surf_usm_h(l)%ns)     )
    10141018          ALLOCATE ( surf_usm_h(l)%waste_heat(1:surf_usm_h(l)%ns) )
     1019          surf_usm_h(l)%t_prev     = 0.0_wp
    10151020          surf_usm_h(l)%waste_heat = 0.0_wp
    10161021       ENDDO
    10171022       DO  l = 0, 3
     1023          ALLOCATE ( surf_usm_v(l)%t_prev(1:surf_usm_v(l)%ns)     )
    10181024          ALLOCATE ( surf_usm_v(l)%waste_heat(1:surf_usm_v(l)%ns) )
     1025          surf_usm_v(l)%t_prev     = 0.0_wp
    10191026          surf_usm_v(l)%waste_heat = 0.0_wp
    10201027       ENDDO
     
    59105917    TYPE( surf_type_1d_usm ), DIMENSION(0:1), SAVE ::  tmp_surf_green_h   !<
    59115918    TYPE( surf_type_1d_usm ), DIMENSION(0:1), SAVE ::  tmp_surf_mliq_h    !<
     5919    TYPE( surf_type_1d_usm ), DIMENSION(0:3), SAVE ::  tmp_surf_t_prev_h  !<
    59125920    TYPE( surf_type_1d_usm ), DIMENSION(0:1), SAVE ::  tmp_surf_wall_h    !<
    59135921    TYPE( surf_type_1d_usm ), DIMENSION(0:1), SAVE ::  tmp_surf_waste_h   !<
     
    59195927
    59205928    TYPE( surf_type_1d_usm ), DIMENSION(0:3), SAVE ::  tmp_surf_green_v   !<
     5929    TYPE( surf_type_1d_usm ), DIMENSION(0:3), SAVE ::  tmp_surf_t_prev_v  !<
    59215930    TYPE( surf_type_1d_usm ), DIMENSION(0:3), SAVE ::  tmp_surf_wall_v    !<
    59225931    TYPE( surf_type_1d_usm ), DIMENSION(0:3), SAVE ::  tmp_surf_waste_v   !<
     
    59295938
    59305939    found = .TRUE.
    5931 
    59325940
    59335941    SELECT CASE ( restart_string(1:length) )
     
    59465954                IF ( ALLOCATED( tmp_surf_mliq_h(l)%val) )     DEALLOCATE( tmp_surf_mliq_h(l)%val )
    59475955                IF ( ALLOCATED( tmp_surf_waste_h(l)%val) )    DEALLOCATE( tmp_surf_waste_h(l)%val )
     5956                IF ( ALLOCATED( tmp_surf_t_prev_h(l)%val) )   DEALLOCATE( tmp_surf_t_prev_h(l)%val )
    59485957             ENDDO
    59495958
     
    59615970                ALLOCATE( tmp_surf_mliq_h(l)%val(1:ns_h_on_file_usm(l)) )
    59625971                ALLOCATE( tmp_surf_waste_h(l)%val(1:ns_h_on_file_usm(l)) )
     5972                ALLOCATE( tmp_surf_t_prev_h(l)%val(1:ns_h_on_file_usm(l)) )
    59635973             ENDDO
    59645974
     
    59775987                IF ( ALLOCATED( tmp_green_v(l)%val ) )        DEALLOCATE( tmp_green_v(l)%val )
    59785988                IF ( ALLOCATED( tmp_surf_waste_v(l)%val ) )   DEALLOCATE( tmp_surf_waste_v(l)%val )
     5989                IF ( ALLOCATED( tmp_surf_t_prev_v(l)%val ) )  DEALLOCATE( tmp_surf_t_prev_v(l)%val )
    59795990             ENDDO
    59805991
     
    59916002                ALLOCATE( tmp_green_v(l)%val(nzb_wall:nzt_wall+1, 1:ns_v_on_file_usm(l) ) )
    59926003                ALLOCATE( tmp_surf_waste_v(l)%val(1:ns_v_on_file_usm(l)) )
     6004                ALLOCATE( tmp_surf_t_prev_v(l)%val(1:ns_v_on_file_usm(l)) )
    59936005             ENDDO
    59946006
     
    60196031       CASE ( 't_surf_wall_h(0)' )
    60206032          IF ( k == 1 )  THEN
    6021              IF ( .NOT.  ALLOCATED( t_surf_wall_h_1(0)%val ) )                                       &
     6033             IF ( .NOT.  ALLOCATED( t_surf_wall_h_1(0)%val ) )                                     &
    60226034                ALLOCATE( t_surf_wall_h_1(0)%val(1:surf_usm_h(0)%ns) )
    60236035             READ ( 13 )  tmp_surf_wall_h(0)%val
    60246036          ENDIF
    6025           CALL surface_restore_elements( t_surf_wall_h_1(0)%val, tmp_surf_wall_h(0)%val,               &
     6037          CALL surface_restore_elements( t_surf_wall_h_1(0)%val, tmp_surf_wall_h(0)%val,           &
    60266038                                         surf_usm_h(0)%start_index, start_index_on_file,           &
    60276039                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    60306042       CASE ( 't_surf_wall_h(1)' )
    60316043          IF ( k == 1 )  THEN
    6032              IF ( .NOT.  ALLOCATED( t_surf_wall_h_1(1)%val ) )                                       &
     6044             IF ( .NOT.  ALLOCATED( t_surf_wall_h_1(1)%val ) )                                     &
    60336045                ALLOCATE( t_surf_wall_h_1(1)%val(1:surf_usm_h(1)%ns) )
    60346046             READ ( 13 )  tmp_surf_wall_h(1)%val
    60356047          ENDIF
    6036           CALL surface_restore_elements( t_surf_wall_h_1(1)%val, tmp_surf_wall_h(1)%val,               &
     6048          CALL surface_restore_elements( t_surf_wall_h_1(1)%val, tmp_surf_wall_h(1)%val,           &
    60376049                                         surf_usm_h(1)%start_index, start_index_on_file,           &
    60386050                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    60416053       CASE ( 't_surf_wall_v(0)' )
    60426054          IF ( k == 1 )  THEN
    6043              IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%val ) )                                       &
     6055             IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(0)%val ) )                                     &
    60446056                ALLOCATE( t_surf_wall_v_1(0)%val(1:surf_usm_v(0)%ns) )
    60456057             READ ( 13 )  tmp_surf_wall_v(0)%val
    60466058          ENDIF
    6047           CALL surface_restore_elements( t_surf_wall_v_1(0)%val, tmp_surf_wall_v(0)%val,               &
     6059          CALL surface_restore_elements( t_surf_wall_v_1(0)%val, tmp_surf_wall_v(0)%val,           &
    60486060                                         surf_usm_v(0)%start_index, start_index_on_file,           &
    60496061                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    60526064       CASE ( 't_surf_wall_v(1)' )
    60536065          IF ( k == 1 )  THEN
    6054              IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%val ) )                                       &
     6066             IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(1)%val ) )                                     &
    60556067                ALLOCATE( t_surf_wall_v_1(1)%val(1:surf_usm_v(1)%ns) )
    60566068             READ ( 13 )  tmp_surf_wall_v(1)%val
    60576069          ENDIF
    6058           CALL surface_restore_elements( t_surf_wall_v_1(1)%val, tmp_surf_wall_v(1)%val,               &
     6070          CALL surface_restore_elements( t_surf_wall_v_1(1)%val, tmp_surf_wall_v(1)%val,           &
    60596071                                         surf_usm_v(1)%start_index, start_index_on_file,           &
    60606072                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    60636075       CASE ( 't_surf_wall_v(2)' )
    60646076          IF ( k == 1 )  THEN
    6065              IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%val ) )                                       &
     6077             IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(2)%val ) )                                     &
    60666078                ALLOCATE( t_surf_wall_v_1(2)%val(1:surf_usm_v(2)%ns) )
    60676079             READ ( 13 )  tmp_surf_wall_v(2)%val
    60686080          ENDIF
    6069           CALL surface_restore_elements( t_surf_wall_v_1(2)%val, tmp_surf_wall_v(2)%val,               &
     6081          CALL surface_restore_elements( t_surf_wall_v_1(2)%val, tmp_surf_wall_v(2)%val,           &
    60706082                                         surf_usm_v(2)%start_index, start_index_on_file,           &
    60716083                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    60746086       CASE ( 't_surf_wall_v(3)' )
    60756087          IF ( k == 1 )  THEN
    6076              IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%val ) )                                       &
     6088             IF ( .NOT.  ALLOCATED( t_surf_wall_v_1(3)%val ) )                                     &
    60776089                ALLOCATE( t_surf_wall_v_1(3)%val(1:surf_usm_v(3)%ns) )
    60786090             READ ( 13 )  tmp_surf_wall_v(3)%val
    60796091          ENDIF
    6080           CALL surface_restore_elements( t_surf_wall_v_1(3)%val, tmp_surf_wall_v(3)%val,               &
     6092          CALL surface_restore_elements( t_surf_wall_v_1(3)%val, tmp_surf_wall_v(3)%val,           &
    60816093                                         surf_usm_v(3)%start_index, start_index_on_file,           &
    60826094                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    60856097       CASE ( 't_surf_window_h(0)' )
    60866098          IF ( k == 1 )  THEN
    6087              IF ( .NOT.  ALLOCATED( t_surf_window_h_1(0)%val ) )                                     &
     6099             IF ( .NOT.  ALLOCATED( t_surf_window_h_1(0)%val ) )                                   &
    60886100                ALLOCATE( t_surf_window_h_1(0)%val(1:surf_usm_h(0)%ns) )
    60896101             READ ( 13 )  tmp_surf_window_h(0)%val
    60906102          ENDIF
    6091           CALL surface_restore_elements( t_surf_window_h_1(0)%val, tmp_surf_window_h(0)%val,           &
     6103          CALL surface_restore_elements( t_surf_window_h_1(0)%val, tmp_surf_window_h(0)%val,       &
    60926104                                         surf_usm_h(0)%start_index, start_index_on_file,           &
    60936105                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    60966108       CASE ( 't_surf_window_h(1)' )
    60976109          IF ( k == 1 )  THEN
    6098              IF ( .NOT.  ALLOCATED( t_surf_window_h_1(1)%val ) )                                     &
     6110             IF ( .NOT.  ALLOCATED( t_surf_window_h_1(1)%val ) )                                   &
    60996111                ALLOCATE( t_surf_window_h_1(1)%val(1:surf_usm_h(1)%ns) )
    61006112             READ ( 13 )  tmp_surf_window_h(1)%val
    61016113          ENDIF
    6102           CALL surface_restore_elements( t_surf_window_h_1(1)%val, tmp_surf_window_h(1)%val,           &
     6114          CALL surface_restore_elements( t_surf_window_h_1(1)%val, tmp_surf_window_h(1)%val,       &
    61036115                                         surf_usm_h(1)%start_index, start_index_on_file,           &
    61046116                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    61076119       CASE ( 't_surf_window_v(0)' )
    61086120          IF ( k == 1 )  THEN
    6109              IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%val ) )                                     &
     6121             IF ( .NOT.  ALLOCATED( t_surf_window_v_1(0)%val ) )                                   &
    61106122                ALLOCATE( t_surf_window_v_1(0)%val(1:surf_usm_v(0)%ns) )
    61116123             READ ( 13 )  tmp_surf_window_v(0)%val
    61126124          ENDIF
    6113           CALL surface_restore_elements( t_surf_window_v_1(0)%val, tmp_surf_window_v(0)%val,           &
     6125          CALL surface_restore_elements( t_surf_window_v_1(0)%val, tmp_surf_window_v(0)%val,       &
    61146126                                         surf_usm_v(0)%start_index, start_index_on_file,           &
    61156127                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    61516163       CASE ( 't_surf_green_h(0)' )
    61526164          IF ( k == 1 )  THEN
    6153              IF ( .NOT.  ALLOCATED( t_surf_green_h_1(0)%val ) )                                      &
     6165             IF ( .NOT.  ALLOCATED( t_surf_green_h_1(0)%val ) )                                    &
    61546166                ALLOCATE( t_surf_green_h_1(0)%val(1:surf_usm_h(0)%ns) )
    61556167             READ ( 13 )  tmp_surf_green_h(0)%val
    61566168          ENDIF
    6157           CALL surface_restore_elements( t_surf_green_h_1(0)%val, tmp_surf_green_h(0)%val,             &
    6158                                          surf_usm_h(0)%start_index, start_index_on_file,         &
     6169          CALL surface_restore_elements( t_surf_green_h_1(0)%val, tmp_surf_green_h(0)%val,         &
     6170                                         surf_usm_h(0)%start_index, start_index_on_file,           &
    61596171                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    61606172                                         nys_on_file, nyn_on_file, nxl_on_file, nxr_on_file )
     
    61626174       CASE ( 't_surf_green_h(1)' )
    61636175          IF ( k == 1 )  THEN
    6164              IF ( .NOT.  ALLOCATED( t_surf_green_h_1(1)%val ) )                                      &
     6176             IF ( .NOT.  ALLOCATED( t_surf_green_h_1(1)%val ) )                                    &
    61656177                ALLOCATE( t_surf_green_h_1(1)%val(1:surf_usm_h(1)%ns) )
    61666178             READ ( 13 )  tmp_surf_green_h(1)%val
    61676179          ENDIF
    6168           CALL surface_restore_elements( t_surf_green_h_1(1)%val, tmp_surf_green_h(1)%val,             &
    6169                                          surf_usm_h(1)%start_index, start_index_on_file,         &
     6180          CALL surface_restore_elements( t_surf_green_h_1(1)%val, tmp_surf_green_h(1)%val,         &
     6181                                         surf_usm_h(1)%start_index, start_index_on_file,           &
    61706182                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    61716183                                         nys_on_file, nyn_on_file, nxl_on_file, nxr_on_file )
     
    61736185       CASE ( 't_surf_green_v(0)' )
    61746186          IF ( k == 1 )  THEN
    6175              IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%val ) )                                      &
     6187             IF ( .NOT.  ALLOCATED( t_surf_green_v_1(0)%val ) )                                    &
    61766188                ALLOCATE( t_surf_green_v_1(0)%val(1:surf_usm_v(0)%ns) )
    61776189             READ ( 13 )  tmp_surf_green_v(0)%val
    61786190          ENDIF
    6179           CALL surface_restore_elements( t_surf_green_v_1(0)%val, tmp_surf_green_v(0)%val,             &
     6191          CALL surface_restore_elements( t_surf_green_v_1(0)%val, tmp_surf_green_v(0)%val,         &
    61806192                                         surf_usm_v(0)%start_index, start_index_on_file,           &
    61816193                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    61846196       CASE ( 't_surf_green_v(1)' )
    61856197          IF ( k == 1 )  THEN
    6186              IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%val ) )                                      &
     6198             IF ( .NOT.  ALLOCATED( t_surf_green_v_1(1)%val ) )                                    &
    61876199                ALLOCATE( t_surf_green_v_1(1)%val(1:surf_usm_v(1)%ns) )
    61886200             READ ( 13 )  tmp_surf_green_v(1)%val
    61896201          ENDIF
    6190           CALL surface_restore_elements( t_surf_green_v_1(1)%val, tmp_surf_green_v(1)%val,             &
     6202          CALL surface_restore_elements( t_surf_green_v_1(1)%val, tmp_surf_green_v(1)%val,         &
    61916203                                         surf_usm_v(1)%start_index, start_index_on_file,           &
    61926204                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    61956207       CASE ( 't_surf_green_v(2)' )
    61966208          IF ( k == 1 )  THEN
    6197              IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%val ) )                                      &
     6209             IF ( .NOT.  ALLOCATED( t_surf_green_v_1(2)%val ) )                                    &
    61986210                ALLOCATE( t_surf_green_v_1(2)%val(1:surf_usm_v(2)%ns) )
    61996211             READ ( 13 )  tmp_surf_green_v(2)%val
    62006212          ENDIF
    6201           CALL surface_restore_elements( t_surf_green_v_1(2)%val, tmp_surf_green_v(2)%val,             &
     6213          CALL surface_restore_elements( t_surf_green_v_1(2)%val, tmp_surf_green_v(2)%val,         &
    62026214                                         surf_usm_v(2)%start_index, start_index_on_file,           &
    62036215                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    62066218       CASE ( 't_surf_green_v(3)' )
    62076219          IF ( k == 1 )  THEN
    6208              IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%val ) )                                      &
     6220             IF ( .NOT.  ALLOCATED( t_surf_green_v_1(3)%val ) )                                    &
    62096221                ALLOCATE( t_surf_green_v_1(3)%val(1:surf_usm_v(3)%ns) )
    62106222             READ ( 13 )  tmp_surf_green_v(3)%val
    62116223          ENDIF
    6212           CALL surface_restore_elements( t_surf_green_v_1(3)%val, tmp_surf_green_v(3)%val,             &
     6224          CALL surface_restore_elements( t_surf_green_v_1(3)%val, tmp_surf_green_v(3)%val,         &
    62136225                                         surf_usm_v(3)%start_index, start_index_on_file,           &
    62146226                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    62436255             READ ( 13 )  tmp_surf_waste_h(0)%val
    62446256          ENDIF
    6245           CALL surface_restore_elements( surf_usm_h(0)%waste_heat, tmp_surf_waste_h(0)%val,          &
     6257          CALL surface_restore_elements( surf_usm_h(0)%waste_heat, tmp_surf_waste_h(0)%val,        &
    62466258                                         surf_usm_h(0)%start_index, start_index_on_file,           &
    62476259                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    62546266             READ ( 13 )  tmp_surf_waste_h(1)%val
    62556267          ENDIF
    6256           CALL surface_restore_elements( surf_usm_h(1)%waste_heat, tmp_surf_waste_h(1)%val,          &
     6268          CALL surface_restore_elements( surf_usm_h(1)%waste_heat, tmp_surf_waste_h(1)%val,        &
    62576269                                         surf_usm_h(1)%start_index, start_index_on_file,           &
    62586270                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    62666278             READ ( 13 )  tmp_surf_waste_v(0)%val
    62676279          ENDIF
    6268           CALL surface_restore_elements( surf_usm_v(0)%waste_heat, tmp_surf_waste_v(0)%val,          &
     6280          CALL surface_restore_elements( surf_usm_v(0)%waste_heat, tmp_surf_waste_v(0)%val,        &
    62696281                                         surf_usm_v(0)%start_index, start_index_on_file,           &
    62706282                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    62776289             READ ( 13 )  tmp_surf_waste_v(1)%val
    62786290          ENDIF
    6279           CALL surface_restore_elements( surf_usm_v(1)%waste_heat, tmp_surf_waste_v(1)%val,          &
     6291          CALL surface_restore_elements( surf_usm_v(1)%waste_heat, tmp_surf_waste_v(1)%val,        &
    62806292                                         surf_usm_v(1)%start_index, start_index_on_file,           &
    62816293                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    62886300             READ ( 13 )  tmp_surf_waste_v(2)%val
    62896301          ENDIF
    6290           CALL surface_restore_elements( surf_usm_v(2)%waste_heat, tmp_surf_waste_v(2)%val,          &
     6302          CALL surface_restore_elements( surf_usm_v(2)%waste_heat, tmp_surf_waste_v(2)%val,        &
    62916303                                         surf_usm_v(2)%start_index, start_index_on_file,           &
    62926304                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    62996311             READ ( 13 )  tmp_surf_waste_v(3)%val
    63006312          ENDIF
    6301           CALL surface_restore_elements( surf_usm_v(3)%waste_heat, tmp_surf_waste_v(3)%val,          &
     6313          CALL surface_restore_elements( surf_usm_v(3)%waste_heat, tmp_surf_waste_v(3)%val,        &
    63026314                                         surf_usm_v(3)%start_index, start_index_on_file,           &
    63036315                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    63046316                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
    63056317
    6306        CASE ( 't_wall_h(0)' )
     6318       CASE ( 't_prev_h(0)' )
    63076319          IF ( k == 1 )  THEN
    6308              IF ( .NOT.  ALLOCATED( t_wall_h_1(0)%val ) )                                            &
    6309                 ALLOCATE( t_wall_h_1(0)%val(nzb_wall:nzt_wall+1, 1:surf_usm_h(0)%ns) )
    6310              READ ( 13 )  tmp_wall_h(0)%val
    6311           ENDIF
    6312           CALL surface_restore_elements( t_wall_h_1(0)%val, tmp_wall_h(0)%val,                         &
     6320             IF ( .NOT.  ALLOCATED( surf_usm_h(0)%t_prev ) )                                       &
     6321                ALLOCATE( surf_usm_h(0)%t_prev(1:surf_usm_h(0)%ns) )
     6322             READ ( 13 )  tmp_surf_t_prev_h(0)%val
     6323          ENDIF
     6324          CALL surface_restore_elements( surf_usm_h(0)%t_prev, tmp_surf_t_prev_h(0)%val,           &
    63136325                                         surf_usm_h(0)%start_index, start_index_on_file,           &
    63146326                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    63156327                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
    63166328
    6317        CASE ( 't_wall_h(1)' )
     6329       CASE ( 't_prev_h(1)' )
    63186330          IF ( k == 1 )  THEN
    6319              IF ( .NOT.  ALLOCATED( t_wall_h_1(1)%val ) )                                            &
    6320                 ALLOCATE( t_wall_h_1(1)%val(nzb_wall:nzt_wall+1, 1:surf_usm_h(1)%ns) )
    6321              READ ( 13 )  tmp_wall_h(1)%val
    6322           ENDIF
    6323           CALL surface_restore_elements( t_wall_h_1(1)%val, tmp_wall_h(1)%val,                         &
     6331             IF ( .NOT.  ALLOCATED( surf_usm_h(1)%t_prev ) )                                       &
     6332                ALLOCATE( surf_usm_h(1)%t_prev(1:surf_usm_h(1)%ns) )
     6333             READ ( 13 )  tmp_surf_t_prev_h(1)%val
     6334          ENDIF
     6335          CALL surface_restore_elements( surf_usm_h(1)%t_prev, tmp_surf_t_prev_h(1)%val,           &
    63246336                                         surf_usm_h(1)%start_index, start_index_on_file,           &
    63256337                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    63266338                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
    63276339
    6328        CASE ( 't_wall_v(0)' )
     6340
     6341       CASE ( 't_prev_v(0)' )
    63296342          IF ( k == 1 )  THEN
    6330              IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%val ) )                                            &
    6331                 ALLOCATE( t_wall_v_1(0)%val(nzb_wall:nzt_wall+1, 1:surf_usm_v(0)%ns) )
    6332              READ ( 13 )  tmp_wall_v(0)%val
    6333           ENDIF
    6334           CALL surface_restore_elements( t_wall_v_1(0)%val, tmp_wall_v(0)%val,                         &
     6343             IF ( .NOT.  ALLOCATED( surf_usm_v(0)%t_prev ) )                                       &
     6344                ALLOCATE( surf_usm_v(0)%t_prev(1:surf_usm_v(0)%ns) )
     6345             READ ( 13 )  tmp_surf_t_prev_v(0)%val
     6346          ENDIF
     6347          CALL surface_restore_elements( surf_usm_v(0)%t_prev, tmp_surf_t_prev_v(0)%val,           &
    63356348                                         surf_usm_v(0)%start_index, start_index_on_file,           &
    63366349                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    63376350                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
    63386351
    6339        CASE ( 't_wall_v(1)' )
     6352       CASE ( 't_prev_v(1)' )
    63406353          IF ( k == 1 )  THEN
    6341              IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%val ) )                                            &
    6342                 ALLOCATE( t_wall_v_1(1)%val(nzb_wall:nzt_wall+1, 1:surf_usm_v(1)%ns) )
    6343              READ ( 13 )  tmp_wall_v(1)%val
    6344           ENDIF
    6345           CALL surface_restore_elements( t_wall_v_1(1)%val, tmp_wall_v(1)%val,                         &
     6354             IF ( .NOT.  ALLOCATED( surf_usm_v(1)%t_prev ) )                                       &
     6355                ALLOCATE( surf_usm_v(1)%t_prev(1:surf_usm_v(1)%ns) )
     6356             READ ( 13 )  tmp_surf_t_prev_v(1)%val
     6357          ENDIF
     6358          CALL surface_restore_elements( surf_usm_v(1)%t_prev, tmp_surf_t_prev_v(1)%val,           &
    63466359                                         surf_usm_v(1)%start_index, start_index_on_file,           &
    63476360                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    63486361                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
    63496362
    6350        CASE ( 't_wall_v(2)' )
     6363       CASE ( 't_prev_v(2)' )
    63516364          IF ( k == 1 )  THEN
    6352              IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%val ) )                                            &
    6353                 ALLOCATE( t_wall_v_1(2)%val(nzb_wall:nzt_wall+1, 1:surf_usm_v(2)%ns) )
    6354              READ ( 13 )  tmp_wall_v(2)%val
    6355           ENDIF
    6356           CALL surface_restore_elements( t_wall_v_1(2)%val, tmp_wall_v(2)%val,                         &
     6365             IF ( .NOT.  ALLOCATED( surf_usm_v(2)%t_prev ) )                                       &
     6366                ALLOCATE( surf_usm_v(2)%t_prev(1:surf_usm_v(2)%ns) )
     6367             READ ( 13 )  tmp_surf_t_prev_v(2)%val
     6368          ENDIF
     6369          CALL surface_restore_elements( surf_usm_v(2)%t_prev, tmp_surf_t_prev_v(2)%val,           &
    63576370                                         surf_usm_v(2)%start_index, start_index_on_file,           &
    63586371                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    63596372                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
    63606373
    6361        CASE ( 't_wall_v(3)' )
     6374       CASE ( 't_prev_v(3)' )
    63626375          IF ( k == 1 )  THEN
    6363              IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%val ) )                                            &
    6364                 ALLOCATE( t_wall_v_1(3)%val(nzb_wall:nzt_wall+1, 1:surf_usm_v(3)%ns) )
    6365              READ ( 13 )  tmp_wall_v(3)%val
    6366           ENDIF
    6367           CALL surface_restore_elements( t_wall_v_1(3)%val, tmp_wall_v(3)%val,                         &
     6376             IF ( .NOT.  ALLOCATED( surf_usm_v(3)%t_prev ) )                                       &
     6377                ALLOCATE( surf_usm_v(3)%t_prev(1:surf_usm_v(3)%ns) )
     6378             READ ( 13 )  tmp_surf_t_prev_v(3)%val
     6379          ENDIF
     6380          CALL surface_restore_elements( surf_usm_v(3)%t_prev, tmp_surf_t_prev_v(3)%val,           &
    63686381                                         surf_usm_v(3)%start_index, start_index_on_file,           &
    63696382                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
    63706383                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
    63716384
     6385       CASE ( 't_wall_h(0)' )
     6386          IF ( k == 1 )  THEN
     6387             IF ( .NOT.  ALLOCATED( t_wall_h_1(0)%val ) )                                          &
     6388                ALLOCATE( t_wall_h_1(0)%val(nzb_wall:nzt_wall+1, 1:surf_usm_h(0)%ns) )
     6389             READ ( 13 )  tmp_wall_h(0)%val
     6390          ENDIF
     6391          CALL surface_restore_elements( t_wall_h_1(0)%val, tmp_wall_h(0)%val,                     &
     6392                                         surf_usm_h(0)%start_index, start_index_on_file,           &
     6393                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     6394                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
     6395
     6396       CASE ( 't_wall_h(1)' )
     6397          IF ( k == 1 )  THEN
     6398             IF ( .NOT.  ALLOCATED( t_wall_h_1(1)%val ) )                                          &
     6399                ALLOCATE( t_wall_h_1(1)%val(nzb_wall:nzt_wall+1, 1:surf_usm_h(1)%ns) )
     6400             READ ( 13 )  tmp_wall_h(1)%val
     6401          ENDIF
     6402          CALL surface_restore_elements( t_wall_h_1(1)%val, tmp_wall_h(1)%val,                     &
     6403                                         surf_usm_h(1)%start_index, start_index_on_file,           &
     6404                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     6405                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
     6406
     6407       CASE ( 't_wall_v(0)' )
     6408          IF ( k == 1 )  THEN
     6409             IF ( .NOT.  ALLOCATED( t_wall_v_1(0)%val ) )                                          &
     6410                ALLOCATE( t_wall_v_1(0)%val(nzb_wall:nzt_wall+1, 1:surf_usm_v(0)%ns) )
     6411             READ ( 13 )  tmp_wall_v(0)%val
     6412          ENDIF
     6413          CALL surface_restore_elements( t_wall_v_1(0)%val, tmp_wall_v(0)%val,                     &
     6414                                         surf_usm_v(0)%start_index, start_index_on_file,           &
     6415                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     6416                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
     6417
     6418       CASE ( 't_wall_v(1)' )
     6419          IF ( k == 1 )  THEN
     6420             IF ( .NOT.  ALLOCATED( t_wall_v_1(1)%val ) )                                          &
     6421                ALLOCATE( t_wall_v_1(1)%val(nzb_wall:nzt_wall+1, 1:surf_usm_v(1)%ns) )
     6422             READ ( 13 )  tmp_wall_v(1)%val
     6423          ENDIF
     6424          CALL surface_restore_elements( t_wall_v_1(1)%val, tmp_wall_v(1)%val,                     &
     6425                                         surf_usm_v(1)%start_index, start_index_on_file,           &
     6426                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     6427                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
     6428
     6429       CASE ( 't_wall_v(2)' )
     6430          IF ( k == 1 )  THEN
     6431             IF ( .NOT.  ALLOCATED( t_wall_v_1(2)%val ) )                                          &
     6432                ALLOCATE( t_wall_v_1(2)%val(nzb_wall:nzt_wall+1, 1:surf_usm_v(2)%ns) )
     6433             READ ( 13 )  tmp_wall_v(2)%val
     6434          ENDIF
     6435          CALL surface_restore_elements( t_wall_v_1(2)%val, tmp_wall_v(2)%val,                     &
     6436                                         surf_usm_v(2)%start_index, start_index_on_file,           &
     6437                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     6438                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
     6439
     6440       CASE ( 't_wall_v(3)' )
     6441          IF ( k == 1 )  THEN
     6442             IF ( .NOT.  ALLOCATED( t_wall_v_1(3)%val ) )                                          &
     6443                ALLOCATE( t_wall_v_1(3)%val(nzb_wall:nzt_wall+1, 1:surf_usm_v(3)%ns) )
     6444             READ ( 13 )  tmp_wall_v(3)%val
     6445          ENDIF
     6446          CALL surface_restore_elements( t_wall_v_1(3)%val, tmp_wall_v(3)%val,                     &
     6447                                         surf_usm_v(3)%start_index, start_index_on_file,           &
     6448                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     6449                                         nys_on_file, nyn_on_file, nxl_on_file,nxr_on_file )
     6450
    63726451       CASE ( 't_window_h(0)' )
    63736452          IF ( k == 1 )  THEN
    6374              IF ( .NOT.  ALLOCATED( t_window_h_1(0)%val ) )                                               &
     6453             IF ( .NOT.  ALLOCATED( t_window_h_1(0)%val ) )                                        &
    63756454                ALLOCATE( t_window_h_1(0)%val(nzb_wall:nzt_wall+1, 1:surf_usm_h(0)%ns) )
    63766455             READ ( 13 )  tmp_window_h(0)%val
    63776456          ENDIF
    6378           CALL surface_restore_elements( t_window_h_1(0)%val, tmp_window_h(0)%val,                     &
     6457          CALL surface_restore_elements( t_window_h_1(0)%val, tmp_window_h(0)%val,                 &
    63796458                                         surf_usm_h(0)%start_index, start_index_on_file,           &
    63806459                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    63836462       CASE ( 't_window_h(1)' )
    63846463          IF ( k == 1 )  THEN
    6385              IF ( .NOT.  ALLOCATED( t_window_h_1(1)%val ) )                                               &
     6464             IF ( .NOT.  ALLOCATED( t_window_h_1(1)%val ) )                                        &
    63866465                ALLOCATE( t_window_h_1(1)%val(nzb_wall:nzt_wall+1, 1:surf_usm_h(1)%ns) )
    63876466             READ ( 13 )  tmp_window_h(1)%val
    63886467          ENDIF
    6389           CALL surface_restore_elements( t_window_h_1(1)%val, tmp_window_h(1)%val,                     &
     6468          CALL surface_restore_elements( t_window_h_1(1)%val, tmp_window_h(1)%val,                 &
    63906469                                         surf_usm_h(1)%start_index, start_index_on_file,           &
    63916470                                         end_index_on_file, nxlc, nysc, nxlf, nxrf, nysf, nynf,    &
     
    65616640       CALL rrd_mpi_io_surface( 't_surf_green_h(' // dum // ')', t_surf_green_h_1(l)%val )
    65626641
    6563        IF ( .NOT.  ALLOCATED( m_liq_usm_h_1(l)%val ) )                                            &
     6642       IF ( .NOT.  ALLOCATED( m_liq_usm_h_1(l)%val ) )                                             &
    65646643          ALLOCATE( m_liq_usm_h_1(l)%val(1:surf_usm_h(l)%ns) )
    65656644       CALL rrd_mpi_io_surface( 'm_liq_usm_h(' // dum // ')', m_liq_usm_h_1(l)%val )
    65666645
    65676646       IF ( indoor_model )  THEN
    6568           IF ( .NOT.  ALLOCATED( surf_usm_h(l)%waste_heat ) )                                     &
     6647          IF ( .NOT.  ALLOCATED( surf_usm_h(l)%waste_heat ) )                                      &
    65696648             ALLOCATE( surf_usm_h(l)%waste_heat(1:surf_usm_h(l)%ns) )
    65706649          CALL rrd_mpi_io_surface( 'waste_heat_h(' // dum // ')', surf_usm_h(l)%waste_heat )
     6650          IF ( .NOT.  ALLOCATED( surf_usm_h(l)%t_prev ) )                                          &
     6651             ALLOCATE( surf_usm_h(l)%t_prev(1:surf_usm_h(l)%ns) )
     6652          CALL rrd_mpi_io_surface( 't_prev_h(' // dum // ')', surf_usm_h(l)%t_prev )
    65716653       ENDIF
    65726654
     
    65966678          ALLOCATE( t_surf_green_v_1(l)%val(1:surf_usm_v(l)%ns) )
    65976679       CALL rrd_mpi_io_surface( 't_surf_green_v(' // dum // ')', t_surf_green_v_1(l)%val)
     6680
     6681       IF ( indoor_model )  THEN
     6682          IF ( .NOT.  ALLOCATED( surf_usm_v(l)%waste_heat ) )                                      &
     6683             ALLOCATE( surf_usm_v(l)%waste_heat(1:surf_usm_v(l)%ns) )
     6684          CALL rrd_mpi_io_surface( 'waste_heat_v(' // dum // ')', surf_usm_v(l)%waste_heat )
     6685          IF ( .NOT.  ALLOCATED( surf_usm_v(l)%t_prev ) )                                          &
     6686             ALLOCATE( surf_usm_v(l)%t_prev(1:surf_usm_v(l)%ns) )
     6687          CALL rrd_mpi_io_surface( 't_prev_v(' // dum // ')', surf_usm_v(l)%t_prev )
     6688       ENDIF
    65986689
    65996690    ENDDO
     
    73727463             CALL wrd_write_string( 'waste_heat_h(' // dum // ')' )
    73737464             WRITE ( 14 )  surf_usm_h(l)%waste_heat
     7465             CALL wrd_write_string( 't_prev_h(' // dum // ')' )
     7466             WRITE ( 14 )  surf_usm_h(l)%t_prev
    73747467          ENDIF
    73757468       ENDDO
     
    73977490             CALL wrd_write_string( 'waste_heat_v(' // dum // ')' )
    73987491             WRITE ( 14 )  surf_usm_v(l)%waste_heat
     7492             CALL wrd_write_string( 't_prev_v(' // dum // ')' )
     7493             WRITE ( 14 )  surf_usm_v(l)%t_prev
    73997494          ENDIF
    74007495
     
    74667561          CALL wrd_mpi_io_surface( 'm_liq_usm_h(' // dum // ')', m_liq_usm_h(l)%val )
    74677562          IF ( indoor_model )  THEN
    7468              CALL wrd_mpi_io_surface( 'waste_heat_h(' // dum // ')', surf_usm_h(l)%waste_heat ) ! NEED TO BE CHECKED!!!!!
     7563             CALL wrd_mpi_io_surface( 'waste_heat_h(' // dum // ')', surf_usm_h(l)%waste_heat )
     7564             CALL wrd_mpi_io_surface( 't_prev_h(' // dum // ')',     surf_usm_h(l)%t_prev     )
    74697565          ENDIF
    74707566
     
    74887584          CALL wrd_mpi_io_surface( 't_surf_green_v(' // dum // ')', t_surf_green_v(l)%val )
    74897585
     7586          IF ( indoor_model )  THEN
     7587             CALL wrd_mpi_io_surface( 'waste_heat_v(' // dum // ')', surf_usm_v(l)%waste_heat )
     7588             CALL wrd_mpi_io_surface( 't_prev_v(' // dum // ')',     surf_usm_v(l)%t_prev     )
     7589          ENDIF
    74907590       ENDDO
    74917591
Note: See TracChangeset for help on using the changeset viewer.