hgeometry-0.12.0.0: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.PlanarSubdivision.Raw

Description

 
Synopsis

Documentation

data Wrap' s Source #

Helper data type and type family to Wrap a proxy type.

type family Wrap (s :: k) :: k where ... Source #

Equations

Wrap s = Wrap' s 

newtype ComponentId s Source #

ComponentId type

Constructors

ComponentId 

Fields

Instances

Instances details
Bounded (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Enum (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Eq (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Ord (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Show (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Generic (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Associated Types

type Rep (ComponentId s) :: Type -> Type #

Methods

from :: ComponentId s -> Rep (ComponentId s) x #

to :: Rep (ComponentId s) x -> ComponentId s #

ToJSON (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

FromJSON (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

type Rep (ComponentId s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

type Rep (ComponentId s) = D1 ('MetaData "ComponentId" "Data.Geometry.PlanarSubdivision.Raw" "hgeometry-0.12.0.0-3A6BqD11e4bE4Mwo2IplDZ" 'True) (C1 ('MetaCons "ComponentId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Raw s ia a Source #

Helper type for the data that we store in a planar subdivision

Constructors

Raw 

Fields

Instances

Instances details
Functor (Raw s ia) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

fmap :: (a -> b) -> Raw s ia a -> Raw s ia b #

(<$) :: a -> Raw s ia b -> Raw s ia a #

Foldable (Raw s ia) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

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 #

toList :: Raw s ia a -> [a] #

null :: Raw s ia a -> Bool #

length :: Raw s ia a -> Int #

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 #

sum :: Num a => Raw s ia a -> a #

product :: Num a => Raw s ia a -> a #

Traversable (Raw s ia) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

traverse :: Applicative f => (a -> f b) -> Raw s ia a -> f (Raw s ia b) #

sequenceA :: Applicative f => Raw s ia (f a) -> f (Raw s ia a) #

mapM :: Monad m => (a -> m b) -> Raw s ia a -> m (Raw s ia b) #

sequence :: Monad m => Raw s ia (m a) -> m (Raw s ia a) #

(Eq ia, Eq a) => Eq (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

(==) :: Raw s ia a -> Raw s ia a -> Bool #

(/=) :: Raw s ia a -> Raw s ia a -> Bool #

(Show ia, Show a) => Show (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

showsPrec :: Int -> Raw s ia a -> ShowS #

show :: Raw s ia a -> String #

showList :: [Raw s ia a] -> ShowS #

Generic (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Associated Types

type Rep (Raw s ia a) :: Type -> Type #

Methods

from :: Raw s ia a -> Rep (Raw s ia a) x #

to :: Rep (Raw s ia a) x -> Raw s ia a #

(ToJSON ia, ToJSON a) => ToJSON (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

toJSON :: Raw s ia a -> Value #

toEncoding :: Raw s ia a -> Encoding #

toJSONList :: [Raw s ia a] -> Value #

toEncodingList :: [Raw s ia a] -> Encoding #

(FromJSON ia, FromJSON a) => FromJSON (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

parseJSON :: Value -> Parser (Raw s ia a) #

parseJSONList :: Value -> Parser [Raw s ia a] #

type Rep (Raw s ia a) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

type Rep (Raw s ia a) = D1 ('MetaData "Raw" "Data.Geometry.PlanarSubdivision.Raw" "hgeometry-0.12.0.0-3A6BqD11e4bE4Mwo2IplDZ" '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))))

dataVal :: Lens (Raw s ia a) (Raw s ia b) a b Source #

get the dataVal of a Raw

data FaceData h f Source #

The Face data consists of the data itself and a list of holes

Constructors

FaceData 

Fields

Instances

Instances details
Bifunctor FaceData Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

bimap :: (a -> b) -> (c -> d) -> FaceData a c -> FaceData b d #

first :: (a -> b) -> FaceData a c -> FaceData b c #

second :: (b -> c) -> FaceData a b -> FaceData a c #

Functor (FaceData h) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

fmap :: (a -> b) -> FaceData h a -> FaceData h b #

(<$) :: a -> FaceData h b -> FaceData h a #

Foldable (FaceData h) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

fold :: Monoid m => FaceData h m -> m #

foldMap :: Monoid m => (a -> m) -> FaceData h a -> m #

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

foldr :: (a -> b -> b) -> b -> FaceData h a -> b #

foldr' :: (a -> b -> b) -> b -> FaceData h a -> b #

foldl :: (b -> a -> b) -> b -> FaceData h a -> b #

foldl' :: (b -> a -> b) -> b -> FaceData h a -> b #

foldr1 :: (a -> a -> a) -> FaceData h a -> a #

foldl1 :: (a -> a -> a) -> FaceData h a -> a #

toList :: FaceData h a -> [a] #

null :: FaceData h a -> Bool #

length :: FaceData h a -> Int #

elem :: Eq a => a -> FaceData h a -> Bool #

maximum :: Ord a => FaceData h a -> a #

minimum :: Ord a => FaceData h a -> a #

sum :: Num a => FaceData h a -> a #

product :: Num a => FaceData h a -> a #

Traversable (FaceData h) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

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

sequenceA :: Applicative f => FaceData h (f a) -> f (FaceData h a) #

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

sequence :: Monad m => FaceData h (m a) -> m (FaceData h a) #

(Eq h, Eq f) => Eq (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

(==) :: FaceData h f -> FaceData h f -> Bool #

(/=) :: FaceData h f -> FaceData h f -> Bool #

(Ord h, Ord f) => Ord (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

compare :: FaceData h f -> FaceData h f -> Ordering #

(<) :: FaceData h f -> FaceData h f -> Bool #

(<=) :: FaceData h f -> FaceData h f -> Bool #

(>) :: FaceData h f -> FaceData h f -> Bool #

(>=) :: FaceData h f -> FaceData h f -> Bool #

max :: FaceData h f -> FaceData h f -> FaceData h f #

min :: FaceData h f -> FaceData h f -> FaceData h f #

(Show h, Show f) => Show (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

showsPrec :: Int -> FaceData h f -> ShowS #

show :: FaceData h f -> String #

showList :: [FaceData h f] -> ShowS #

Generic (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Associated Types

type Rep (FaceData h f) :: Type -> Type #

Methods

from :: FaceData h f -> Rep (FaceData h f) x #

to :: Rep (FaceData h f) x -> FaceData h f #

(ToJSON h, ToJSON f) => ToJSON (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

(FromJSON h, FromJSON f) => FromJSON (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

type Rep (FaceData h f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

type Rep (FaceData h f) = D1 ('MetaData "FaceData" "Data.Geometry.PlanarSubdivision.Raw" "hgeometry-0.12.0.0-3A6BqD11e4bE4Mwo2IplDZ" 'False) (C1 ('MetaCons "FaceData" 'PrefixI 'True) (S1 ('MetaSel ('Just "_holes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq h)) :*: S1 ('MetaSel ('Just "_fData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 f)))

holes :: forall h f h. Lens (FaceData h f) (FaceData h f) (Seq h) (Seq h) Source #

fData :: forall h f f. Lens (FaceData h f) (FaceData h f) f f Source #

data RawFace s f Source #

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).

Constructors

RawFace 

Fields

Instances

Instances details
Functor (RawFace s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

fmap :: (a -> b) -> RawFace s a -> RawFace s b #

(<$) :: a -> RawFace s b -> RawFace s a #

Foldable (RawFace s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

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] #

null :: RawFace s a -> Bool #

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 #

sum :: Num a => RawFace s a -> a #

product :: Num a => RawFace s a -> a #

Traversable (RawFace s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

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

sequenceA :: Applicative f => RawFace s (f a) -> f (RawFace s a) #

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

sequence :: Monad m => RawFace s (m a) -> m (RawFace s a) #

Eq f => Eq (RawFace s f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

(==) :: RawFace s f -> RawFace s f -> Bool #

(/=) :: RawFace s f -> RawFace s f -> Bool #

Show f => Show (RawFace s f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Methods

showsPrec :: Int -> RawFace s f -> ShowS #

show :: RawFace s f -> String #

showList :: [RawFace s f] -> ShowS #

Generic (RawFace s f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

Associated Types

type Rep (RawFace s f) :: Type -> Type #

Methods

from :: RawFace s f -> Rep (RawFace s f) x #

to :: Rep (RawFace s f) x -> RawFace s f #

type Rep (RawFace s f) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Raw

type Rep (RawFace s f) = D1 ('MetaData "RawFace" "Data.Geometry.PlanarSubdivision.Raw" "hgeometry-0.12.0.0-3A6BqD11e4bE4Mwo2IplDZ" '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))))

faceIdx :: forall k (s :: k) f. Lens' (RawFace (s :: k) f) (Maybe (ComponentId s, FaceId' (Wrap s))) Source #

faceDataVal :: forall k (s :: k) f f. Lens (RawFace (s :: k) f) (RawFace (s :: k) f) (FaceData (Dart s) f) (FaceData (Dart s) f) Source #