Ignore:
Timestamp:
Oct 1, 2018 2:37:10 AM (6 years ago)
Author:
raasch
Message:

modularization of the ocean code

File:
1 edited

Legend:

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

    r3291 r3294  
    2525! -----------------
    2626! $Id$
     27! changes concerning modularization of ocean option
     28!
     29! 3291 2018-09-28 11:33:03Z scharf
    2730! corrected previous commit for 3D topography
    2831!
     
    211214
    212215    USE arrays_3d,                                                             &
    213         ONLY:  dzw, e, heatflux_output_conversion, nc, nr, p, prr, pt,         &
    214                q, qc, ql, ql_c, ql_v, qr, rho_ocean, s, sa, u, v, vpt, w,      &
    215                waterflux_output_conversion, d_exner
     216        ONLY:  dzw, d_exner, e, heatflux_output_conversion, nc, nr, p, prr,    &
     217               pt, q, qc, ql, ql_c, ql_v, qr, s, u, v, vpt, w,                 &
     218               waterflux_output_conversion
    216219
    217220    USE averaging,                                                             &
    218         ONLY:  e_av, ghf_av, lpt_av, lwp_av,                                   &
    219                ol_av, p_av, pc_av, pr_av, pt_av, q_av, ql_av,                  &
    220                ql_c_av, ql_v_av, ql_vp_av, qsws_av, qv_av, r_a_av,             &
    221                rho_ocean_av, s_av, sa_av, shf_av, ssws_av, ts_av, tsurf_av,    &
    222                u_av, us_av, v_av, vpt_av, w_av, z0_av, z0h_av, z0q_av
     221        ONLY:  e_av, ghf_av, lpt_av, lwp_av, ol_av, p_av, pc_av, pr_av, pt_av, &
     222               q_av, ql_av, ql_c_av, ql_v_av, ql_vp_av, qsws_av, qv_av,        &
     223               r_a_av, s_av, shf_av, ssws_av, ts_av, tsurf_av, u_av, us_av,    &
     224               v_av, vpt_av, w_av, z0_av, z0h_av, z0q_av
    223225
    224226    USE basic_constants_and_equations_mod,                                     &
     
    232234
    233235    USE control_parameters,                                                    &
    234         ONLY:  air_chemistry, average_count_3d, doav, doav_n,                  &
    235                land_surface, rho_surface, urban_surface, uv_exposure,          &
     236        ONLY:  air_chemistry, average_count_3d, doav, doav_n, land_surface,    &
     237               ocean_mode, rho_surface, urban_surface, uv_exposure,            &
    236238               varnamelength
    237239
     
    249251    USE land_surface_model_mod,                                                &
    250252        ONLY:  lsm_3d_data_averaging
     253
     254    USE ocean_mod,                                                             &
     255        ONLY:  ocean_3d_data_averaging
    251256
    252257    USE particle_attributes,                                                   &
     
    412417                r_a_av = 0.0_wp
    413418
    414              CASE ( 'rho_ocean' )
    415                 IF ( .NOT. ALLOCATED( rho_ocean_av ) )  THEN
    416                    ALLOCATE( rho_ocean_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    417                 ENDIF
    418                 rho_ocean_av = 0.0_wp
    419 
    420419             CASE ( 's' )
    421420                IF ( .NOT. ALLOCATED( s_av ) )  THEN
     
    423422                ENDIF
    424423                s_av = 0.0_wp
    425 
    426              CASE ( 'sa' )
    427                 IF ( .NOT. ALLOCATED( sa_av ) )  THEN
    428                    ALLOCATE( sa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    429                 ENDIF
    430                 sa_av = 0.0_wp
    431424
    432425             CASE ( 'shf*' )
     
    501494                ENDIF
    502495                z0q_av = 0.0_wp
     496
     497             CASE ( 'usm_output' )
    503498!             
    504 !--          Block of urban surface model outputs
    505              CASE ( 'usm_output' )
    506 
     499!--             Block of urban surface model outputs
    507500                CALL usm_average_3d_data( 'allocate', doav(ii) )
    508501             
     
    511504
    512505!
    513 !--             Turbulence closure module
    514                 CALL tcm_3d_data_averaging( 'allocate', doav(ii) )
    515 
    516 !
    517 !--             Microphysics module quantities
     506!--             Allocating and initializing data arrays for other modules
    518507                IF ( bulk_cloud_model )  THEN
    519508                   CALL bcm_3d_data_averaging( 'allocate', doav(ii) )
    520509                ENDIF
    521510
    522 !
    523 !--             Land surface quantity
     511                IF ( air_chemistry  .AND.  trimvar(1:3) == 'kc_')  THEN
     512                   CALL chem_3d_data_averaging( 'allocate', doav(ii) )
     513                ENDIF
     514
     515                IF ( gust_module_enabled )  THEN
     516                   CALL gust_3d_data_averaging( 'allocate', doav(ii) )
     517                ENDIF
     518
    524519                IF ( land_surface )  THEN
    525520                   CALL lsm_3d_data_averaging( 'allocate', doav(ii) )
    526521                ENDIF
    527522
    528 !
    529 !--             Radiation quantity
     523                IF ( ocean_mode )  THEN
     524                   CALL ocean_3d_data_averaging( 'allocate', doav(ii) )
     525                ENDIF
     526
    530527                IF ( radiation )  THEN
    531528                   CALL radiation_3d_data_averaging( 'allocate', doav(ii) )
    532529                ENDIF
    533530
    534 !
    535 !--             Gust module quantities
    536                 IF ( gust_module_enabled )  THEN
    537                    CALL gust_3d_data_averaging( 'allocate', doav(ii) )
    538                 ENDIF
    539 
    540 !
    541 !--             Chemical quantity                                           
    542                 IF ( air_chemistry  .AND.  trimvar(1:3) == 'kc_')  THEN
    543                    CALL chem_3d_data_averaging( 'allocate', doav(ii) )
    544                 ENDIF
    545 
    546 !
    547 !--             UV exposure quantity
    548531                IF ( uv_exposure  .AND.  trimvar(1:5) == 'uvem_')  THEN
    549532                   CALL uvem_3d_data_averaging( 'allocate', doav(ii) )
    550533                ENDIF
    551534
    552 !
    553 !--             User-defined quantity
     535                CALL tcm_3d_data_averaging( 'allocate', doav(ii) )
     536
     537!
     538!--             User-defined quantities
    554539                CALL user_3d_data_averaging( 'allocate', doav(ii) )
    555540
     
    877862             ENDIF
    878863
    879           CASE ( 'rho_ocean' )
    880              IF ( ALLOCATED( rho_ocean_av ) ) THEN
    881                 DO  i = nxlg, nxrg
    882                    DO  j = nysg, nyng
    883                       DO  k = nzb, nzt+1
    884                          rho_ocean_av(k,j,i) = rho_ocean_av(k,j,i) + rho_ocean(k,j,i)
    885                       ENDDO
    886                    ENDDO
    887                 ENDDO
    888              ENDIF 
    889 
    890864          CASE ( 's' )
    891865             IF ( ALLOCATED( s_av ) ) THEN
     
    894868                      DO  k = nzb, nzt+1
    895869                         s_av(k,j,i) = s_av(k,j,i) + s(k,j,i)
    896                       ENDDO
    897                    ENDDO
    898                 ENDDO
    899              ENDIF
    900 
    901           CASE ( 'sa' )
    902              IF ( ALLOCATED( sa_av ) ) THEN
    903                 DO  i = nxlg, nxrg
    904                    DO  j = nysg, nyng
    905                       DO  k = nzb, nzt+1
    906                          sa_av(k,j,i) = sa_av(k,j,i) + sa(k,j,i)
    907870                      ENDDO
    908871                   ENDDO
     
    11821145                ENDDO
    11831146             ENDIF
     1147
     1148          CASE ( 'usm_output' )
    11841149!             
    1185 !--       Block of urban surface model outputs.
    1186 !--       In case of urban surface variables it should be always checked
    1187 !--       if respective arrays are allocated, at least in case of a restart
    1188 !--       run, as averaged usm arrays are not read from file at the moment.
    1189           CASE ( 'usm_output' )
     1150!--          Block of urban surface model outputs.
     1151!--          In case of urban surface variables it should be always checked
     1152!--          if respective arrays are allocated, at least in case of a restart
     1153!--          run, as averaged usm arrays are not read from file at the moment.
    11901154             CALL usm_average_3d_data( 'allocate', doav(ii) )
    11911155             CALL usm_average_3d_data( 'sum', doav(ii) )
     
    11931157          CASE DEFAULT
    11941158!
    1195 !--          Turbulence closure module
    1196              CALL tcm_3d_data_averaging( 'sum', doav(ii) )
    1197 
    1198 !
    1199 !--          Microphysics module quantities
     1159!--          Summing up data from other modules
    12001160             IF ( bulk_cloud_model )  THEN
    12011161                CALL bcm_3d_data_averaging( 'sum', doav(ii) )
    12021162             ENDIF
    12031163
    1204 !
    1205 !--          Land surface quantity
     1164             IF ( air_chemistry  .AND.  trimvar(1:3) == 'kc_')  THEN
     1165                CALL chem_3d_data_averaging( 'sum',doav(ii) )
     1166             ENDIF
     1167
     1168             IF ( gust_module_enabled )  THEN
     1169                CALL gust_3d_data_averaging( 'sum', doav(ii) )
     1170             ENDIF
     1171
    12061172             IF ( land_surface )  THEN
    12071173                CALL lsm_3d_data_averaging( 'sum', doav(ii) )
    12081174             ENDIF
    12091175
    1210 !
    1211 !--          Radiation quantity
     1176             IF ( ocean_mode )  THEN
     1177                CALL ocean_3d_data_averaging( 'sum', doav(ii) )
     1178             ENDIF
     1179
    12121180             IF ( radiation )  THEN
    12131181                CALL radiation_3d_data_averaging( 'sum', doav(ii) )
    12141182             ENDIF
    12151183
    1216 !
    1217 !--          Gust module quantities
    1218              IF ( gust_module_enabled )  THEN
    1219                 CALL gust_3d_data_averaging( 'sum', doav(ii) )
    1220              ENDIF
    1221 
    1222 !
    1223 !--          Chemical quantity
    1224              IF ( air_chemistry  .AND.  trimvar(1:3) == 'kc_')  THEN
    1225                 CALL chem_3d_data_averaging( 'sum',doav(ii) )
    1226              ENDIF
    1227 
    1228 !
    1229 !--          UV exposure quantity
     1184             CALL tcm_3d_data_averaging( 'sum', doav(ii) )
     1185
    12301186             IF ( uv_exposure )  THEN
    12311187                CALL uvem_3d_data_averaging( 'sum', doav(ii) )
     
    12331189
    12341190!
    1235 !--          User-defined quantity
     1191!--          User-defined quantities
    12361192             CALL user_3d_data_averaging( 'sum', doav(ii) )
    12371193
Note: See TracChangeset for help on using the changeset viewer.