{-# LANGUAGE CPP, DeriveDataTypeable, RankNTypes, ScopedTypeVariables, TupleSections #-}
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE TypeApplications #-}
#endif
module Language.Haskell.TH.Desugar.Util (
newUniqueName,
impossible,
nameOccursIn, allNamesIn, mkTypeName, mkDataName, mkNameWith, isDataName,
stripVarP_maybe, extractBoundNamesStmt,
concatMapM, mapAccumLM, mapMaybeM, expectJustM,
stripPlainTV_maybe,
thirdOf3, splitAtList, extractBoundNamesDec,
extractBoundNamesPat,
tvbToType, tvbToTypeWithSig, tvbToTANormalWithSig,
nameMatches, thdOf3, liftFst, liftSnd, firstMatch,
unboxedSumDegree_maybe, unboxedSumNameDegree_maybe,
tupleDegree_maybe, tupleNameDegree_maybe, unboxedTupleDegree_maybe,
unboxedTupleNameDegree_maybe, splitTuple_maybe,
topEverywhereM, isInfixDataCon,
isTypeKindName, typeKindName,
unSigType, unfoldType, ForallTelescope(..), FunArgs(..), VisFunArg(..),
filterVisFunArgs, ravelType, unravelType,
TypeArg(..), applyType, filterTANormals, probablyWrongUnTypeArg
#if __GLASGOW_HASKELL__ >= 800
, bindIP
#endif
) where
import Prelude hiding (mapM, foldl, concatMap, any)
import Language.Haskell.TH hiding ( cxt )
import Language.Haskell.TH.Datatype.TyVarBndr
import qualified Language.Haskell.TH.Desugar.OSet as OS
import Language.Haskell.TH.Desugar.OSet (OSet)
import Language.Haskell.TH.Syntax
import qualified Control.Monad.Fail as Fail
import Data.Foldable
import Data.Generics hiding ( Fixity )
import Data.Traversable
import Data.Maybe
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid
#endif
#if __GLASGOW_HASKELL__ >= 800
import qualified Data.Kind as Kind
import GHC.Classes ( IP )
import Unsafe.Coerce ( unsafeCoerce )
#endif
newUniqueName :: Quasi q => String -> q Name
newUniqueName :: String -> q Name
newUniqueName String
str = do
Name
n <- String -> q Name
forall (m :: * -> *). Quasi m => String -> m Name
qNewName String
str
String -> q Name
forall (m :: * -> *). Quasi m => String -> m Name
qNewName (String -> q Name) -> String -> q Name
forall a b. (a -> b) -> a -> b
$ Name -> String
forall a. Show a => a -> String
show Name
n
mkNameWith :: Quasi q => (String -> q (Maybe Name))
-> (String -> String -> String -> Name)
-> String -> q Name
mkNameWith :: (String -> q (Maybe Name))
-> (String -> String -> String -> Name) -> String -> q Name
mkNameWith String -> q (Maybe Name)
lookup_fun String -> String -> String -> Name
mkName_fun String
str = do
Maybe Name
m_name <- String -> q (Maybe Name)
lookup_fun String
str
case Maybe Name
m_name of
Just Name
name -> Name -> q Name
forall (m :: * -> *) a. Monad m => a -> m a
return Name
name
Maybe Name
Nothing -> do
Loc { loc_package :: Loc -> String
loc_package = String
pkg, loc_module :: Loc -> String
loc_module = String
modu } <- q Loc
forall (m :: * -> *). Quasi m => m Loc
qLocation
Name -> q Name
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> q Name) -> Name -> q Name
forall a b. (a -> b) -> a -> b
$ String -> String -> String -> Name
mkName_fun String
pkg String
modu String
str
mkTypeName :: Quasi q => String -> q Name
mkTypeName :: String -> q Name
mkTypeName = (String -> q (Maybe Name))
-> (String -> String -> String -> Name) -> String -> q Name
forall (q :: * -> *).
Quasi q =>
(String -> q (Maybe Name))
-> (String -> String -> String -> Name) -> String -> q Name
mkNameWith (Bool -> String -> q (Maybe Name)
forall (m :: * -> *). Quasi m => Bool -> String -> m (Maybe Name)
qLookupName Bool
True) String -> String -> String -> Name
mkNameG_tc
mkDataName :: Quasi q => String -> q Name
mkDataName :: String -> q Name
mkDataName = (String -> q (Maybe Name))
-> (String -> String -> String -> Name) -> String -> q Name
forall (q :: * -> *).
Quasi q =>
(String -> q (Maybe Name))
-> (String -> String -> String -> Name) -> String -> q Name
mkNameWith (Bool -> String -> q (Maybe Name)
forall (m :: * -> *). Quasi m => Bool -> String -> m (Maybe Name)
qLookupName Bool
False) String -> String -> String -> Name
mkNameG_d
isDataName :: Name -> Bool
isDataName :: Name -> Bool
isDataName (Name OccName
_ (NameG NameSpace
DataName PkgName
_ ModName
_)) = Bool
True
isDataName Name
_ = Bool
False
stripVarP_maybe :: Pat -> Maybe Name
stripVarP_maybe :: Pat -> Maybe Name
stripVarP_maybe (VarP Name
name) = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
name
stripVarP_maybe Pat
_ = Maybe Name
forall a. Maybe a
Nothing
stripPlainTV_maybe :: TyVarBndr_ flag -> Maybe Name
stripPlainTV_maybe :: TyVarBndr_ flag -> Maybe Name
stripPlainTV_maybe = (Name -> Maybe Name)
-> (Name -> Kind -> Maybe Name) -> TyVarBndr_ flag -> Maybe Name
forall r flag.
(Name -> r) -> (Name -> Kind -> r) -> TyVarBndr_ flag -> r
elimTV Name -> Maybe Name
forall a. a -> Maybe a
Just (\Name
_ Kind
_ -> Maybe Name
forall a. Maybe a
Nothing)
impossible :: Fail.MonadFail q => String -> q a
impossible :: String -> q a
impossible String
err = String -> q a
forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail (String
err String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n This should not happen in Haskell.\n Please email rae@cs.brynmawr.edu with your code if you see this.")
tvbToType :: TyVarBndr_ flag -> Type
tvbToType :: TyVarBndr_ flag -> Kind
tvbToType = Name -> Kind
VarT (Name -> Kind)
-> (TyVarBndr_ flag -> Name) -> TyVarBndr_ flag -> Kind
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyVarBndr_ flag -> Name
forall flag. TyVarBndr_ flag -> Name
tvName
tvbToTypeWithSig :: TyVarBndr_ flag -> Type
tvbToTypeWithSig :: TyVarBndr_ flag -> Kind
tvbToTypeWithSig = (Name -> Kind) -> (Name -> Kind -> Kind) -> TyVarBndr_ flag -> Kind
forall r flag.
(Name -> r) -> (Name -> Kind -> r) -> TyVarBndr_ flag -> r
elimTV Name -> Kind
VarT (\Name
n Kind
k -> Kind -> Kind -> Kind
SigT (Name -> Kind
VarT Name
n) Kind
k)
tvbToTANormalWithSig :: TyVarBndr_ flag -> TypeArg
tvbToTANormalWithSig :: TyVarBndr_ flag -> TypeArg
tvbToTANormalWithSig = Kind -> TypeArg
TANormal (Kind -> TypeArg)
-> (TyVarBndr_ flag -> Kind) -> TyVarBndr_ flag -> TypeArg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyVarBndr_ flag -> Kind
forall flag. TyVarBndr_ flag -> Kind
tvbToTypeWithSig
nameMatches :: Name -> Name -> Bool
nameMatches :: Name -> Name -> Bool
nameMatches n1 :: Name
n1@(Name OccName
occ1 NameFlavour
flav1) n2 :: Name
n2@(Name OccName
occ2 NameFlavour
flav2)
| NameFlavour
NameS <- NameFlavour
flav1 = OccName
occ1 OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== OccName
occ2
| NameFlavour
NameS <- NameFlavour
flav2 = OccName
occ1 OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== OccName
occ2
| NameQ ModName
mod1 <- NameFlavour
flav1
, NameQ ModName
mod2 <- NameFlavour
flav2
= ModName
mod1 ModName -> ModName -> Bool
forall a. Eq a => a -> a -> Bool
== ModName
mod2 Bool -> Bool -> Bool
&& OccName
occ1 OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== OccName
occ2
| NameQ ModName
mod1 <- NameFlavour
flav1
, NameG NameSpace
_ PkgName
_ ModName
mod2 <- NameFlavour
flav2
= ModName
mod1 ModName -> ModName -> Bool
forall a. Eq a => a -> a -> Bool
== ModName
mod2 Bool -> Bool -> Bool
&& OccName
occ1 OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== OccName
occ2
| NameG NameSpace
_ PkgName
_ ModName
mod1 <- NameFlavour
flav1
, NameQ ModName
mod2 <- NameFlavour
flav2
= ModName
mod1 ModName -> ModName -> Bool
forall a. Eq a => a -> a -> Bool
== ModName
mod2 Bool -> Bool -> Bool
&& OccName
occ1 OccName -> OccName -> Bool
forall a. Eq a => a -> a -> Bool
== OccName
occ2
| Bool
otherwise
= Name
n1 Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
n2
tupleDegree_maybe :: String -> Maybe Int
tupleDegree_maybe :: String -> Maybe Int
tupleDegree_maybe String
s = do
Char
'(' : String
s1 <- String -> Maybe String
forall (m :: * -> *) a. Monad m => a -> m a
return String
s
(String
commas, String
")") <- (String, String) -> Maybe (String, String)
forall (m :: * -> *) a. Monad m => a -> m a
return ((String, String) -> Maybe (String, String))
-> (String, String) -> Maybe (String, String)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
',') String
s1
let degree :: Int
degree
| String
"" <- String
commas = Int
0
| Bool
otherwise = String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
commas Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
Int -> Maybe Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
degree
tupleNameDegree_maybe :: Name -> Maybe Int
tupleNameDegree_maybe :: Name -> Maybe Int
tupleNameDegree_maybe = String -> Maybe Int
tupleDegree_maybe (String -> Maybe Int) -> (Name -> String) -> Name -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase
unboxedSumDegree_maybe :: String -> Maybe Int
unboxedSumDegree_maybe :: String -> Maybe Int
unboxedSumDegree_maybe = Char -> String -> Maybe Int
unboxedSumTupleDegree_maybe Char
'|'
unboxedSumNameDegree_maybe :: Name -> Maybe Int
unboxedSumNameDegree_maybe :: Name -> Maybe Int
unboxedSumNameDegree_maybe = String -> Maybe Int
unboxedSumDegree_maybe (String -> Maybe Int) -> (Name -> String) -> Name -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase
unboxedTupleDegree_maybe :: String -> Maybe Int
unboxedTupleDegree_maybe :: String -> Maybe Int
unboxedTupleDegree_maybe = Char -> String -> Maybe Int
unboxedSumTupleDegree_maybe Char
','
unboxedSumTupleDegree_maybe :: Char -> String -> Maybe Int
unboxedSumTupleDegree_maybe :: Char -> String -> Maybe Int
unboxedSumTupleDegree_maybe Char
sep String
s = do
Char
'(' : Char
'#' : String
s1 <- String -> Maybe String
forall (m :: * -> *) a. Monad m => a -> m a
return String
s
(String
seps, String
"#)") <- (String, String) -> Maybe (String, String)
forall (m :: * -> *) a. Monad m => a -> m a
return ((String, String) -> Maybe (String, String))
-> (String, String) -> Maybe (String, String)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
sep) String
s1
let degree :: Int
degree
| String
"" <- String
seps = Int
0
| Bool
otherwise = String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
seps Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
Int -> Maybe Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
degree
unboxedTupleNameDegree_maybe :: Name -> Maybe Int
unboxedTupleNameDegree_maybe :: Name -> Maybe Int
unboxedTupleNameDegree_maybe = String -> Maybe Int
unboxedTupleDegree_maybe (String -> Maybe Int) -> (Name -> String) -> Name -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase
splitTuple_maybe :: Type -> Maybe [Type]
splitTuple_maybe :: Kind -> Maybe [Kind]
splitTuple_maybe Kind
t = [Kind] -> Kind -> Maybe [Kind]
go [] Kind
t
where go :: [Kind] -> Kind -> Maybe [Kind]
go [Kind]
args (Kind
t1 `AppT` Kind
t2) = [Kind] -> Kind -> Maybe [Kind]
go (Kind
t2Kind -> [Kind] -> [Kind]
forall a. a -> [a] -> [a]
:[Kind]
args) Kind
t1
go [Kind]
args (Kind
t1 `SigT` Kind
_k) = [Kind] -> Kind -> Maybe [Kind]
go [Kind]
args Kind
t1
go [Kind]
args (ConT Name
con_name)
| Just Int
degree <- Name -> Maybe Int
tupleNameDegree_maybe Name
con_name
, [Kind] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Kind]
args Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
degree
= [Kind] -> Maybe [Kind]
forall a. a -> Maybe a
Just [Kind]
args
go [Kind]
args (TupleT Int
degree)
| [Kind] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Kind]
args Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
degree
= [Kind] -> Maybe [Kind]
forall a. a -> Maybe a
Just [Kind]
args
go [Kind]
_ Kind
_ = Maybe [Kind]
forall a. Maybe a
Nothing
data ForallTelescope
= ForallVis [TyVarBndrUnit]
| ForallInvis [TyVarBndrSpec]
deriving (ForallTelescope -> ForallTelescope -> Bool
(ForallTelescope -> ForallTelescope -> Bool)
-> (ForallTelescope -> ForallTelescope -> Bool)
-> Eq ForallTelescope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForallTelescope -> ForallTelescope -> Bool
$c/= :: ForallTelescope -> ForallTelescope -> Bool
== :: ForallTelescope -> ForallTelescope -> Bool
$c== :: ForallTelescope -> ForallTelescope -> Bool
Eq, Int -> ForallTelescope -> String -> String
[ForallTelescope] -> String -> String
ForallTelescope -> String
(Int -> ForallTelescope -> String -> String)
-> (ForallTelescope -> String)
-> ([ForallTelescope] -> String -> String)
-> Show ForallTelescope
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ForallTelescope] -> String -> String
$cshowList :: [ForallTelescope] -> String -> String
show :: ForallTelescope -> String
$cshow :: ForallTelescope -> String
showsPrec :: Int -> ForallTelescope -> String -> String
$cshowsPrec :: Int -> ForallTelescope -> String -> String
Show, Typeable, Typeable ForallTelescope
DataType
Constr
Typeable ForallTelescope
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ForallTelescope -> c ForallTelescope)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ForallTelescope)
-> (ForallTelescope -> Constr)
-> (ForallTelescope -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ForallTelescope))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ForallTelescope))
-> ((forall b. Data b => b -> b)
-> ForallTelescope -> ForallTelescope)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ForallTelescope -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ForallTelescope -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ForallTelescope -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ForallTelescope -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope)
-> Data ForallTelescope
ForallTelescope -> DataType
ForallTelescope -> Constr
(forall b. Data b => b -> b) -> ForallTelescope -> ForallTelescope
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ForallTelescope -> c ForallTelescope
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ForallTelescope
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) -> ForallTelescope -> u
forall u. (forall d. Data d => d -> u) -> ForallTelescope -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ForallTelescope -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ForallTelescope -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ForallTelescope
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ForallTelescope -> c ForallTelescope
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ForallTelescope)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ForallTelescope)
$cForallInvis :: Constr
$cForallVis :: Constr
$tForallTelescope :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope
gmapMp :: (forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope
gmapM :: (forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ForallTelescope -> m ForallTelescope
gmapQi :: Int -> (forall d. Data d => d -> u) -> ForallTelescope -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ForallTelescope -> u
gmapQ :: (forall d. Data d => d -> u) -> ForallTelescope -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ForallTelescope -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ForallTelescope -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ForallTelescope -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ForallTelescope -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ForallTelescope -> r
gmapT :: (forall b. Data b => b -> b) -> ForallTelescope -> ForallTelescope
$cgmapT :: (forall b. Data b => b -> b) -> ForallTelescope -> ForallTelescope
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ForallTelescope)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ForallTelescope)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ForallTelescope)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ForallTelescope)
dataTypeOf :: ForallTelescope -> DataType
$cdataTypeOf :: ForallTelescope -> DataType
toConstr :: ForallTelescope -> Constr
$ctoConstr :: ForallTelescope -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ForallTelescope
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ForallTelescope
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ForallTelescope -> c ForallTelescope
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ForallTelescope -> c ForallTelescope
$cp1Data :: Typeable ForallTelescope
Data)
data FunArgs
= FANil
| FAForalls ForallTelescope FunArgs
| FACxt Cxt FunArgs
| FAAnon Type FunArgs
deriving (FunArgs -> FunArgs -> Bool
(FunArgs -> FunArgs -> Bool)
-> (FunArgs -> FunArgs -> Bool) -> Eq FunArgs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FunArgs -> FunArgs -> Bool
$c/= :: FunArgs -> FunArgs -> Bool
== :: FunArgs -> FunArgs -> Bool
$c== :: FunArgs -> FunArgs -> Bool
Eq, Int -> FunArgs -> String -> String
[FunArgs] -> String -> String
FunArgs -> String
(Int -> FunArgs -> String -> String)
-> (FunArgs -> String)
-> ([FunArgs] -> String -> String)
-> Show FunArgs
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FunArgs] -> String -> String
$cshowList :: [FunArgs] -> String -> String
show :: FunArgs -> String
$cshow :: FunArgs -> String
showsPrec :: Int -> FunArgs -> String -> String
$cshowsPrec :: Int -> FunArgs -> String -> String
Show, Typeable, Typeable FunArgs
DataType
Constr
Typeable FunArgs
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunArgs -> c FunArgs)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunArgs)
-> (FunArgs -> Constr)
-> (FunArgs -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunArgs))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunArgs))
-> ((forall b. Data b => b -> b) -> FunArgs -> FunArgs)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunArgs -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunArgs -> r)
-> (forall u. (forall d. Data d => d -> u) -> FunArgs -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> FunArgs -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunArgs -> m FunArgs)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunArgs -> m FunArgs)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunArgs -> m FunArgs)
-> Data FunArgs
FunArgs -> DataType
FunArgs -> Constr
(forall b. Data b => b -> b) -> FunArgs -> FunArgs
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunArgs -> c FunArgs
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunArgs
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) -> FunArgs -> u
forall u. (forall d. Data d => d -> u) -> FunArgs -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunArgs -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunArgs -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunArgs -> m FunArgs
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunArgs -> m FunArgs
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunArgs
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunArgs -> c FunArgs
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunArgs)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunArgs)
$cFAAnon :: Constr
$cFACxt :: Constr
$cFAForalls :: Constr
$cFANil :: Constr
$tFunArgs :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> FunArgs -> m FunArgs
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunArgs -> m FunArgs
gmapMp :: (forall d. Data d => d -> m d) -> FunArgs -> m FunArgs
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FunArgs -> m FunArgs
gmapM :: (forall d. Data d => d -> m d) -> FunArgs -> m FunArgs
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FunArgs -> m FunArgs
gmapQi :: Int -> (forall d. Data d => d -> u) -> FunArgs -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FunArgs -> u
gmapQ :: (forall d. Data d => d -> u) -> FunArgs -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FunArgs -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunArgs -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunArgs -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunArgs -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunArgs -> r
gmapT :: (forall b. Data b => b -> b) -> FunArgs -> FunArgs
$cgmapT :: (forall b. Data b => b -> b) -> FunArgs -> FunArgs
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunArgs)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunArgs)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FunArgs)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunArgs)
dataTypeOf :: FunArgs -> DataType
$cdataTypeOf :: FunArgs -> DataType
toConstr :: FunArgs -> Constr
$ctoConstr :: FunArgs -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunArgs
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunArgs
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunArgs -> c FunArgs
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunArgs -> c FunArgs
$cp1Data :: Typeable FunArgs
Data)
data VisFunArg
= VisFADep TyVarBndrUnit
| VisFAAnon Type
deriving (VisFunArg -> VisFunArg -> Bool
(VisFunArg -> VisFunArg -> Bool)
-> (VisFunArg -> VisFunArg -> Bool) -> Eq VisFunArg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VisFunArg -> VisFunArg -> Bool
$c/= :: VisFunArg -> VisFunArg -> Bool
== :: VisFunArg -> VisFunArg -> Bool
$c== :: VisFunArg -> VisFunArg -> Bool
Eq, Int -> VisFunArg -> String -> String
[VisFunArg] -> String -> String
VisFunArg -> String
(Int -> VisFunArg -> String -> String)
-> (VisFunArg -> String)
-> ([VisFunArg] -> String -> String)
-> Show VisFunArg
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VisFunArg] -> String -> String
$cshowList :: [VisFunArg] -> String -> String
show :: VisFunArg -> String
$cshow :: VisFunArg -> String
showsPrec :: Int -> VisFunArg -> String -> String
$cshowsPrec :: Int -> VisFunArg -> String -> String
Show, Typeable, Typeable VisFunArg
DataType
Constr
Typeable VisFunArg
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VisFunArg -> c VisFunArg)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VisFunArg)
-> (VisFunArg -> Constr)
-> (VisFunArg -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VisFunArg))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VisFunArg))
-> ((forall b. Data b => b -> b) -> VisFunArg -> VisFunArg)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VisFunArg -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VisFunArg -> r)
-> (forall u. (forall d. Data d => d -> u) -> VisFunArg -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> VisFunArg -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg)
-> Data VisFunArg
VisFunArg -> DataType
VisFunArg -> Constr
(forall b. Data b => b -> b) -> VisFunArg -> VisFunArg
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VisFunArg -> c VisFunArg
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VisFunArg
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) -> VisFunArg -> u
forall u. (forall d. Data d => d -> u) -> VisFunArg -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VisFunArg -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VisFunArg -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VisFunArg
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VisFunArg -> c VisFunArg
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VisFunArg)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VisFunArg)
$cVisFAAnon :: Constr
$cVisFADep :: Constr
$tVisFunArg :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg
gmapMp :: (forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg
gmapM :: (forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> VisFunArg -> m VisFunArg
gmapQi :: Int -> (forall d. Data d => d -> u) -> VisFunArg -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VisFunArg -> u
gmapQ :: (forall d. Data d => d -> u) -> VisFunArg -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VisFunArg -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VisFunArg -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VisFunArg -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VisFunArg -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VisFunArg -> r
gmapT :: (forall b. Data b => b -> b) -> VisFunArg -> VisFunArg
$cgmapT :: (forall b. Data b => b -> b) -> VisFunArg -> VisFunArg
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VisFunArg)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VisFunArg)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c VisFunArg)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VisFunArg)
dataTypeOf :: VisFunArg -> DataType
$cdataTypeOf :: VisFunArg -> DataType
toConstr :: VisFunArg -> Constr
$ctoConstr :: VisFunArg -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VisFunArg
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VisFunArg
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VisFunArg -> c VisFunArg
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VisFunArg -> c VisFunArg
$cp1Data :: Typeable VisFunArg
Data)
filterVisFunArgs :: FunArgs -> [VisFunArg]
filterVisFunArgs :: FunArgs -> [VisFunArg]
filterVisFunArgs FunArgs
FANil = []
filterVisFunArgs (FAForalls ForallTelescope
tele FunArgs
args) =
case ForallTelescope
tele of
ForallVis [TyVarBndr_ flag]
tvbs -> (TyVarBndr_ flag -> VisFunArg) -> [TyVarBndr_ flag] -> [VisFunArg]
forall a b. (a -> b) -> [a] -> [b]
map TyVarBndr_ flag -> VisFunArg
VisFADep [TyVarBndr_ flag]
tvbs [VisFunArg] -> [VisFunArg] -> [VisFunArg]
forall a. [a] -> [a] -> [a]
++ [VisFunArg]
args'
ForallInvis [TyVarBndr_ flag]
_ -> [VisFunArg]
args'
where
args' :: [VisFunArg]
args' = FunArgs -> [VisFunArg]
filterVisFunArgs FunArgs
args
filterVisFunArgs (FACxt [Kind]
_ FunArgs
args) =
FunArgs -> [VisFunArg]
filterVisFunArgs FunArgs
args
filterVisFunArgs (FAAnon Kind
t FunArgs
args) =
Kind -> VisFunArg
VisFAAnon Kind
tVisFunArg -> [VisFunArg] -> [VisFunArg]
forall a. a -> [a] -> [a]
:FunArgs -> [VisFunArg]
filterVisFunArgs FunArgs
args
ravelType :: FunArgs -> Type -> Type
ravelType :: FunArgs -> Kind -> Kind
ravelType FunArgs
FANil Kind
res = Kind
res
ravelType (FAForalls (ForallInvis [TyVarBndr_ flag]
tvbs) (FACxt [Kind]
p FunArgs
args)) Kind
res =
[TyVarBndr_ flag] -> [Kind] -> Kind -> Kind
ForallT [TyVarBndr_ flag]
tvbs [Kind]
p (FunArgs -> Kind -> Kind
ravelType FunArgs
args Kind
res)
ravelType (FAForalls (ForallInvis [TyVarBndr_ flag]
tvbs) FunArgs
args) Kind
res = [TyVarBndr_ flag] -> [Kind] -> Kind -> Kind
ForallT [TyVarBndr_ flag]
tvbs [] (FunArgs -> Kind -> Kind
ravelType FunArgs
args Kind
res)
ravelType (FAForalls (ForallVis [TyVarBndr_ flag]
_tvbs) FunArgs
_args) Kind
_res =
#if __GLASGOW_HASKELL__ >= 809
[TyVarBndr_ flag] -> Kind -> Kind
ForallVisT [TyVarBndr_ flag]
_tvbs (FunArgs -> Kind -> Kind
ravelType FunArgs
_args Kind
_res)
#else
error "Visible dependent quantification supported only on GHC 8.10+"
#endif
ravelType (FACxt [Kind]
cxt FunArgs
args) Kind
res = [TyVarBndr_ flag] -> [Kind] -> Kind -> Kind
ForallT [] [Kind]
cxt (FunArgs -> Kind -> Kind
ravelType FunArgs
args Kind
res)
ravelType (FAAnon Kind
t FunArgs
args) Kind
res = Kind -> Kind -> Kind
AppT (Kind -> Kind -> Kind
AppT Kind
ArrowT Kind
t) (FunArgs -> Kind -> Kind
ravelType FunArgs
args Kind
res)
unravelType :: Type -> (FunArgs, Type)
unravelType :: Kind -> (FunArgs, Kind)
unravelType (ForallT [TyVarBndr_ flag]
tvbs [Kind]
cxt Kind
ty) =
let (FunArgs
args, Kind
res) = Kind -> (FunArgs, Kind)
unravelType Kind
ty in
(ForallTelescope -> FunArgs -> FunArgs
FAForalls ([TyVarBndr_ flag] -> ForallTelescope
ForallInvis [TyVarBndr_ flag]
tvbs) ([Kind] -> FunArgs -> FunArgs
FACxt [Kind]
cxt FunArgs
args), Kind
res)
unravelType (AppT (AppT Kind
ArrowT Kind
t1) Kind
t2) =
let (FunArgs
args, Kind
res) = Kind -> (FunArgs, Kind)
unravelType Kind
t2 in
(Kind -> FunArgs -> FunArgs
FAAnon Kind
t1 FunArgs
args, Kind
res)
#if __GLASGOW_HASKELL__ >= 809
unravelType (ForallVisT [TyVarBndr_ flag]
tvbs Kind
ty) =
let (FunArgs
args, Kind
res) = Kind -> (FunArgs, Kind)
unravelType Kind
ty in
(ForallTelescope -> FunArgs -> FunArgs
FAForalls ([TyVarBndr_ flag] -> ForallTelescope
ForallVis [TyVarBndr_ flag]
tvbs) FunArgs
args, Kind
res)
#endif
unravelType Kind
t = (FunArgs
FANil, Kind
t)
unSigType :: Type -> Type
unSigType :: Kind -> Kind
unSigType (SigT Kind
t Kind
_) = Kind
t
unSigType (AppT Kind
f Kind
x) = Kind -> Kind -> Kind
AppT (Kind -> Kind
unSigType Kind
f) (Kind -> Kind
unSigType Kind
x)
unSigType (ForallT [TyVarBndr_ flag]
tvbs [Kind]
ctxt Kind
t) =
[TyVarBndr_ flag] -> [Kind] -> Kind -> Kind
ForallT [TyVarBndr_ flag]
tvbs ((Kind -> Kind) -> [Kind] -> [Kind]
forall a b. (a -> b) -> [a] -> [b]
map Kind -> Kind
unSigPred [Kind]
ctxt) (Kind -> Kind
unSigType Kind
t)
#if __GLASGOW_HASKELL__ >= 800
unSigType (InfixT Kind
t1 Name
n Kind
t2) = Kind -> Name -> Kind -> Kind
InfixT (Kind -> Kind
unSigType Kind
t1) Name
n (Kind -> Kind
unSigType Kind
t2)
unSigType (UInfixT Kind
t1 Name
n Kind
t2) = Kind -> Name -> Kind -> Kind
UInfixT (Kind -> Kind
unSigType Kind
t1) Name
n (Kind -> Kind
unSigType Kind
t2)
unSigType (ParensT Kind
t) = Kind -> Kind
ParensT (Kind -> Kind
unSigType Kind
t)
#endif
#if __GLASGOW_HASKELL__ >= 807
unSigType (AppKindT Kind
t Kind
k) = Kind -> Kind -> Kind
AppKindT (Kind -> Kind
unSigType Kind
t) (Kind -> Kind
unSigType Kind
k)
unSigType (ImplicitParamT String
n Kind
t) = String -> Kind -> Kind
ImplicitParamT String
n (Kind -> Kind
unSigType Kind
t)
#endif
unSigType Kind
t = Kind
t
unSigPred :: Pred -> Pred
#if __GLASGOW_HASKELL__ >= 710
unSigPred :: Kind -> Kind
unSigPred = Kind -> Kind
unSigType
#else
unSigPred (ClassP n tys) = ClassP n (map unSigType tys)
unSigPred (EqualP t1 t2) = EqualP (unSigType t1) (unSigType t2)
#endif
unfoldType :: Type -> (Type, [TypeArg])
unfoldType :: Kind -> (Kind, [TypeArg])
unfoldType = [TypeArg] -> Kind -> (Kind, [TypeArg])
go []
where
go :: [TypeArg] -> Type -> (Type, [TypeArg])
go :: [TypeArg] -> Kind -> (Kind, [TypeArg])
go [TypeArg]
acc (ForallT [TyVarBndr_ flag]
_ [Kind]
_ Kind
ty) = [TypeArg] -> Kind -> (Kind, [TypeArg])
go [TypeArg]
acc Kind
ty
go [TypeArg]
acc (AppT Kind
ty1 Kind
ty2) = [TypeArg] -> Kind -> (Kind, [TypeArg])
go (Kind -> TypeArg
TANormal Kind
ty2TypeArg -> [TypeArg] -> [TypeArg]
forall a. a -> [a] -> [a]
:[TypeArg]
acc) Kind
ty1
go [TypeArg]
acc (SigT Kind
ty Kind
_) = [TypeArg] -> Kind -> (Kind, [TypeArg])
go [TypeArg]
acc Kind
ty
#if __GLASGOW_HASKELL__ >= 800
go [TypeArg]
acc (ParensT Kind
ty) = [TypeArg] -> Kind -> (Kind, [TypeArg])
go [TypeArg]
acc Kind
ty
#endif
#if __GLASGOW_HASKELL__ >= 807
go [TypeArg]
acc (AppKindT Kind
ty Kind
ki) = [TypeArg] -> Kind -> (Kind, [TypeArg])
go (Kind -> TypeArg
TyArg Kind
kiTypeArg -> [TypeArg] -> [TypeArg]
forall a. a -> [a] -> [a]
:[TypeArg]
acc) Kind
ty
#endif
go [TypeArg]
acc Kind
ty = (Kind
ty, [TypeArg]
acc)
data TypeArg
= TANormal Type
| TyArg Kind
deriving (TypeArg -> TypeArg -> Bool
(TypeArg -> TypeArg -> Bool)
-> (TypeArg -> TypeArg -> Bool) -> Eq TypeArg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeArg -> TypeArg -> Bool
$c/= :: TypeArg -> TypeArg -> Bool
== :: TypeArg -> TypeArg -> Bool
$c== :: TypeArg -> TypeArg -> Bool
Eq, Int -> TypeArg -> String -> String
[TypeArg] -> String -> String
TypeArg -> String
(Int -> TypeArg -> String -> String)
-> (TypeArg -> String)
-> ([TypeArg] -> String -> String)
-> Show TypeArg
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeArg] -> String -> String
$cshowList :: [TypeArg] -> String -> String
show :: TypeArg -> String
$cshow :: TypeArg -> String
showsPrec :: Int -> TypeArg -> String -> String
$cshowsPrec :: Int -> TypeArg -> String -> String
Show, Typeable, Typeable TypeArg
DataType
Constr
Typeable TypeArg
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeArg -> c TypeArg)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeArg)
-> (TypeArg -> Constr)
-> (TypeArg -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TypeArg))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeArg))
-> ((forall b. Data b => b -> b) -> TypeArg -> TypeArg)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeArg -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeArg -> r)
-> (forall u. (forall d. Data d => d -> u) -> TypeArg -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> TypeArg -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TypeArg -> m TypeArg)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TypeArg -> m TypeArg)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TypeArg -> m TypeArg)
-> Data TypeArg
TypeArg -> DataType
TypeArg -> Constr
(forall b. Data b => b -> b) -> TypeArg -> TypeArg
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeArg -> c TypeArg
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeArg
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) -> TypeArg -> u
forall u. (forall d. Data d => d -> u) -> TypeArg -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeArg -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeArg -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TypeArg -> m TypeArg
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TypeArg -> m TypeArg
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeArg
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeArg -> c TypeArg
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TypeArg)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeArg)
$cTyArg :: Constr
$cTANormal :: Constr
$tTypeArg :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TypeArg -> m TypeArg
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TypeArg -> m TypeArg
gmapMp :: (forall d. Data d => d -> m d) -> TypeArg -> m TypeArg
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TypeArg -> m TypeArg
gmapM :: (forall d. Data d => d -> m d) -> TypeArg -> m TypeArg
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TypeArg -> m TypeArg
gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeArg -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TypeArg -> u
gmapQ :: (forall d. Data d => d -> u) -> TypeArg -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TypeArg -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeArg -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeArg -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeArg -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeArg -> r
gmapT :: (forall b. Data b => b -> b) -> TypeArg -> TypeArg
$cgmapT :: (forall b. Data b => b -> b) -> TypeArg -> TypeArg
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeArg)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeArg)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TypeArg)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TypeArg)
dataTypeOf :: TypeArg -> DataType
$cdataTypeOf :: TypeArg -> DataType
toConstr :: TypeArg -> Constr
$ctoConstr :: TypeArg -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeArg
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeArg
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeArg -> c TypeArg
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeArg -> c TypeArg
$cp1Data :: Typeable TypeArg
Data)
applyType :: Type -> [TypeArg] -> Type
applyType :: Kind -> [TypeArg] -> Kind
applyType = (Kind -> TypeArg -> Kind) -> Kind -> [TypeArg] -> Kind
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Kind -> TypeArg -> Kind
apply
where
apply :: Type -> TypeArg -> Type
apply :: Kind -> TypeArg -> Kind
apply Kind
f (TANormal Kind
x) = Kind
f Kind -> Kind -> Kind
`AppT` Kind
x
apply Kind
f (TyArg Kind
_x) =
#if __GLASGOW_HASKELL__ >= 807
Kind
f Kind -> Kind -> Kind
`AppKindT` Kind
_x
#else
f
#endif
filterTANormals :: [TypeArg] -> [Type]
filterTANormals :: [TypeArg] -> [Kind]
filterTANormals = (TypeArg -> Maybe Kind) -> [TypeArg] -> [Kind]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe TypeArg -> Maybe Kind
getTANormal
where
getTANormal :: TypeArg -> Maybe Type
getTANormal :: TypeArg -> Maybe Kind
getTANormal (TANormal Kind
t) = Kind -> Maybe Kind
forall a. a -> Maybe a
Just Kind
t
getTANormal (TyArg {}) = Maybe Kind
forall a. Maybe a
Nothing
probablyWrongUnTypeArg :: TypeArg -> Type
probablyWrongUnTypeArg :: TypeArg -> Kind
probablyWrongUnTypeArg (TANormal Kind
t) = Kind
t
probablyWrongUnTypeArg (TyArg Kind
k) = Kind
k
nameOccursIn :: Data a => Name -> a -> Bool
nameOccursIn :: Name -> a -> Bool
nameOccursIn Name
n = (Bool -> Bool -> Bool) -> GenericQ Bool -> GenericQ Bool
forall r. (r -> r -> r) -> GenericQ r -> GenericQ r
everything Bool -> Bool -> Bool
(||) (GenericQ Bool -> GenericQ Bool) -> GenericQ Bool -> GenericQ Bool
forall a b. (a -> b) -> a -> b
$ Bool -> (Name -> Bool) -> a -> Bool
forall a b r. (Typeable a, Typeable b) => r -> (b -> r) -> a -> r
mkQ Bool
False (Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
n)
allNamesIn :: Data a => a -> [Name]
allNamesIn :: a -> [Name]
allNamesIn = ([Name] -> [Name] -> [Name]) -> GenericQ [Name] -> GenericQ [Name]
forall r. (r -> r -> r) -> GenericQ r -> GenericQ r
everything [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
(++) (GenericQ [Name] -> GenericQ [Name])
-> GenericQ [Name] -> GenericQ [Name]
forall a b. (a -> b) -> a -> b
$ [Name] -> (Name -> [Name]) -> a -> [Name]
forall a b r. (Typeable a, Typeable b) => r -> (b -> r) -> a -> r
mkQ [] (Name -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[])
extractBoundNamesStmt :: Stmt -> OSet Name
(BindS Pat
pat Exp
_) = Pat -> OSet Name
extractBoundNamesPat Pat
pat
extractBoundNamesStmt (LetS [Dec]
decs) = (Dec -> OSet Name) -> [Dec] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Dec -> OSet Name
extractBoundNamesDec [Dec]
decs
extractBoundNamesStmt (NoBindS Exp
_) = OSet Name
forall a. OSet a
OS.empty
extractBoundNamesStmt (ParS [[Stmt]]
stmtss) = ([Stmt] -> OSet Name) -> [[Stmt]] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Stmt -> OSet Name) -> [Stmt] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Stmt -> OSet Name
extractBoundNamesStmt) [[Stmt]]
stmtss
#if __GLASGOW_HASKELL__ >= 807
extractBoundNamesStmt (RecS [Stmt]
stmtss) = (Stmt -> OSet Name) -> [Stmt] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Stmt -> OSet Name
extractBoundNamesStmt [Stmt]
stmtss
#endif
extractBoundNamesDec :: Dec -> OSet Name
(FunD Name
name [Clause]
_) = Name -> OSet Name
forall a. a -> OSet a
OS.singleton Name
name
extractBoundNamesDec (ValD Pat
pat Body
_ [Dec]
_) = Pat -> OSet Name
extractBoundNamesPat Pat
pat
extractBoundNamesDec Dec
_ = OSet Name
forall a. OSet a
OS.empty
extractBoundNamesPat :: Pat -> OSet Name
(LitP Lit
_) = OSet Name
forall a. OSet a
OS.empty
extractBoundNamesPat (VarP Name
name) = Name -> OSet Name
forall a. a -> OSet a
OS.singleton Name
name
extractBoundNamesPat (TupP [Pat]
pats) = (Pat -> OSet Name) -> [Pat] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pat -> OSet Name
extractBoundNamesPat [Pat]
pats
extractBoundNamesPat (UnboxedTupP [Pat]
pats) = (Pat -> OSet Name) -> [Pat] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pat -> OSet Name
extractBoundNamesPat [Pat]
pats
extractBoundNamesPat (ConP Name
_
#if __GLASGOW_HASKELL__ >= 901
_
#endif
[Pat]
pats) = (Pat -> OSet Name) -> [Pat] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pat -> OSet Name
extractBoundNamesPat [Pat]
pats
extractBoundNamesPat (InfixP Pat
p1 Name
_ Pat
p2) = Pat -> OSet Name
extractBoundNamesPat Pat
p1 OSet Name -> OSet Name -> OSet Name
forall a. Ord a => OSet a -> OSet a -> OSet a
`OS.union`
Pat -> OSet Name
extractBoundNamesPat Pat
p2
extractBoundNamesPat (UInfixP Pat
p1 Name
_ Pat
p2) = Pat -> OSet Name
extractBoundNamesPat Pat
p1 OSet Name -> OSet Name -> OSet Name
forall a. Ord a => OSet a -> OSet a -> OSet a
`OS.union`
Pat -> OSet Name
extractBoundNamesPat Pat
p2
extractBoundNamesPat (ParensP Pat
pat) = Pat -> OSet Name
extractBoundNamesPat Pat
pat
extractBoundNamesPat (TildeP Pat
pat) = Pat -> OSet Name
extractBoundNamesPat Pat
pat
extractBoundNamesPat (BangP Pat
pat) = Pat -> OSet Name
extractBoundNamesPat Pat
pat
extractBoundNamesPat (AsP Name
name Pat
pat) = Name -> OSet Name
forall a. a -> OSet a
OS.singleton Name
name OSet Name -> OSet Name -> OSet Name
forall a. Ord a => OSet a -> OSet a -> OSet a
`OS.union`
Pat -> OSet Name
extractBoundNamesPat Pat
pat
extractBoundNamesPat Pat
WildP = OSet Name
forall a. OSet a
OS.empty
extractBoundNamesPat (RecP Name
_ [FieldPat]
field_pats) = let ([Name]
_, [Pat]
pats) = [FieldPat] -> ([Name], [Pat])
forall a b. [(a, b)] -> ([a], [b])
unzip [FieldPat]
field_pats in
(Pat -> OSet Name) -> [Pat] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pat -> OSet Name
extractBoundNamesPat [Pat]
pats
extractBoundNamesPat (ListP [Pat]
pats) = (Pat -> OSet Name) -> [Pat] -> OSet Name
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pat -> OSet Name
extractBoundNamesPat [Pat]
pats
extractBoundNamesPat (SigP Pat
pat Kind
_) = Pat -> OSet Name
extractBoundNamesPat Pat
pat
extractBoundNamesPat (ViewP Exp
_ Pat
pat) = Pat -> OSet Name
extractBoundNamesPat Pat
pat
#if __GLASGOW_HASKELL__ >= 801
extractBoundNamesPat (UnboxedSumP Pat
pat Int
_ Int
_) = Pat -> OSet Name
extractBoundNamesPat Pat
pat
#endif
#if __GLASGOW_HASKELL__ >= 800
newtype MagicIP name a r = MagicIP (IP name a => r)
bindIP :: forall name a r. a -> (IP name a => r) -> r
bindIP :: a -> (IP name a => r) -> r
bindIP a
val IP name a => r
k = (MagicIP name a r -> a -> r
forall a b. a -> b
unsafeCoerce ((IP name a => r) -> MagicIP name a r
forall (name :: Symbol) a r. (IP name a => r) -> MagicIP name a r
MagicIP @name IP name a => r
k) :: a -> r) a
val
#endif
splitAtList :: [a] -> [b] -> ([b], [b])
splitAtList :: [a] -> [b] -> ([b], [b])
splitAtList [] [b]
x = ([], [b]
x)
splitAtList (a
_ : [a]
t) (b
x : [b]
xs) =
let ([b]
as, [b]
bs) = [a] -> [b] -> ([b], [b])
forall a b. [a] -> [b] -> ([b], [b])
splitAtList [a]
t [b]
xs in
(b
x b -> [b] -> [b]
forall a. a -> [a] -> [a]
: [b]
as, [b]
bs)
splitAtList (a
_ : [a]
_) [] = ([], [])
thdOf3 :: (a,b,c) -> c
thdOf3 :: (a, b, c) -> c
thdOf3 (a
_,b
_,c
c) = c
c
liftFst :: (a -> b) -> (a, c) -> (b, c)
liftFst :: (a -> b) -> (a, c) -> (b, c)
liftFst a -> b
f (a
a,c
c) = (a -> b
f a
a, c
c)
liftSnd :: (a -> b) -> (c, a) -> (c, b)
liftSnd :: (a -> b) -> (c, a) -> (c, b)
liftSnd a -> b
f (c
c,a
a) = (c
c, a -> b
f a
a)
thirdOf3 :: (a -> b) -> (c, d, a) -> (c, d, b)
thirdOf3 :: (a -> b) -> (c, d, a) -> (c, d, b)
thirdOf3 a -> b
f (c
c, d
d, a
a) = (c
c, d
d, a -> b
f a
a)
concatMapM :: (Monad monad, Monoid monoid, Traversable t)
=> (a -> monad monoid) -> t a -> monad monoid
concatMapM :: (a -> monad monoid) -> t a -> monad monoid
concatMapM a -> monad monoid
fn t a
list = do
t monoid
bss <- (a -> monad monoid) -> t a -> monad (t monoid)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM a -> monad monoid
fn t a
list
monoid -> monad monoid
forall (m :: * -> *) a. Monad m => a -> m a
return (monoid -> monad monoid) -> monoid -> monad monoid
forall a b. (a -> b) -> a -> b
$ t monoid -> monoid
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold t monoid
bss
mapAccumLM :: Monad m
=> (acc -> x -> m (acc, y))
-> acc
-> [x]
-> m (acc, [y])
mapAccumLM :: (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
mapAccumLM acc -> x -> m (acc, y)
_ acc
s [] = (acc, [y]) -> m (acc, [y])
forall (m :: * -> *) a. Monad m => a -> m a
return (acc
s, [])
mapAccumLM acc -> x -> m (acc, y)
f acc
s (x
x:[x]
xs) = do
(acc
s1, y
x') <- acc -> x -> m (acc, y)
f acc
s x
x
(acc
s2, [y]
xs') <- (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
forall (m :: * -> *) acc x y.
Monad m =>
(acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
mapAccumLM acc -> x -> m (acc, y)
f acc
s1 [x]
xs
(acc, [y]) -> m (acc, [y])
forall (m :: * -> *) a. Monad m => a -> m a
return (acc
s2, y
x' y -> [y] -> [y]
forall a. a -> [a] -> [a]
: [y]
xs')
mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM :: (a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM a -> m (Maybe b)
_ [] = [b] -> m [b]
forall (m :: * -> *) a. Monad m => a -> m a
return []
mapMaybeM a -> m (Maybe b)
f (a
x:[a]
xs) = do
Maybe b
y <- a -> m (Maybe b)
f a
x
[b]
ys <- (a -> m (Maybe b)) -> [a] -> m [b]
forall (m :: * -> *) a b.
Monad m =>
(a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM a -> m (Maybe b)
f [a]
xs
[b] -> m [b]
forall (m :: * -> *) a. Monad m => a -> m a
return ([b] -> m [b]) -> [b] -> m [b]
forall a b. (a -> b) -> a -> b
$ case Maybe b
y of
Maybe b
Nothing -> [b]
ys
Just b
z -> b
z b -> [b] -> [b]
forall a. a -> [a] -> [a]
: [b]
ys
expectJustM :: Fail.MonadFail m => String -> Maybe a -> m a
expectJustM :: String -> Maybe a -> m a
expectJustM String
_ (Just a
x) = a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
expectJustM String
err Maybe a
Nothing = String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail String
err
firstMatch :: (a -> Maybe b) -> [a] -> Maybe b
firstMatch :: (a -> Maybe b) -> [a] -> Maybe b
firstMatch a -> Maybe b
f [a]
xs = [b] -> Maybe b
forall a. [a] -> Maybe a
listToMaybe ([b] -> Maybe b) -> [b] -> Maybe b
forall a b. (a -> b) -> a -> b
$ (a -> Maybe b) -> [a] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe a -> Maybe b
f [a]
xs
topEverywhereM :: (Typeable a, Data b, Monad m) => (a -> m a) -> b -> m b
topEverywhereM :: (a -> m a) -> b -> m b
topEverywhereM a -> m a
handler =
(forall d. Data d => d -> m d) -> b -> m b
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> a -> m a
gmapM ((a -> m a) -> d -> m d
forall a b (m :: * -> *).
(Typeable a, Data b, Monad m) =>
(a -> m a) -> b -> m b
topEverywhereM a -> m a
handler) (b -> m b) -> (a -> m a) -> b -> m b
forall (m :: * -> *) a b.
(Monad m, Typeable a, Typeable b) =>
(a -> m a) -> (b -> m b) -> a -> m a
`extM` a -> m a
handler
isInfixDataCon :: String -> Bool
isInfixDataCon :: String -> Bool
isInfixDataCon (Char
':':String
_) = Bool
True
isInfixDataCon String
_ = Bool
False
isTypeKindName :: Name -> Bool
isTypeKindName :: Name -> Bool
isTypeKindName Name
n = Name
n Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
typeKindName
#if __GLASGOW_HASKELL__ < 805
|| n == starKindName
|| n == uniStarKindName
#endif
typeKindName :: Name
#if __GLASGOW_HASKELL__ >= 800
typeKindName :: Name
typeKindName = ''Kind.Type
#else
typeKindName = starKindName
#endif
#if __GLASGOW_HASKELL__ < 805
starKindName :: Name
#if __GLASGOW_HASKELL__ >= 800
starKindName = ''(Kind.*)
#else
starKindName = mkNameG_tc "ghc-prim" "GHC.Prim" "*"
#endif
uniStarKindName :: Name
#if __GLASGOW_HASKELL__ >= 800
uniStarKindName = ''(Kind.★)
#else
uniStarKindName = starKindName
#endif
#endif