Ignore:
Timestamp:
Mar 26, 2018 9:39:22 AM (6 years ago)
Author:
maronga
Message:

renamed all Fortran NAMELISTS

File:
1 edited

Legend:

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

    r2930 r2932  
    2828! -----------------
    2929! $Id$
     30! renamed radiation_par to radiation_parameters
     31!
     32! 2930 2018-03-23 16:30:46Z suehring
    3033! Remove default surfaces from radiation model, does not make much sense to
    3134! apply radiation model without energy-balance solvers; Further, add check for
     
    25712574! Description:
    25722575! ------------
    2573 !> Parin for &radiation_par for radiation model
     2576!> Parin for &radiation_parameters for radiation model
    25742577!------------------------------------------------------------------------------!
    25752578    SUBROUTINE radiation_parin
     
    25922595                                  average_radiation,                           &
    25932596                                  surf_reflections, svfnorm_report_thresh
    2594        
     2597   
     2598       NAMELIST /radiation_parameters/   albedo, albedo_type, albedo_lw_dir,   &
     2599                                  albedo_lw_dif, albedo_sw_dir, albedo_sw_dif, &
     2600                                  constant_albedo, dt_radiation, emissivity,   &
     2601                                  lw_radiation, net_radiation,                 &
     2602                                  radiation_scheme, skip_time_do_radiation,    &
     2603                                  sw_radiation, unscheduled_radiation_calls,   &
     2604                                  split_diffusion_radiation,                   &
     2605                                  max_raytracing_dist, min_irrf_value,         &
     2606                                  nrefsteps, mrt_factors, rma_lad_raytrace,    &
     2607                                  dist_max_svf,                                &
     2608                                  average_radiation,                           &
     2609                                  surf_reflections, svfnorm_report_thresh
     2610   
    25952611       line = ' '
    25962612       
    25972613!
    2598 !--    Try to find radiation model package
     2614!--    Try to find radiation model namelist
    25992615       REWIND ( 11 )
    26002616       line = ' '
    2601        DO   WHILE ( INDEX( line, '&radiation_par' ) == 0 )
     2617       DO   WHILE ( INDEX( line, '&radiation_parameters' ) == 0 )
    26022618          READ ( 11, '(A)', END=10 )  line
    26032619       ENDDO
     
    26062622!
    26072623!--    Read user-defined namelist
    2608        READ ( 11, radiation_par )
     2624       READ ( 11, radiation_parameters )
    26092625
    26102626!
    26112627!--    Set flag that indicates that the radiation model is switched on
    26122628       radiation = .TRUE.
     2629       
     2630       GOTO 12
     2631!
     2632!--    Try to find old namelist
     2633 10    REWIND ( 11 )
     2634       line = ' '
     2635       DO   WHILE ( INDEX( line, '&radiation_par' ) == 0 )
     2636          READ ( 11, '(A)', END=12 )  line
     2637       ENDDO
     2638       BACKSPACE ( 11 )
     2639
     2640!
     2641!--    Read user-defined namelist
     2642       READ ( 11, radiation_par )
     2643       
     2644       message_string = 'namelist radiation_par is deprecated and will be ' // &
     2645                     'removed in near future. Please &use namelist ' //        &
     2646                     'radiation_parameters instead'
     2647       CALL message( 'radiation_parin', 'PA0487', 0, 1, 0, 6, 0 )
     2648
     2649       
     2650!
     2651!--    Set flag that indicates that the radiation model is switched on
     2652       radiation = .TRUE.
     2653
     2654 12    CONTINUE
     2655       
     2656
    26132657
    26142658!--    Set radiation_interactions flag according to urban_ and land_surface flag
    2615        IF ( urban_surface  .OR.  land_surface ) radiation_interactions = .TRUE.
    2616 
    2617  10    CONTINUE
     2659       IF ( urban_surface  .OR.  land_surface )  radiation_interactions = .TRUE.
    26182660       
    2619 
    26202661    END SUBROUTINE radiation_parin
    26212662
     
    54515492               CASE DEFAULT
    54525493                  WRITE(message_string, *) 'ERROR: the surface type ',td , ' is not supported for calculating SVF'
    5453                   CALL message( 'radiation_calc_svf', 'PA0XXX', 1, 2, 0, 6, 0 )
     5494                  CALL message( 'radiation_calc_svf', 'PA0488', 1, 2, 0, 6, 0 )
    54545495            END SELECT
    54555496
Note: See TracChangeset for help on using the changeset viewer.