Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Wrap' s
- type family Wrap (s :: k) :: k where ...
- newtype ComponentId s = ComponentId {}
- data Raw s ia a = Raw {
- _compId :: !(ComponentId s)
- _idxVal :: !ia
- _dataVal :: !a
- dataVal :: Lens (Raw s ia a) (Raw s ia b) a b
- data FaceData h f = FaceData {}
- holes :: forall h f h. Lens (FaceData h f) (FaceData h f) (Seq h) (Seq h)
- fData :: forall h f f. Lens (FaceData h f) (FaceData h f) f f
- data RawFace s f = RawFace {
- _faceIdx :: !(Maybe (ComponentId s, FaceId' (Wrap s)))
- _faceDataVal :: !(FaceData (Dart s) f)
- faceIdx :: forall k (s :: k) f. Lens' (RawFace (s :: k) f) (Maybe (ComponentId s, FaceId' (Wrap s)))
- faceDataVal :: forall k (s :: k) f f. Lens (RawFace (s :: k) f) (RawFace (s :: k) f) (FaceData (Dart s) f) (FaceData (Dart s) f)
Documentation
newtype ComponentId s Source #
ComponentId type
Instances
Helper type for the data that we store in a planar subdivision
Raw | |
|
Instances
Functor (Raw s ia) Source # | |
Foldable (Raw s ia) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Raw fold :: Monoid m => Raw s ia m -> m # foldMap :: Monoid m => (a -> m) -> Raw s ia a -> m # foldMap' :: Monoid m => (a -> m) -> Raw s ia a -> m # foldr :: (a -> b -> b) -> b -> Raw s ia a -> b # foldr' :: (a -> b -> b) -> b -> Raw s ia a -> b # foldl :: (b -> a -> b) -> b -> Raw s ia a -> b # foldl' :: (b -> a -> b) -> b -> Raw s ia a -> b # foldr1 :: (a -> a -> a) -> Raw s ia a -> a # foldl1 :: (a -> a -> a) -> Raw s ia a -> a # elem :: Eq a => a -> Raw s ia a -> Bool # maximum :: Ord a => Raw s ia a -> a # minimum :: Ord a => Raw s ia a -> a # | |
Traversable (Raw s ia) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Raw | |
(Eq ia, Eq a) => Eq (Raw s ia a) Source # | |
(Show ia, Show a) => Show (Raw s ia a) Source # | |
Generic (Raw s ia a) Source # | |
(ToJSON ia, ToJSON a) => ToJSON (Raw s ia a) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Raw | |
(FromJSON ia, FromJSON a) => FromJSON (Raw s ia a) Source # | |
type Rep (Raw s ia a) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Raw type Rep (Raw s ia a) = D1 ('MetaData "Raw" "Data.Geometry.PlanarSubdivision.Raw" "hgeometry-0.12.0.1-744QXwUb5uS54emseMX1Co" 'False) (C1 ('MetaCons "Raw" 'PrefixI 'True) (S1 ('MetaSel ('Just "_compId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ComponentId s)) :*: (S1 ('MetaSel ('Just "_idxVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ia) :*: S1 ('MetaSel ('Just "_dataVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))) |
The Face data consists of the data itself and a list of holes
Instances
Face data, if the face is an inner face, store the component and faceId of it. If not, this face must be the outer face (and thus we can find all the face id's it correponds to through the FaceData).
RawFace | |
|
Instances
Functor (RawFace s) Source # | |
Foldable (RawFace s) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Raw fold :: Monoid m => RawFace s m -> m # foldMap :: Monoid m => (a -> m) -> RawFace s a -> m # foldMap' :: Monoid m => (a -> m) -> RawFace s a -> m # foldr :: (a -> b -> b) -> b -> RawFace s a -> b # foldr' :: (a -> b -> b) -> b -> RawFace s a -> b # foldl :: (b -> a -> b) -> b -> RawFace s a -> b # foldl' :: (b -> a -> b) -> b -> RawFace s a -> b # foldr1 :: (a -> a -> a) -> RawFace s a -> a # foldl1 :: (a -> a -> a) -> RawFace s a -> a # toList :: RawFace s a -> [a] # length :: RawFace s a -> Int # elem :: Eq a => a -> RawFace s a -> Bool # maximum :: Ord a => RawFace s a -> a # minimum :: Ord a => RawFace s a -> a # | |
Traversable (RawFace s) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Raw | |
Eq f => Eq (RawFace s f) Source # | |
Show f => Show (RawFace s f) Source # | |
Generic (RawFace s f) Source # | |
type Rep (RawFace s f) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Raw type Rep (RawFace s f) = D1 ('MetaData "RawFace" "Data.Geometry.PlanarSubdivision.Raw" "hgeometry-0.12.0.1-744QXwUb5uS54emseMX1Co" 'False) (C1 ('MetaCons "RawFace" 'PrefixI 'True) (S1 ('MetaSel ('Just "_faceIdx") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (ComponentId s, FaceId' (Wrap s)))) :*: S1 ('MetaSel ('Just "_faceDataVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (FaceData (Dart s) f)))) |