Safe Haskell | None |
---|
Particle tracking for spatial grid for DSMC.
This module is used to sort (classify) particles into ordered vector of cells for collision step or macroscopic parameter sampling. We do not provide any special cell datatype since it varies which cell data is required on every step, so only particles in every cell are stored.
Monad is provided for storing grid options during the whole program run.
- data Cells
- type CellContents = Vector Particle
- getCell :: Cells -> Int -> Maybe CellContents
- cellMap :: (Int -> Maybe CellContents -> a) -> Cells -> Array D DIM1 a
- type Classifier = Particle -> Int
- classifyParticles :: (Int, Classifier) -> Ensemble -> Cells
- data Grid = UniformGrid !Domain !Double !Double !Double
- makeUniformClassifier :: Grid -> (Int, Classifier)
- makeUniformIndexer :: Grid -> Indexer
- type GridMonad = ReaderT GridWares DSMCRootMonad
- data GridWares = GridWares {
- classifier :: (Int, Classifier)
- indexer :: Int -> Point
- volumes :: !(Vector Double)
- runGrid :: GridMonad a -> ParallelSeeds -> Grid -> Body -> Int -> DSMCRootMonad a
- cellVolumes :: ParallelSeeds -> Grid -> Body -> Int -> Vector Double
Generic functions for cells
Particles sorted by cells.
We store contents of all cells in a single densely packed unboxed
vector. Additionally cell count, cell starting positions in vector
(s
) and cell sizes (l
) are stored.
s1 s2 s3 | | | {[ooooooooo][oooo][oooooo]...} cell1 c2 c3 l1=9 l2=4 l3=6
Note that any extra data about cells (like position or volume) should be maintained separately from cell contents. We use this approach because collision sampling and macroscopic parameter calculation require different
type CellContents = Vector ParticleSource
Cell contents with particles.
cellMap :: (Int -> Maybe CellContents -> a) -> Cells -> Array D DIM1 aSource
Map a function over cell indices and contents of every cell.
Particle tracking
type Classifier = Particle -> IntSource
Assuming there's a linear ordering on all cells, Classifier must yield index of cell for given particle.
:: (Int, Classifier) | Cell count and classifier. |
-> Ensemble | |
-> Cells |
Classify particle ensemble into N
cells using the classifier
function.
Classifier's extent must match N
, yielding numbers between 0
and N-1
.
Grids
Domain divided in uniform grid with given steps by X, Y and Z axes.
makeUniformClassifier :: Grid -> (Int, Classifier)Source
Return grid cell count and classifier for a grid.
makeUniformIndexer :: Grid -> IndexerSource
Return indexer for a grid.
Monadic interface
type GridMonad = ReaderT GridWares DSMCRootMonadSource
Monad used to keep grid options and cell volumes. Due to the
low-level Cells
structure we use to store particles sorted in
cells, things may break badly if improper/inconsistent
classifier/indexer parameters are used with cells structure. It
also helps to maintain precalculated cell volumes. See
MacroSamplingMonad
.
Data stored in GridMonad
.
GridWares | |
|
:: GridMonad a | |
-> ParallelSeeds | One-use seeds used for |
-> Grid | |
-> Body | Body within the domain of the grid. |
-> Int | Use that many points to approximate every cell volume. |
-> DSMCRootMonad a |
Run action using spatial subdivision.
:: ParallelSeeds | One-use seeds for cut cell volume approximation. |
-> Grid | |
-> Body | |
-> Int | |
-> Vector Double |
Calculate volumes of grid cells wrt body within the domain. For
every cell, freeVolume
is called with the domain of cell.
Calculation is performed in parallel.
Since our grid are static, this is usually done only once when the grid is first defined. We throw away the used seeds.