Ignore:
Timestamp:
Jan 9, 2018 7:03:53 AM (6 years ago)
Author:
maronga
Message:

adjustments in spinup mechanism

File:
1 edited

Legend:

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

    r2724 r2728  
    2525! -----------------
    2626! $Id$
     27! Set velocity componenets to homogeneous values during spinup
     28!
     29! 2724 2018-01-05 12:12:38Z maronga
    2730! Use dt_spinup for all active components during spinup
    2831!
     
    6568 
    6669    USE arrays_3d,                                                             &
    67         ONLY:  pt, pt_p
     70        ONLY:  pt, pt_p, u, v
    6871
    6972    USE control_parameters,                                                    &
     
    7174               coupling_start_time, current_timestep_number,                   &
    7275               data_output_during_spinup, disturbance_created, dopr_n, do_sum, &
    73                dt_averaging_input_pr, dt_dopr, dt_dots, dt_do2d_xy, dt_do3d, dt_run_control,        &
    74                dt_spinup, dt_3d, humidity, intermediate_timestep_count,               &
     76               dt_averaging_input_pr, dt_dopr, dt_dots, dt_do2d_xy, dt_do3d,   &
     77               dt_run_control, dt_spinup, dt_3d, humidity,                     &
     78               intermediate_timestep_count,                                    &
    7579               intermediate_timestep_count_max, land_surface,                  &
    7680               simulated_time, simulated_time_chr,                             &
    77                skip_time_dopr, skip_time_do2d_xy, skip_time_do3d, spinup, spinup_pt_amplitude, &
    78                spinup_pt_mean, spinup_time, timestep_count, timestep_scheme,   &
    79                time_dopr, time_dopr_av, time_dots, time_do2d_xy, time_do3d, time_run_control,           &
    80                time_since_reference_point, urban_surface
     81               skip_time_dopr, skip_time_do2d_xy, skip_time_do3d, spinup,      &
     82               spinup_pt_amplitude, spinup_pt_mean, spinup_time,               &
     83               timestep_count, timestep_scheme, time_dopr, time_dopr_av,       &
     84               time_dots, time_do2d_xy, time_do3d, time_run_control,           &
     85               time_since_reference_point, ug_surface, vg_surface, urban_surface
    8186
    8287    USE constants,                                                             &
     
    141146    REAL(wp) ::  dt_save     !< temporary storage for time step
    142147                 
    143     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_save   !< temporary storage of temperature
    144 
     148    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_save  !< temporary storage of temperature
     149    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_save   !< temporary storage of u wind component
     150    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_save   !< temporary storage of v wind component
     151
     152
     153!
     154!-- Save 3D arrays because they are to be changed for spinup purpose
    145155    ALLOCATE( pt_save(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     156    ALLOCATE( u_save(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     157    ALLOCATE( v_save(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    146158
    147159    CALL exchange_horiz( pt, nbgp )   
     160    CALL exchange_horiz( u,  nbgp ) 
     161    CALL exchange_horiz( v,  nbgp ) 
     162 
    148163    pt_save = pt
     164    u_save  = u
     165    v_save  = v
     166
     167!
     168!-- Set the same wall-adjacent velocity to all grid points. The sign of the
     169!-- original velocity field must be preserved because the surface schemes crash
     170!-- otherwise. The precise reason is still unknown. A minimum velocity of 0.1
     171!-- m/s is used to maintain turbulent transfer at the surface.
     172    u = SIGN(1.0_wp,u) * MAX(ug_surface,0.1_wp)
     173    v = SIGN(1.0_wp,v) * MAX(vg_surface,0.1_wp)
    149174
    150175    dt_save = dt_3d
     
    453478
    454479!
    455 !-- Write back saved temperature to the 3D arrays
    456     pt(:,:,:)   = pt_save
    457     pt_p(:,:,:) = pt_save
     480!-- Write back saved arrays to the 3D arrays
     481    pt   = pt_save
     482    pt_p = pt_save
     483    u    = u_save
     484    v    = v_save
    458485
    459486!
     
    462489
    463490    DEALLOCATE(pt_save)
     491    DEALLOCATE(u_save)
     492    DEALLOCATE(v_save)
    464493
    465494    CALL location_message( 'finished spinup-sequence', .TRUE. )
Note: See TracChangeset for help on using the changeset viewer.