nspace-0.2.0.0: Efficient, infinite-precision 2D and 3D spatial containers.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.OctTree

Synopsis

Documentation

data OctTree a Source #

A type mapping values at (infinitely precise) locations in 3D space. That is, you can consider an OctTree to be a function V3 Rational -> a, equipped with efficient means of querying the space.

OctTrees should usually be constructed using their Monoidal or Applicative interfaces, as well as by way of the fill function.

Constructors

OctTree 

Fields

Instances

Instances details
Applicative OctTree Source # 
Instance details

Defined in Data.OctTree

Methods

pure :: a -> OctTree a #

(<*>) :: OctTree (a -> b) -> OctTree a -> OctTree b #

liftA2 :: (a -> b -> c) -> OctTree a -> OctTree b -> OctTree c #

(*>) :: OctTree a -> OctTree b -> OctTree b #

(<*) :: OctTree a -> OctTree b -> OctTree a #

Functor OctTree Source # 
Instance details

Defined in Data.OctTree

Methods

fmap :: (a -> b) -> OctTree a -> OctTree b #

(<$) :: a -> OctTree b -> OctTree a #

Monoid a => Monoid (OctTree a) Source # 
Instance details

Defined in Data.OctTree

Methods

mempty :: OctTree a #

mappend :: OctTree a -> OctTree a -> OctTree a #

mconcat :: [OctTree a] -> OctTree a #

Semigroup a => Semigroup (OctTree a) Source # 
Instance details

Defined in Data.OctTree

Methods

(<>) :: OctTree a -> OctTree a -> OctTree a #

sconcat :: NonEmpty (OctTree a) -> OctTree a #

stimes :: Integral b => b -> OctTree a -> OctTree a #

Num a => Num (OctTree a) Source # 
Instance details

Defined in Data.OctTree

Methods

(+) :: OctTree a -> OctTree a -> OctTree a #

(-) :: OctTree a -> OctTree a -> OctTree a #

(*) :: OctTree a -> OctTree a -> OctTree a #

negate :: OctTree a -> OctTree a #

abs :: OctTree a -> OctTree a #

signum :: OctTree a -> OctTree a #

fromInteger :: Integer -> OctTree a #

Show a => Show (OctTree a) Source # 
Instance details

Defined in Data.OctTree

Methods

showsPrec :: Int -> OctTree a -> ShowS #

show :: OctTree a -> String #

showList :: [OctTree a] -> ShowS #

Eq a => Eq (OctTree a) Source # 
Instance details

Defined in Data.OctTree

Methods

(==) :: OctTree a -> OctTree a -> Bool #

(/=) :: OctTree a -> OctTree a -> Bool #

Semilattice a => Semilattice (OctTree a) Source # 
Instance details

Defined in Data.OctTree

Methods

(/\) :: OctTree a -> OctTree a -> OctTree a Source #

Constructing OctTrees

fill :: forall a. Cube Rational -> a -> OctTree a -> OctTree a Source #

Fill a Cube with the given value in an OctTree

combineAla :: forall n a. (Coercible a n, Semigroup n) => (a -> n) -> OctTree a -> OctTree a -> OctTree a Source #

Combine two OctTrees using a different semigroup than usual. For example, in order to replace any values in ot1 with those covered by ot2, we can use:

combineAla Last ot1 ot2

Spatially Querying OctTrees

lookup :: V3 Rational -> OctTree a -> a Source #

Get the value at the given position in the OctTree.

query :: Semilattice s => (a -> s) -> Cube Rational -> OctTree a -> s Source #

Query a region of space in an OctTree. This method is a special case of foldMap, specialized to finite regions.

For example, if you'd like to check if everything in the Cube has a specific value, use All as your choice of Semilattice. If you'd like to check whether anything in the space has a value, instead use Any.

Eliminating OctTrees

fuse :: Eq a => OctTree a -> OctTree a Source #

Fuse together all adjacent regions of space which contain the same value. This will speed up subsequent queries, but requires traversing the entire tree.

