ghc-lib-parser-9.6.1.20230312: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Haskell.Syntax.Concrete

Description

Bits of concrete syntax (tokens, layout).

Synopsis

Documentation

type LHsToken tok p = XRec p (HsToken tok) Source #

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.

Constructors

HsTok 

Instances

Instances details
KnownSymbol tok => Data (HsToken tok) Source # 
Instance details

Defined in Language.Haskell.Syntax.Concrete

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsToken tok -> c (HsToken tok) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsToken tok) #

toConstr :: HsToken tok -> Constr #

dataTypeOf :: HsToken tok -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsToken tok)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsToken tok)) #

gmapT :: (forall b. Data b => b -> b) -> HsToken tok -> HsToken tok #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsToken tok -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsToken tok -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsToken tok -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsToken tok -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsToken tok -> m (HsToken tok) #

KnownSymbol tok => Outputable (HsToken tok) Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

ppr :: HsToken tok -> SDoc Source #

type Anno (HsToken tok) Source # 
Instance details

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.

Constructors

HsNormalTok 
HsUnicodeTok 

Instances

Instances details
(KnownSymbol tok, KnownSymbol utok) => Data (HsUniToken tok utok) Source # 
Instance details

Defined in Language.Haskell.Syntax.Concrete

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsUniToken tok utok -> c (HsUniToken tok utok) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsUniToken tok utok) #

toConstr :: HsUniToken tok utok -> Constr #

dataTypeOf :: HsUniToken tok utok -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsUniToken tok utok)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsUniToken tok utok)) #

gmapT :: (forall b. Data b => b -> b) -> HsUniToken tok utok -> HsUniToken tok utok #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsUniToken tok utok -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsUniToken tok utok -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsUniToken tok utok -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsUniToken tok utok -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUniToken tok utok -> m (HsUniToken tok utok) #

(KnownSymbol tok, KnownSymbol utok) => Outputable (HsUniToken tok utok) Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

ppr :: HsUniToken tok utok -> SDoc Source #

type Anno (HsUniToken tok utok) Source # 
Instance details

Defined in GHC.Hs.Extension

type Anno (HsUniToken tok utok) = TokenLocation

data LayoutInfo pass Source #

Layout information for declarations.

Constructors

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

Fields

  • !Int

    Layout column (indentation level, begins at 1)

NoLayoutInfo

Empty or compiler-generated blocks do not have layout information associated with them.

Instances

Instances details
Typeable p => Data (LayoutInfo (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LayoutInfo (GhcPass p) -> c (LayoutInfo (GhcPass p)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LayoutInfo (GhcPass p)) #

toConstr :: LayoutInfo (GhcPass p) -> Constr #

dataTypeOf :: LayoutInfo (GhcPass p) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LayoutInfo (GhcPass p))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LayoutInfo (GhcPass p))) #

gmapT :: (forall b. Data b => b -> b) -> LayoutInfo (GhcPass p) -> LayoutInfo (GhcPass p) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo (GhcPass p) -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo (GhcPass p) -> r #

gmapQ :: (forall d. Data d => d -> u) -> LayoutInfo (GhcPass p) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LayoutInfo (GhcPass p) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) #