Ignore:
Timestamp:
Mar 15, 2018 9:17:58 AM (6 years ago)
Author:
Giersch
Message:

Reading/Writing? data in case of restart runs revised

File:
1 edited

Legend:

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

    r2881 r2894  
    2525! -----------------
    2626! $Id$
     27! read_var_list has been renamed to rrd_global, all module related _parin
     28! routines are called before reading the global restart data to overwrite them
     29! in case of restart runs
     30!
     31! 2881 2018-03-13 16:24:40Z suehring
    2732! Added flag for switching on/off calculation of soil moisture
    2833!
     
    408413
    409414    USE radiation_model_mod,                                                   &
    410         ONLY: radiation_parin 
     415        ONLY: radiation_parin
     416
     417    USE read_restart_data_mod,                                                 &
     418        ONLY:  rrd_global     
    411419
    412420    USE spectra_mod,                                                           &
     
    614622
    615623!
     624!--       Try to read runtime parameters given by the user for this run
     625!--       (namelist "d3par"). The namelist "d3par" can be omitted. In that case
     626!--       default values are used for the parameters.
     627 12       line = ' '
     628
     629          REWIND ( 11 )
     630          line = ' '
     631          DO   WHILE ( INDEX( line, '&d3par' ) == 0 )
     632             READ ( 11, '(A)', END=20 )  line
     633          ENDDO
     634          BACKSPACE ( 11 )
     635
     636!
     637!--       Read namelist
     638          READ ( 11, d3par )
     639
     640 20       CONTINUE
     641
     642!
     643!--       Check if land surface model is used and read &lsm_par if required
     644          CALL lsm_parin
     645
     646!
     647!--       Check if urban surface model is used and read &urban_surface_par if required
     648          CALL usm_parin
     649
     650!
     651!--       Check if spectra shall be calculated and read spectra_par if required
     652          CALL spectra_parin
     653
     654!
     655!--       Check if radiation model is used and read &radiation_par if required
     656          CALL radiation_parin
     657
     658!
     659!--       Check if gust module is used and read &gust_par if required
     660          CALL gust_parin
     661 
     662 
     663!--       Check if plant canopy model is used and read &canopy_par if required
     664          CALL pcm_parin
     665 
     666!
     667!--       Read control parameters for optionally used model software packages
     668          CALL package_parin
     669
     670!
     671!--       Check if wind turbine model is used and read &wind_turbine_par if
     672!--       required
     673          CALL wtm_parin
     674!
     675!--       Check if virtual flights should be carried out and read &flight_par
     676!--       if required
     677          CALL flight_parin
     678!
     679!--       Check if synthetic turbulence generator is used and read stg_par if
     680!--       required
     681          CALL stg_parin
     682!
     683!--       Read chemistry variables
     684          CALL chem_parin
     685!
     686!--       Check if uv exposure model is used and read &uvexposure_par
     687          CALL uvem_parin
     688!
     689!--       Read user-defined variables
     690          CALL user_parin
     691
     692!
    616693!--       If required, read control parameters from restart file (produced by
    617694!--       a prior run). All PEs are reading from file created by PE0 (see
    618695!--       check_open)
    619  12       IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
    620              CALL read_var_list
    621 
     696          IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
     697
     698             CALL rrd_global
    622699!
    623700!--          Increment the run count
     
    724801
    725802!
    726 !--       Try to read runtime parameters given by the user for this run
    727 !--       (namelist "d3par"). The namelist "d3par" can be omitted. In that case
    728 !--       default values are used for the parameters.
    729           line = ' '
    730 
    731           REWIND ( 11 )
    732           line = ' '
    733           DO   WHILE ( INDEX( line, '&d3par' ) == 0 )
    734              READ ( 11, '(A)', END=20 )  line
    735           ENDDO
    736           BACKSPACE ( 11 )
    737 
    738 !
    739 !--       Read namelist
    740           READ ( 11, d3par )
    741 
    742  20       CONTINUE
    743 
    744 !
    745 !--       Check if land surface model is used and read &lsm_par if required
    746           CALL lsm_parin
    747 
    748 !
    749 !--       Check if urban surface model is used and read &urban_surface_par if required
    750           CALL usm_parin
    751 
    752 !
    753 !--       Check if spectra shall be calculated and read spectra_par if required
    754           CALL spectra_parin
    755 
    756 !
    757 !--       Check if radiation model is used and read &radiation_par if required
    758           CALL radiation_parin
    759 
    760 !
    761 !--       Check if gust module is used and read &gust_par if required
    762           CALL gust_parin
    763  
    764  
    765 !--       Check if plant canopy model is used and read &canopy_par if required
    766           CALL pcm_parin
    767  
    768 !
    769 !--       Read control parameters for optionally used model software packages
    770           CALL package_parin
    771 
    772 !
    773 !--       Check if wind turbine model is used and read &wind_turbine_par if
    774 !--       required
    775           CALL wtm_parin
    776 !
    777 !--       Check if virtual flights should be carried out and read &flight_par
    778 !--       if required
    779           CALL flight_parin
    780 !
    781 !--       Check if synthetic turbulence generator is used and read stg_par if
    782 !--       required
    783           CALL stg_parin
    784 !
    785 !--       Read chemistry variables
    786           CALL chem_parin
    787 !
    788 !--       Check if uv exposure model is used and read &uvexposure_par
    789           CALL uvem_parin
    790 !
    791 !--       Read user-defined variables
    792           CALL user_parin
    793 
    794 !
    795 !--       The restart file will be reopened when reading the subdomain data
    796           IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
    797              CALL close_file( 13 )
    798           ENDIF
    799 
    800 !
    801803!--       Check in case of initial run, if the grid point numbers are well
    802804!--       defined and allocate some arrays which are already needed in
    803805!--       init_pegrid or check_parameters. During restart jobs, these arrays
    804 !--       will be allocated in read_var_list. All other arrays are allocated
     806!--       will be allocated in rrd_global. All other arrays are allocated
    805807!--       in init_3d_model.
    806808          IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
     
    823825!
    824826!--          ATTENTION: in case of changes to the following statement please
    825 !--                  also check the allocate statement in routine read_var_list
     827!--                  also check the allocate statement in routine rrd_global
    826828             ALLOCATE( pt_init(0:nz+1), q_init(0:nz+1), s_init(0:nz+1),        &
    827829                       ref_state(0:nz+1), sa_init(0:nz+1), ug(0:nz+1),         &
Note: See TracChangeset for help on using the changeset viewer.