{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE EmptyDataDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module GHC.Hs.Extension where
import GHC.Prelude
import GHC.TypeLits (KnownSymbol, symbolVal)
import Data.Data hiding ( Fixity )
import Language.Haskell.Syntax.Concrete
import Language.Haskell.Syntax.Extension
import GHC.Types.Name
import GHC.Types.Name.Reader
import GHC.Types.Var
import GHC.Utils.Outputable hiding ((<>))
import GHC.Types.SrcLoc (GenLocated(..), unLoc)
import GHC.Utils.Panic
import GHC.Parser.Annotation
type instance XRec (GhcPass p) a = GenLocated (Anno a) a
type instance Anno RdrName = SrcSpanAnnN
type instance Anno Name = SrcSpanAnnN
type instance Anno Id = SrcSpanAnnN
type IsSrcSpanAnn p a = ( Anno (IdGhcP p) ~ SrcSpanAnn' (EpAnn a),
IsPass p)
instance UnXRec (GhcPass p) where
unXRec :: forall a. XRec (GhcPass p) a -> a
unXRec = XRec (GhcPass p) a -> a
GenLocated (Anno a) a -> a
forall l e. GenLocated l e -> e
unLoc
instance MapXRec (GhcPass p) where
mapXRec :: forall a b.
(Anno a ~ Anno b) =>
(a -> b) -> XRec (GhcPass p) a -> XRec (GhcPass p) b
mapXRec = (a -> b) -> XRec (GhcPass p) a -> XRec (GhcPass p) b
(a -> b) -> GenLocated (Anno b) a -> GenLocated (Anno b) b
forall a b.
(a -> b) -> GenLocated (Anno b) a -> GenLocated (Anno b) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
data GhcPass (c :: Pass) where
GhcPs :: GhcPass 'Parsed
GhcRn :: GhcPass 'Renamed
GhcTc :: GhcPass 'Typechecked
instance Typeable p => Data (GhcPass p) where
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (GhcPass p)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_ Constr
_ = String -> c (GhcPass p)
forall a. HasCallStack => String -> a
panic String
"instance Data GhcPass"
toConstr :: GhcPass p -> Constr
toConstr GhcPass p
_ = String -> Constr
forall a. HasCallStack => String -> a
panic String
"instance Data GhcPass"
dataTypeOf :: GhcPass p -> DataType
dataTypeOf GhcPass p
_ = String -> DataType
forall a. HasCallStack => String -> a
panic String
"instance Data GhcPass"
data Pass = Parsed | Renamed | Typechecked
deriving (Typeable Pass
Typeable Pass =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pass -> c Pass)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pass)
-> (Pass -> Constr)
-> (Pass -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pass))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass))
-> ((forall b. Data b => b -> b) -> Pass -> Pass)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r)
-> (forall u. (forall d. Data d => d -> u) -> Pass -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Pass -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass)
-> Data Pass
Pass -> Constr
Pass -> DataType
(forall b. Data b => b -> b) -> Pass -> Pass
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Pass -> u
forall u. (forall d. Data d => d -> u) -> Pass -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pass
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pass -> c Pass
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pass)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pass -> c Pass
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pass -> c Pass
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pass
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pass
$ctoConstr :: Pass -> Constr
toConstr :: Pass -> Constr
$cdataTypeOf :: Pass -> DataType
dataTypeOf :: Pass -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pass)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pass)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass)
$cgmapT :: (forall b. Data b => b -> b) -> Pass -> Pass
gmapT :: (forall b. Data b => b -> b) -> Pass -> Pass
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Pass -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Pass -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pass -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pass -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pass -> m Pass
Data)
type GhcPs = GhcPass 'Parsed
type GhcRn = GhcPass 'Renamed
type GhcTc = GhcPass 'Typechecked
class ( NoGhcTcPass (NoGhcTcPass p) ~ NoGhcTcPass p
, IsPass (NoGhcTcPass p)
) => IsPass p where
ghcPass :: GhcPass p
instance IsPass 'Parsed where
ghcPass :: GhcPass 'Parsed
ghcPass = GhcPass 'Parsed
GhcPs
instance IsPass 'Renamed where
ghcPass :: GhcPass 'Renamed
ghcPass = GhcPass 'Renamed
GhcRn
instance IsPass 'Typechecked where
ghcPass :: GhcPass 'Typechecked
ghcPass = GhcPass 'Typechecked
GhcTc
type instance IdP (GhcPass p) = IdGhcP p
type family IdGhcP pass where
IdGhcP 'Parsed = RdrName
IdGhcP 'Renamed = Name
IdGhcP 'Typechecked = Id
type instance NoGhcTc (GhcPass pass) = GhcPass (NoGhcTcPass pass)
type family NoGhcTcPass (p :: Pass) :: Pass where
NoGhcTcPass 'Typechecked = 'Renamed
NoGhcTcPass other = other
type OutputableBndrId pass =
( OutputableBndr (IdGhcP pass)
, OutputableBndr (IdGhcP (NoGhcTcPass pass))
, Outputable (GenLocated (Anno (IdGhcP pass)) (IdGhcP pass))
, Outputable (GenLocated (Anno (IdGhcP (NoGhcTcPass pass))) (IdGhcP (NoGhcTcPass pass)))
, IsPass pass
)
pprIfPs :: forall p. IsPass p => (p ~ 'Parsed => SDoc) -> SDoc
pprIfPs :: forall (p :: Pass). IsPass p => ((p ~ 'Parsed) => SDoc) -> SDoc
pprIfPs (p ~ 'Parsed) => SDoc
pp = case forall (p :: Pass). IsPass p => GhcPass p
ghcPass @p of GhcPass p
GhcPs -> SDoc
(p ~ 'Parsed) => SDoc
pp
GhcPass p
_ -> SDoc
forall doc. IsOutput doc => doc
empty
pprIfRn :: forall p. IsPass p => (p ~ 'Renamed => SDoc) -> SDoc
pprIfRn :: forall (p :: Pass). IsPass p => ((p ~ 'Renamed) => SDoc) -> SDoc
pprIfRn (p ~ 'Renamed) => SDoc
pp = case forall (p :: Pass). IsPass p => GhcPass p
ghcPass @p of GhcPass p
GhcRn -> SDoc
(p ~ 'Renamed) => SDoc
pp
GhcPass p
_ -> SDoc
forall doc. IsOutput doc => doc
empty
pprIfTc :: forall p. IsPass p => (p ~ 'Typechecked => SDoc) -> SDoc
pprIfTc :: forall (p :: Pass).
IsPass p =>
((p ~ 'Typechecked) => SDoc) -> SDoc
pprIfTc (p ~ 'Typechecked) => SDoc
pp = case forall (p :: Pass). IsPass p => GhcPass p
ghcPass @p of GhcPass p
GhcTc -> SDoc
(p ~ 'Typechecked) => SDoc
pp
GhcPass p
_ -> SDoc
forall doc. IsOutput doc => doc
empty
type instance Anno (HsToken tok) = TokenLocation
noHsTok :: GenLocated TokenLocation (HsToken tok)
noHsTok :: forall (tok :: Symbol). GenLocated TokenLocation (HsToken tok)
noHsTok = TokenLocation
-> HsToken tok -> GenLocated TokenLocation (HsToken tok)
forall l e. l -> e -> GenLocated l e
L TokenLocation
NoTokenLoc HsToken tok
forall (tok :: Symbol). HsToken tok
HsTok
type instance Anno (HsUniToken tok utok) = TokenLocation
noHsUniTok :: GenLocated TokenLocation (HsUniToken tok utok)
noHsUniTok :: forall (tok :: Symbol) (utok :: Symbol).
GenLocated TokenLocation (HsUniToken tok utok)
noHsUniTok = TokenLocation
-> HsUniToken tok utok
-> GenLocated TokenLocation (HsUniToken tok utok)
forall l e. l -> e -> GenLocated l e
L TokenLocation
NoTokenLoc HsUniToken tok utok
forall (tok :: Symbol) (utok :: Symbol). HsUniToken tok utok
HsNormalTok
instance Outputable NoExtField where
ppr :: NoExtField -> SDoc
ppr NoExtField
_ = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"NoExtField"
instance Outputable DataConCantHappen where
ppr :: DataConCantHappen -> SDoc
ppr = DataConCantHappen -> SDoc
forall a. DataConCantHappen -> a
dataConCantHappen
instance KnownSymbol tok => Outputable (HsToken tok) where
ppr :: HsToken tok -> SDoc
ppr HsToken tok
_ = String -> SDoc
forall doc. IsLine doc => String -> doc
text (Proxy tok -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy tok
forall {k} (t :: k). Proxy t
Proxy :: Proxy tok))
instance (KnownSymbol tok, KnownSymbol utok) => Outputable (HsUniToken tok utok) where
ppr :: HsUniToken tok utok -> SDoc
ppr HsUniToken tok utok
HsNormalTok = String -> SDoc
forall doc. IsLine doc => String -> doc
text (Proxy tok -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy tok
forall {k} (t :: k). Proxy t
Proxy :: Proxy tok))
ppr HsUniToken tok utok
HsUnicodeTok = String -> SDoc
forall doc. IsLine doc => String -> doc
text (Proxy utok -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy utok
forall {k} (t :: k). Proxy t
Proxy :: Proxy utok))
deriving instance Typeable p => Data (LayoutInfo (GhcPass p))