elements :: Ord a => OctTree a -> Set a Source #

Get the unique elements contained in the OctTree.

toCubes :: OctTree a -> [(Cube Rational, a)] Source #

Partition the OctTree into contiguous, singular-valued Cubes. Satsifies the law

foldMap (uncurry $ cube (defaultValue ot)) (toCubes ot) == ot

boundingCube :: OctTree a -> Cube Rational Source #

Get a Cube guaranteed to bound all of the non-defaulted values in the OctTree.

defaultValue :: OctTree a -> a Source #

Get the value used to fill the infinity of space in an OctTree.

Constructing Cubes

data Cube a Source #

An axis-aligned bounding box in 3-space.

Constructors

Cube 

Fields

Instances

Instances details
Functor Cube Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

fmap :: (a -> b) -> Cube a -> Cube b #

(<$) :: a -> Cube b -> Cube a #

Generic (Cube a) Source # 
Instance details

Defined in Data.OctTree.Internal

Associated Types

type Rep (Cube a) :: Type -> Type #

Methods

from :: Cube a -> Rep (Cube a) x #

to :: Rep (Cube a) x -> Cube a #

Read a => Read (Cube a) Source # 
Instance details

Defined in Data.OctTree.Internal

Show a => Show (Cube a) Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

showsPrec :: Int -> Cube a -> ShowS #

show :: Cube a -> String #

showList :: [Cube a] -> ShowS #

Eq a => Eq (Cube a) Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

(==) :: Cube a -> Cube a -> Bool #

(/=) :: Cube a -> Cube a -> Bool #

Ord a => Ord (Cube a) Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

compare :: Cube a -> Cube a -> Ordering #

(<) :: Cube a -> Cube a -> Bool #

(<=) :: Cube a -> Cube a -> Bool #

(>) :: Cube a -> Cube a -> Bool #

(>=) :: Cube a -> Cube a -> Bool #

max :: Cube a -> Cube a -> Cube a #

min :: Cube a -> Cube a -> Cube a #

type Rep (Cube a) Source # 
Instance details

Defined in Data.OctTree.Internal

