| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.TH.TypeGraph.Stack
Description
The HasStack monad used in MIMO to construct lenses that look deep into a record type. However, it does not involve the Path type mechanism, and is unaware of View instances and other things that modify the type graph. Lets see how it adapts.
- data StackElement = StackElement FieldType Con Dec
- prettyStack :: [StackElement] -> String
- foldField :: MonadReaders [StackElement] m => (FieldType -> m r) -> Dec -> Con -> FieldType -> m r
- type HasStack = MonadReaders [StackElement]
- type StackT m = ReaderT [StackElement] m
- execStackT :: Monad m => StackT m a -> m a
- withStack :: (Monad m, MonadReaders [StackElement] m) => ([StackElement] -> m a) -> m a
- push :: MonadReaders [StackElement] m => FieldType -> Con -> Dec -> m a -> m a
- stackAccessor :: (Quasi m, MonadReaders [StackElement] m) => m Exp
- traceIndented :: MonadReaders [StackElement] m => String -> m ()
- lensNamer :: String -> String
Documentation
data StackElement Source
The information required to extact a field value from a value. We keep a stack of these as we traverse a declaration. Generally, we only need the field names.
Constructors
| StackElement FieldType Con Dec |
Instances
prettyStack :: [StackElement] -> String Source
foldField :: MonadReaders [StackElement] m => (FieldType -> m r) -> Dec -> Con -> FieldType -> m r Source
Push the stack and process the field.
Stack+instance map monad
type HasStack = MonadReaders [StackElement] Source
type StackT m = ReaderT [StackElement] m Source
execStackT :: Monad m => StackT m a -> m a Source
withStack :: (Monad m, MonadReaders [StackElement] m) => ([StackElement] -> m a) -> m a Source
push :: MonadReaders [StackElement] m => FieldType -> Con -> Dec -> m a -> m a Source
Stack operations
stackAccessor :: (Quasi m, MonadReaders [StackElement] m) => m Exp Source
Return a lambda function that turns a value of Type typ0 into the type implied by the stack elements.
traceIndented :: MonadReaders [StackElement] m => String -> m () Source