{-# LANGUAGE CPP #-}
module GHC.SourceGen.Type
( HsType'
, tyPromotedVar
, stringTy
, numTy
, listTy
, listPromotedTy
, tuplePromotedTy
, (-->)
, forall'
, HsTyVarBndr'
, (==>)
, kindedVar
) where
import Data.String (fromString)
#if MIN_VERSION_ghc(9,0,0)
import GHC.Hs.Type
import GHC.Parser.Annotation
#else
import GHC.Hs.Type
#endif
import GHC.SourceGen.Syntax.Internal
import GHC.SourceGen.Lit.Internal (noSourceText)
import GHC.SourceGen.Name.Internal
import GHC.SourceGen.Type.Internal
tyPromotedVar :: RdrNameStr -> HsType'
tyPromotedVar :: RdrNameStr -> HsType'
tyPromotedVar = (NoExtField -> PromotionFlag -> LocatedN RdrName -> HsType')
-> PromotionFlag -> LocatedN RdrName -> HsType'
forall a. (NoExtField -> a) -> a
withEpAnnNotUsed NoExtField -> PromotionFlag -> LocatedN RdrName -> HsType'
forall pass.
XTyVar pass -> PromotionFlag -> Located (IdP pass) -> HsType pass
HsTyVar PromotionFlag
promoted (LocatedN RdrName -> HsType')
-> (RdrNameStr -> LocatedN RdrName) -> RdrNameStr -> HsType'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrNameStr -> LocatedN RdrName
typeRdrName
stringTy :: String -> HsType'
stringTy :: String -> HsType'
stringTy = (NoExtField -> HsTyLit -> HsType') -> HsTyLit -> HsType'
forall a. (NoExtField -> a) -> a
noExt NoExtField -> HsTyLit -> HsType'
forall pass. XTyLit pass -> HsTyLit -> HsType pass
HsTyLit (HsTyLit -> HsType') -> (String -> HsTyLit) -> String -> HsType'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceText -> FastString -> HsTyLit) -> FastString -> HsTyLit
forall a. (SourceText -> a) -> a
noSourceText SourceText -> FastString -> HsTyLit
HsStrTy (FastString -> HsTyLit)
-> (String -> FastString) -> String -> HsTyLit
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> FastString
forall a. IsString a => String -> a
fromString
numTy :: Integer -> HsType'
numTy :: Integer -> HsType'
numTy = (NoExtField -> HsTyLit -> HsType') -> HsTyLit -> HsType'
forall a. (NoExtField -> a) -> a
noExt NoExtField -> HsTyLit -> HsType'
forall pass. XTyLit pass -> HsTyLit -> HsType pass
HsTyLit (HsTyLit -> HsType') -> (Integer -> HsTyLit) -> Integer -> HsType'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceText -> Integer -> HsTyLit) -> Integer -> HsTyLit
forall a. (SourceText -> a) -> a
noSourceText SourceText -> Integer -> HsTyLit
HsNumTy
listTy :: HsType' -> HsType'
listTy :: HsType' -> HsType'
listTy = (NoExtField -> LHsType GhcPs -> HsType')
-> LHsType GhcPs -> HsType'
forall a. (NoExtField -> a) -> a
withEpAnnNotUsed NoExtField -> LHsType GhcPs -> HsType'
forall pass. XListTy pass -> LHsType pass -> HsType pass
HsListTy (LHsType GhcPs -> HsType')
-> (HsType' -> LHsType GhcPs) -> HsType' -> HsType'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated
listPromotedTy :: [HsType'] -> HsType'
listPromotedTy :: [HsType'] -> HsType'
listPromotedTy = ([LHsType GhcPs] -> HsType') -> [LHsType GhcPs] -> HsType'
forall a. a -> a
withPlaceHolder ((NoExtField -> PromotionFlag -> [LHsType GhcPs] -> HsType')
-> PromotionFlag -> [LHsType GhcPs] -> HsType'
forall a. (NoExtField -> a) -> a
withEpAnnNotUsed NoExtField -> PromotionFlag -> [LHsType GhcPs] -> HsType'
forall pass.
XExplicitListTy pass
-> PromotionFlag -> [LHsType pass] -> HsType pass
HsExplicitListTy PromotionFlag
promoted) ([LHsType GhcPs] -> HsType')
-> ([HsType'] -> [LHsType GhcPs]) -> [HsType'] -> HsType'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HsType' -> LHsType GhcPs) -> [HsType'] -> [LHsType GhcPs]
forall a b. (a -> b) -> [a] -> [b]
map HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated
tuplePromotedTy :: [HsType'] -> HsType'
tuplePromotedTy :: [HsType'] -> HsType'
tuplePromotedTy = ([LHsType GhcPs] -> HsType') -> [LHsType GhcPs] -> HsType'
forall a. a -> a
withPlaceHolders ((NoExtField -> [LHsType GhcPs] -> HsType')
-> [LHsType GhcPs] -> HsType'
forall a. (NoExtField -> a) -> a
withEpAnnNotUsed NoExtField -> [LHsType GhcPs] -> HsType'
forall pass. XExplicitTupleTy pass -> [LHsType pass] -> HsType pass
HsExplicitTupleTy) ([LHsType GhcPs] -> HsType')
-> ([HsType'] -> [LHsType GhcPs]) -> [HsType'] -> HsType'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HsType' -> LHsType GhcPs) -> [HsType'] -> [LHsType GhcPs]
forall a b. (a -> b) -> [a] -> [b]
map HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated
(-->) :: HsType' -> HsType' -> HsType'
HsType'
a --> :: HsType' -> HsType' -> HsType'
--> HsType'
b = (NoExtField -> LHsType GhcPs -> LHsType GhcPs -> HsType')
-> LHsType GhcPs -> LHsType GhcPs -> HsType'
forall a. (NoExtField -> a) -> a
withEpAnnNotUsed NoExtField -> LHsType GhcPs -> LHsType GhcPs -> HsType'
forall pass.
XFunTy pass -> LHsType pass -> LHsType pass -> HsType pass
HsFunTy
#if MIN_VERSION_ghc(9,0,0)
(HsUnrestrictedArrow NormalSyntax)
#endif
(LHsType GhcPs -> LHsType GhcPs
parenthesizeTypeForFun (LHsType GhcPs -> LHsType GhcPs) -> LHsType GhcPs -> LHsType GhcPs
forall a b. (a -> b) -> a -> b
$ HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated HsType'
a) (HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated HsType'
b)
infixr 0 -->
forall' :: [HsTyVarBndrS'] -> HsType' -> HsType'
forall' :: [HsTyVarBndrS'] -> HsType' -> HsType'
forall' [HsTyVarBndrS']
ts = (NoExtField -> [LHsTyVarBndr GhcPs] -> LHsType GhcPs -> HsType')
-> [LHsTyVarBndr GhcPs] -> LHsType GhcPs -> HsType'
forall a. (NoExtField -> a) -> a
noExt NoExtField -> [LHsTyVarBndr GhcPs] -> LHsType GhcPs -> HsType'
forall pass.
XForAllTy pass
-> [LHsTyVarBndr pass] -> LHsType pass -> HsType pass
hsForAllTy ((HsTyVarBndrS' -> LHsTyVarBndr GhcPs)
-> [HsTyVarBndrS'] -> [LHsTyVarBndr GhcPs]
forall a b. (a -> b) -> [a] -> [b]
map HsTyVarBndrS' -> LHsTyVarBndr GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated [HsTyVarBndrS']
ts) (LHsType GhcPs -> HsType')
-> (HsType' -> LHsType GhcPs) -> HsType' -> HsType'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated
where
#if MIN_VERSION_ghc(9,2,0)
hsForAllTy x = HsForAllTy x . withEpAnnNotUsed mkHsForAllInvisTele
#elif MIN_VERSION_ghc(9,0,0)
hsForAllTy x = HsForAllTy x . mkHsForAllInvisTele
#elif MIN_VERSION_ghc(8,10,0)
fvf :: ForallVisFlag
fvf = ForallVisFlag
ForallInvis
hsForAllTy :: XForAllTy pass
-> [LHsTyVarBndr pass] -> LHsType pass -> HsType pass
hsForAllTy XForAllTy pass
x = XForAllTy pass
-> ForallVisFlag
-> [LHsTyVarBndr pass]
-> LHsType pass
-> HsType pass
forall pass.
XForAllTy pass
-> ForallVisFlag
-> [LHsTyVarBndr pass]
-> LHsType pass
-> HsType pass
HsForAllTy XForAllTy pass
x ForallVisFlag
fvf
#else
hsForAllTy = HsForAllTy
#endif
(==>) :: [HsType'] -> HsType' -> HsType'
==> :: [HsType'] -> HsType' -> HsType'
(==>) [HsType']
cs = LHsContext GhcPs -> LHsType GhcPs -> HsType'
hsQualTy ([LHsType GhcPs] -> LHsContext GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated ((HsType' -> LHsType GhcPs) -> [HsType'] -> [LHsType GhcPs]
forall a b. (a -> b) -> [a] -> [b]
map HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated [HsType']
cs)) (LHsType GhcPs -> HsType')
-> (HsType' -> LHsType GhcPs) -> HsType' -> HsType'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated
where
#if MIN_VERSION_ghc(9,2,0)
hsQualTy = noExt HsQualTy . Just
#else
hsQualTy :: LHsContext GhcPs -> LHsType GhcPs -> HsType'
hsQualTy = (NoExtField -> LHsContext GhcPs -> LHsType GhcPs -> HsType')
-> LHsContext GhcPs -> LHsType GhcPs -> HsType'
forall a. (NoExtField -> a) -> a
noExt NoExtField -> LHsContext GhcPs -> LHsType GhcPs -> HsType'
forall pass.
XQualTy pass -> LHsContext pass -> LHsType pass -> HsType pass
HsQualTy
#endif
infixr 0 ==>
kindedVar :: OccNameStr -> HsType' -> HsTyVarBndr'
kindedVar :: OccNameStr -> HsType' -> HsTyVarBndrS'
kindedVar OccNameStr
v HsType'
t = (NoExtField -> LocatedN RdrName -> LHsType GhcPs -> HsTyVarBndrS')
-> LocatedN RdrName -> LHsType GhcPs -> HsTyVarBndrS'
forall a. (NoExtField -> a) -> a
withEpAnnNotUsed NoExtField -> LocatedN RdrName -> LHsType GhcPs -> HsTyVarBndrS'
forall pass.
XKindedTyVar pass
-> Located (IdP pass) -> LHsKind pass -> HsTyVarBndr pass
KindedTyVar
#if MIN_VERSION_ghc(9,0,0)
()
#endif
(RdrNameStr -> LocatedN RdrName
typeRdrName (RdrNameStr -> LocatedN RdrName) -> RdrNameStr -> LocatedN RdrName
forall a b. (a -> b) -> a -> b
$ OccNameStr -> RdrNameStr
UnqualStr OccNameStr
v) (HsType' -> LHsType GhcPs
forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated HsType'
t)