Ignore:
Timestamp:
Oct 26, 2015 4:17:44 PM (9 years ago)
Author:
maronga
Message:

various bugfixes and modifications of the atmosphere-land-surface-radiation interaction. Completely re-written routine to calculate surface fluxes (surface_layer_fluxes.f90) that replaces prandtl_fluxes. Minor formatting corrections and renamings

File:
1 edited

Legend:

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

    r1683 r1691  
    1414! PALM. If not, see <http://www.gnu.org/licenses/>.
    1515!
    16 ! Copyright 1997-2014 Leibniz Universitaet Hannover
     16! Copyright 1997-2015 Leibniz Universitaet Hannover
    1717!--------------------------------------------------------------------------------!
    1818!
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Added option for spin-ups without land surface and radiation models. Moved calls
     22! for radiation and lan surface schemes.
    2223!
    2324! Former revisions:
     
    170171               averaging_interval_sp, bc_lr_cyc, bc_ns_cyc, bc_pt_t_val,       &
    171172               bc_q_t_val, call_psolver_at_all_substeps, cloud_droplets,       &
    172                cloud_physics, constant_heatflux, create_disturbances, dopr_n,  &
    173                constant_diffusion, coupling_mode, coupling_start_time,        &
    174                current_timestep_number, disturbance_created,                   &
    175                disturbance_energy_limit, dist_range, do_sum, dt_3d,            &
    176                dt_averaging_input, dt_averaging_input_pr, dt_coupling,         &
    177                dt_data_output_av, dt_disturb, dt_do2d_xy, dt_do2d_xz,          &
    178                dt_do2d_yz, dt_do3d, dt_domask,dt_dopts, dt_dopr,               &
     173               cloud_physics, constant_flux_layer, constant_heatflux,          &
     174               create_disturbances, dopr_n, constant_diffusion, coupling_mode, &
     175               coupling_start_time, current_timestep_number,                   &
     176               disturbance_created, disturbance_energy_limit, dist_range,      &
     177               do_sum, dt_3d, dt_averaging_input, dt_averaging_input_pr,       &
     178               dt_coupling, dt_data_output_av, dt_disturb, dt_do2d_xy,         &
     179               dt_do2d_xz, dt_do2d_yz, dt_do3d, dt_domask,dt_dopts, dt_dopr,   &
    179180               dt_dopr_listing, dt_dosp, dt_dots, dt_dvrp, dt_run_control,     &
    180181               end_time, first_call_lpm, galilei_transformation, humidity,     &
     
    183184               loop_optimization, lsf_surf, lsf_vert, masks, mid,              &
    184185               netcdf_data_format, neutral, nr_timesteps_this_run, nudging,    &
    185                ocean, on_device, passive_scalar, prandtl_layer, precipitation, &
     186               ocean, on_device, passive_scalar, precipitation,                &
    186187               prho_reference, pt_reference, pt_slope_offset, random_heatflux, &
    187188               run_coupled, simulated_time, simulated_time_chr,                &
     
    213214
    214215    USE land_surface_model_mod,                                                &
    215         ONLY:  land_surface, lsm_energy_balance, lsm_soil_model
     216        ONLY:  land_surface, lsm_energy_balance, lsm_soil_model,               &
     217               skip_time_do_lsm
    216218
    217219    USE ls_forcing_mod,                                                        &
     
    238240
    239241    USE radiation_model_mod,                                                   &
    240         ONLY: dt_radiation, radiation, radiation_clearsky,                     &
    241               radiation_rrtmg, radiation_scheme, time_radiation
     242        ONLY: dt_radiation, force_radiation_call, radiation,                   &
     243              radiation_clearsky, radiation_rrtmg, radiation_scheme,           &
     244              skip_time_do_radiation, time_radiation
    242245
    243246    USE statistics,                                                            &
    244247        ONLY:  flow_statistics_called, hom, pr_palm, sums_ls_l
     248
     249    USE surface_layer_fluxes_mod,                                              &
     250        ONLY:  surface_layer_fluxes
    245251
    246252    USE user_actions_mod,                                                      &
     
    374380          ENDIF
    375381
    376           IF ( radiation .AND. intermediate_timestep_count                     &
    377                == intermediate_timestep_count_max  )  THEN
    378 
    379                time_radiation = time_radiation + dt_3d
    380 
    381              IF ( time_radiation >= dt_radiation )  THEN
    382 
    383                 CALL cpu_log( log_point(50), 'radiation', 'start' )
    384 
    385                 time_radiation = time_radiation - dt_radiation
    386                 IF ( radiation_scheme == 'clear-sky' )  THEN
    387                    CALL radiation_clearsky
    388                 ELSEIF ( radiation_scheme == 'rrtmg' )  THEN
    389                    CALL radiation_rrtmg
    390                 ENDIF
    391 
    392                 CALL cpu_log( log_point(50), 'radiation', 'stop' )
    393              ENDIF
    394           ENDIF
    395382!
    396383!--       Solve the prognostic equations. A fast cache optimized version with
     
    631618!--       velocities at the outflow in case of a non-cyclic lateral wall)
    632619          CALL boundary_conds
    633 
    634 !
    635 !--       When using the land surface model:
    636 !--       1) solve energy balance equation to calculate new skin temperature
    637 !--       2) run soil model
    638           IF ( land_surface )  THEN
    639 
    640              CALL cpu_log( log_point(54), 'land_surface', 'start' )
    641 
    642              CALL lsm_energy_balance
    643              CALL lsm_soil_model
    644 
    645              CALL cpu_log( log_point(54), 'land_surface', 'stop' )
    646 
    647           ENDIF
    648620
    649621!
     
    731703
    732704!
    733 !--          First the vertical fluxes in the Prandtl layer are being computed
    734              IF ( prandtl_layer )  THEN
    735                 CALL cpu_log( log_point(19), 'prandtl_fluxes', 'start' )
    736                 CALL prandtl_fluxes
    737                 CALL cpu_log( log_point(19), 'prandtl_fluxes', 'stop' )
    738              ENDIF
    739 
     705!--          First the vertical fluxes in the surface (constant flux) layer are computed
     706             IF ( constant_flux_layer )  THEN
     707                CALL cpu_log( log_point(19), 'surface_layer_fluxes', 'start' )
     708                CALL surface_layer_fluxes
     709                CALL cpu_log( log_point(19), 'surface_layer_fluxes', 'stop' )
     710             ENDIF
     711
     712!
     713!--          If required, solve the energy balance for the surface and run soil
     714!--          model
     715             IF ( land_surface .AND. simulated_time > skip_time_do_lsm)  THEN
     716
     717                CALL cpu_log( log_point(54), 'land_surface', 'start' )
     718                CALL lsm_energy_balance
     719                CALL lsm_soil_model
     720                CALL cpu_log( log_point(54), 'land_surface', 'stop' )
     721             ENDIF
    740722!
    741723!--          Compute the diffusion coefficients
     
    752734             CALL cpu_log( log_point(17), 'diffusivities', 'stop' )
    753735
     736          ENDIF
     737
     738!
     739!--       If required, calculate radiative fluxes and heating rates
     740          IF ( radiation .AND. intermediate_timestep_count                     &
     741               == intermediate_timestep_count_max .AND. simulated_time >    &
     742               skip_time_do_radiation )  THEN
     743
     744               time_radiation = time_radiation + dt_3d
     745
     746             IF ( time_radiation >= dt_radiation .OR. force_radiation_call )   &
     747             THEN
     748
     749                CALL cpu_log( log_point(50), 'radiation', 'start' )
     750
     751                IF ( .NOT. force_radiation_call )  THEN
     752                   time_radiation = time_radiation - dt_radiation
     753                ELSE
     754                   WRITE(9,*) "Unscheduled radiation call at ", simulated_time
     755                   CALL LOCAL_FLUSH ( 9 )
     756                ENDIF
     757
     758                IF ( radiation_scheme == 'clear-sky' )  THEN
     759                   CALL radiation_clearsky
     760                ELSEIF ( radiation_scheme == 'rrtmg' )  THEN
     761                   CALL radiation_rrtmg
     762                ENDIF
     763
     764                CALL cpu_log( log_point(50), 'radiation', 'stop' )
     765             ENDIF
    754766          ENDIF
    755767
Note: See TracChangeset for help on using the changeset viewer.