type Rep (Cube a) = D1 ('MetaData "Cube" "Data.OctTree.Internal" "nspace-0.2.0.0-JcrzAw5ubjR6TX1H0E6SmC" 'False) (C1 ('MetaCons "Cube" 'PrefixI 'True) (S1 ('MetaSel ('Just "r_pos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Just "r_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a))))

mkCubeByPow :: Integer -> Cube Rational Source #

Construct a Cube centered around $(0, 0, 0)$, with side length $2n$.

Eliminating Cubes

midpoint :: Fractional a => Cube a -> V3 a Source #

Compute the center of a Cube.

subdivide :: Fractional a => Cube a -> Oct (Cube a) Source #

Subdivide a Cube into eight Cubes which fill up the same volume.

cubeCorners :: Num a => Cube a -> Oct (V3 a) Source #

Get the co-ordinates of the corners of a Cube.

Indexing Types

data V3 a #

A 3-dimensional vector

Constructors

V3 !a !a !a 

Instances

Instances details
Representable V3 
Instance details

Defined in Linear.V3

Associated Types

type Rep V3 #

Methods

tabulate :: (Rep V3 -> a) -> V3 a #

index :: V3 a -> Rep V3 -> a #

MonadFix V3 
Instance details

Defined in Linear.V3

Methods

mfix :: (a -> V3 a) -> V3 a #

MonadZip V3 
Instance details

Defined in Linear.V3

Methods

mzip :: V3 a -> V3 b -> V3 (a, b) #

mzipWith :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

munzip :: V3 (a, b) -> (V3 a, V3 b) #

Foldable V3 
Instance details

Defined in Linear.V3

Methods

fold :: Monoid m => V3 m -> m #

foldMap :: Monoid m => (a -> m) -> V3 a -> m #

foldMap' :: Monoid m => (a -> m) -> V3 a -> m #

foldr :: (a -> b -> b) -> b -> V3 a -> b #

foldr' :: (a -> b -> b) -> b -> V3 a -> b #

foldl :: (b -> a -> b) -> b -> V3 a -> b #

foldl' :: (b -> a -> b) -> b -> V3 a -> b #

foldr1 :: (a -> a -> a) -> V3 a -> a #

foldl1 :: (a -> a -> a) -> V3 a -> a #

toList :: V3 a -> [a] #

null :: V3 a -> Bool #

length :: V3 a -> Int #

elem :: Eq a => a -> V3 a -> Bool #

maximum :: Ord a => V3 a -> a #

minimum :: Ord a => V3 a -> a #

sum :: Num a => V3 a -> a #

product :: Num a => V3 a -> a #

Eq1 V3 
Instance details

Defined in Linear.V3

Methods

liftEq :: (a -> b -> Bool) -> V3 a -> V3 b -> Bool #

Ord1 V3 
Instance details

Defined in Linear.V3

Methods

liftCompare :: (a -> b -> Ordering) -> V3 a -> V3 b -> Ordering #

Read1 V3 
Instance details

Defined in Linear.V3

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V3 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V3 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V3 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V3 a] #

Show1 V3 
Instance details

Defined in Linear.V3

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V3 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V3 a] -> ShowS #

Traversable V3 
Instance details

Defined in Linear.V3

Methods

traverse :: Applicative f => (a -> f b) -> V3 a -> f (V3 b) #

sequenceA :: Applicative f => V3 (f a) -> f (V3 a) #

mapM :: Monad m => (a -> m b) -> V3 a -> m (V3 b) #

sequence :: Monad m => V3 (m a) -> m (V3 a) #

Applicative V3 
Instance details

Defined in Linear.V3

Methods

pure :: a -> V3 a #

(<*>) :: V3 (a -> b) -> V3 a -> V3 b #

liftA2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

(*>) :: V3 a -> V3 b -> V3 b #

(<*) :: V3 a -> V3 b -> V3 a #

Functor V3 
Instance details

Defined in Linear.V3

Methods

fmap :: (a -> b) -> V3 a -> V3 b #

(<$) :: a -> V3 b -> V3 a #

Monad V3 
Instance details

Defined in Linear.V3

Methods

(>>=) :: V3 a -> (a -> V3 b) -> V3 b #

(>>) :: V3 a -> V3 b -> V3 b #

return :: a -> V3 a #

Serial1 V3 
Instance details

Defined in Linear.V3

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V3 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V3 a) #

Distributive V3 
Instance details

Defined in Linear.V3

Methods

distribute :: Functor f => f (V3 a) -> V3 (f a) #

collect :: Functor f => (a -> V3 b) -> f a -> V3 (f b) #

distributeM :: Monad m => m (V3 a) -> V3 (m a) #

collectM :: Monad m => (a -> V3 b) -> m a -> V3 (m b) #

Foldable1 V3 
Instance details

Defined in Linear.V3

Methods

fold1 :: Semigroup m => V3 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V3 a -> m #

foldMap1' :: Semigroup m => (a -> m) -> V3 a -> m #

toNonEmpty :: V3 a -> NonEmpty a #

maximum :: Ord a => V3 a -> a #

minimum :: Ord a => V3 a -> a #

head :: V3 a -> a #

last :: V3 a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> V3 a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V3 a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> V3 a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V3 a -> b #

Hashable1 V3 
Instance details

Defined in Linear.V3

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V3 a -> Int #

Metric V3 
Instance details

Defined in Linear.V3

Methods

dot :: Num a => V3 a -> V3 a -> a #

quadrance :: Num a => V3 a -> a #

qd :: Num a => V3 a -> V3 a -> a #

distance :: Floating a => V3 a -> V3 a -> a #

norm :: Floating a => V3 a -> a #

signorm :: Floating a => V3 a -> V3 a #

Finite V3 
Instance details

Defined in Linear.V3

Associated Types

type Size V3 :: Nat #

