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

    r3274 r3294  
    2525! -----------------
    2626! $Id$
     27! changes concerning modularization of ocean option
     28!
     29! 3274 2018-09-24 15:42:55Z knoop
    2730! Modularization of all bulk cloud physics code components
    2831!
     
    238241    USE arrays_3d,                                                             &
    239242        ONLY:  dzw, e, heatflux_output_conversion, nc, nr, p, pt,              &
    240                precipitation_amount, prr, q, qc, ql, ql_c, ql_v, qr,           &
    241                rho_ocean, s, sa, tend, u, v, vpt, w, zu, zw,                   &
    242                waterflux_output_conversion, hyrho, d_exner
     243               precipitation_amount, prr, q, qc, ql, ql_c, ql_v, qr, s, tend,  &
     244               u, v, vpt, w, zu, zw, waterflux_output_conversion, hyrho, d_exner
    243245
    244246    USE averaging
     
    258260               ibc_uv_b, io_blocks, io_group, land_surface, message_string,    &
    259261               ntdim_2d_xy, ntdim_2d_xz, ntdim_2d_yz,                          &
    260                psolver, section, simulated_time,                               &
     262               ocean_mode, psolver, section, simulated_time,                   &
    261263               time_since_reference_point, uv_exposure
    262264
     
    284286               id_var_time_xy, id_var_time_xz, id_var_time_yz, nc_stat,        &
    285287               netcdf_data_format, netcdf_handle_error
     288
     289    USE ocean_mod,                                                             &
     290        ONLY:  ocean_data_output_2d
    286291
    287292    USE particle_attributes,                                                   &
     
    940945                level_z(nzb+1) = zu(nzb+1)
    941946
    942              CASE ( 'rho_ocean_xy', 'rho_ocean_xz', 'rho_ocean_yz' )
    943                 IF ( av == 0 )  THEN
    944                    to_be_resorted => rho_ocean
    945                 ELSE
    946                    IF ( .NOT. ALLOCATED( rho_ocean_av ) ) THEN
    947                       ALLOCATE( rho_ocean_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    948                       rho_ocean_av = REAL( fill_value, KIND = wp )
    949                    ENDIF
    950                    to_be_resorted => rho_ocean_av
    951                 ENDIF
    952 
    953947             CASE ( 's_xy', 's_xz', 's_yz' )
    954948                IF ( av == 0 )  THEN
     
    960954                   ENDIF
    961955                   to_be_resorted => s_av
    962                 ENDIF
    963 
    964              CASE ( 'sa_xy', 'sa_xz', 'sa_yz' )
    965                 IF ( av == 0 )  THEN
    966                    to_be_resorted => sa
    967                 ELSE
    968                    IF ( .NOT. ALLOCATED( sa_av ) ) THEN
    969                       ALLOCATE( sa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    970                       sa_av = REAL( fill_value, KIND = wp )
    971                    ENDIF
    972                    to_be_resorted => sa_av
    973956                ENDIF
    974957
     
    13061289
    13071290!
    1308 !--             Turbulence closure variables
    1309                 IF ( .NOT. found )  THEN
    1310                    CALL tcm_data_output_2d( av, do2d(av,if), found, grid, mode,&
    1311                                              local_pf, nzb_do, nzt_do )
    1312                 ENDIF
    1313 
    1314 !
    1315 !--             Microphysics module quantities
     1291!--             Quantities of other modules
    13161292                IF ( .NOT. found  .AND.  bulk_cloud_model )  THEN
    13171293                   CALL bcm_data_output_2d( av, do2d(av,if), found, grid, mode,&
     
    13191295                ENDIF
    13201296
    1321 !
    1322 !--             Land surface model quantity
     1297                IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
     1298                   CALL gust_data_output_2d( av, do2d(av,if), found, grid,     &
     1299                                             local_pf, two_d, nzb_do, nzt_do )
     1300                ENDIF
     1301
    13231302                IF ( .NOT. found  .AND.  land_surface )  THEN
    13241303                   CALL lsm_data_output_2d( av, do2d(av,if), found, grid, mode,&
     
    13261305                ENDIF
    13271306
    1328 !
    1329 !--             Radiation quantity
     1307                IF ( .NOT. found  .AND.  ocean_mode )  THEN
     1308                   CALL ocean_data_output_2d( av, do2d(av,if), found, grid,    &
     1309                                              mode, local_pf, nzb_do, nzt_do )
     1310                ENDIF
     1311
    13301312                IF ( .NOT. found  .AND.  radiation )  THEN
    13311313                   CALL radiation_data_output_2d( av, do2d(av,if), found, grid,&
     
    13341316                ENDIF
    13351317
    1336 !
    1337 !--             Gust module quantities
    1338                 IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
    1339                    CALL gust_data_output_2d( av, do2d(av,if), found, grid,     &
    1340                                              local_pf, two_d, nzb_do, nzt_do )
    1341                 ENDIF
    1342 
    1343 !
    1344 !--             UV exposure model quantity
     1318                IF ( .NOT. found )  THEN
     1319                   CALL tcm_data_output_2d( av, do2d(av,if), found, grid, mode,&
     1320                                             local_pf, nzb_do, nzt_do )
     1321                ENDIF
     1322
    13451323                IF ( .NOT. found  .AND.  uv_exposure )  THEN
    13461324                   CALL uvem_data_output_2d( av, do2d(av,if), found, grid,     &
     
    13491327
    13501328!
    1351 !--             User defined quantity
     1329!--             User defined quantities
    13521330                IF ( .NOT. found )  THEN
    13531331                   CALL user_data_output_2d( av, do2d(av,if), found, grid,     &
Note: See TracChangeset for help on using the changeset viewer.