Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Data type for representing Darts (edges) in a planar graph.
Synopsis
- newtype Arc s = Arc {}
- data Direction
- rev :: Direction -> Direction
- data Dart s = Dart {
- _arc :: !(Arc s)
- _direction :: !Direction
- direction :: forall s. Lens' (Dart s) Direction
- arc :: forall s s. Lens (Dart s) (Dart s) (Arc s) (Arc s)
- twin :: Dart s -> Dart s
- isPositive :: Dart s -> Bool
- allDarts :: [Dart s]
Documentation
>>>
:{
let dart i s = Dart (Arc i) (read s) :}
An Arc is a directed edge in a planar graph. The type s is used to tie this arc to a particular graph.
Darts have a direction which is either Positive or Negative (shown as +1 or -1, respectively).
Instances
Bounded Direction Source # | |
Enum Direction Source # | |
Defined in Data.PlanarGraph.Dart succ :: Direction -> Direction # pred :: Direction -> Direction # fromEnum :: Direction -> Int # enumFrom :: Direction -> [Direction] # enumFromThen :: Direction -> Direction -> [Direction] # enumFromTo :: Direction -> Direction -> [Direction] # enumFromThenTo :: Direction -> Direction -> Direction -> [Direction] # | |
Eq Direction Source # | |
Ord Direction Source # | |
Defined in Data.PlanarGraph.Dart | |
Read Direction Source # | |
Show Direction Source # | |
Generic Direction Source # | |
Arbitrary Direction Source # | |
NFData Direction Source # | |
Defined in Data.PlanarGraph.Dart | |
type Rep Direction Source # | |
A dart represents a bi-directed edge. I.e. a dart has a direction, however the dart of the oposite direction is always present in the planar graph as well.
Dart | |
|
Instances
Enum (Dart s) Source # | |
Defined in Data.PlanarGraph.Dart | |
Eq (Dart s) Source # | |
Ord (Dart s) Source # | |
Show (Dart s) Source # | |
Generic (Dart s) Source # | |
Arbitrary (Dart s) Source # | |
NFData (Dart s) Source # | |
Defined in Data.PlanarGraph.Dart | |
HasDataOf (PlanarGraph s w v e f) (Dart s) Source # | |
Defined in Data.PlanarGraph.Core dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) Source # | |
type Rep (Dart s) Source # | |
Defined in Data.PlanarGraph.Dart type Rep (Dart s) = D1 (MetaData "Dart" "Data.PlanarGraph.Dart" "hgeometry-combinatorial-0.11.0.0-Cktt0ZWYuCrAhHfx7XTJDd" False) (C1 (MetaCons "Dart" PrefixI True) (S1 (MetaSel (Just "_arc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Arc s)) :*: S1 (MetaSel (Just "_direction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Direction))) | |
type DataOf (PlanarGraph s w v e f) (Dart s) Source # | |
Defined in Data.PlanarGraph.Core |
twin :: Dart s -> Dart s Source #
Get the twin of this dart (edge)
>>>
twin (dart 0 "+1")
Dart (Arc 0) -1>>>
twin (dart 0 "-1")
Dart (Arc 0) +1
isPositive :: Dart s -> Bool Source #
test if a dart is Positive