backprop-0.2.6.1: Heterogeneous automatic differentation

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Numeric.Backprop.Num

Contents

Description

Provides the exact same API as Numeric.Backprop, except requiring Num instances for all types involved instead of Backprop instances.

This was the original API of the library (for version 0.1).

Num is strictly more powerful than Backprop, and is a stronger constraint on types than is necessary for proper backpropagating. In particular, fromInteger is a problem for many types, preventing useful backpropagation for lists, variable-length vectors (like Data.Vector) and variable-size matrices from linear algebra libraries like hmatrix and accelerate.

However, this module might be useful in situations where you are working with external types with Num instances, and you want to avoid writing orphan instances for external types.

If you have external types that are not Num instances, consider instead Numeric.Backprop.External.

If you need a Num instance for tuples, you can use the orphan instances in the <https://hackage.haskell.org/package/NumInstances NumInstances> package (in particular, Data.NumInstances.Tuple) if you are writing an application and do not have to worry about orphan instances.

See Numeric.Backprop for fuller documentation on using these functions.

Since: backprop-0.2.0.0

Synopsis

Types

data BVar s a Source #

A BVar s a is a value of type a that can be "backpropagated".

Functions referring to BVars are tracked by the library and can be automatically differentiated to get their gradients and results.

For simple numeric values, you can use its Num, Fractional, and Floating instances to manipulate them as if they were the numbers they represent.

If a contains items, the items can be accessed and extracted using lenses. A Lens' b a can be used to access an a inside a b, using ^^. (viewVar):

(^.)  ::        a -> Lens' a b ->        b
(^^.) :: BVar s a -> Lens' a b -> BVar s b

There is also ^^? (previewVar), to use a Prism' or Traversal' to extract a target that may or may not be present (which can implement pattern matching), ^^.. (toListOfVar) to use a Traversal' to extract all targets inside a BVar, and .~~ (setVar) to set and update values inside a BVar.

If you have control over your data type definitions, you can also use splitBV and joinBV to manipulate data types by easily extracting fields out of a BVar of data types and creating BVars of data types out of BVars of their fields. See Numeric.Backprop for a tutorial on this use pattern.

For more complex operations, libraries can provide functions on BVars using liftOp and related functions. This is how you can create primitive functions that users can use to manipulate your library's values. See https://backprop.jle.im/08-equipping-your-library.html for a detailed guide.

For example, the hmatrix library has a matrix-vector multiplication function, #> :: L m n -> R n -> L m.

A library could instead provide a function #> :: BVar (L m n) -> BVar (R n) -> BVar (R m), which the user can then use to manipulate their BVars of L m ns and R ns, etc.

See Numeric.Backprop and documentation for liftOp for more information.

Instances
BVGroup s ([] :: [*]) (K1 i a :: * -> *) (K1 i (BVar s a) :: * -> *) Source # 
Instance details

Defined in Numeric.Backprop.Explicit

Methods

gsplitBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> BVar s (K1 i a ()) -> K1 i (BVar s a) ()

gjoinBV :: Rec AddFunc [] -> Rec ZeroFunc [] -> K1 i (BVar s a) () -> BVar s (K1 i a ())

Eq a => Eq (BVar s a) Source #

Compares the values inside the BVar.

Since: backprop-0.1.5.0

Instance details

Defined in Numeric.Backprop.Internal

Methods

(==) :: BVar s a -> BVar s a -> Bool #

(/=) :: BVar s a -> BVar s a -> Bool #

(Floating a, Reifies s W) => Floating (BVar s a) Source # 
Instance details

Defined in Numeric.Backprop.Internal

Methods

pi :: BVar s a #

exp :: BVar s a -> BVar s a #

log :: BVar s a -> BVar s a #

sqrt :: BVar s a -> BVar s a #

(**) :: BVar s a -> BVar s a -> BVar s a #

logBase :: BVar s a -> BVar s a -> BVar s a #

sin :: BVar s a -> BVar s a #

cos :: BVar s a -> BVar s a #

tan :: BVar s a -> BVar s a #

asin :: BVar s a -> BVar s a #

acos :: BVar s a -> BVar s a #

atan :: BVar s a -> BVar s a #

sinh :: BVar s a -> BVar s a #

cosh :: BVar s a -> BVar s a #

