Copyright | (c) 2019-2021 Edward Kmett |
---|---|
License | BSD-2-Clause OR Apache-2.0 |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
skyline packing using stb_rect_pack.h
Synopsis
- data Atlas s
- create :: (HasCallStack, PrimMonad m) => Int -> Int -> m (Atlas (PrimState m))
- createExplicit :: HasCallStack => PrimMonad m => Int -> Int -> Maybe Int -> m (Atlas (PrimState m))
- reset :: PrimMonad m => Atlas (PrimState m) -> m ()
- data Heuristic
- setHeuristic :: PrimMonad m => Atlas (PrimState m) -> Heuristic -> m ()
- setAllowOutOfMem :: PrimMonad m => Atlas (PrimState m) -> Bool -> m ()
- data Pt = Pt Int Int
- pack :: (PrimMonad m, Traversable f) => Atlas (PrimState m) -> (a -> Pt) -> (Maybe Pt -> a -> b) -> (Pt -> a -> c) -> f a -> m (Either (f b) (f c))
- pack1 :: PrimMonad m => Atlas (PrimState m) -> Pt -> m (Maybe Pt)
- packM :: (PrimBase m, Traversable f) => Atlas (PrimState m) -> (a -> m Pt) -> (Maybe Pt -> a -> b) -> (Pt -> a -> c) -> f a -> m (Either (f b) (f c))
Documentation
create :: (HasCallStack, PrimMonad m) => Int -> Int -> m (Atlas (PrimState m)) Source #
Create a packing context.
createExplicit :: HasCallStack => PrimMonad m => Int -> Int -> Maybe Int -> m (Atlas (PrimState m)) Source #
Initialization with an optional node count, when node count < width
is used this results in quantization unless
setAllowOutOfMem
is enabled. When no value is supplied, it defaults to the width of the Atlas
.
reset :: PrimMonad m => Atlas (PrimState m) -> m () Source #
Reinitialize an atlas with the same parameters
Setup
BottomLeft | bottom-left sort-height |
BestFirst | best first sort-height |
Instances
Bounded Heuristic Source # | |
Enum Heuristic Source # | |
Defined in Data.Atlas.Internal succ :: Heuristic -> Heuristic # pred :: Heuristic -> Heuristic # fromEnum :: Heuristic -> Int # enumFrom :: Heuristic -> [Heuristic] # enumFromThen :: Heuristic -> Heuristic -> [Heuristic] # enumFromTo :: Heuristic -> Heuristic -> [Heuristic] # enumFromThenTo :: Heuristic -> Heuristic -> Heuristic -> [Heuristic] # | |
Eq Heuristic Source # | |
Ord Heuristic Source # | |
Defined in Data.Atlas.Internal | |
Read Heuristic Source # | |
Show Heuristic Source # | |
Ix Heuristic Source # | |
Defined in Data.Atlas.Internal range :: (Heuristic, Heuristic) -> [Heuristic] # index :: (Heuristic, Heuristic) -> Heuristic -> Int # unsafeIndex :: (Heuristic, Heuristic) -> Heuristic -> Int inRange :: (Heuristic, Heuristic) -> Heuristic -> Bool # rangeSize :: (Heuristic, Heuristic) -> Int # unsafeRangeSize :: (Heuristic, Heuristic) -> Int | |
Lift Heuristic Source # | |
Default Heuristic Source # | |
Defined in Data.Atlas.Internal |
setHeuristic :: PrimMonad m => Atlas (PrimState m) -> Heuristic -> m () Source #
setAllowOutOfMem :: PrimMonad m => Atlas (PrimState m) -> Bool -> m () Source #
Using a context
Use and cast back and forth to ints instead for more natural API?
:: (PrimMonad m, Traversable f) | |
=> Atlas (PrimState m) | The atlas you want to pack these rectangles into. |
-> (a -> Pt) | for each item you want to pack, extract the size. |
-> (Maybe Pt -> a -> b) | when some fail to pack this will be called, with
|
-> (Pt -> a -> c) | when all succeed this will be called with each position. |
-> f a | A container full of things that you'd like to pack into the atlas. |
-> m (Either (f b) (f c)) | Either a mixture of successes and failures, or a successful pack. |
:: (PrimBase m, Traversable f) | |
=> Atlas (PrimState m) | The |
-> (a -> m Pt) | for each item you want to pack, extract the size,
with effects in |
-> (Maybe Pt -> a -> b) | when some fail to pack this will be called, with
|
-> (Pt -> a -> c) | when all succeed, this will be called with each position. |
-> f a | A container full of things that you'd like to pack into the atlas. |
-> m (Either (f b) (f c)) |
|