lens-5.2.3: Lenses, Folds and Traversals
Copyright(C) 2013-2016 Edward Kmett and Eric Mertens
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Control.Lens.Internal.TH

Description

 
Synopsis

Documentation

appsT :: TypeQ -> [TypeQ] -> TypeQ Source #

Apply arguments to a type constructor

appsE1 :: ExpQ -> [ExpQ] -> ExpQ Source #

Apply arguments to a function

toTupleT :: [TypeQ] -> TypeQ Source #

Construct a tuple type given a list of types.

toTupleE :: [ExpQ] -> ExpQ Source #

Construct a tuple value given a list of expressions.

toTupleP :: [PatQ] -> PatQ Source #

Construct a tuple pattern given a list of patterns.

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

Apply arguments to a type constructor.

newNames Source #

Arguments

:: String

base name

-> Int

count

-> Q [Name] 

Generate many new names from a given base name.

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

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

Either Int Char

would be unfolded to this:

(ConT ''Either, [ConT ''Int, ConT ''Char])

This function ignores explicit parentheses and visible kind applications.

dropSigsIfNonDataFam :: DatatypeInfo -> [Type] -> [Type] Source #

In an effort to prevent users from having to enable KindSignatures every time that they use lens' TH functionality, we strip off reified kind annotations from when:

  1. The kind of a type does not contain any kind variables. If it *does* contain kind variables, we want to preserve them so that we can generate type signatures that preserve the dependency order of kind and type variables. (The data types in test/T917.hs contain examples where this is important.) This will require enabling PolyKinds, but since PolyKinds implies KindSignatures, we can at least accomplish two things at once.
  2. The data type is not an instance of a data family. We make an exception for data family instances, since the presence or absence of a kind annotation can be the difference between typechecking or not. (See T917DataFam in tests/T917.hs for an example.) Moreover, the TypeFamilies extension implies KindSignatures.

quantifyType :: Cxt -> Type -> Type Source #

Template Haskell wants type variables declared in a forall, so we find all free type variables in a given type and declare them.

quantifyType' :: Set Name -> Cxt -> Type -> Type Source #

This function works like quantifyType except that it takes a list of variables to exclude from quantification.

tvbToType :: TyVarBndr_ flag -> Type Source #

Convert a TyVarBndr into its corresponding Type.

unSigT :: Type -> Type Source #

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

phantom2 :: (Functor f, Contravariant f) => f a -> f b Source #

type TyVarBndrVis = TyVarBndr_ BndrVis #

A TyVarBndr with a BndrVis flag. This is used for TyVarBndrs in type-level declarations (e.g., the binders in data D @k (a :: k)).