tanh :: BVar s a -> BVar s a #

asinh :: BVar s a -> BVar s a #

acosh :: BVar s a -> BVar s a #

atanh :: BVar s a -> BVar s a #

log1p :: BVar s a -> BVar s a #

expm1 :: BVar s a -> BVar s a #

log1pexp :: BVar s a -> BVar s a #

log1mexp :: BVar s a -> BVar s a #

(Fractional a, Reifies s W) => Fractional (BVar s a) Source # 
Instance details

Defined in Numeric.Backprop.Internal

Methods

(/) :: BVar s a -> BVar s a -> BVar s a #

recip :: BVar s a -> BVar s a #

fromRational :: Rational -> BVar s a #

(Num a, Reifies s W) => Num (BVar s a) Source # 
Instance details

Defined in Numeric.Backprop.Internal

Methods

(+) :: BVar s a -> BVar s a -> BVar s a #

(-) :: BVar s a -> BVar s a -> BVar s a #

(*) :: BVar s a -> BVar s a -> BVar s a #

negate :: BVar s a -> BVar s a #

abs :: BVar s a -> BVar s a #

signum :: BVar s a -> BVar s a #

fromInteger :: Integer -> BVar s a #

Ord a => Ord (BVar s a) Source #

Compares the values inside the BVar.

Since: backprop-0.1.5.0

Instance details

Defined in Numeric.Backprop.Internal

Methods

compare :: BVar s a -> BVar s a -> Ordering #

(<) :: BVar s a -> BVar s a -> Bool #

(<=) :: BVar s a -> BVar s a -> Bool #

(>) :: BVar s a -> BVar s a -> Bool #

(>=) :: BVar s a -> BVar s a -> Bool #

max :: BVar s a -> BVar s a -> BVar s a #

min :: BVar s a -> BVar s a -> BVar s a #

NFData a => NFData (BVar s a) Source #

This will force the value inside, as well.

Instance details

Defined in Numeric.Backprop.Internal

Methods

rnf :: BVar s a -> () #

(Backprop a, Reifies s W) => Backprop (BVar s a) Source #

Since: backprop-0.2.2.0

Instance details

Defined in Numeric.Backprop.Internal

Methods

zero :: BVar s a -> BVar s a Source #

add :: BVar s a -> BVar s a -> BVar s a Source #

one :: BVar s a -> BVar s a Source #

data W Source #

An ephemeral Wengert Tape in the environment. Used internally to track of the computational graph of variables.

For the end user, one can just imagine Reifies s W as a required constraint on s that allows backpropagation to work.

Running

