Ignore:
Timestamp:
Sep 24, 2018 3:42:55 PM (6 years ago)
Author:
knoop
Message:

Modularization of all bulk cloud physics code components

File:
1 edited

Legend:

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

    r3241 r3274  
    2525! -----------------
    2626! $Id: check_parameters.f90 2520 2017-10-05 13:50:26Z gronemeier &
     27! Modularization of all bulk cloud physics code components
     28!
     29! 2520 2017-10-05 13:50:26Z gronemeier
    2730! unused variables removed
    2831!
     
    298301!
    299302! 1994 2016-08-15 09:52:21Z suehring
    300 ! Add missing check for cloud_physics and cloud_droplets
     303! Add missing check for bulk_cloud_model and cloud_droplets
    301304!
    302305! 1992 2016-08-12 15:14:59Z suehring
     
    665668
    666669    USE arrays_3d
     670
     671    USE bulk_cloud_model_mod,                                                  &
     672        ONLY:  bulk_cloud_model, bcm_check_parameters, bcm_check_data_output,  &
     673               bcm_check_data_output_pr
     674
    667675    USE chemistry_model_mod,                                                   &
    668676        ONLY:  chem_boundary_conds, chem_check_data_output,                    &
    669                chem_check_data_output_pr, chem_species                 
     677               chem_check_data_output_pr, chem_species
    670678    USE chem_modules
    671     USE cloud_parameters
    672     USE constants
     679    USE basic_constants_and_equations_mod
    673680    USE control_parameters
    674681    USE dvrp_variables
     
    10581065          WRITE( action, '(A)' )  'galilei_transformation = .TRUE.'
    10591066       ENDIF
    1060        IF ( cloud_physics )  THEN
    1061           WRITE( action, '(A)' )  'cloud_physics = .TRUE.'
     1067       IF ( bulk_cloud_model )  THEN
     1068          WRITE( action, '(A)' )  'bulk_cloud_model = .TRUE.'
    10621069       ENDIF
    10631070       IF ( cloud_droplets )  THEN
     
    11861193
    11871194    ENDIF
    1188 !
    1189 !-- Check cloud scheme
    1190     IF ( cloud_scheme == 'saturation_adjust' )  THEN
    1191        microphysics_sat_adjust = .TRUE.
    1192        microphysics_seifert    = .FALSE.
    1193        microphysics_kessler    = .FALSE.
    1194        precipitation           = .FALSE.
    1195     ELSEIF ( cloud_scheme == 'seifert_beheng' )  THEN
    1196        microphysics_sat_adjust = .FALSE.
    1197        microphysics_seifert    = .TRUE.
    1198        microphysics_kessler    = .FALSE.
    1199        microphysics_morrison  = .FALSE.
    1200        precipitation           = .TRUE.
    1201     ELSEIF ( cloud_scheme == 'kessler' )  THEN
    1202        microphysics_sat_adjust = .FALSE.
    1203        microphysics_seifert    = .FALSE.
    1204        microphysics_kessler    = .TRUE.
    1205        microphysics_morrison   = .FALSE.
    1206        precipitation           = .TRUE.
    1207     ELSEIF ( cloud_scheme == 'morrison' )  THEN
    1208        microphysics_sat_adjust = .FALSE.
    1209        microphysics_seifert    = .TRUE.
    1210        microphysics_kessler    = .FALSE.
    1211        microphysics_morrison   = .TRUE.
    1212        precipitation           = .TRUE.
    1213     ELSE
    1214        message_string = 'unknown cloud microphysics scheme cloud_scheme ="' // &
    1215                         TRIM( cloud_scheme ) // '"'
    1216        CALL message( 'check_parameters', 'PA0357', 1, 2, 0, 6, 0 )
    1217     ENDIF
    1218 !
    1219 !-- Check aerosol
    1220     IF ( aerosol_bulk == 'nacl' )  THEN
    1221        aerosol_nacl   = .TRUE.
    1222        aerosol_c3h4o4 = .FALSE.
    1223        aerosol_nh4no3 = .FALSE.
    1224     ELSEIF ( aerosol_bulk == 'c3h4o4' )  THEN
    1225        aerosol_nacl   = .FALSE.
    1226        aerosol_c3h4o4 = .TRUE.
    1227        aerosol_nh4no3 = .FALSE.
    1228     ELSEIF ( aerosol_bulk == 'nh4no3' )  THEN
    1229        aerosol_nacl   = .FALSE.
    1230        aerosol_c3h4o4 = .FALSE.
    1231        aerosol_nh4no3 = .TRUE.
    1232     ELSE
    1233        message_string = 'unknown aerosol = "' // TRIM( aerosol_bulk ) // '"'
    1234        CALL message( 'check_parameters', 'PA0469', 1, 2, 0, 6, 0 )
    1235     ENDIF
    12361195
    12371196!
     
    13521311!
    13531312!-- Check for proper settings for microphysics
    1354     IF ( cloud_physics  .AND.  cloud_droplets )  THEN
    1355        message_string = 'cloud_physics = .TRUE. is not allowed with ' //       &
     1313    IF ( bulk_cloud_model  .AND.  cloud_droplets )  THEN
     1314       message_string = 'bulk_cloud_model = .TRUE. is not allowed with ' //    &
    13561315                        'cloud_droplets = .TRUE.'
    13571316       CALL message( 'check_parameters', 'PA0442', 1, 2, 0, 6, 0 )
     
    14581417    ENDIF
    14591418
    1460     IF ( cloud_physics  .AND.  .NOT.  humidity )  THEN
    1461        WRITE( message_string, * ) 'cloud_physics = ', cloud_physics, ' is ',   &
    1462               'not allowed with humidity = ', humidity
     1419    IF ( bulk_cloud_model  .AND.  .NOT.  humidity )  THEN
     1420       WRITE( message_string, * ) 'bulk_cloud_model = ', bulk_cloud_model,     &
     1421              ' is not allowed with humidity = ', humidity
    14631422       CALL message( 'check_parameters', 'PA0034', 1, 2, 0, 6, 0 )
    14641423    ENDIF
     
    14831442!-- When land surface model is used, perform additional checks
    14841443    IF ( land_surface )  CALL lsm_check_parameters
     1444!
     1445!-- When microphysics module is used, perform additional checks
     1446    IF ( bulk_cloud_model )  CALL bcm_check_parameters
    14851447
    14861448!
     
    23942356
    23952357!
    2396 !-- Set the default value for the integration interval of precipitation amount
    2397     IF ( microphysics_seifert  .OR.  microphysics_kessler )  THEN
    2398        IF ( precipitation_amount_interval == 9999999.9_wp )  THEN
    2399           precipitation_amount_interval = dt_do2d_xy
    2400        ELSE
    2401           IF ( precipitation_amount_interval > dt_do2d_xy )  THEN
    2402              WRITE( message_string, * )  'precipitation_amount_interval = ',   &
    2403                  precipitation_amount_interval, ' must not be larger than ',   &
    2404                  'dt_do2d_xy = ', dt_do2d_xy
    2405              CALL message( 'check_parameters', 'PA0090', 1, 2, 0, 6, 0 )
    2406           ENDIF
    2407        ENDIF
    2408     ENDIF
    2409 
    2410 !
    24112358!-- Determine the number of output profiles and check whether they are
    24122359!-- permissible
     
    24472394
    24482395          CASE ( 'pt', '#pt' )
    2449              IF ( .NOT. cloud_physics ) THEN
     2396             IF ( .NOT. bulk_cloud_model ) THEN
    24502397                dopr_index(i) = 4
    24512398                dopr_unit(i)  = 'K'
     
    26822629
    26832630          CASE ( 'qv', '#qv' )
    2684              IF ( .NOT. cloud_physics ) THEN
     2631             IF ( .NOT. bulk_cloud_model ) THEN
    26852632                dopr_index(i) = 41
    26862633                dopr_unit(i)  = 'kg/kg'
     
    27052652
    27062653          CASE ( 'lpt', '#lpt' )
    2707              IF ( .NOT. cloud_physics ) THEN
     2654             IF ( .NOT. bulk_cloud_model ) THEN
    27082655                message_string = 'data_output_pr = ' //                        &
    27092656                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2710                                  'lemented for cloud_physics = .FALSE.'
     2657                                 'lemented for bulk_cloud_model = .FALSE.'
    27112658                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
    27122659             ELSE
     
    28212768
    28222769          CASE ( 'w"qv"' )
    2823              IF ( humidity  .AND.  .NOT.  cloud_physics )  THEN
     2770             IF ( humidity  .AND.  .NOT.  bulk_cloud_model )  THEN
    28242771                dopr_index(i) = 48
    28252772                dopr_unit(i)  = TRIM ( waterflux_output_unit )
    28262773                hom(:,2,48,:) = SPREAD( zw, 2, statistic_regions+1 )
    2827              ELSEIF ( humidity  .AND.  cloud_physics )  THEN
     2774             ELSEIF ( humidity  .AND.  bulk_cloud_model )  THEN
    28282775                dopr_index(i) = 51
    28292776                dopr_unit(i)  = TRIM ( waterflux_output_unit )
     
    28322779                message_string = 'data_output_pr = ' //                        &
    28332780                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2834                                  'lemented for cloud_physics = .FALSE. an' // &
    2835                                  'd humidity = .FALSE.'
     2781                                 'lemented for bulk_cloud_model = .FALSE. ' // &
     2782                                 'and humidity = .FALSE.'
    28362783                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
    28372784             ENDIF
    28382785
    28392786          CASE ( 'w*qv*' )
    2840              IF ( humidity  .AND.  .NOT. cloud_physics )                       &
    2841              THEN
     2787             IF ( humidity  .AND.  .NOT. bulk_cloud_model )  THEN
    28422788                dopr_index(i) = 49
    28432789                dopr_unit(i)  = TRIM ( waterflux_output_unit )
    28442790                hom(:,2,49,:) = SPREAD( zw, 2, statistic_regions+1 )
    2845              ELSEIF( humidity .AND. cloud_physics ) THEN
     2791             ELSEIF( humidity .AND. bulk_cloud_model ) THEN
    28462792                dopr_index(i) = 52
    28472793                dopr_unit(i)  = TRIM ( waterflux_output_unit )
     
    28502796                message_string = 'data_output_pr = ' //                        &
    28512797                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2852                                  'lemented for cloud_physics = .FALSE. an' // &
    2853                                  'd humidity = .FALSE.'
     2798                                 'lemented for bulk_cloud_model = .FALSE. ' // &
     2799                                 'and humidity = .FALSE.'
    28542800                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
    28552801             ENDIF
    28562802
    28572803          CASE ( 'wqv' )
    2858              IF ( humidity  .AND.  .NOT.  cloud_physics )  THEN
     2804             IF ( humidity  .AND.  .NOT.  bulk_cloud_model )  THEN
    28592805                dopr_index(i) = 50
    28602806                dopr_unit(i)  = TRIM ( waterflux_output_unit )
    28612807                hom(:,2,50,:) = SPREAD( zw, 2, statistic_regions+1 )
    2862              ELSEIF ( humidity  .AND.  cloud_physics )  THEN
     2808             ELSEIF ( humidity  .AND.  bulk_cloud_model )  THEN
    28632809                dopr_index(i) = 53
    28642810                dopr_unit(i)  = TRIM ( waterflux_output_unit )
     
    28672813                message_string = 'data_output_pr = ' //                        &
    28682814                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2869                                  'lemented for cloud_physics = .FALSE. an' // &
    2870                                  'd humidity = .FALSE.'
     2815                                 'lemented for bulk_cloud_model = .FALSE. ' // &
     2816                                 'and humidity = .FALSE.'
    28712817                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
    28722818             ENDIF
    28732819
    28742820          CASE ( 'ql' )
    2875              IF (  .NOT.  cloud_physics  .AND.  .NOT.  cloud_droplets )  THEN
     2821             IF (  .NOT.  bulk_cloud_model  .AND.  .NOT.  cloud_droplets )  THEN
    28762822                message_string = 'data_output_pr = ' //                        &
    28772823                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2878                                  'lemented for cloud_physics = .FALSE. and' // &
    2879                                  'cloud_droplets = .FALSE.'
     2824                                 'lemented for bulk_cloud_model = .FALSE. ' // &
     2825                                 'and cloud_droplets = .FALSE.'
    28802826                CALL message( 'check_parameters', 'PA0096', 1, 2, 0, 6, 0 )
    28812827             ELSE
     
    30342980             hom(:,2,120,:) = SPREAD( zw, 2, statistic_regions+1 )
    30352981
    3036           CASE ( 'nc' )
    3037              IF (  .NOT.  cloud_physics )  THEN
    3038                 message_string = 'data_output_pr = ' //                        &
    3039                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    3040                                  'lemented for cloud_physics = .FALSE.'
    3041                 CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
    3042              ELSEIF ( .NOT.  microphysics_morrison )  THEN
    3043                 message_string = 'data_output_pr = ' //                        &
    3044                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    3045                                  'lemented for cloud_scheme /= morrison'
    3046                 CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
    3047              ELSE
    3048                 dopr_index(i) = 89
    3049                 dopr_unit(i)  = '1/m3'
    3050                 hom(:,2,89,:)  = SPREAD( zu, 2, statistic_regions+1 )
    3051              ENDIF
    3052 
    3053           CASE ( 'nr' )
    3054              IF (  .NOT.  cloud_physics )  THEN
    3055                 message_string = 'data_output_pr = ' //                        &
    3056                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    3057                                  'lemented for cloud_physics = .FALSE.'
    3058                 CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
    3059              ELSEIF ( .NOT.  microphysics_seifert )  THEN
    3060                 message_string = 'data_output_pr = ' //                        &
    3061                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    3062                                  'lemented for cloud_scheme /= seifert_beheng'
    3063                 CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
    3064              ELSE
    3065                 dopr_index(i) = 73
    3066                 dopr_unit(i)  = '1/m3'
    3067                 hom(:,2,73,:)  = SPREAD( zu, 2, statistic_regions+1 )
    3068              ENDIF
    3069 
    3070           CASE ( 'qr' )
    3071              IF (  .NOT.  cloud_physics )  THEN
    3072                 message_string = 'data_output_pr = ' //                        &
    3073                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    3074                                  'lemented for cloud_physics = .FALSE.'
    3075                 CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
    3076              ELSEIF ( .NOT.  microphysics_seifert )  THEN
    3077                 message_string = 'data_output_pr = ' //                        &
    3078                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    3079                                  'lemented for cloud_scheme /= seifert_beheng'
    3080                 CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
    3081              ELSE
    3082                 dopr_index(i) = 74
    3083                 dopr_unit(i)  = 'kg/kg'
    3084                 hom(:,2,74,:)  = SPREAD( zu, 2, statistic_regions+1 )
    3085              ENDIF
    3086 
    3087           CASE ( 'qc' )
    3088              IF (  .NOT.  cloud_physics )  THEN
    3089                 message_string = 'data_output_pr = ' //                        &
    3090                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    3091                                  'lemented for cloud_physics = .FALSE.'
    3092                 CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
    3093              ELSE
    3094                 dopr_index(i) = 75
    3095                 dopr_unit(i)  = 'kg/kg'
    3096                 hom(:,2,75,:)  = SPREAD( zu, 2, statistic_regions+1 )
    3097              ENDIF
    3098 
    3099           CASE ( 'prr' )
    3100              IF (  .NOT.  cloud_physics )  THEN
    3101                 message_string = 'data_output_pr = ' //                        &
    3102                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    3103                                  'lemented for cloud_physics = .FALSE.'
    3104                 CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
    3105              ELSEIF ( microphysics_sat_adjust )  THEN
    3106                 message_string = 'data_output_pr = ' //                        &
    3107                                  TRIM( data_output_pr(i) ) // ' is not ava' // &
    3108                                  'ilable for cloud_scheme = saturation_adjust'
    3109                 CALL message( 'check_parameters', 'PA0422', 1, 2, 0, 6, 0 )
    3110              ELSE
    3111                 dopr_index(i) = 76
    3112                 dopr_unit(i)  = 'kg/kg m/s'
    3113                 hom(:,2,76,:)  = SPREAD( zu, 2, statistic_regions+1 )
    3114              ENDIF
    3115 
    31162982          CASE ( 'ug' )
    31172983             dopr_index(i) = 78
     
    31543020             CALL lsm_check_data_output_pr( data_output_pr(i), i, unit,        &
    31553021                                            dopr_unit(i) )
     3022!
     3023!--          Block of microphysics module profile outputs
     3024             IF ( unit == 'illegal'  .AND.  bulk_cloud_model  )  THEN
     3025                   CALL bcm_check_data_output_pr(data_output_pr(i), i, unit,   &
     3026                                                 dopr_unit(i) )
     3027             ENDIF
    31563028
    31573029             IF ( unit == 'illegal' )  THEN
     
    32603132
    32613133          CASE ( 'lpt' )
    3262              IF (  .NOT.  cloud_physics )  THEN
     3134             IF (  .NOT.  bulk_cloud_model )  THEN
    32633135                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3264                          'res cloud_physics = .TRUE.'
     3136                         'res bulk_cloud_model = .TRUE.'
    32653137                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    32663138             ENDIF
    32673139             unit = 'K'
    3268 
    3269           CASE ( 'nc' )
    3270              IF (  .NOT.  cloud_physics )  THEN
    3271                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3272                          'res cloud_physics = .TRUE.'
    3273                 CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    3274              ELSEIF ( .NOT.  microphysics_morrison )  THEN
    3275                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3276                          'res = morrison '
    3277                 CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
    3278              ENDIF
    3279              unit = '1/m3'
    3280 
    3281           CASE ( 'nr' )
    3282              IF (  .NOT.  cloud_physics )  THEN
    3283                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3284                          'res cloud_physics = .TRUE.'
    3285                 CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    3286              ELSEIF ( .NOT.  microphysics_seifert )  THEN
    3287                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3288                          'res cloud_scheme = seifert_beheng'
    3289                 CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
    3290              ENDIF
    3291              unit = '1/m3'
    32923140
    32933141          CASE ( 'pc', 'pr' )
     
    33013149             IF ( TRIM( var ) == 'pr' )  unit = 'm'
    33023150
    3303           CASE ( 'prr' )
    3304              IF (  .NOT.  cloud_physics )  THEN
    3305                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3306                          'res cloud_physics = .TRUE.'
    3307                 CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    3308              ELSEIF ( microphysics_sat_adjust )  THEN
    3309                 message_string = 'output of "' // TRIM( var ) // '" is ' //    &
    3310                          'not available for cloud_scheme = saturation_adjust'
    3311                 CALL message( 'check_parameters', 'PA0423', 1, 2, 0, 6, 0 )
    3312              ENDIF
    3313              unit = 'kg/kg m/s'
    3314 
    33153151          CASE ( 'q', 'vpt' )
    33163152             IF (  .NOT.  humidity )  THEN
     
    33223158             IF ( TRIM( var ) == 'vpt' )  unit = 'K'
    33233159
    3324           CASE ( 'qc' )
    3325              IF (  .NOT.  cloud_physics )  THEN
     3160          CASE ( 'ql' )
     3161             IF ( .NOT.  ( bulk_cloud_model  .OR.  cloud_droplets ) )  THEN
    33263162                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3327                          'res cloud_physics = .TRUE.'
    3328                 CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    3329              ENDIF
    3330              unit = 'kg/kg'
    3331 
    3332           CASE ( 'ql' )
    3333              IF ( .NOT.  ( cloud_physics  .OR.  cloud_droplets ) )  THEN
    3334                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3335                          'res cloud_physics = .TRUE. or cloud_droplets = .TRUE.'
     3163                      'res bulk_cloud_model = .TRUE. or cloud_droplets = .TRUE.'
    33363164                CALL message( 'check_parameters', 'PA0106', 1, 2, 0, 6, 0 )
    33373165             ENDIF
     
    33483176             IF ( TRIM( var ) == 'ql_vp' )  unit = 'none'
    33493177
    3350           CASE ( 'qr' )
    3351              IF (  .NOT.  cloud_physics )  THEN
     3178          CASE ( 'qv' )
     3179             IF (  .NOT.  bulk_cloud_model )  THEN
    33523180                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3353                          'res cloud_physics = .TRUE.'
    3354                 CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    3355              ELSEIF ( .NOT.  microphysics_seifert ) THEN
    3356                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3357                          'res cloud_scheme = seifert_beheng'
    3358                 CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
    3359              ENDIF
    3360              unit = 'kg/kg'
    3361 
    3362           CASE ( 'qv' )
    3363              IF (  .NOT.  cloud_physics )  THEN
    3364                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3365                                  'res cloud_physics = .TRUE.'
     3181                                 'res bulk_cloud_model = .TRUE.'
    33663182                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    33673183             ENDIF
     
    34003216             CONTINUE
    34013217
    3402           CASE ( 'ghf*', 'lwp*', 'ol*', 'pra*', 'prr*', 'qsws*', 'r_a*',       &
     3218          CASE ( 'ghf*', 'lwp*', 'ol*', 'qsws*', 'r_a*',                       &
    34033219                 'shf*', 'ssws*', 't*', 'tsurf*', 'u*', 'z0*', 'z0h*', 'z0q*' )
    34043220             IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
     
    34093225             ENDIF
    34103226
    3411              IF ( TRIM( var ) == 'lwp*'  .AND.  .NOT. cloud_physics )  THEN
     3227             IF ( TRIM( var ) == 'lwp*'  .AND.  .NOT. bulk_cloud_model )  THEN
    34123228                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3413                                  'res cloud_physics = .TRUE.'
     3229                                 'res bulk_cloud_model = .TRUE.'
    34143230                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    3415              ENDIF
    3416              IF ( TRIM( var ) == 'pra*'  .AND.                                 &
    3417                   .NOT. ( microphysics_kessler .OR. microphysics_seifert ) )  THEN
    3418                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3419                                  'res cloud_scheme = kessler or seifert_beheng'
    3420                 CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
    3421              ENDIF
    3422              IF ( TRIM( var ) == 'pra*'  .AND.  j == 1 )  THEN
    3423                 message_string = 'temporal averaging of precipitation ' //     &
    3424                           'amount "' // TRIM( var ) // '" is not possible'
    3425                 CALL message( 'check_parameters', 'PA0113', 1, 2, 0, 6, 0 )
    3426              ENDIF
    3427              IF ( TRIM( var ) == 'prr*'  .AND.                                 &
    3428                   .NOT. ( microphysics_kessler .OR. microphysics_seifert ) )  THEN
    3429                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3430                                  'res cloud_scheme = kessler or seifert_beheng'
    3431                 CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
    34323231             ENDIF
    34333232             IF ( TRIM( var ) == 'qsws*'  .AND.  .NOT.  humidity )  THEN
     
    34603259             IF ( TRIM( var ) == 'lwp*'   )  unit = 'kg/m2'
    34613260             IF ( TRIM( var ) == 'ol*'    )  unit = 'm'
    3462              IF ( TRIM( var ) == 'pra*'   )  unit = 'mm'
    3463              IF ( TRIM( var ) == 'prr*'   )  unit = 'mm/s'
    34643261             IF ( TRIM( var ) == 'qsws*'  )  unit = 'kgm/kgs'
    34653262             IF ( TRIM( var ) == 'r_a*'   )  unit = 's/m'     
     
    34833280
    34843281             CALL tcm_check_data_output ( var, unit )
     3282
     3283!
     3284!--          Block of microphysics module outputs
     3285             IF ( unit == 'illegal'  .AND.  bulk_cloud_model  )  THEN
     3286                CALL bcm_check_data_output ( var, unit )
     3287             ENDIF
    34853288
    34863289             IF ( unit == 'illegal' )  THEN
Note: See TracChangeset for help on using the changeset viewer.