Ignore:
Timestamp:
Jun 6, 2019 12:16:46 PM (5 years ago)
Author:
schwenkel
Message:

Modularization of all lagrangian particle model code components

File:
1 edited

Legend:

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

    r3761 r4017  
    1 !> @file header.f90
     1! !> @file header.f90
    22!------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
     
    437437        ONLY:  day_of_year_init, time_utc_init
    438438
    439     USE dvrp_variables,                                                        &
    440         ONLY:  use_seperate_pe_for_dvrp_output
    441 
    442439    USE grid_variables,                                                        &
    443440        ONLY:  dx, dy
     
    462459               sa_vertical_gradient, sa_vertical_gradient_level,               &
    463460               sa_vertical_gradient_level_ind
    464 
    465     USE particle_attributes,                                                   &
    466         ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
    467                curvature_solution_effects,                                     &
    468                density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
    469                dt_write_particle_data, end_time_prel,                          &
    470                number_of_particle_groups, particle_advection,                  &
    471                particle_advection_start,                                       &
    472                particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
    473                pst, radius, radius_classes, random_start_position,             &
    474                seed_follows_topography,                                        &
    475                total_number_of_particles, use_sgs_for_particles,               &
    476                vertical_particle_advection, write_particle_statistics
    477461
    478462    USE pegrid
     
    509493   
    510494    CHARACTER (LEN=40) ::  output_format       !< netcdf format
    511    
     495       
    512496    CHARACTER (LEN=70) ::  char1               !< dummy varialbe used for various strings
    513497    CHARACTER (LEN=70) ::  char2               !< string containing informating about the advected distance in case of Galilei transformation
     
    651635       WRITE ( io, 107 )  'y'
    652636    ENDIF
    653     IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
    654637    IF ( numprocs /= maximum_parallel_io_streams )  THEN
    655638       WRITE ( io, 108 )  maximum_parallel_io_streams
     
    18361819    ENDIF
    18371820
    1838 #if defined( __dvrp_graphics )
    1839 !
    1840 !-- Dvrp-output
    1841     IF ( dt_dvrp /= 9999999.9_wp )  THEN
    1842        WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
    1843                           TRIM( dvrp_username ), TRIM( dvrp_directory )
    1844        i = 1
    1845        l = 0
    1846        m = 0
    1847        DO WHILE ( mode_dvrp(i) /= ' ' )
    1848           IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
    1849              READ ( mode_dvrp(i), '(10X,I2)' )  j
    1850              l = l + 1
    1851              IF ( do3d(0,j) /= ' ' )  THEN
    1852                 WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
    1853                                    isosurface_color(:,l)
    1854              ENDIF
    1855           ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
    1856              READ ( mode_dvrp(i), '(6X,I2)' )  j
    1857              m = m + 1
    1858              IF ( do2d(0,j) /= ' ' )  THEN
    1859                 WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
    1860                                    slicer_range_limits_dvrp(:,m)
    1861              ENDIF
    1862           ENDIF
    1863           i = i + 1
    1864        ENDDO
    1865 
    1866        WRITE ( io, 365 )  groundplate_color, superelevation_x, &
    1867                           superelevation_y, superelevation, clip_dvrp_l, &
    1868                           clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
    1869 
    1870        IF ( TRIM( topography ) /= 'flat' )  THEN
    1871           WRITE ( io, 366 )  topography_color
    1872           IF ( cluster_size > 1 )  THEN
    1873              WRITE ( io, 367 )  cluster_size
    1874           ENDIF
    1875        ENDIF
    1876 
    1877     ENDIF
    1878 #endif
    1879 
    1880 
    18811821    WRITE ( io, 99 )
    18821822
     
    19121852       WRITE ( io, 431 )
    19131853    ENDIF
    1914     IF ( humidity  .AND.  cloud_droplets )  THEN
    1915        WRITE ( io, 433 )
    1916        IF ( curvature_solution_effects )  WRITE ( io, 434 )
    1917        IF ( collision_kernel /= 'none' )  THEN
    1918           WRITE ( io, 435 )  TRIM( collision_kernel )
    1919           IF ( collision_kernel(6:9) == 'fast' )  THEN
    1920              WRITE ( io, 436 )  radius_classes, dissipation_classes
    1921           ENDIF
    1922        ELSE
    1923           WRITE ( io, 437 )
    1924        ENDIF
    1925     ENDIF
    1926 
    19271854!
    19281855!-- LES / turbulence parameters
     
    19671894       WRITE ( io, 477 )  q_surface_initial_change       
    19681895    ENDIF
    1969 
    1970     IF ( particle_advection )  THEN
    1971 !
    1972 !--    Particle attributes
    1973        WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
    1974                           bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
    1975                           end_time_prel
    1976        IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
    1977        IF ( random_start_position )  WRITE ( io, 481 )
    1978        IF ( seed_follows_topography )  WRITE ( io, 496 )
    1979        IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
    1980        WRITE ( io, 495 )  total_number_of_particles
    1981        IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
    1982           WRITE ( io, 485 )  dt_write_particle_data
    1983           IF ( netcdf_data_format > 1 )  THEN
    1984              output_format = 'netcdf (64 bit offset) and binary'
    1985           ELSE
    1986              output_format = 'netcdf and binary'
    1987           ENDIF
    1988           IF ( netcdf_deflate == 0 )  THEN
    1989              WRITE ( io, 344 )  output_format
    1990           ELSE
    1991              WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
    1992           ENDIF
    1993        ENDIF
    1994        IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
    1995        IF ( write_particle_statistics )  WRITE ( io, 486 )
    1996 
    1997        WRITE ( io, 487 )  number_of_particle_groups
    1998 
    1999        DO  i = 1, number_of_particle_groups
    2000           IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
    2001              WRITE ( io, 490 )  i, 0.0_wp
    2002              WRITE ( io, 492 )
    2003           ELSE
    2004              WRITE ( io, 490 )  i, radius(i)
    2005              IF ( density_ratio(i) /= 0.0_wp )  THEN
    2006                 WRITE ( io, 491 )  density_ratio(i)
    2007              ELSE
    2008                 WRITE ( io, 492 )
    2009              ENDIF
    2010           ENDIF
    2011           WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
    2012                              pdx(i), pdy(i), pdz(i)
    2013           IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
    2014        ENDDO
    2015 
    2016     ENDIF
    2017 
    20181896
    20191897!
     
    20551933104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
    20561934              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
    2057 105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
    20581935107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
    20591936108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
     
    22782155353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
    22792156354 FORMAT ('       Output format: ',A, '   compressed with level: ',I1/)
    2280 #if defined( __dvrp_graphics )
    2281 360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
    2282             '       Output every      ',F7.1,' s'/ &
    2283             '       Output mode:      ',A/ &
    2284             '       Host / User:      ',A,' / ',A/ &
    2285             '       Directory:        ',A// &
    2286             '       The sequence contains:')
    2287 361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
    2288             '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
    2289 362 FORMAT (/'       Slicer plane ',A/ &
    2290             '       Slicer limits: [',F6.2,',',F6.2,']')
    2291 365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
    2292             '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
    2293                      ')'/ &
    2294             '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
    2295             '                        from y = ',F9.1,' m to y = ',F9.1,' m')
    2296 366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
    2297 367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
    2298 #endif
    22992157400 FORMAT (//' Physical quantities:'/ &
    23002158              ' -------------------'/)
     
    23502208              ' ----------------------------------'/)
    23512209431 FORMAT ('    Humidity is considered, bu no condensation')
    2352 433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
    2353                  'icle model')
    2354 434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
    2355                  ' droplets < 1.0E-6 m')
    2356 435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
    2357 436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
    2358                     'are used'/ &
    2359             '          number of radius classes:       ',I3,'    interval ', &
    2360                        '[1.0E-6,2.0E-4] m'/ &
    2361             '          number of dissipation classes:   ',I2,'    interval ', &
    2362                        '[0,1000] cm**2/s**3')
    2363 437 FORMAT ('    Droplet collision is switched off')
    23642210450 FORMAT (//' LES / Turbulence quantities:'/ &
    23652211              ' ---------------------------'/)
     
    24012247            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
    24022248                 ' the 3D-simulation'/)
    2403 480 FORMAT ('    Particles:'/ &
    2404             '    ---------'// &
    2405             '       Particle advection is active (switched on at t = ', F7.1, &
    2406                     ' s)'/ &
    2407             '       Start of new particle generations every  ',F6.1,' s'/ &
    2408             '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
    2409             '                            bottom:     ', A, ' top:         ', A/&
    2410             '       Maximum particle age:                 ',F9.1,' s'/ &
    2411             '       Advection stopped at t = ',F9.1,' s'/)
    2412 481 FORMAT ('       Particles have random start positions'/)
    2413 482 FORMAT ('          Particles are advected only horizontally'/)
    2414 485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
    2415 486 FORMAT ('       Particle statistics are written on file'/)
    2416 487 FORMAT ('       Number of particle groups: ',I2/)
    2417 488 FORMAT ('       SGS velocity components are used for particle advection'/ &
    2418             '          minimum timestep for advection:', F8.5/)
    2419 489 FORMAT ('       Number of particles simultaneously released at each ', &
    2420                     'point: ', I5/)
    2421 490 FORMAT ('       Particle group ',I2,':'/ &
    2422             '          Particle radius: ',E10.3, 'm')
    2423 491 FORMAT ('          Particle inertia is activated'/ &
    2424             '             density_ratio (rho_fluid/rho_particle) =',F6.3/)
    2425 492 FORMAT ('          Particles are advected only passively (no inertia)'/)
    2426 493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
    2427             '                                         y:',F8.1,' - ',F8.1,' m'/&
    2428             '                                         z:',F8.1,' - ',F8.1,' m'/&
    2429             '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
    2430                        ' m  dz = ',F8.1,' m'/)
    2431 494 FORMAT ('       Output of particle time series in NetCDF format every ', &
    2432                     F8.2,' s'/)
    2433 495 FORMAT ('       Number of particles in total domain: ',I10/)
    2434 496 FORMAT ('       Initial vertical particle positions are interpreted ', &
    2435                     'as relative to the given topography')
    24362249500 FORMAT (//' 1D-Model parameters:'/                           &
    24372250              ' -------------------'//                           &
Note: See TracChangeset for help on using the changeset viewer.