Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
This module contains compatibility constructs to write type signatures across multiple ghc-exactprint versions, accepting that anything more ambitious is pretty much impossible with the GHC 9.2 redesign of ghc-exactprint
Synopsis
- class Typeable a => ExactPrint a
- exactPrint :: ExactPrint ast => ast -> String
- makeDeltaAst :: ExactPrint ast => ast -> ast
- data Annotated ast
- pattern Annotated :: ast -> ApiAnns -> Annotated ast
- $sel:astA:Annotated :: Annotated ast -> ast
- $sel:annsA:Annotated :: Annotated ast -> ApiAnns
Documentation
class Typeable a => ExactPrint a #
An AST fragment with an annotation must be able to return the
requirements for nesting another one, captured in an Entry
, and
to be able to use the rest of the exactprint machinery to print the
element. In the analogy to Outputable, exact
plays the role of
ppr
.
Instances
exactPrint :: ExactPrint ast => ast -> String #
makeDeltaAst :: ExactPrint ast => ast -> ast #
Transform concrete annotations into relative annotations which
are more useful when transforming an AST. This corresponds to the
earlier relativiseApiAnns
.
Annotated
packages an AST fragment with the annotations necessary to
exactPrint
or transform
that AST.
Instances
Foldable Annotated | |
Defined in Retrie.ExactPrint.Annotated fold :: Monoid m => Annotated m -> m # foldMap :: Monoid m => (a -> m) -> Annotated a -> m # foldMap' :: Monoid m => (a -> m) -> Annotated a -> m # foldr :: (a -> b -> b) -> b -> Annotated a -> b # foldr' :: (a -> b -> b) -> b -> Annotated a -> b # foldl :: (b -> a -> b) -> b -> Annotated a -> b # foldl' :: (b -> a -> b) -> b -> Annotated a -> b # foldr1 :: (a -> a -> a) -> Annotated a -> a # foldl1 :: (a -> a -> a) -> Annotated a -> a # toList :: Annotated a -> [a] # length :: Annotated a -> Int # elem :: Eq a => a -> Annotated a -> Bool # maximum :: Ord a => Annotated a -> a # minimum :: Ord a => Annotated a -> a # | |
Traversable Annotated | |
Defined in Retrie.ExactPrint.Annotated | |
Functor Annotated | |
Data ast => Data (Annotated ast) | |
Defined in Retrie.ExactPrint.Annotated gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotated ast -> c (Annotated ast) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Annotated ast) # toConstr :: Annotated ast -> Constr # dataTypeOf :: Annotated ast -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Annotated ast)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Annotated ast)) # gmapT :: (forall b. Data b => b -> b) -> Annotated ast -> Annotated ast # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotated ast -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotated ast -> r # gmapQ :: (forall d. Data d => d -> u) -> Annotated ast -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotated ast -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotated ast -> m (Annotated ast) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotated ast -> m (Annotated ast) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotated ast -> m (Annotated ast) # | |
(Data ast, Monoid ast) => Monoid (Annotated ast) | |
(Data ast, Monoid ast) => Semigroup (Annotated ast) | |
Show (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
Default ast => Default (Annotated ast) | |
Defined in Retrie.ExactPrint.Annotated | |
NFData (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.ExactPrint rnf :: Annotated ParsedSource -> () # |
$sel:astA:Annotated :: Annotated ast -> ast Source #
$sel:annsA:Annotated :: Annotated ast -> ApiAnns Source #