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/check_parameters.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 output of Obukhov length (ol) and radiative heating rates for RRTMG.
     22! Added checks for use of radiation / lsm with topography.
    2223!
    2324! Former revisions:
     
    307308    USE transpose_indices
    308309
     310
    309311    IMPLICIT NONE
    310312
     
    650652          WRITE( action, '(A)' )  'cloud_droplets = .TRUE.'
    651653       ENDIF
    652        IF ( .NOT. prandtl_layer )  THEN
    653           WRITE( action, '(A)' )  'prandtl_layer = .FALSE.'
     654       IF ( .NOT. constant_flux_layer )  THEN
     655          WRITE( action, '(A)' )  'constant_flux_layer = .FALSE.'
    654656       ENDIF
    655657       IF ( action /= ' ' )  THEN
     
    10071009       ENDIF
    10081010
    1009        IF ( .NOT. prandtl_layer )  THEN
     1011       IF ( .NOT. constant_flux_layer )  THEN
    10101012          message_string = 'lsm requires '//                                   &
    1011                            'prandtl_layer = .T.'
     1013                           'constant_flux_layer = .T.'
    10121014          CALL message( 'check_parameters', 'PA0400', 1, 2, 0, 6, 0 )
     1015       ENDIF
     1016
     1017       IF ( topography /= 'flat' )  THEN
     1018          message_string = 'lsm cannot be used ' //  &
     1019                           'in combination with  topography /= "flat"'
     1020          CALL message( 'check_parameters', 'PA0415', 1, 2, 0, 6, 0 )
    10131021       ENDIF
    10141022
     
    11961204          CALL message( 'check_parameters', 'PA0411', 1, 2, 0, 6, 0 )
    11971205       ENDIF
    1198 
    1199     ENDIF
    1200 
     1206       IF ( topography /= 'flat' )  THEN
     1207          message_string = 'radiation scheme cannot be used ' //  &
     1208                           'in combination with  topography /= "flat"'
     1209          CALL message( 'check_parameters', 'PA0414', 1, 2, 0, 6, 0 )
     1210       ENDIF
     1211    ENDIF
    12011212
    12021213    IF ( .NOT. ( loop_optimization == 'cache'  .OR.                            &
     
    17291740!-- In case of using a prandtl-layer, calculated (or prescribed) surface
    17301741!-- fluxes have to be used in the diffusion-terms
    1731     IF ( prandtl_layer )  use_surface_fluxes = .TRUE.
     1742    IF ( constant_flux_layer )  use_surface_fluxes = .TRUE.
    17321743
    17331744!
     
    17961807    ELSEIF ( bc_e_b == '(u*)**2+neumann' )  THEN
    17971808       ibc_e_b = 2
    1798        IF ( .NOT. prandtl_layer )  THEN
     1809       IF ( .NOT. constant_flux_layer )  THEN
    17991810          bc_e_b = 'neumann'
    18001811          ibc_e_b = 1
     
    20032014       IF ( surface_waterflux == 9999999.9_wp  )  THEN
    20042015          constant_waterflux = .FALSE.
    2005           IF ( large_scale_forcing )  THEN
     2016          IF ( large_scale_forcing .OR. land_surface )  THEN
    20062017             IF ( ibc_q_b == 0 )  THEN
    20072018                constant_waterflux = .FALSE.
     
    20452056    ELSEIF ( bc_uv_b == 'neumann' )  THEN
    20462057       ibc_uv_b = 1
    2047        IF ( prandtl_layer )  THEN
     2058       IF ( constant_flux_layer )  THEN
    20482059          message_string = 'boundary condition: bc_uv_b = "' // &
    2049                TRIM( bc_uv_b ) // '" is not allowed with prandtl_layer = .TRUE.'
     2060               TRIM( bc_uv_b ) // '" is not allowed with constant_flux_layer'  &
     2061               // ' = .TRUE.'
    20502062          CALL message( 'check_parameters', 'PA0075', 1, 2, 0, 6, 0 )
    20512063       ENDIF
     
    23562368             dopr_unit(i)  = 'm2/s2'
    23572369             hom(:,2,12,:) = SPREAD( zw, 2, statistic_regions+1 )
    2358              IF ( prandtl_layer )  hom(nzb,2,12,:) = zu(1)
     2370             IF ( constant_flux_layer )  hom(nzb,2,12,:) = zu(1)
    23592371
    23602372          CASE ( 'w*u*' )
     
    23672379             dopr_unit(i)  = 'm2/s2'
    23682380             hom(:,2,14,:) = SPREAD( zw, 2, statistic_regions+1 )
    2369              IF ( prandtl_layer )  hom(nzb,2,14,:) = zu(1)
     2381             IF ( constant_flux_layer )  hom(nzb,2,14,:) = zu(1)
    23702382
    23712383          CASE ( 'w*v*' )
     
    23932405             dopr_unit(i)  = 'm2/s2'
    23942406             hom(:,2,19,:) = SPREAD( zw, 2, statistic_regions+1 )
    2395              IF ( prandtl_layer )  hom(nzb,2,19,:) = zu(1)
     2407             IF ( constant_flux_layer )  hom(nzb,2,19,:) = zu(1)
    23962408
    23972409          CASE ( 'wv' )
     
    23992411             dopr_unit(i)  = 'm2/s2'
    24002412             hom(:,2,20,:) = SPREAD( zw, 2, statistic_regions+1 )
    2401              IF ( prandtl_layer )  hom(nzb,2,20,:) = zu(1)
     2413             IF ( constant_flux_layer )  hom(nzb,2,20,:) = zu(1)
    24022414
    24032415          CASE ( 'w*pt*BC' )
     
    31533165             ENDIF
    31543166
     3167          CASE ( 'rad_lw_cs_hr' )
     3168             IF ( (.NOT. radiation) .OR. radiation_scheme /= 'rrtmg' )  THEN
     3169                message_string = 'data_output_pr = ' //                        &
     3170                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     3171                                 'lable for radiation = .FALSE. or ' //        &
     3172                                 'radiation_scheme /= "rrtmg"'
     3173                CALL message( 'check_parameters', 'PA0413', 1, 2, 0, 6, 0 )
     3174             ELSE
     3175                dopr_index(i) = 106
     3176                dopr_unit(i)  = 'K/h'
     3177                hom(:,2,106,:)  = SPREAD( zu, 2, statistic_regions+1 )
     3178             ENDIF
     3179
     3180          CASE ( 'rad_lw_hr' )
     3181             IF ( (.NOT. radiation) .OR. radiation_scheme /= 'rrtmg' )  THEN
     3182                message_string = 'data_output_pr = ' //                        &
     3183                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     3184                                 'lable for radiation = .FALSE. or ' //        &
     3185                                 'radiation_scheme /= "rrtmg"'
     3186                CALL message( 'check_parameters', 'PA0413', 1, 2, 0, 6, 0 )
     3187             ELSE
     3188                dopr_index(i) = 107
     3189                dopr_unit(i)  = 'K/h'
     3190                hom(:,2,107,:)  = SPREAD( zu, 2, statistic_regions+1 )
     3191             ENDIF
     3192
     3193          CASE ( 'rad_sw_cs_hr' )
     3194             IF ( (.NOT. radiation) .OR. radiation_scheme /= 'rrtmg' )  THEN
     3195                message_string = 'data_output_pr = ' //                        &
     3196                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     3197                                 'lable for radiation = .FALSE. or ' //        &
     3198                                 'radiation_scheme /= "rrtmg"'
     3199                CALL message( 'check_parameters', 'PA0413', 1, 2, 0, 6, 0 )
     3200             ELSE
     3201                dopr_index(i) = 108
     3202                dopr_unit(i)  = 'K/h'
     3203                hom(:,2,108,:)  = SPREAD( zu, 2, statistic_regions+1 )
     3204             ENDIF
     3205
     3206          CASE ( 'rad_sw_hr' )
     3207             IF ( (.NOT. radiation) .OR. radiation_scheme /= 'rrtmg' )  THEN
     3208                message_string = 'data_output_pr = ' //                        &
     3209                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     3210                                 'lable for radiation = .FALSE. or ' //        &
     3211                                 'radiation_scheme /= "rrtmg"'
     3212                CALL message( 'check_parameters', 'PA0413', 1, 2, 0, 6, 0 )
     3213             ELSE
     3214                dopr_index(i) = 109
     3215                dopr_unit(i)  = 'K/h'
     3216                hom(:,2,109,:)  = SPREAD( zu, 2, statistic_regions+1 )
     3217             ENDIF
     3218
    31553219          CASE DEFAULT
    31563220
     
    33513415             unit = 'kg/kg'
    33523416
    3353 
    3354           CASE ( 'rad_lw_in', 'rad_lw_out', 'rad_sw_in', 'rad_sw_out' )
     3417          CASE ( 'rad_lw_in', 'rad_lw_out', 'rad_lw_cs_hr', 'rad_lw_hr',       &
     3418                 'rad_sw_in', 'rad_sw_out', 'rad_sw_cs_hr', 'rad_sw_hr' )
    33553419             IF ( .NOT. radiation .OR. radiation_scheme /= 'rrtmg' )  THEN
    3356                 message_string = '"output of "' // TRIM( var ) // '" requi' //  &
     3420                message_string = '"output of "' // TRIM( var ) // '" requi' // &
    33573421                                 'res radiation = .TRUE. and ' //              &
    33583422                                 'radiation_scheme = "rrtmg"'
     
    33953459
    33963460          CASE ( 'c_liq*', 'c_soil*', 'c_veg*', 'ghf_eb*', 'lai*', 'lwp*',     &
    3397                  'm_liq_eb*', 'pra*', 'prr*', 'qsws*', 'qsws_eb*',             &
     3461                 'm_liq_eb*', 'ol*', 'pra*', 'prr*', 'qsws*', 'qsws_eb*',      &
    33983462                 'qsws_liq_eb*', 'qsws_soil_eb*', 'qsws_veg_eb*', 'rad_net*',  &
    33993463                 'rrtm_aldif*', 'rrtm_aldir*', 'rrtm_asdif*', 'rrtm_asdir*',   &
     
    35143578             IF ( TRIM( var ) == 'ghf_eb*')  unit = 'W/m2'
    35153579             IF ( TRIM( var ) == 'lai*'   )  unit = 'none'
    3516              IF ( TRIM( var ) == 'lwp*'   )  unit = 'kg/kg*m'
     3580             IF ( TRIM( var ) == 'lwp*'   )  unit = 'kg/m2'
     3581             IF ( TRIM( var ) == 'm_liq_eb*'     )  unit = 'm'
     3582             IF ( TRIM( var ) == 'ol*'   )   unit = 'm'
    35173583             IF ( TRIM( var ) == 'pra*'   )  unit = 'mm'
    35183584             IF ( TRIM( var ) == 'prr*'   )  unit = 'mm/s'
     
    37883854          constant_diffusion = .TRUE.
    37893855
    3790           IF ( prandtl_layer )  THEN
    3791              message_string = 'prandtl_layer is not allowed with fixed ' //    &
    3792                               'value of km'
     3856          IF ( constant_flux_layer )  THEN
     3857             message_string = 'constant_flux_layer is not allowed with fixed ' &
     3858                              // 'value of km'
    37933859             CALL message( 'check_parameters', 'PA0123', 1, 2, 0, 6, 0 )
    37943860          ENDIF
     
    38163882
    38173883!
    3818 !-- Check value range for rif
    3819     IF ( rif_min >= rif_max )  THEN
    3820        WRITE( message_string, * )  'rif_min = ', rif_min, ' must be less ',    &
    3821                                    'than rif_max = ', rif_max
     3884!-- Check value range for zeta = z/L
     3885    IF ( zeta_min >= zeta_max )  THEN
     3886       WRITE( message_string, * )  'zeta_min = ', zeta_min, ' must be less ',  &
     3887                                   'than zeta_max = ', zeta_max
    38223888       CALL message( 'check_parameters', 'PA0125', 1, 2, 0, 6, 0 )
    38233889    ENDIF
     
    42354301
    42364302!
     4303!-- Check for valid setting of most_method
     4304    IF ( TRIM( most_method ) /= 'circular'  .AND.                              &
     4305         TRIM( most_method ) /= 'newton'  .AND.                                &
     4306         TRIM( most_method ) /= 'lookup' )  THEN
     4307       message_string = 'most_method = "' // TRIM( most_method ) //      &
     4308                        '" is unknown'
     4309       CALL message( 'check_parameters', 'PA0416', 1, 2, 0, 6, 0 )
     4310    ENDIF
     4311
     4312!
    42374313!-- Check &userpar parameters
    42384314    CALL user_check_parameters
Note: See TracChangeset for help on using the changeset viewer.