th-context-0.24: Test instance context

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.Expand

Description

The Expanded class helps keep track of which Type values have been fully expanded to a canonical form. This lets us use the Eq and Ord relationships on Type and Pred values when reasoning about instance context. What the expandType function does is use the function from th-desugar to replace occurrences of ConT name with the associated Type if name is a declared type synonym TySynD name _ typ. For convenience, a wrapper type E is provided, along with the Expanded instances E Type and E Pred. Now the expandType and expandPred functions can be used to return values of type E Type and E Pred respectively.

Instances Expanded Type Type and Expanded Pred Pred are provided in Language.Haskell.TH.Context.Unsafe, for when less type safety is required.

Synopsis

Documentation

newtype E a Source #

A concrete type used to mark type which have been expanded

Constructors

E 

Fields

Instances

Eq a => Eq (E a) Source # 

Methods

(==) :: E a -> E a -> Bool #

(/=) :: E a -> E a -> Bool #

Data a => Data (E a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> E a -> c (E a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (E a) #

toConstr :: E a -> Constr #

dataTypeOf :: E a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (E a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (E a)) #

gmapT :: (forall b. Data b => b -> b) -> E a -> E a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> E a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> E a -> r #

gmapQ :: (forall d. Data d => d -> u) -> E a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> E a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> E a -> m (E a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> E a -> m (E a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> E a -> m (E a) #

Ord a => Ord (E a) Source # 

Methods

compare :: E a -> E a -> Ordering #

(<) :: E a -> E a -> Bool #

(<=) :: E a -> E a -> Bool #

(>) :: E a -> E a -> Bool #

(>=) :: E a -> E a -> Bool #

max :: E a -> E a -> E a #

min :: E a -> E a -> E a #

Show a => Show (E a) Source # 

Methods

showsPrec :: Int -> E a -> ShowS #

show :: E a -> String #

showList :: [E a] -> ShowS #

Lift (E Type) Source # 

Methods

lift :: E Type -> Q Exp #

Ppr a => Ppr (E a) Source # 

Methods

ppr :: E a -> Doc #

ppr_list :: [E a] -> Doc #

unE :: forall a a. Iso (E a) (E a) a a Source #

type ExpandMap = Map Type (E Type) Source #

The state type used to memoize expansions.

expandType :: (DsMonad m, MonadStates ExpandMap m) => Type -> m (E Type) Source #

Apply the th-desugar expand function to a Type and mark it as expanded.

expandPred :: (DsMonad m, MonadStates ExpandMap m) => Type -> m (E Type) Source #

Apply the th-desugar expand function to a Pred and mark it as expanded. Note that the definition of Pred changed in template-haskell-2.10.0.0.

expandClassP :: forall m. (DsMonad m, MonadStates ExpandMap m) => Name -> [Type] -> m (E Type) Source #

Expand a list of Type and build an expanded ClassP Pred.

pprint1 :: (Ppr a, Data a) => a -> [Char] Source #