Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Bits of concrete syntax (tokens, layout).
Synopsis
- type LHsToken tok p = XRec p (HsToken tok)
- type LHsUniToken tok utok p = XRec p (HsUniToken tok utok)
- data HsToken (tok :: Symbol) = HsTok
- data HsUniToken (tok :: Symbol) (utok :: Symbol)
- data LayoutInfo pass
- = ExplicitBraces !(LHsToken "{" pass) !(LHsToken "}" pass)
- | VirtualBraces !Int
- | NoLayoutInfo
Documentation
type LHsUniToken tok utok p = XRec p (HsUniToken tok utok) Source #
data HsToken (tok :: Symbol) Source #
A token stored in the syntax tree. For example, when parsing a
let-expression, we store HsToken "let"
and HsToken "in"
.
The locations of those tokens can be used to faithfully reproduce
(exactprint) the original program text.
Instances
KnownSymbol tok => Data (HsToken tok) Source # | |
Defined in Language.Haskell.Syntax.Concrete gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsToken tok -> c (HsToken tok) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsToken tok) Source # toConstr :: HsToken tok -> Constr Source # dataTypeOf :: HsToken tok -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsToken tok)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsToken tok)) Source # gmapT :: (forall b. Data b => b -> b) -> HsToken tok -> HsToken tok Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsToken tok -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsToken tok -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsToken tok -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsToken tok -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) Source # | |
KnownSymbol tok => Outputable (HsToken tok) Source # | |
type Anno (HsToken tok) Source # | |
Defined in GHC.Hs.Extension |
data HsUniToken (tok :: Symbol) (utok :: Symbol) Source #
With UnicodeSyntax
, there might be multiple ways to write the same
token. For example an arrow could be either ->
or →
. This choice must be
recorded in order to exactprint such tokens, so instead of HsToken "->"
we
introduce HsUniToken "->" "→"
.
See also IsUnicodeSyntax
in GHC.Parser.Annotation
; we do not use here to
avoid a dependency.
Instances
(KnownSymbol tok, KnownSymbol utok) => Data (HsUniToken tok utok) Source # | |
Defined in Language.Haskell.Syntax.Concrete gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsUniToken tok utok -> c (HsUniToken tok utok) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsUniToken tok utok) Source # toConstr :: HsUniToken tok utok -> Constr Source # dataTypeOf :: HsUniToken tok utok -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsUniToken tok utok)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsUniToken tok utok)) Source # gmapT :: (forall b. Data b => b -> b) -> HsUniToken tok utok -> HsUniToken tok utok Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsUniToken tok utok -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsUniToken tok utok -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsUniToken tok utok -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsUniToken tok utok -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) Source # | |
(KnownSymbol tok, KnownSymbol utok) => Outputable (HsUniToken tok utok) Source # | |
Defined in GHC.Hs.Extension ppr :: HsUniToken tok utok -> SDoc Source # | |
type Anno (HsUniToken tok utok) Source # | |
Defined in GHC.Hs.Extension |
data LayoutInfo pass Source #
Layout information for declarations.
ExplicitBraces !(LHsToken "{" pass) !(LHsToken "}" pass) | Explicit braces written by the user. class C a where { foo :: a; bar :: a } |
VirtualBraces | Virtual braces inserted by the layout algorithm. class C a where foo :: a bar :: a |
| |
NoLayoutInfo | Empty or compiler-generated blocks do not have layout information associated with them. |
Instances
Typeable p => Data (LayoutInfo (GhcPass p)) Source # | |
Defined in GHC.Hs.Extension gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LayoutInfo (GhcPass p) -> c (LayoutInfo (GhcPass p)) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LayoutInfo (GhcPass p)) Source # toConstr :: LayoutInfo (GhcPass p) -> Constr Source # dataTypeOf :: LayoutInfo (GhcPass p) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LayoutInfo (GhcPass p))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LayoutInfo (GhcPass p))) Source # gmapT :: (forall b. Data b => b -> b) -> LayoutInfo (GhcPass p) -> LayoutInfo (GhcPass p) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo (GhcPass p) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo (GhcPass p) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LayoutInfo (GhcPass p) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LayoutInfo (GhcPass p) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) Source # |