backprop :: (Num a, Num b) => (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> (b, a) Source #

backprop, but with Num constraints instead of Backprop constraints.

See module documentation for Numeric.Backprop.Num for information on using this with tuples.

evalBP :: (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> b Source #

Turn a function BVar s a -> BVar s b into the function a -> b that it represents.

Benchmarks show that this should have virtually no overhead over directly writing a a -> b. BVar is, in this situation, a zero-cost abstraction, performance-wise.

See documentation of backprop for more information.

gradBP :: (Num a, Num b) => (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> a Source #

gradBP, but with Num constraints instead of Backprop constraints.

backpropWith :: Num a => (forall s. Reifies s W => BVar s a -> BVar s b) -> a -> (b, b -> a) Source #

backpropWith, but with Num constraints instead of Backprop constraints.

See module documentation for Numeric.Backprop.Num for information on using this with tuples.

Note that argument order changed in v0.2.4.

Since: backprop-0.2.0.0

Multiple inputs

evalBP0 :: (forall s. Reifies s W => BVar s a) -> a Source #

evalBP but with no arguments. Useful when everything is just given through constVar.

backprop2 :: (Num a, Num b, Num c) => (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) -> a -> b -> (c, (a, b)) Source #

backprop2, but with Num constraints instead of Backprop constraints.

evalBP2 :: (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) -> a -> b -> c Source #

evalBP for a two-argument function. See backprop2 for notes.

gradBP2 :: (Num a, Num b, Num c) => (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) -> a -> b -> (a, b) Source #

gradBP2, but with Num constraints instead of Backprop constraints.

backpropWith2 Source #

Arguments

:: (Num a, Num b) 
=> (forall s. Reifies s W => BVar s a -> BVar s b -> BVar s c) 
-> a 
-> b 
-> (c, c -> (a, b))

Takes function giving gradient of final result given the output of function

backpropWith2, but with Num constraints instead of Backprop constraints.

Note that argument order changed in v0.2.4.

Since: backprop-0.2.0.0

backpropN :: (RPureConstrained Num as, Num b) => (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> (b, Rec Identity as) Source #

backpropN, but with Num constraints instead of Backprop constraints.

The RPureConstrained Num as in the constraint says that every value in the type-level list as must have a Num instance. This means you can use, say, '[Double, Float, Int], but not '[Double, Bool, String].

If you stick to concerete, monomorphic usage of this (with specific types, typed into source code, known at compile-time), then AllPureConstrained Num as should be fulfilled automatically.

evalBPN :: forall as b. (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> b Source #

evalBP generalized to multiple inputs of different types. See documentation for backpropN for more details.

gradBPN :: (RPureConstrained Num as, Num b) => (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> Rec Identity as Source #

gradBPN, but with Num constraints instead of Backprop constraints.

backpropWithN :: RPureConstrained Num as => (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Rec Identity as -> (b, b -> Rec Identity as) Source #

backpropWithN, but with Num constraints instead of Backprop constraints.

See backpropN for information on the AllConstrained constraint.

Note that argument order changed in v0.2.4.

Since: backprop-0.2.0.0

Manipulating BVar

constVar :: a -> BVar s a Source #

Lift a value into a BVar representing a constant value.

This value will not be considered an input, and its gradients will not be backpropagated.

auto :: a -> BVar s a Source #

Shorter alias for constVar, inspired by the ad library.

Since: backprop-0.2.0.0

coerceVar :: Coercible a b => BVar s a -> BVar s b Source #

Coerce a BVar contents. Useful for things like newtype wrappers.

Since: backprop-0.1.5.2

(^^.) :: forall b a s. (Num a, Num b, Reifies s W) => BVar s b -> Lens' b a -> BVar s a infixl 8 Source #

^^., but with Num constraints instead of Backprop constraints.

(.~~) :: (Num a, Num b, Reifies s W) => Lens' b a -> BVar s a -> BVar s b -> BVar s b infixl 8 Source #

.~~, but with Num constraints instead of Backprop constraints.

(%~~) :: (Num a, Num b, Reifies s W) => Lens' b a -> (BVar s a -> BVar s a) -> BVar s b -> BVar s b infixr 4 Source #

%~~, but with Num constraints instead of Backprop constraints.

Since: backprop-0.2.4.0

(^^?) :: forall b a s. (Num b, Num a, Reifies s W) => BVar s b -> Traversal' b a -> Maybe (BVar s a) infixl 8 Source #

^^?, but with Num constraints instead of Backprop constraints.

Note that many automatically-generated prisms by the lens package use tuples, which cannot work this this by default (because tuples do not have a Num instance).

If you are writing an application or don't have to worry about orphan instances, you can pull in the orphan instances from NumInstances. Alternatively, you can chain those prisms with conversions to the anonymous canonical strict tuple types in Numeric.Backprop.Tuple, which do have Num instances.

myPrism                   :: Prism' c (a, b)
myPrism . iso tupT2 t2Tup :: Prism' c (T2 a b)

(^^..) :: forall b a s. (Num b, Num a, Reifies s W) => BVar s b -> Traversal' b a -> [BVar s a] Source #

^^.., but with Num constraints instead of Backprop constraints.

(^^?!) :: forall b a s. (Num b, Num a, Reifies s W) => BVar s b -> Traversal' b a -> BVar s a infixl 8 Source #

^^?!, but with Num constraints instead of Backprop constraints.

Like ^^?!, is *UNSAFE*.

Since: backprop-0.2.1.0

viewVar :: forall b a s. (Num a, Num b, Reifies s W) => Lens' b a -> BVar s b -> BVar s a Source #

viewVar, but with Num constraints instead of Backprop constraints.

setVar :: forall a b s. (Num a, Num b, Reifies s W) => Lens' b a -> BVar s a -> BVar s b -> BVar s b Source #

setVar, but with Num constraints instead of Backprop constraints.

overVar :: (Num a, Num b, Reifies s W) => Lens' b a -> (BVar s a -> BVar s a) -> BVar s b -> BVar s b Source #

overVar, but with Num constraints instead of Backprop constraints.

Since: backprop-0.2.4.0

sequenceVar :: (Traversable t, Num a, Reifies s W) => BVar s (t a) -> t (BVar s a) Source #

sequenceVar, but with Num constraints instead of Backprop constraints.

Since v0.2.4, requires a Num constraint on t a.

collectVar :: (Foldable t, Functor t, Num a, Reifies s W) => t (BVar s a) -> BVar s (t a) Source #

collectVar, but with Num constraints instead of Backprop constraints.

Prior to v0.2.3, required a Num constraint on t a.

previewVar :: forall b a s. (Num b, Num a, Reifies s W) => Traversal' b a -> BVar s b -> Maybe (BVar s a) Source #

previewVar, but with Num constraints instead of Backprop constraints.

See documentation for ^^? for more information and important notes.

toListOfVar :: forall b a s. (Num b, Num a, Reifies s W) => Traversal' b a -> BVar s b -> [BVar s a] Source #

toListOfVar, but with Num constraints instead of Backprop constraints.

With Isomorphisms

isoVar :: (Num a, Reifies s W) => (a -> b) -> (b -> a) -> BVar s a -> BVar s b Source #

isoVar, but with Num constraints instead of Backprop constraints.

isoVar2 :: (Num a, Num b, Reifies s W) => (a -> b -> c) -> (c -> (a, b)) -> BVar s a -> BVar s b -> BVar s c Source #

isoVar, but with Num constraints instead of Backprop constraints.

isoVar3 :: (Num a, Num b, Num c, Reifies s W) => (a -> b -> c -> d) -> (d -> (a, b, c)) -> BVar s a -> BVar s b -> BVar s c -> BVar s d Source #

isoVar3, but with Num constraints instead of Backprop constraints.

isoVarN :: (RPureConstrained Num as, Reifies s W) => (Rec Identity as -> b) -> (b -> Rec Identity as) -> Rec (BVar s) as -> BVar s b Source #

isoVarN, but with Num constraints instead of Backprop constraints.

With Ops

liftOp :: (RPureConstrained Num as, Reifies s W) => Op as b -> Rec (BVar s) as -> BVar s b Source #

liftOp, but with Num constraints instead of Backprop constraints.

liftOp1 :: (Num a, Reifies s W) => Op '[a] b -> BVar s a -> BVar s b Source #

liftOp1, but with Num constraints instead of Backprop constraints.

liftOp2 :: (Num a, Num b, Reifies s W) => Op '[a, b] c -> BVar s a -> BVar s b -> BVar s c Source #

liftOp2, but with Num constraints instead of Backprop constraints.

liftOp3 :: (Num a, Num b, Num c, Reifies s W) => Op '[a, b, c] d -> BVar s a -> BVar s b -> BVar s c -> BVar s d Source #

liftOp3, but with Num constraints instead of Backprop constraints.

Op

newtype Op as a Source #

An Op as a describes a differentiable function from as to a.

For example, a value of type

Op '[Int, Bool] Double

is a function from an Int and a Bool, returning a Double. It can be differentiated to give a gradient of an Int and a Bool if given a total derivative for the Double. If we call Bool \(2\), then, mathematically, it is akin to a:

\[ f : \mathbb{Z} \times 2 \rightarrow \mathbb{R} \]

See runOp, gradOp, and gradOpWith for examples on how to run it, and Op for instructions on creating it.

It is simpler to not use this type constructor directly, and instead use the op2, op1, op2, and op3 helper smart constructors.

See Numeric.Backprop.Op for a mini-tutorial on using Rec and 'Rec Identity'.

To use an Op with the backprop library, see liftOp, liftOp1, liftOp2, and liftOp3.

Constructors

Op

Construct an Op by giving a function creating the result, and also a continuation on how to create the gradient, given the total derivative of a.

See the module documentation for Numeric.Backprop.Op for more details on the function that this constructor and Op expect.

Fields

Instances
(RPureConstrained Num as, Floating a) => Floating (Op as a) Source # 
Instance details

Defined in Numeric.Backprop.Op

Methods

pi :: Op as a #

exp :: Op as a -> Op as a #

log :: Op as a -> Op as a #

sqrt :: Op as a -> Op as a #

(**) :: Op as a -> Op as a -> Op as a #

logBase :: Op as a -> Op as a -> Op as a #

sin :: Op as a -> Op as a #

cos :: Op as a -> Op as a #

tan :: Op as a -> Op as a #

asin :: Op as a -> Op as a #

acos :: Op as a -> Op as a #

atan :: Op as a -> Op as a #

sinh :: Op as a -> Op as a #

cosh :: Op as a -> Op as a #

tanh :: Op as a -> Op as a #

asinh :: Op as a -> Op as a #

acosh :: Op as a -> Op as a #

atanh :: Op as a -> Op as a #

log1p :: Op as a -> Op as a #

expm1 :: Op as a -> Op as a #

log1pexp :: Op as a -> Op as a #

log1mexp :: Op as a -> Op as a #

(RPureConstrained Num as, Fractional a) => Fractional (Op as a) Source # 
Instance details

Defined in Numeric.Backprop.Op

Methods

(/) :: Op as a -> Op as a -> Op as a #

recip :: Op as a -> Op as a #

fromRational :: Rational -> Op as a #

(RPureConstrained Num as, Num a) => Num (Op as a) Source # 
Instance details

Defined in Numeric.Backprop.Op

Methods

(+) :: Op as a -> Op as a -> Op as a #

(-) :: Op as a -> Op as a -> Op as a #

(*) :: Op as a -> Op as a -> Op as a #

negate :: Op as a -> Op as a #

abs :: Op as a -> Op as a #

signum :: Op as a -> Op as a #

fromInteger :: Integer -> Op as a #

Creation

op0 :: a -> Op '[] a Source #

Create an Op that takes no inputs and always returns the given value.

There is no gradient, of course (using gradOp will give you an empty tuple), because there is no input to have a gradient of.

>>> runOp (op0 10) RNil
(10, RNil)

For a constant Op that takes input and ignores it, see opConst and opConst'.

opConst :: forall as a. RPureConstrained Num as => a -> Op as a Source #

An Op that ignores all of its inputs and returns a given constant value.

>>> gradOp' (opConst 10) (1 :& 2 :& 3 :& RNil)
(10, 0 :& 0 :& 0 :& RNil)

idOp :: Op '[a] a Source #

An Op that just returns whatever it receives. The identity function.

idOp = opIso id id

bpOp :: RPureConstrained Num as => (forall s. Reifies s W => Rec (BVar s) as -> BVar s b) -> Op as b Source #

bpOp, but with Num constraints instead of Backprop constraints.

Giving gradients directly

op1 :: (a -> (b, b -> a)) -> Op '[a] b Source #

Create an Op of a function taking one input, by giving its explicit derivative. The function should return a tuple containing the result of the function, and also a function taking the derivative of the result and return the derivative of the input.

If we have

\[ \eqalign{ f &: \mathbb{R} \rightarrow \mathbb{R}\cr y &= f(x)\cr z &= g(y) } \]

Then the derivative \( \frac{dz}{dx} \), it would be:

\[ \frac{dz}{dx} = \frac{dz}{dy} \frac{dy}{dx} \]

If our Op represents \(f\), then the second item in the resulting tuple should be a function that takes \(\frac{dz}{dy}\) and returns \(\frac{dz}{dx}\).

As an example, here is an Op that squares its input:

square :: Num a => Op '[a] a
square = op1 $ \x -> (x*x, \d -> 2 * d * x
                     )

Remember that, generally, end users shouldn't directly construct Ops; they should be provided by libraries or generated automatically.

op2 :: (a -> b -> (c, c -> (a, b))) -> Op '[a, b] c Source #

Create an Op of a function taking two inputs, by giving its explicit gradient. The function should return a tuple containing the result of the function, and also a function taking the derivative of the result and return the derivative of the input.

If we have

\[ \eqalign{ f &: \mathbb{R}^2 \rightarrow \mathbb{R}\cr z &= f(x, y)\cr k &= g(z) } \]

Then the gradient \( \left< \frac{\partial k}{\partial x}, \frac{\partial k}{\partial y} \right> \) would be:

\[ \left< \frac{\partial k}{\partial x}, \frac{\partial k}{\partial y} \right> = \left< \frac{dk}{dz} \frac{\partial z}{dx}, \frac{dk}{dz} \frac{\partial z}{dy} \right> \]

If our Op represents \(f\), then the second item in the resulting tuple should be a function that takes \(\frac{dk}{dz}\) and returns \( \left< \frac{\partial k}{dx}, \frac{\partial k}{dx} \right> \).

As an example, here is an Op that multiplies its inputs:

mul :: Num a => Op '[a, a] a
mul = op2' $ \x y -> (x*y, \d -> (d*y, x*d)
                     )

Remember that, generally, end users shouldn't directly construct Ops; they should be provided by libraries or generated automatically.

op3 :: (a -> b -> c -> (d, d -> (a, b, c))) -> Op '[a, b, c] d Source #

Create an Op of a function taking three inputs, by giving its explicit gradient. See documentation for op2 for more details.

From Isomorphisms

opCoerce :: Coercible a b => Op '[a] b Source #

An Op that coerces an item into another item whose type has the same runtime representation.

>>> gradOp' opCoerce (Identity 5) :: (Int, Identity Int)
(5, Identity 1)
opCoerce = opIso coerced coerce

opTup :: Op as (Rec Identity as) Source #

An Op that takes as and returns exactly the input tuple.

>>> gradOp' opTup (1 :& 2 :& 3 :& RNil)
(1 :& 2 :& 3 :& RNil, 1 :& 1 :& 1 :& RNil)

opIso :: (a -> b) -> (b -> a) -> Op '[a] b Source #

An Op that runs the input value through an isomorphism.

Warning: This is unsafe! It assumes that the isomorphisms themselves have derivative 1, so will break for things like exp & log. Basically, don't use this for any "numeric" isomorphisms.

opIsoN :: (Rec Identity as -> b) -> (b -> Rec Identity as) -> Op as b Source #

An Op that runs the input value through an isomorphism between a tuple of values and a value. See opIso for caveats.

In Numeric.Backprop.Op since version 0.1.2.0, but only exported from Numeric.Backprop since version 0.1.3.0.

Since: backprop-0.1.2.0

opLens :: Num a => Lens' a b -> Op '[a] b Source #

An Op that extracts a value from an input value using a Lens'.

Warning: This is unsafe! It assumes that it extracts a specific value unchanged, with derivative 1, so will break for things that numerically manipulate things before returning them.

No gradients

noGrad1 :: (a -> b) -> Op '[a] b Source #

Create an Op with no gradient. Can be evaluated with evalOp, but will throw a runtime exception when asked for the gradient.

Can be used with BVar with liftOp1, and evalBP will work fine. gradBP and backprop will also work fine if the result is never used in the final answer, but will throw a runtime exception if the final answer depends on the result of this operation.

Useful if your only API is exposed through backprop. Just be sure to tell your users that this will explode when finding the gradient if the result is used in the final result.

Since: backprop-0.1.3.0

noGrad :: (Rec Identity as -> b) -> Op as b Source #

Create an Op with no gradient. Can be evaluated with evalOp, but will throw a runtime exception when asked for the gradient.

Can be used with BVar with liftOp, and evalBP will work fine. gradBP and backprop will also work fine if the result is never used in the final answer, but will throw a runtime exception if the final answer depends on the result of this operation.

Useful if your only API is exposed through backprop. Just be sure to tell your users that this will explode when finding the gradient if the result is used in the final result.

Since: backprop-0.1.3.0

Utility

class Reifies (s :: k) a | s -> a #

Minimal complete definition

reflect

Instances
KnownNat n => Reifies (n :: Nat) Integer 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer #

KnownSymbol n => Reifies (n :: Symbol) String 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> String #

Reifies Z Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy Z -> Int #

Reifies n Int => Reifies (D n :: *) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (D n) -> Int #

Reifies n Int => Reifies (SD n :: *) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (SD n) -> Int #

Reifies n Int => Reifies (PD n :: *) Int 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (PD n) -> Int #

(B b0, B b1, B b2, B b3, B b4, B b5, B b6, B b7, w0 ~ W b0 b1 b2 b3, w1 ~ W b4 b5 b6 b7) => Reifies (Stable w0 w1 a :: *) a 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy (Stable w0 w1 a) -> a #