Ignore:
Timestamp:
Jun 9, 2017 11:57:32 AM (7 years ago)
Author:
suehring
Message:

Enable restarts with USM with different number of PEs; some bugfixes in new surface structure in USM; formatting adjustments and descriptions in surface_mod

File:
1 edited

Legend:

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

    r2233 r2269  
    2525! -----------------
    2626! $Id$
     27! Enable restart runs for urban_surface_mod
     28!
     29! 2233 2017-05-30 18:08:54Z suehring
    2730!
    2831! 2232 2017-05-30 17:47:52Z suehring
     
    132135    USE control_parameters,                                                    &
    133136        ONLY:  iran, land_surface, message_string, outflow_l, outflow_n,       &
    134                outflow_r, outflow_s
     137               outflow_r, outflow_s, urban_surface
    135138
    136139    USE cpulog,                                                                &
     
    165168    USE surface_mod,                                                           &
    166169        ONLY :  surface_read_restart_data
     170       
     171    USE urban_surface_mod,                                                     &
     172        ONLY:  usm_read_restart_data
    167173
    168174    IMPLICIT NONE
     
    10121018                                      nys_on_file, offset_xa, offset_ya,       &
    10131019                                      overlap_count(i), tmp_2d )
     1020
     1021       ENDIF
     1022       
     1023!
     1024!--    Read land surface restart data
     1025       IF ( urban_surface )  THEN
     1026          CALL usm_read_restart_data( i, nxlfa, nxl_on_file, nxrfa,            &
     1027                                      nxr_on_file, nynfa, nyn_on_file, nysfa,  &
     1028                                      nys_on_file, offset_xa, offset_ya,       &
     1029                                      overlap_count(i) )
    10141030       ENDIF
    10151031
Note: See TracChangeset for help on using the changeset viewer.