Methods

toV :: V3 a -> V (Size V3) a #

fromV :: V (Size V3) a -> V3 a #

R1 V3 
Instance details

Defined in Linear.V3

Methods

_x :: Lens' (V3 a) a #

R2 V3 
Instance details

Defined in Linear.V3

Methods

_y :: Lens' (V3 a) a #

_xy :: Lens' (V3 a) (V2 a) #

R3 V3 
Instance details

Defined in Linear.V3

Methods

_z :: Lens' (V3 a) a #

_xyz :: Lens' (V3 a) (V3 a) #

Additive V3 
Instance details

Defined in Linear.V3

Methods

zero :: Num a => V3 a #

(^+^) :: Num a => V3 a -> V3 a -> V3 a #

(^-^) :: Num a => V3 a -> V3 a -> V3 a #

lerp :: Num a => a -> V3 a -> V3 a -> V3 a #

liftU2 :: (a -> a -> a) -> V3 a -> V3 a -> V3 a #

liftI2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Apply V3 
Instance details

Defined in Linear.V3

Methods

(<.>) :: V3 (a -> b) -> V3 a -> V3 b #

(.>) :: V3 a -> V3 b -> V3 b #

(<.) :: V3 a -> V3 b -> V3 a #

liftF2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Bind V3 
Instance details

Defined in Linear.V3

Methods

(>>-) :: V3 a -> (a -> V3 b) -> V3 b #

join :: V3 (V3 a) -> V3 a #

Traversable1 V3 
Instance details

Defined in Linear.V3

Methods

traverse1 :: Apply f => (a -> f b) -> V3 a -> f (V3 b) #

sequence1 :: Apply f => V3 (f b) -> f (V3 b) #

Generic1 V3 
Instance details

Defined in Linear.V3

Associated Types

type Rep1 V3 :: k -> Type #

Methods

from1 :: forall (a :: k). V3 a -> Rep1 V3 a #

to1 :: forall (a :: k). Rep1 V3 a -> V3 a #

Unbox a => Vector Vector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicUnsafeFreeze :: Mutable Vector s (V3 a) -> ST s (Vector (V3 a)) #

basicUnsafeThaw :: Vector (V3 a) -> ST s (Mutable Vector s (V3 a)) #

basicLength :: Vector (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a) #

basicUnsafeIndexM :: Vector (V3 a) -> Int -> Box (V3 a) #

basicUnsafeCopy :: Mutable Vector s (V3 a) -> Vector (V3 a) -> ST s () #

elemseq :: Vector (V3 a) -> V3 a -> b -> b #

Unbox a => MVector MVector (V3 a) 
Instance details

Defined in Linear.V3

Methods

basicLength :: MVector s (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V3 a) -> MVector s (V3 a) #

basicOverlaps :: MVector s (V3 a) -> MVector s (V3 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V3 a)) #

basicInitialize :: MVector s (V3 a) -> ST s () #

basicUnsafeReplicate :: Int -> V3 a -> ST s (MVector s (V3 a)) #

basicUnsafeRead :: MVector s (V3 a) -> Int -> ST s (V3 a) #

basicUnsafeWrite :: MVector s (V3 a) -> Int -> V3 a -> ST s () #

basicClear :: MVector s (V3 a) -> ST s () #

basicSet :: MVector s (V3 a) -> V3 a -> ST s () #

basicUnsafeCopy :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () #

basicUnsafeMove :: MVector s (V3 a) -> MVector s (V3 a) -> ST s () #

basicUnsafeGrow :: MVector s (V3 a) -> Int -> ST s (MVector s (V3 a)) #

Data a => Data (V3 a) 
Instance details

Defined in Linear.V3

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V3 a -> c (V3 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V3 a) #

toConstr :: V3 a -> Constr #

dataTypeOf :: V3 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V3 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V3 a)) #

gmapT :: (forall b. Data b => b -> b) -> V3 a -> V3 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V3 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V3 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

Storable a => Storable (V3 a) 
Instance details

