th-typegraph-0.32: Graph of the subtype relation

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.TypeGraph.TypeGraph

Contents

Description

Abstract operations on Maps containing graph edges.

Synopsis

Documentation

makeTypeGraph :: MonadReaders TypeInfo m => GraphEdges TGV -> m TypeGraph Source

Build a TypeGraph given a set of edges and the TypeInfo environment

graphFromMap :: forall key. Ord key => GraphEdges key -> (Graph, Vertex -> ((), key, [key]), key -> Maybe Vertex) Source

Build a graph from the result of typeGraphEdges, each edge goes from a type to one of the types it contains. Thus, each edge represents a primitive lens, and each path in the graph is a composition of lenses.

TypeGraph queries

allPathNodes :: forall m. (DsMonad m, MonadStates ExpandMap m, MonadReaders TypeGraph m, MonadReaders TypeInfo m) => m (Set TGV) Source

All the nodes in the TGV (unsimplified) graph, where each field of a record is a distinct node.

allPathStarts :: forall m. (DsMonad m, MonadStates ExpandMap m, MonadReaders TypeGraph m, MonadReaders TypeInfo m) => m (Set TGVSimple) Source

All the nodes in the TGVSimple graph, where each field representa a different type.

lensKeys :: (DsMonad m, MonadStates ExpandMap m, MonadReaders TypeGraph m, MonadReaders TypeInfo m) => TGVSimple -> m (Set TGV) Source

Return the nodes adjacent to x in the lens graph.

allLensKeys :: (DsMonad m, MonadStates ExpandMap m, MonadReaders TypeGraph m, MonadReaders TypeInfo m) => m (Map TGVSimple (Set TGV)) Source

Each lens represents a single step in a path. The start point is a simplified vertex and the endpoint is an unsimplified vertex.

pathKeys :: (DsMonad m, MonadStates ExpandMap m, MonadReaders TypeGraph m, MonadReaders TypeInfo m) => TGVSimple -> m (Set TGVSimple) Source

Return the nodes reachable from x in the path graph.

goalReachableFull :: (Functor m, DsMonad m, MonadReaders TypeGraph m) => TGV -> TGV -> m Bool Source

Can we reach the goal type from the start type in this key?

goalReachableSimple :: (Functor m, DsMonad m, MonadReaders TypeGraph m) => TGVSimple -> TGVSimple -> m Bool Source

Can we reach the goal type in the simplified graph?

goalReachableSimple' :: (Functor m, DsMonad m, MonadReaders TypeGraph m) => TGV -> TGV -> m Bool Source

Version of goalReachableSimple that first simplifies its argument nodes

data VertexStatus typ Source

When a VertexStatus value is associated with a Type it describes alterations in the type graph from the usual default.

Constructors

Vertex

normal case

Sink

out degree zero - don't create any outgoing edges

Divert typ

replace all outgoing edges with an edge to an alternate type

Extra typ

add an extra outgoing edge to the given type

Instances

adjacent :: forall m. (MonadReaders TypeInfo m, DsMonad m, MonadStates ExpandMap m) => TGV -> m (Set TGV) Source

Return the set of adjacent vertices according to the default type graph - i.e. the one determined only by the type definitions, not by any additional hinting function.

typeGraphVertex :: (MonadReaders TypeInfo m, MonadStates ExpandMap m, DsMonad m) => Type -> m TGV Source

Return the TGV associated with a particular type, with no field specified.

typeGraphVertexOfField :: (MonadReaders TypeInfo m, MonadStates ExpandMap m, DsMonad m) => (Name, Name, Either Int Name) -> Type -> m TGV Source

Return the TGV associated with a particular type and field.