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/data_output_3d.f90

    r3241 r3274  
    2525! -----------------
    2626! $Id$
     27! Modularization of all bulk cloud physics code components
     28!
     29! 3241 2018-09-12 15:02:00Z raasch
    2730! unused variables and format statements removed
    2831!
     
    206209    USE arrays_3d,                                                             &
    207210        ONLY:  e, nc, nr, p, pt, prr, q, qc, ql, ql_c, ql_v, qr, rho_ocean, s, &
    208                sa, tend, u, v, vpt, w
    209        
     211               sa, tend, u, v, vpt, w, d_exner
     212
    210213    USE averaging
    211        
     214
     215    USE basic_constants_and_equations_mod,                                     &
     216        ONLY:  lv_d_cp
     217
     218    USE bulk_cloud_model_mod,                                                  &
     219        ONLY:  bulk_cloud_model, bcm_data_output_3d
     220
    212221    USE chemistry_model_mod,                                                   &
    213222        ONLY:  chem_data_output_3d
    214223
    215     USE cloud_parameters,                                                      &
    216         ONLY:  l_d_cp, pt_d_t
    217        
    218224    USE control_parameters,                                                    &
    219         ONLY:  air_chemistry, cloud_physics, do3d, do3d_no, do3d_time_count,   &
     225        ONLY:  air_chemistry, do3d, do3d_no, do3d_time_count,                  &
    220226               io_blocks, io_group, land_surface, message_string,              &
    221227               ntdim_3d, nz_do3d,  plant_canopy,                               &
    222228               psolver, simulated_time, time_since_reference_point,            &
    223229               urban_surface, varnamelength
    224        
     230
    225231    USE cpulog,                                                                &
    226232        ONLY:  log_point, cpu_log
     
    228234    USE gust_mod,                                                              &
    229235        ONLY: gust_data_output_3d, gust_module_enabled
    230        
     236
    231237    USE indices,                                                               &
    232238        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt,     &
    233239               wall_flags_0
    234        
     240
    235241    USE kinds
    236    
     242
    237243    USE land_surface_model_mod,                                                &
    238244        ONLY: lsm_data_output_3d, nzb_soil, nzt_soil
     
    399405                ENDIF
    400406                to_be_resorted => lpt_av
    401              ENDIF
    402 
    403           CASE ( 'nc' )
    404              IF ( av == 0 )  THEN
    405                 to_be_resorted => nc
    406              ELSE
    407                 IF ( .NOT. ALLOCATED( nc_av ) ) THEN
    408                    ALLOCATE( nc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    409                    nc_av = REAL( fill_value, KIND = wp )
    410                 ENDIF
    411                 to_be_resorted => nc_av
    412              ENDIF
    413 
    414           CASE ( 'nr' )
    415              IF ( av == 0 )  THEN
    416                 to_be_resorted => nr
    417              ELSE
    418                 IF ( .NOT. ALLOCATED( nr_av ) ) THEN
    419                    ALLOCATE( nr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    420                    nr_av = REAL( fill_value, KIND = wp )
    421                 ENDIF
    422                 to_be_resorted => nr_av
    423407             ENDIF
    424408
     
    506490             ENDIF
    507491
    508           CASE ( 'prr' )
    509              IF ( av == 0 )  THEN
    510                 DO  i = nxl, nxr
    511                    DO  j = nys, nyn
    512                       DO  k = nzb_do, nzt_do
    513                          local_pf(i,j,k) = prr(k,j,i)
    514                       ENDDO
    515                    ENDDO
    516                 ENDDO
    517              ELSE
    518                 IF ( .NOT. ALLOCATED( prr_av ) ) THEN
    519                    ALLOCATE( prr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    520                    prr_av = REAL( fill_value, KIND = wp )
    521                 ENDIF
    522                 DO  i = nxl, nxr
    523                    DO  j = nys, nyn
    524                       DO  k = nzb_do, nzt_do
    525                          local_pf(i,j,k) = prr_av(k,j,i)
    526                       ENDDO
    527                    ENDDO
    528                 ENDDO
    529              ENDIF
    530              resorted = .TRUE.
    531 
    532492          CASE ( 'pt' )
    533493             IF ( av == 0 )  THEN
    534                 IF ( .NOT. cloud_physics ) THEN
     494                IF ( .NOT. bulk_cloud_model ) THEN
    535495                   to_be_resorted => pt
    536496                ELSE
     
    538498                      DO  j = nys, nyn
    539499                         DO  k = nzb_do, nzt_do
    540                             local_pf(i,j,k) = pt(k,j,i) + l_d_cp *             &
    541                                                           pt_d_t(k) *          &
     500                            local_pf(i,j,k) = pt(k,j,i) + lv_d_cp *            &
     501                                                          d_exner(k) *         &
    542502                                                          ql(k,j,i)
    543503                         ENDDO
     
    563523                ENDIF
    564524                to_be_resorted => q_av
    565              ENDIF
    566 
    567           CASE ( 'qc' )
    568              IF ( av == 0 )  THEN
    569                 to_be_resorted => qc
    570              ELSE
    571                 IF ( .NOT. ALLOCATED( qc_av ) ) THEN
    572                    ALLOCATE( qc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    573                    qc_av = REAL( fill_value, KIND = wp )
    574                 ENDIF
    575                 to_be_resorted => qc_av
    576525             ENDIF
    577526
     
    647596             ENDIF
    648597
    649           CASE ( 'qr' )
    650              IF ( av == 0 )  THEN
    651                 to_be_resorted => qr
    652              ELSE
    653                 IF ( .NOT. ALLOCATED( qr_av ) ) THEN
    654                    ALLOCATE( qr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    655                    qr_av = REAL( fill_value, KIND = wp )
    656                 ENDIF
    657                 to_be_resorted => qr_av
    658              ENDIF
    659 
    660598          CASE ( 'qv' )
    661599             IF ( av == 0 )  THEN
     
    758696!--       Block of urban surface model outputs   
    759697          CASE ( 'usm_output' )
    760              CALL usm_data_output_3d( av, do3d(av,if), found, local_pf,     &
     698             CALL usm_data_output_3d( av, do3d(av,if), found, local_pf,        &
    761699                                         nzb_do, nzt_do )
    762700
    763701          CASE DEFAULT
    764702
     703             IF ( .NOT. found )  THEN
     704                CALL tcm_data_output_3d( av, do3d(av,if), found, local_pf,     &
     705                                         nzb_do, nzt_do )
     706                resorted = .TRUE.
     707             ENDIF
     708
     709!
     710!--          Microphysic module quantities
     711             IF ( .NOT. found  .AND.  bulk_cloud_model )  THEN
     712                CALL bcm_data_output_3d( av, do3d(av,if), found, local_pf,     &
     713                                         nzb_do, nzt_do )
     714                resorted = .TRUE.
     715             ENDIF
     716
    765717!
    766718!--          Land surface quantity
    767              IF ( land_surface )  THEN
     719             IF ( .NOT. found  .AND.  land_surface )  THEN
    768720!
    769721!--             For soil model quantities, it is required to re-allocate local_pf
     
    788740                ENDIF
    789741
    790              ENDIF
    791 
    792              IF ( .NOT. found )  THEN
    793                 CALL tcm_data_output_3d( av, do3d(av,if), found, local_pf,     &
    794                                          nzb_do, nzt_do )
    795                 resorted = .TRUE.
    796742             ENDIF
    797743
Note: See TracChangeset for help on using the changeset viewer.