Defined in Linear.V3

Methods

sizeOf :: V3 a -> Int #

alignment :: V3 a -> Int #

peekElemOff :: Ptr (V3 a) -> Int -> IO (V3 a) #

pokeElemOff :: Ptr (V3 a) -> Int -> V3 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V3 a) #

pokeByteOff :: Ptr b -> Int -> V3 a -> IO () #

peek :: Ptr (V3 a) -> IO (V3 a) #

poke :: Ptr (V3 a) -> V3 a -> IO () #

Monoid a => Monoid (V3 a) 
Instance details

Defined in Linear.V3

Methods

mempty :: V3 a #

mappend :: V3 a -> V3 a -> V3 a #

mconcat :: [V3 a] -> V3 a #

Semigroup a => Semigroup (V3 a) 
Instance details

Defined in Linear.V3

Methods

(<>) :: V3 a -> V3 a -> V3 a #

sconcat :: NonEmpty (V3 a) -> V3 a #

stimes :: Integral b => b -> V3 a -> V3 a #

Bounded a => Bounded (V3 a) 
Instance details

Defined in Linear.V3

Methods

minBound :: V3 a #

maxBound :: V3 a #

Floating a => Floating (V3 a) 
Instance details

Defined in Linear.V3

Methods

pi :: V3 a #

exp :: V3 a -> V3 a #

log :: V3 a -> V3 a #

sqrt :: V3 a -> V3 a #

(**) :: V3 a -> V3 a -> V3 a #

logBase :: V3 a -> V3 a -> V3 a #

sin :: V3 a -> V3 a #

cos :: V3 a -> V3 a #

tan :: V3 a -> V3 a #

asin :: V3 a -> V3 a #

acos :: V3 a -> V3 a #

atan :: V3 a -> V3 a #

sinh :: V3 a -> V3 a #

cosh :: V3 a -> V3 a #

tanh :: V3 a -> V3 a #

asinh :: V3 a -> V3 a #

acosh :: V3 a -> V3 a #

atanh :: V3 a -> V3 a #

log1p :: V3 a -> V3 a #

expm1 :: V3 a -> V3 a #

log1pexp :: V3 a -> V3 a #

log1mexp :: V3 a -> V3 a #

Generic (V3 a) 
Instance details

Defined in Linear.V3

Associated Types

type Rep (V3 a) :: Type -> Type #

Methods

from :: V3 a -> Rep (V3 a) x #

to :: Rep (V3 a) x -> V3 a #

Ix a => Ix (V3 a) 
Instance details

Defined in Linear.V3

Methods

range :: (V3 a, V3 a) -> [V3 a] #

index :: (V3 a, V3 a) -> V3 a -> Int #

unsafeIndex :: (V3 a, V3 a) -> V3 a -> Int #

inRange :: (V3 a, V3 a) -> V3 a -> Bool #

rangeSize :: (V3 a, V3 a) -> Int #

unsafeRangeSize :: (V3 a, V3 a) -> Int #

Num a => Num (V3 a) 
Instance details

Defined in Linear.V3

Methods

(+) :: V3 a -> V3 a -> V3 a #

(-) :: V3 a -> V3 a -> V3 a #

(*) :: V3 a -> V3 a -> V3 a #

negate :: V3 a -> V3 a #

abs :: V3 a -> V3 a #

signum :: V3 a -> V3 a #

fromInteger :: Integer -> V3 a #

Read a => Read (V3 a) 
Instance details

Defined in Linear.V3

Fractional a => Fractional (V3 a) 
Instance details

Defined in Linear.V3

Methods

(/) :: V3 a -> V3 a -> V3 a #

recip :: V3 a -> V3 a #

fromRational :: Rational -> V3 a #

Show a => Show (V3 a) 
Instance details

Defined in Linear.V3

Methods

showsPrec :: Int -> V3 a -> ShowS #

show :: V3 a -> String #

showList :: [V3 a] -> ShowS #

Binary a => Binary (V3 a) 
Instance details

