{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE BangPatterns #-}
module Language.Haskell.Liquid.GHC.API (
module Ghc
#ifdef MIN_VERSION_GLASGOW_HASKELL
#if MIN_VERSION_GLASGOW_HASKELL(8,6,5,0) && !MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)
, VarBndr
, AnonArgFlag(..)
, pattern Bndr
, pattern FunTy
, pattern AnonTCB
, pattern LitString
, pattern LitFloat
, pattern LitDouble
, pattern LitChar
, ft_af, ft_arg, ft_res
, bytesFS
, mkFunTy
, isEvVarType
, isEqPrimPred
#endif
#endif
, tyConRealArity
, dataConExTyVars
) where
import Avail as Ghc
import GHC as Ghc hiding (Warning)
import ConLike as Ghc
import Var as Ghc
import Module as Ghc
import DataCon as Ghc
import TysWiredIn as Ghc
import BasicTypes as Ghc
import CoreSyn as Ghc hiding (AnnExpr, AnnExpr' (..), AnnRec, AnnCase)
import NameSet as Ghc
import InstEnv as Ghc
import Literal as Ghc
import TcType as Ghc (isClassPred)
import Class as Ghc
import Unique as Ghc
import RdrName as Ghc
import SrcLoc as Ghc
import Name as Ghc hiding (varName)
import TysPrim as Ghc
import HscTypes as Ghc
import HscMain as Ghc
import Id as Ghc hiding (lazySetIdInfo, setIdExported, setIdNotExported)
import ErrUtils as Ghc
import DynFlags as Ghc
#ifdef MIN_VERSION_GLASGOW_HASKELL
#if MIN_VERSION_GLASGOW_HASKELL(8,6,5,0) && !MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)
import Binary
import Data.ByteString (ByteString)
import Data.Data (Data)
import Outputable
import Kind as Ghc (classifiesTypeWithValues)
import FastString as Ghc hiding (bytesFS, LitString)
import TyCoRep as Ghc hiding (Type (FunTy), mkFunTy)
import TyCon as Ghc hiding (TyConBndrVis(AnonTCB))
import Type as Ghc hiding (typeKind, mkFunTy)
import qualified Type as Ghc
import qualified TyCoRep as Ty
import qualified Literal as Lit
import qualified TyCon as Ty
import qualified Var as Var
import qualified GHC.Real
#endif
#endif
#ifdef MIN_VERSION_GLASGOW_HASKELL
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0)
import Type as Ghc hiding (typeKind , isPredTy)
import TyCon as Ghc
import TyCoRep as Ghc
import FastString as Ghc
import Predicate as Ghc (isEqPred, getClassPredTys_maybe, isEvVarType, isEqPrimPred)
import Data.Foldable (asum)
#endif
#endif
#ifdef MIN_VERSION_GLASGOW_HASKELL
#if MIN_VERSION_GLASGOW_HASKELL(8,6,5,0) && !MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)
data AnonArgFlag
= VisArg
| InvisArg
deriving (Eq, Ord, Data)
instance Outputable AnonArgFlag where
ppr VisArg = text "[vis]"
ppr InvisArg = text "[invis]"
instance Binary AnonArgFlag where
put_ bh VisArg = putByte bh 0
put_ bh InvisArg = putByte bh 1
get bh = do
h <- getByte bh
case h of
0 -> return VisArg
_ -> return InvisArg
bytesFS :: FastString -> ByteString
bytesFS = fastStringToByteString
mkFunTy :: AnonArgFlag -> Type -> Type -> Type
mkFunTy _ = Ty.FunTy
pattern Bndr :: var -> argf -> Var.TyVarBndr var argf
pattern Bndr var argf <- TvBndr var argf where
Bndr var argf = TvBndr var argf
type VarBndr = TyVarBndr
pattern FunTy :: AnonArgFlag -> Type -> Type -> Type
pattern FunTy { ft_af, ft_arg, ft_res } <- ((VisArg,) -> (ft_af, Ty.FunTy ft_arg ft_res)) where
FunTy _ft_af ft_arg ft_res = Ty.FunTy ft_arg ft_res
pattern AnonTCB :: AnonArgFlag -> Ty.TyConBndrVis
pattern AnonTCB af <- ((VisArg,) -> (af, Ty.AnonTCB)) where
AnonTCB _af = Ty.AnonTCB
pattern LitString :: ByteString -> Lit.Literal
pattern LitString bs <- Lit.MachStr bs where
LitString bs = Lit.MachStr bs
pattern LitFloat :: GHC.Real.Ratio Integer -> Lit.Literal
pattern LitFloat f <- Lit.MachFloat f where
LitFloat f = Lit.MachFloat f
pattern LitDouble :: GHC.Real.Ratio Integer -> Lit.Literal
pattern LitDouble d <- Lit.MachDouble d where
LitDouble d = Lit.MachDouble d
pattern LitChar :: Char -> Lit.Literal
pattern LitChar c <- Lit.MachChar c where
LitChar c = Lit.MachChar c
tyConRealArity :: TyCon -> Int
tyConRealArity = tyConArity
isEvVarType :: Type -> Bool
isEvVarType = Ghc.isPredTy
isEqPrimPred :: Type -> Bool
isEqPrimPred = Ghc.isPredTy
#endif
#if MIN_VERSION_GLASGOW_HASKELL(8,10,0,0)
tyConRealArity :: TyCon -> Int
tyConRealArity :: TyCon -> Int
tyConRealArity TyCon
tc = Int -> Kind -> Int
go Int
0 (TyCon -> Kind
tyConKind TyCon
tc)
where
go :: Int -> Kind -> Int
go :: Int -> Kind -> Int
go !Int
acc Kind
k =
case [Maybe Kind] -> Maybe Kind
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [((Kind, Kind) -> Kind) -> Maybe (Kind, Kind) -> Maybe Kind
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Kind, Kind) -> Kind
forall a b. (a, b) -> b
snd (Kind -> Maybe (Kind, Kind)
splitFunTy_maybe Kind
k), ((TyCoVar, Kind) -> Kind) -> Maybe (TyCoVar, Kind) -> Maybe Kind
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TyCoVar, Kind) -> Kind
forall a b. (a, b) -> b
snd (Kind -> Maybe (TyCoVar, Kind)
splitForAllTy_maybe Kind
k)] of
Maybe Kind
Nothing -> Int
acc
Just Kind
ks -> Int -> Kind -> Int
go (Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Kind
ks
dataConExTyVars :: DataCon -> [TyVar]
dataConExTyVars :: DataCon -> [TyCoVar]
dataConExTyVars = DataCon -> [TyCoVar]
dataConExTyCoVars
#endif
#endif