Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module provides functions to map Proxy types
p1 :: Proxy (Either Int Bool) p1 = Proxy p2 = proxy1of2 p2 ghci> :t p2 p2 :: Proxy Int
A toy example with a class that creates Strings from Proxy types:
class FromProxy t where createString :: Proxy t -> String instance FromProxy Int where createString _ = "Int" instance FromProxy Bool where createString _ = "Bool" instance (FromProxy a, FromProxy b) => FromProxy (Either a b) where createString p = "Either " ++ proxy1of2 p ++ " " ++ proxy2of2 p instance (FromProxy a, FromProxy b) => FromProxy ((->) a b) where createString p = createString (proxy1of2 p) ++ " -> " ++ createString (proxy2of2 p) ghci> createString (Proxy :: Proxy (Either Int Bool)) "Either Int Bool" ghci> createString (Proxy :: Proxy (Int -> Bool -> Either Int Bool)) "Int -> Bool -> Either Int Bool"
A toy example where an Integer is computed from a Proxy type:
{-# Language DataKinds #-} {-# Language KindSignatures #-} import GHC.TypeLits import Data.Kind (Type) import Data.Proxy import Data.Proxy.Mapping class Compute t where compute :: Proxy t -> Integer data Number (n :: Nat) data Add a b data Apply (f :: Type -> Type) (a :: Type) instance KnownNat n => Compute (Number n) where compute p = natVal (proxy1of1 p) instance (Compute a, Compute b) => Compute (Add a b) where compute p = (compute $ proxy1of2 p) + (compute $ proxy2of2 p) instance (Compute a, Compute (f a)) => Compute (Apply f a) where compute p = compute (proxyApply (proxy1of2 p) (proxy2of2 p))
ghci> compute (Proxy :: Proxy (Apply (Add (Number 1)) (Number 2))) 3
- proxyHead :: Proxy (x ': xs) -> Proxy x
- proxyTail :: Proxy (x ': xs) -> Proxy xs
- proxyApply :: Proxy f -> Proxy a -> Proxy (f a)
- proxySucc :: Proxy n -> Proxy (n + 1)
- proxyPred :: 1 <= n => Proxy n -> Proxy (n - 1)
- proxy0of1 :: Proxy (t a) -> Proxy t
- proxy1of1 :: Proxy (t a) -> Proxy a
- proxy0of2 :: Proxy (t a b) -> Proxy t
- proxy1of2 :: Proxy (t a b) -> Proxy a
- proxy2of2 :: Proxy (t a b) -> Proxy b
- proxy0of3 :: Proxy (t a b c) -> Proxy t
- proxy1of3 :: Proxy (t a b c) -> Proxy a
- proxy2of3 :: Proxy (t a b c) -> Proxy b
- proxy3of3 :: Proxy (t a b c) -> Proxy c
- proxy0of4 :: Proxy (t a b c d) -> Proxy t
- proxy1of4 :: Proxy (t a b c d) -> Proxy a
- proxy2of4 :: Proxy (t a b c d) -> Proxy b
- proxy3of4 :: Proxy (t a b c d) -> Proxy c
- proxy4of4 :: Proxy (t a b c d) -> Proxy d
- proxy0of5 :: Proxy (t a b c d e) -> Proxy t
- proxy1of5 :: Proxy (t a b c d e) -> Proxy a
- proxy2of5 :: Proxy (t a b c d e) -> Proxy b
- proxy3of5 :: Proxy (t a b c d e) -> Proxy c
- proxy4of5 :: Proxy (t a b c d e) -> Proxy d
- proxy5of5 :: Proxy (t a b c d e) -> Proxy e
- proxy0of6 :: Proxy (t a b c d e f) -> Proxy t
- proxy1of6 :: Proxy (t a b c d e f) -> Proxy a
- proxy2of6 :: Proxy (t a b c d e f) -> Proxy b
- proxy3of6 :: Proxy (t a b c d e f) -> Proxy c
- proxy4of6 :: Proxy (t a b c d e f) -> Proxy d
- proxy5of6 :: Proxy (t a b c d e f) -> Proxy e
- proxy6of6 :: Proxy (t a b c d e f) -> Proxy f
- proxy0of7 :: Proxy (t a b c d e f g) -> Proxy t
- proxy1of7 :: Proxy (t a b c d e f g) -> Proxy a
- proxy2of7 :: Proxy (t a b c d e f g) -> Proxy b
- proxy3of7 :: Proxy (t a b c d e f g) -> Proxy c
- proxy4of7 :: Proxy (t a b c d e f g) -> Proxy d
- proxy5of7 :: Proxy (t a b c d e f g) -> Proxy e
- proxy6of7 :: Proxy (t a b c d e f g) -> Proxy f
- proxy7of7 :: Proxy (t a b c d e f g) -> Proxy g
- proxy0of8 :: Proxy (t a b c d e f g h) -> Proxy t
- proxy1of8 :: Proxy (t a b c d e f g h) -> Proxy a
- proxy2of8 :: Proxy (t a b c d e f g h) -> Proxy b
- proxy3of8 :: Proxy (t a b c d e f g h) -> Proxy c
- proxy4of8 :: Proxy (t a b c d e f g h) -> Proxy d
- proxy5of8 :: Proxy (t a b c d e f g h) -> Proxy e
- proxy6of8 :: Proxy (t a b c d e f g h) -> Proxy f
- proxy7of8 :: Proxy (t a b c d e f g h) -> Proxy g
- proxy8of8 :: Proxy (t a b c d e f g h) -> Proxy h
- proxy0of9 :: Proxy (t a b c d e f g h i) -> Proxy t
- proxy1of9 :: Proxy (t a b c d e f g h i) -> Proxy a
- proxy2of9 :: Proxy (t a b c d e f g h i) -> Proxy b
- proxy3of9 :: Proxy (t a b c d e f g h i) -> Proxy c
- proxy4of9 :: Proxy (t a b c d e f g h i) -> Proxy d
- proxy5of9 :: Proxy (t a b c d e f g h i) -> Proxy e
- proxy6of9 :: Proxy (t a b c d e f g h i) -> Proxy f
- proxy7of9 :: Proxy (t a b c d e f g h i) -> Proxy g
- proxy8of9 :: Proxy (t a b c d e f g h i) -> Proxy h
- proxy9of9 :: Proxy (t a b c d e f g h i) -> Proxy i
- proxy0of10 :: Proxy (t a b c d e f g h i j) -> Proxy t
- proxy1of10 :: Proxy (t a b c d e f g h i j) -> Proxy a
- proxy2of10 :: Proxy (t a b c d e f g h i j) -> Proxy b
- proxy3of10 :: Proxy (t a b c d e f g h i j) -> Proxy c
- proxy4of10 :: Proxy (t a b c d e f g h i j) -> Proxy d
- proxy5of10 :: Proxy (t a b c d e f g h i j) -> Proxy e
- proxy6of10 :: Proxy (t a b c d e f g h i j) -> Proxy f
- proxy7of10 :: Proxy (t a b c d e f g h i j) -> Proxy g
- proxy8of10 :: Proxy (t a b c d e f g h i j) -> Proxy h
- proxy9of10 :: Proxy (t a b c d e f g h i j) -> Proxy i
- proxy10of10 :: Proxy (t a b c d e f g h i j) -> Proxy j
- proxy0of11 :: Proxy (t a b c d e f g h i j k) -> Proxy t
- proxy1of11 :: Proxy (t a b c d e f g h i j k) -> Proxy a
- proxy2of11 :: Proxy (t a b c d e f g h i j k) -> Proxy b
- proxy3of11 :: Proxy (t a b c d e f g h i j k) -> Proxy c
- proxy4of11 :: Proxy (t a b c d e f g h i j k) -> Proxy d
- proxy5of11 :: Proxy (t a b c d e f g h i j k) -> Proxy e
- proxy6of11 :: Proxy (t a b c d e f g h i j k) -> Proxy f
- proxy7of11 :: Proxy (t a b c d e f g h i j k) -> Proxy g
- proxy8of11 :: Proxy (t a b c d e f g h i j k) -> Proxy h
- proxy9of11 :: Proxy (t a b c d e f g h i j k) -> Proxy i
- proxy10of11 :: Proxy (t a b c d e f g h i j k) -> Proxy j
- proxy11of11 :: Proxy (t a b c d e f g h i j k) -> Proxy k
- proxy0of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy t
- proxy1of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy a
- proxy2of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy b
- proxy3of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy c
- proxy4of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy d
- proxy5of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy e
- proxy6of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy f
- proxy7of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy g
- proxy8of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy h
- proxy9of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy i
- proxy10of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy j
- proxy11of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy k
- proxy12of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy l
- proxy0of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy t
- proxy1of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy a
- proxy2of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy b
- proxy3of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy c
- proxy4of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy d
- proxy5of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy e
- proxy6of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy f
- proxy7of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy g
- proxy8of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy h
- proxy9of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy i
- proxy10of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy j
- proxy11of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy k
- proxy12of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy l
- proxy13of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy m
- proxy0of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy t
- proxy1of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy a
- proxy2of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy b
- proxy3of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy c
- proxy4of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy d
- proxy5of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy e
- proxy6of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy f
- proxy7of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy g
- proxy8of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy h
- proxy9of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy i
- proxy10of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy j
- proxy11of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy k
- proxy12of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy l
- proxy13of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy m
- proxy14of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy n
- proxy0of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy t
- proxy1of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy a
- proxy2of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy b
- proxy3of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy c
- proxy4of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy d
- proxy5of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy e
- proxy6of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy f
- proxy7of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy g
- proxy8of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy h
- proxy9of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy i
- proxy10of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy j
- proxy11of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy k
- proxy12of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy l
- proxy13of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy m
- proxy14of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy n
- proxy15of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy o
- proxy0of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy t
- proxy1of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy a
- proxy2of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy b
- proxy3of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy c
- proxy4of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy d
- proxy5of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy e
- proxy6of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy f
- proxy7of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy g
- proxy8of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy h
- proxy9of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy i
- proxy10of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy j
- proxy11of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy k
- proxy12of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy l
- proxy13of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy m
- proxy14of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy n
- proxy15of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy o
- proxy16of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy p
Head and Tail
Application
Successor and Predecessor
Accessing type constructor and parameters
proxy0of1 :: Proxy (t a) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 1 parameter
proxy1of1 :: Proxy (t a) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 1 parameter
proxy0of2 :: Proxy (t a b) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 2 parameters
proxy1of2 :: Proxy (t a b) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 2 parameters
proxy2of2 :: Proxy (t a b) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 2 parameters
proxy0of3 :: Proxy (t a b c) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 3 parameters
proxy1of3 :: Proxy (t a b c) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 3 parameters
proxy2of3 :: Proxy (t a b c) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 3 parameters
proxy3of3 :: Proxy (t a b c) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 3 parameters
proxy0of4 :: Proxy (t a b c d) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 4 parameters
proxy1of4 :: Proxy (t a b c d) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 4 parameters
proxy2of4 :: Proxy (t a b c d) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 4 parameters
proxy3of4 :: Proxy (t a b c d) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 4 parameters
proxy4of4 :: Proxy (t a b c d) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 4 parameters
proxy0of5 :: Proxy (t a b c d e) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 5 parameters
proxy1of5 :: Proxy (t a b c d e) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 5 parameters
proxy2of5 :: Proxy (t a b c d e) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 5 parameters
proxy3of5 :: Proxy (t a b c d e) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 5 parameters
proxy4of5 :: Proxy (t a b c d e) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 5 parameters
proxy5of5 :: Proxy (t a b c d e) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 5 parameters
proxy0of6 :: Proxy (t a b c d e f) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 6 parameters
proxy1of6 :: Proxy (t a b c d e f) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 6 parameters
proxy2of6 :: Proxy (t a b c d e f) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 6 parameters
proxy3of6 :: Proxy (t a b c d e f) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 6 parameters
proxy4of6 :: Proxy (t a b c d e f) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 6 parameters
proxy5of6 :: Proxy (t a b c d e f) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 6 parameters
proxy6of6 :: Proxy (t a b c d e f) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 6 parameters
proxy0of7 :: Proxy (t a b c d e f g) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 7 parameters
proxy1of7 :: Proxy (t a b c d e f g) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 7 parameters
proxy2of7 :: Proxy (t a b c d e f g) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 7 parameters
proxy3of7 :: Proxy (t a b c d e f g) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 7 parameters
proxy4of7 :: Proxy (t a b c d e f g) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 7 parameters
proxy5of7 :: Proxy (t a b c d e f g) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 7 parameters
proxy6of7 :: Proxy (t a b c d e f g) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 7 parameters
proxy7of7 :: Proxy (t a b c d e f g) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 7 parameters
proxy0of8 :: Proxy (t a b c d e f g h) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 8 parameters
proxy1of8 :: Proxy (t a b c d e f g h) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 8 parameters
proxy2of8 :: Proxy (t a b c d e f g h) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 8 parameters
proxy3of8 :: Proxy (t a b c d e f g h) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 8 parameters
proxy4of8 :: Proxy (t a b c d e f g h) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 8 parameters
proxy5of8 :: Proxy (t a b c d e f g h) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 8 parameters
proxy6of8 :: Proxy (t a b c d e f g h) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 8 parameters
proxy7of8 :: Proxy (t a b c d e f g h) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 8 parameters
proxy8of8 :: Proxy (t a b c d e f g h) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 8 parameters
proxy0of9 :: Proxy (t a b c d e f g h i) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 9 parameters
proxy1of9 :: Proxy (t a b c d e f g h i) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 9 parameters
proxy2of9 :: Proxy (t a b c d e f g h i) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 9 parameters
proxy3of9 :: Proxy (t a b c d e f g h i) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 9 parameters
proxy4of9 :: Proxy (t a b c d e f g h i) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 9 parameters
proxy5of9 :: Proxy (t a b c d e f g h i) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 9 parameters
proxy6of9 :: Proxy (t a b c d e f g h i) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 9 parameters
proxy7of9 :: Proxy (t a b c d e f g h i) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 9 parameters
proxy8of9 :: Proxy (t a b c d e f g h i) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 9 parameters
proxy9of9 :: Proxy (t a b c d e f g h i) -> Proxy i Source #
Mapping to the 9th type parameter (i) of a type with 9 parameters
proxy0of10 :: Proxy (t a b c d e f g h i j) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 10 parameters
proxy1of10 :: Proxy (t a b c d e f g h i j) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 10 parameters
proxy2of10 :: Proxy (t a b c d e f g h i j) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 10 parameters
proxy3of10 :: Proxy (t a b c d e f g h i j) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 10 parameters
proxy4of10 :: Proxy (t a b c d e f g h i j) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 10 parameters
proxy5of10 :: Proxy (t a b c d e f g h i j) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 10 parameters
proxy6of10 :: Proxy (t a b c d e f g h i j) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 10 parameters
proxy7of10 :: Proxy (t a b c d e f g h i j) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 10 parameters
proxy8of10 :: Proxy (t a b c d e f g h i j) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 10 parameters
proxy9of10 :: Proxy (t a b c d e f g h i j) -> Proxy i Source #
Mapping to the 9th type parameter (i) of a type with 10 parameters
proxy10of10 :: Proxy (t a b c d e f g h i j) -> Proxy j Source #
Mapping to the 10th type parameter (j) of a type with 10 parameters
proxy0of11 :: Proxy (t a b c d e f g h i j k) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 11 parameters
proxy1of11 :: Proxy (t a b c d e f g h i j k) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 11 parameters
proxy2of11 :: Proxy (t a b c d e f g h i j k) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 11 parameters
proxy3of11 :: Proxy (t a b c d e f g h i j k) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 11 parameters
proxy4of11 :: Proxy (t a b c d e f g h i j k) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 11 parameters
proxy5of11 :: Proxy (t a b c d e f g h i j k) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 11 parameters
proxy6of11 :: Proxy (t a b c d e f g h i j k) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 11 parameters
proxy7of11 :: Proxy (t a b c d e f g h i j k) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 11 parameters
proxy8of11 :: Proxy (t a b c d e f g h i j k) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 11 parameters
proxy9of11 :: Proxy (t a b c d e f g h i j k) -> Proxy i Source #
Mapping to the 9th type parameter (i) of a type with 11 parameters
proxy10of11 :: Proxy (t a b c d e f g h i j k) -> Proxy j Source #
Mapping to the 10th type parameter (j) of a type with 11 parameters
proxy11of11 :: Proxy (t a b c d e f g h i j k) -> Proxy k Source #
Mapping to the 11th type parameter (k) of a type with 11 parameters
proxy0of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 12 parameters
proxy1of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 12 parameters
proxy2of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 12 parameters
proxy3of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 12 parameters
proxy4of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 12 parameters
proxy5of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 12 parameters
proxy6of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 12 parameters
proxy7of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 12 parameters
proxy8of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 12 parameters
proxy9of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy i Source #
Mapping to the 9th type parameter (i) of a type with 12 parameters
proxy10of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy j Source #
Mapping to the 10th type parameter (j) of a type with 12 parameters
proxy11of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy k Source #
Mapping to the 11th type parameter (k) of a type with 12 parameters
proxy12of12 :: Proxy (t a b c d e f g h i j k l) -> Proxy l Source #
Mapping to the 12th type parameter (l) of a type with 12 parameters
proxy0of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 13 parameters
proxy1of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 13 parameters
proxy2of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 13 parameters
proxy3of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 13 parameters
proxy4of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 13 parameters
proxy5of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 13 parameters
proxy6of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 13 parameters
proxy7of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 13 parameters
proxy8of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 13 parameters
proxy9of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy i Source #
Mapping to the 9th type parameter (i) of a type with 13 parameters
proxy10of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy j Source #
Mapping to the 10th type parameter (j) of a type with 13 parameters
proxy11of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy k Source #
Mapping to the 11th type parameter (k) of a type with 13 parameters
proxy12of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy l Source #
Mapping to the 12th type parameter (l) of a type with 13 parameters
proxy13of13 :: Proxy (t a b c d e f g h i j k l m) -> Proxy m Source #
Mapping to the 13th type parameter (m) of a type with 13 parameters
proxy0of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 14 parameters
proxy1of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 14 parameters
proxy2of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 14 parameters
proxy3of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 14 parameters
proxy4of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 14 parameters
proxy5of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 14 parameters
proxy6of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 14 parameters
proxy7of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 14 parameters
proxy8of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 14 parameters
proxy9of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy i Source #
Mapping to the 9th type parameter (i) of a type with 14 parameters
proxy10of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy j Source #
Mapping to the 10th type parameter (j) of a type with 14 parameters
proxy11of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy k Source #
Mapping to the 11th type parameter (k) of a type with 14 parameters
proxy12of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy l Source #
Mapping to the 12th type parameter (l) of a type with 14 parameters
proxy13of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy m Source #
Mapping to the 13th type parameter (m) of a type with 14 parameters
proxy14of14 :: Proxy (t a b c d e f g h i j k l m n) -> Proxy n Source #
Mapping to the 14th type parameter (n) of a type with 14 parameters
proxy0of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 15 parameters
proxy1of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 15 parameters
proxy2of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 15 parameters
proxy3of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 15 parameters
proxy4of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 15 parameters
proxy5of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 15 parameters
proxy6of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 15 parameters
proxy7of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 15 parameters
proxy8of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 15 parameters
proxy9of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy i Source #
Mapping to the 9th type parameter (i) of a type with 15 parameters
proxy10of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy j Source #
Mapping to the 10th type parameter (j) of a type with 15 parameters
proxy11of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy k Source #
Mapping to the 11th type parameter (k) of a type with 15 parameters
proxy12of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy l Source #
Mapping to the 12th type parameter (l) of a type with 15 parameters
proxy13of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy m Source #
Mapping to the 13th type parameter (m) of a type with 15 parameters
proxy14of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy n Source #
Mapping to the 14th type parameter (n) of a type with 15 parameters
proxy15of15 :: Proxy (t a b c d e f g h i j k l m n o) -> Proxy o Source #
Mapping to the 15th type parameter (o) of a type with 15 parameters
proxy0of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy t Source #
Mapping to the type constructor (t) of a type with 16 parameters
proxy1of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy a Source #
Mapping to the 1st type parameter (a) of a type with 16 parameters
proxy2of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy b Source #
Mapping to the 2nd type parameter (b) of a type with 16 parameters
proxy3of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy c Source #
Mapping to the 3rd type parameter (c) of a type with 16 parameters
proxy4of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy d Source #
Mapping to the 4th type parameter (d) of a type with 16 parameters
proxy5of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy e Source #
Mapping to the 5th type parameter (e) of a type with 16 parameters
proxy6of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy f Source #
Mapping to the 6th type parameter (f) of a type with 16 parameters
proxy7of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy g Source #
Mapping to the 7th type parameter (g) of a type with 16 parameters
proxy8of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy h Source #
Mapping to the 8th type parameter (h) of a type with 16 parameters
proxy9of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy i Source #
Mapping to the 9th type parameter (i) of a type with 16 parameters
proxy10of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy j Source #
Mapping to the 10th type parameter (j) of a type with 16 parameters
proxy11of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy k Source #
Mapping to the 11th type parameter (k) of a type with 16 parameters
proxy12of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy l Source #
Mapping to the 12th type parameter (l) of a type with 16 parameters
proxy13of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy m Source #
Mapping to the 13th type parameter (m) of a type with 16 parameters
proxy14of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy n Source #
Mapping to the 14th type parameter (n) of a type with 16 parameters
proxy15of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy o Source #
Mapping to the 15th type parameter (o) of a type with 16 parameters
proxy16of16 :: Proxy (t a b c d e f g h i j k l m n o p) -> Proxy p Source #
Mapping to the 16th type parameter (p) of a type with 16 parameters