Defined in Linear.V3

Methods

put :: V3 a -> Put #

get :: Get (V3 a) #

putList :: [V3 a] -> Put #

Serial a => Serial (V3 a) 
Instance details

Defined in Linear.V3

Methods

serialize :: MonadPut m => V3 a -> m () #

deserialize :: MonadGet m => m (V3 a) #

Serialize a => Serialize (V3 a) 
Instance details

Defined in Linear.V3

Methods

put :: Putter (V3 a) #

get :: Get (V3 a) #

NFData a => NFData (V3 a) 
Instance details

Defined in Linear.V3

Methods

rnf :: V3 a -> () #

Eq a => Eq (V3 a) 
Instance details

Defined in Linear.V3

Methods

(==) :: V3 a -> V3 a -> Bool #

(/=) :: V3 a -> V3 a -> Bool #

Ord a => Ord (V3 a) 
Instance details

Defined in Linear.V3

Methods

compare :: V3 a -> V3 a -> Ordering #

(<) :: V3 a -> V3 a -> Bool #

(<=) :: V3 a -> V3 a -> Bool #

(>) :: V3 a -> V3 a -> Bool #

(>=) :: V3 a -> V3 a -> Bool #

max :: V3 a -> V3 a -> V3 a #

min :: V3 a -> V3 a -> V3 a #

Hashable a => Hashable (V3 a) 
Instance details

Defined in Linear.V3

Methods

hashWithSalt :: Int -> V3 a -> Int #

hash :: V3 a -> Int #

Ixed (V3 a) 
Instance details

Defined in Linear.V3

Methods

ix :: Index (V3 a) -> Traversal' (V3 a) (IxValue (V3 a)) #

Epsilon a => Epsilon (V3 a) 
Instance details

Defined in Linear.V3

Methods

nearZero :: V3 a -> Bool #

Random a => Random (V3 a) 
Instance details

Defined in Linear.V3

Methods

randomR :: RandomGen g => (V3 a, V3 a) -> g -> (V3 a, g) #

random :: RandomGen g => g -> (V3 a, g) #

randomRs :: RandomGen g => (V3 a, V3 a) -> g -> [V3 a] #

randoms :: RandomGen g => g -> [V3 a] #

Unbox a => Unbox (V3 a) 
Instance details

Defined in Linear.V3

FoldableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

ifoldMap :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifoldMap' :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifoldr :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

ifoldr' :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl' :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

FunctorWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

imap :: (E V3 -> a -> b) -> V3 a -> V3 b #

TraversableWithIndex (E V3) V3 
Instance details

Defined in Linear.V3

Methods

itraverse :: Applicative f => (E V3 -> a -> f b) -> V3 a -> f (V3 b) #

Lift a => Lift (V3 a :: Type) 
Instance details

Defined in Linear.V3

Methods

lift :: Quote m => V3 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => V3 a -> Code m (V3 a) #

Each (V3 a) (V3 b) a b 
Instance details

Defined in Linear.V3

Methods

each :: Traversal (V3 a) (V3 b) a b #

Field1 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_1 :: Lens (V3 a) (V3 a) a a #

Field2 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_2 :: Lens (V3 a) (V3 a) a a #

Field3 (V3 a) (V3 a) a a 
Instance details

Defined in Linear.V3

Methods

_3 :: Lens (V3 a) (V3 a) a a #

type Rep V3 
Instance details

Defined in Linear.V3

type Rep V3 = E V3
type Size V3 
Instance details

Defined in Linear.V3

type Size V3 = 3
type Rep1 V3 
Instance details

Defined in Linear.V3

data MVector s (V3 a) 
Instance details

Defined in Linear.V3

data MVector s (V3 a) = MV_V3 !Int !(MVector s a)
type Rep (V3 a) 
Instance details

Defined in Linear.V3

type Index (V3 a) 
Instance details

Defined in Linear.V3

type Index (V3 a) = E V3
type IxValue (V3 a) 
Instance details

