deriving-compat-0.6: Backports of GHC deriving extensions
Copyright(C) 2015-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
PortabilityTemplate Haskell
Safe HaskellNone
LanguageHaskell2010

Data.Deriving.Internal

Description

Template Haskell-related utilities.

Note: this is an internal module, and as such, the API presented here is not guaranteed to be stable, even between minor releases of this library.

Synopsis

Documentation

data Via a b infix 0 Source #

A type-level modifier intended to be used in conjunction with deriveVia. Refer to the documentation for deriveVia for more details.

fmapConst :: f b -> (a -> b) -> f a -> f b Source #

replaceConst :: f a -> a -> f b -> f a Source #

foldrConst :: b -> (a -> b -> b) -> b -> t a -> b Source #

foldMapConst :: m -> (a -> m) -> t a -> m Source #

nullConst :: Bool -> t a -> Bool Source #

traverseConst :: f (t b) -> (a -> f b) -> t a -> f (t b) Source #

eqConst :: Bool -> a -> a -> Bool Source #

eq1Const :: Bool -> f a -> f a -> Bool Source #

liftEqConst :: Bool -> (a -> b -> Bool) -> f a -> f b -> Bool Source #

liftEq2Const :: Bool -> (a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool Source #

ltConst :: Bool -> a -> a -> Bool Source #

compare1Const :: Ordering -> f a -> f a -> Ordering Source #

liftCompareConst :: Ordering -> (a -> b -> Ordering) -> f a -> f b -> Ordering Source #

liftCompare2Const :: Ordering -> (a -> b -> Ordering) -> (c -> d -> Ordering) -> f a c -> f b d -> Ordering Source #

readsPrec1Const :: ReadS (f a) -> Int -> ReadS (f a) Source #

liftReadsPrecConst :: ReadS (f a) -> (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a) Source #

liftReadsPrec2Const :: ReadS (f a b) -> (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (f a b) Source #

liftReadPrec2Const :: ReadPrec (f a b) -> ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (f a b) Source #

liftShowsPrecConst :: ShowS -> (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #

liftShowsPrec2Const :: ShowS -> (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> f a b -> ShowS Source #

data StarKindStatus Source #

Whether a type is not of kind *, is of kind *, or is a kind variable.

Instances

Instances details
Eq StarKindStatus Source # 
Instance details

Defined in Data.Deriving.Internal

canRealizeKindStar :: Type -> StarKindStatus Source #

Does a Type have kind * or k (for some kind variable k)?

starKindStatusToName :: StarKindStatus -> Maybe Name Source #

Returns Just the kind variable Name of a StarKindStatus if it exists. Otherwise, returns Nothing.

catKindVarNames :: [StarKindStatus] -> [Name] Source #

Concat together all of the StarKindStatuses that are IsKindVar and extract the kind variables' Names out.

buildTypeInstance Source #

Arguments

:: ClassRep a 
=> a

The typeclass for which an instance should be derived

-> Name

The type constructor or data family name

-> Cxt

The datatype context

-> [Type]

The types to instantiate the instance with

-> DatatypeVariant

Are we dealing with a data family instance or not

-> Q (Cxt, Type) 

deriveConstraint :: ClassRep a => a -> Type -> (Maybe Pred, [Name]) Source #

Attempt to derive a constraint on a Type. If successful, return Just the constraint and any kind variable names constrained to *. Otherwise, return Nothing and the empty list.

See Note [Type inference in derived instances] for the heuristics used to come up with constraints.

checkExistentialContext :: ClassRep a => a -> TyVarMap b -> Cxt -> Name -> Q c -> Q c Source #

noConstructorsError :: Q a Source #

The given datatype has no constructors, and we don't know what to do with it.

derivingKindError :: ClassRep a => a -> Name -> Q b Source #

Either the given data type doesn't have enough type variables, or one of the type variables to be eta-reduced cannot realize kind *.

contravarianceError :: Name -> Q a Source #

The last type variable appeared in a contravariant position when deriving Functor.

noFunctionsError :: Name -> Q a Source #

A constructor has a function argument in a derived Foldable or Traversable instance.

etaReductionError :: Type -> Q a Source #

One of the last type variables cannot be eta-reduced (see the canEtaReduce function for the criteria it would have to meet).

datatypeContextError :: Name -> Type -> Q a Source #

The data type has a DatatypeContext which mentions one of the eta-reduced type variables.

existentialContextError :: Name -> Q a Source #

The data type has an existential constraint which mentions one of the eta-reduced type variables.

outOfPlaceTyVarError :: ClassRep a => a -> Name -> Q b Source #

The data type mentions one of the n eta-reduced type variables in a place other than the last nth positions of a data type in a constructor's field.

type TyVarMap a = Map Name (OneOrTwoNames a) Source #

A mapping of type variable Names to their auxiliary function Names.

data OneOrTwoNames a where Source #

data One Source #

data Two Source #

interleave :: [a] -> [a] -> [a] Source #

filterByList :: [Bool] -> [a] -> [a] Source #

filterByList takes a list of Bools and a list of some elements and filters out these elements for which the corresponding value in the list of Bools is False. This function does not check whether the lists have equal length.

filterByLists :: [Bool] -> [a] -> [a] -> [a] Source #

filterByLists takes a list of Bools and two lists as input, and outputs a new list consisting of elements from the last two input lists. For each Bool in the list, if it is True, then it takes an element from the former list. If it is False, it takes an element from the latter list. The elements taken correspond to the index of the Bool in its list. For example:

filterByLists [True, False, True, False] "abcd" "wxyz" = "axcz"

This function does not check whether the lists have equal length.

partitionByList :: [Bool] -> [a] -> ([a], [a]) Source #

partitionByList takes a list of Bools and a list of some elements and partitions the list according to the list of Bools. Elements corresponding to True go to the left; elements corresponding to False go to the right. For example, partitionByList [True, False, True] [1,2,3] == ([1,3], [2]) This function does not check whether the lists have equal length.

hasKindStar :: Type -> Bool Source #

Returns True if a Type has kind *.

hasKindVarChain :: Int -> Type -> Maybe [Name] Source #

hasKindVarChain n kind Checks if kind is of the form k_0 -> k_1 -> ... -> k_(n-1), where k0, k1, ..., and k_(n-1) can be * or kind variables.

tyKind :: Type -> Kind Source #

If a Type is a SigT, returns its kind signature. Otherwise, return *.

zipWithAndUnzipM :: Monad m => (a -> b -> m (c, d)) -> [a] -> [b] -> m ([c], [d]) Source #

zipWith3AndUnzipM :: Monad m => (a -> b -> c -> m (d, e)) -> [a] -> [b] -> [c] -> m ([d], [e]) Source #

thd3 :: (a, b, c) -> c Source #

unsnoc :: [a] -> Maybe ([a], a) Source #

conArity :: ConstructorInfo -> Int Source #

Returns the number of fields for the constructor.

isProductType :: [ConstructorInfo] -> Bool Source #

Returns True if it's a datatype with exactly one, non-existential constructor.

isEnumerationType :: [ConstructorInfo] -> Bool Source #

Returns True if it's a datatype with one or more nullary, non-GADT constructors.

isVanillaCon :: ConstructorInfo -> Bool Source #

Returns False if we're dealing with existential quantification or GADTs.

newNameList :: String -> Int -> Q [Name] Source #

Generate a list of fresh names with a common prefix, and numbered suffixes.

tvbKind :: TyVarBndr_ flag -> Kind Source #

Extracts the kind from a TyVarBndr.

tvbToType :: TyVarBndr_ flag -> Type Source #

Convert a TyVarBndr to a Type.

applyClass :: Name -> Name -> Pred Source #

Applies a typeclass constraint to a type.

canEtaReduce :: [Type] -> [Type] -> Bool Source #

Checks to see if the last types in a data family instance can be safely eta- reduced (i.e., dropped), given the other types. This checks for three conditions:

  1. All of the dropped types are type variables
  2. All of the dropped types are distinct
  3. None of the remaining types mention any of the dropped types

conTToName :: Type -> Name Source #

Extract the Name from a type constructor. If the argument Type is not a type variable, throw an error.

varTToName_maybe :: Type -> Maybe Name Source #

Extract Just the Name from a type variable. If the argument Type is not a type variable, return Nothing.

varTToName :: Type -> Name Source #

Extract the Name from a type variable. If the argument Type is not a type variable, throw an error.

unSigT :: Type -> Type Source #

Peel off a kind signature from a Type (if it has one).

isTyVar :: Type -> Bool Source #

Is the given type a variable?

isInTypeFamilyApp :: [Name] -> Type -> [Type] -> Q Bool Source #

Detect if a Name in a list of provided Names occurs as an argument to some type family. This makes an effort to exclude oversaturated arguments to type families. For instance, if one declared the following type family:

type family F a :: Type -> Type

Then in the type F a b, we would consider a to be an argument to F, but not b.

allDistinct :: Ord a => [a] -> Bool Source #

Are all of the items in a list (which have an ordering) distinct?

This uses Set (as opposed to nub) for better asymptotic time complexity.

mentionsName :: Type -> [Name] -> Bool Source #

Does the given type mention any of the Names in the list?

predMentionsName :: Pred -> [Name] -> Bool Source #

Does an instance predicate mention any of the Names in the list?

applyTy :: Type -> [Type] -> Type Source #

Construct a type via curried application.

applyTyCon :: Name -> [Type] -> Type Source #

Fully applies a type constructor to its type variables.

unapplyTy :: Type -> (Type, [Type]) Source #

Split an applied type into its individual components. For example, this:

Either Int Char

would split to this:

[Either, Int, Char]

uncurryTy :: Type -> (Cxt, [Type]) Source #

Split a type signature by the arrows on its spine. For example, this:

forall a b. (a ~ b) => (a -> b) -> Char -> ()

would split to this:

(a ~ b, [a -> b, Char, ()])

uncurryKind :: Kind -> [Kind] Source #

Like uncurryType, except on a kind level.

untagExpr :: [(Name, Name)] -> Q Exp -> Q Exp Source #

isNonUnitTuple :: Name -> Bool Source #

Checks if a Name represents a tuple type constructor (other than ())

isNonUnitTupleString :: String -> Bool Source #

Checks if a String represents a tuple (other than ())

isInfixDataCon :: String -> Bool Source #

Checks if a String names a valid Haskell infix data constructor (i.e., does it begin with a colon?).