Ignore:
Timestamp:
Dec 14, 2017 5:12:51 PM (7 years ago)
Author:
kanani
Message:

Merge of branch palm4u into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/parin.f90

    r2600 r2696  
    11!> @file parin.f90
    22!------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    44!
    55! PALM is free software: you can redistribute it and/or modify it under the
     
    2525! -----------------
    2626! $Id$
     27! Implementation of uv exposure model (FK)
     28! Added rans_mode and turbulence_closure to inipar (TG)
     29! Implementation of chemistry module
     30! Sorting of USE list (FK)
     31! Forcing implemented, and initialization with inifor (MS)
     32!
     33! 2600 2017-11-01 14:11:20Z raasch
    2734! some comments added and variables renamed concerning r2599
    2835!
     
    316323
    317324    USE arrays_3d,                                                             &
    318         ONLY:  pt_init, q_init, ref_state, s_init, sa_init, ug, u_init, v_init,&
    319                vg
     325        ONLY:  pt_init, q_init, ref_state, s_init, sa_init,                    &     
     326               ug, u_init, v_init, vg
     327
     328#if defined( __chem )
     329    USE chemistry_model_mod,                                                   &
     330        ONLY:  chem_parin
     331       
     332    USE chem_modules
     333#endif
     334
     335    USE control_parameters
     336
     337    USE cpulog,                                                                &
     338        ONLY:  cpu_log_barrierwait
    320339
    321340    USE date_and_time_mod,                                                     &
    322341        ONLY:  day_of_year_init, time_utc_init
    323                
    324     USE plant_canopy_model_mod,                                                &
    325          ONLY: pcm_parin 
    326 
    327     USE control_parameters
    328 
    329     USE cpulog,                                                                &
    330         ONLY:  cpu_log_barrierwait
    331342
    332343    USE dvrp_variables,                                                        &
     
    353364               sigma_bulk, ventilation_effect
    354365
    355 
    356366    USE model_1d_mod,                                                          &
    357367        ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
    358368
    359     USE pegrid
    360 
    361369    USE netcdf_interface,                                                      &
    362370        ONLY:  netcdf_data_format, netcdf_deflate, netcdf_precision
    363371
     372    USE pegrid
     373               
     374    USE plant_canopy_model_mod,                                                &
     375         ONLY: pcm_parin
     376
    364377    USE pmc_interface,                                                         &
    365378        ONLY:  nested_run, nesting_mode
     
    386399        ONLY: usm_parin
    387400
     401    USE uv_exposure_model_mod,                                                 &
     402        ONLY:  uvem_parin
     403
     404    USE vertical_nesting_mod,                                                  &
     405        ONLY:  vnest_start_time
     406
    388407    USE wind_turbine_model_mod,                                                &
    389408        ONLY:  wtm_parin
    390409
    391     USE vertical_nesting_mod,                                                  &
    392         ONLY:  vnest_start_time
    393410
    394411    IMPLICIT NONE
     
    422439             dz_stretch_factor, dz_stretch_level, end_time_1d,                 &
    423440             ensemble_member_nr, e_init, e_min, fft_method,                    &
    424              flux_input_mode, flux_output_mode,                                &
     441             flux_input_mode, flux_output_mode, forcing,                       &
    425442             galilei_transformation, humidity,                                 &
    426443             inflow_damping_height, inflow_damping_width,                      &
     
    439456             pt_vertical_gradient_level, q_surface, q_surface_initial_change,  &
    440457             q_vertical_gradient, q_vertical_gradient_level,                   &
    441              random_generator, random_heatflux,                                &
     458             random_generator, random_heatflux, rans_mode,                     &
    442459             rayleigh_damping_factor, rayleigh_damping_height,                 &
    443460             recycling_width, recycling_yshift,                                &
     
    456473             top_scalarflux, transpose_compute_overlap,                        &
    457474             tunnel_height, tunnel_length, tunnel_width_x, tunnel_width_y,     &
    458              tunnel_wall_depth,                                                &
     475             tunnel_wall_depth, turbulence_closure,                            &
    459476             turbulent_inflow, turbulent_outflow,                              &
    460477             use_subsidence_tendencies, ug_surface, ug_vertical_gradient,      &
     
    617634          ENDIF
    618635
     636          IF ( forcing )  THEN
     637             bc_lr   = 'forcing'
     638             bc_ns   = 'forcing'
     639             bc_uv_t = 'forcing'
     640             bc_pt_t = 'forcing'
     641             bc_q_t  = 'forcing'
     642             bc_s_t  = 'forcing'  ! scalar boundary condition is not clear
     643             bc_p_t  = 'neumann'
     644
     645          ENDIF
     646
    619647!         
    620648!--       In case of nested runs, make sure that initializing_actions =
     
    625653!--       are set properly. An exception is made in case of restart runs and
    626654!--       if user decides to do everything by its own.
    627 !--       MS: is this setting really necessary?
    628           IF ( nest_domain  .AND.  (                                           &
    629                TRIM( initializing_actions ) /= 'read_restart_data'  .OR.       &
    630                TRIM( initializing_actions ) /= 'by_user' ) )  THEN
     655!--       MS: is this really necessary?
     656          IF ( nest_domain  .AND.  .NOT. (                                     &
     657               TRIM( initializing_actions ) == 'read_restart_data'  .OR.       &
     658               TRIM( initializing_actions ) == 'by_user'            .OR.       &
     659               TRIM( initializing_actions ) == 'inifor' ) )  THEN
    631660             initializing_actions = 'set_constant_profiles'
    632661          ENDIF
     
    637666!--       therefore cannot be check in check_parameters
    638667          IF ( bc_lr /= 'cyclic'  .AND.  bc_lr /= 'dirichlet/radiation'  .AND. &
    639                bc_lr /= 'radiation/dirichlet'  .AND.  bc_lr /= 'nested' )  THEN
     668               bc_lr /= 'radiation/dirichlet'  .AND.  bc_lr /= 'nested'  .AND. &
     669               bc_lr /= 'forcing' )  THEN
    640670             message_string = 'unknown boundary condition: bc_lr = "' // &
    641671                              TRIM( bc_lr ) // '"'
     
    643673          ENDIF
    644674          IF ( bc_ns /= 'cyclic'  .AND.  bc_ns /= 'dirichlet/radiation'  .AND. &
    645                bc_ns /= 'radiation/dirichlet'  .AND.  bc_ns /= 'nested' )  THEN
     675               bc_ns /= 'radiation/dirichlet'  .AND.  bc_ns /= 'nested'  .AND. &
     676               bc_ns /= 'forcing' )  THEN
    646677             message_string = 'unknown boundary condition: bc_ns = "' // &
    647678                              TRIM( bc_ns ) // '"'
    648679             CALL message( 'check_parameters', 'PA0050', 1, 2, 0, 6, 0 )
    649680          ENDIF
    650 
    651681!
    652682!--       Set internal variables used for speed optimization in if clauses
     
    707737!--       required
    708738          CALL stg_parin
     739!
     740!--       Read chemistry variables
     741#if defined( __chem )
     742          CALL chem_parin
     743#endif
     744!
     745!--       Check if uv exposure model is used and read &uvexposure_par
     746          CALL uvem_parin
    709747!
    710748!--       Read user-defined variables
Note: See TracChangeset for help on using the changeset viewer.