Defined in Linear.V3

type IxValue (V3 a) = a
data Vector (V3 a) 
Instance details

Defined in Linear.V3

data Vector (V3 a) = V_V3 !Int !(Vector a)

data Oct a Source #

An 8-tuple of values.

Constructors

Oct !(V4 a) !(V4 a) 

Instances

Instances details
Foldable Oct Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

fold :: Monoid m => Oct m -> m #

foldMap :: Monoid m => (a -> m) -> Oct a -> m #

foldMap' :: Monoid m => (a -> m) -> Oct a -> m #

foldr :: (a -> b -> b) -> b -> Oct a -> b #

foldr' :: (a -> b -> b) -> b -> Oct a -> b #

foldl :: (b -> a -> b) -> b -> Oct a -> b #

foldl' :: (b -> a -> b) -> b -> Oct a -> b #

foldr1 :: (a -> a -> a) -> Oct a -> a #

foldl1 :: (a -> a -> a) -> Oct a -> a #

toList :: Oct a -> [a] #

null :: Oct a -> Bool #

length :: Oct a -> Int #

elem :: Eq a => a -> Oct a -> Bool #

maximum :: Ord a => Oct a -> a #

minimum :: Ord a => Oct a -> a #

sum :: Num a => Oct a -> a #

product :: Num a => Oct a -> a #

Traversable Oct Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Oct a -> f (Oct b) #

sequenceA :: Applicative f => Oct (f a) -> f (Oct a) #

mapM :: Monad m => (a -> m b) -> Oct a -> m (Oct b) #

sequence :: Monad m => Oct (m a) -> m (Oct a) #

Applicative Oct Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

pure :: a -> Oct a #

(<*>) :: Oct (a -> b) -> Oct a -> Oct b #

liftA2 :: (a -> b -> c) -> Oct a -> Oct b -> Oct c #

(*>) :: Oct a -> Oct b -> Oct b #

(<*) :: Oct a -> Oct b -> Oct a #

Functor Oct Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

fmap :: (a -> b) -> Oct a -> Oct b #

(<$) :: a -> Oct b -> Oct a #

Monoid a => Monoid (Oct a) Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

mempty :: Oct a #

mappend :: Oct a -> Oct a -> Oct a #

mconcat :: [Oct a] -> Oct a #

Semigroup a => Semigroup (Oct a) Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

(<>) :: Oct a -> Oct a -> Oct a #

sconcat :: NonEmpty (Oct a) -> Oct a #

stimes :: Integral b => b -> Oct a -> Oct a #

Generic (Oct a) Source # 
Instance details

Defined in Data.OctTree.Internal

Associated Types

type Rep (Oct a) :: Type -> Type #

Methods

from :: Oct a -> Rep (Oct a) x #

to :: Rep (Oct a) x -> Oct a #

Show a => Show (Oct a) Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

showsPrec :: Int -> Oct a -> ShowS #

show :: Oct a -> String #

showList :: [Oct a] -> ShowS #

Eq a => Eq (Oct a) Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

(==) :: Oct a -> Oct a -> Bool #

(/=) :: Oct a -> Oct a -> Bool #

Ord a => Ord (Oct a) Source # 
Instance details

Defined in Data.OctTree.Internal

Methods

compare :: Oct a -> Oct a -> Ordering #

(<) :: Oct a -> Oct a -> Bool #

(<=) :: Oct a -> Oct a -> Bool #

(>) :: Oct a -> Oct a -> Bool #

(>=) :: Oct a -> Oct a -> Bool #

max :: Oct a -> Oct a -> Oct a #

min :: Oct a -> Oct a -> Oct a #

type Rep (Oct a) Source # 
Instance details

Defined in Data.OctTree.Internal

type Rep (Oct a) = D1 ('MetaData "Oct" "Data.OctTree.Internal" "nspace-0.2.0.0-JcrzAw5ubjR6TX1H0E6SmC" 'False) (C1 ('MetaCons "Oct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V4 a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V4 a))))