Safe Haskell | None |
---|---|
Language | Haskell2010 |
Construction and elimination of tuples in the object language
Synopsis
- data Tuple sig where
- Tup2 :: Tuple (a :-> (b :-> Full (a, b)))
- Tup3 :: Tuple (a :-> (b :-> (c :-> Full (a, b, c))))
- Tup4 :: Tuple (a :-> (b :-> (c :-> (d :-> Full (a, b, c, d)))))
- Tup5 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> Full (a, b, c, d, e))))))
- Tup6 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> Full (a, b, c, d, e, f)))))))
- Tup7 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> Full (a, b, c, d, e, f, g))))))))
- Tup8 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> Full (a, b, c, d, e, f, g, h)))))))))
- Tup9 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> Full (a, b, c, d, e, f, g, h, i))))))))))
- Tup10 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> Full (a, b, c, d, e, f, g, h, i, j)))))))))))
- Tup11 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> Full (a, b, c, d, e, f, g, h, i, j, k))))))))))))
- Tup12 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> (l :-> Full (a, b, c, d, e, f, g, h, i, j, k, l)))))))))))))
- Tup13 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> (l :-> (m :-> Full (a, b, c, d, e, f, g, h, i, j, k, l, m))))))))))))))
- Tup14 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> (l :-> (m :-> (n :-> Full (a, b, c, d, e, f, g, h, i, j, k, l, m, n)))))))))))))))
- Tup15 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> (l :-> (m :-> (n :-> (o :-> Full (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o))))))))))))))))
- type family Sel1' a
- type family Sel2' a
- type family Sel3' a
- type family Sel4' a
- type family Sel5' a
- type family Sel6' a
- type family Sel7' a
- type family Sel8' a
- type family Sel9' a
- type family Sel10' a
- type family Sel11' a
- type family Sel12' a
- type family Sel13' a
- type family Sel14' a
- type family Sel15' a
- data Select a where
- Sel1 :: (Sel1 a b, Sel1' a ~ b) => Select (a :-> Full b)
- Sel2 :: (Sel2 a b, Sel2' a ~ b) => Select (a :-> Full b)
- Sel3 :: (Sel3 a b, Sel3' a ~ b) => Select (a :-> Full b)
- Sel4 :: (Sel4 a b, Sel4' a ~ b) => Select (a :-> Full b)
- Sel5 :: (Sel5 a b, Sel5' a ~ b) => Select (a :-> Full b)
- Sel6 :: (Sel6 a b, Sel6' a ~ b) => Select (a :-> Full b)
- Sel7 :: (Sel7 a b, Sel7' a ~ b) => Select (a :-> Full b)
- Sel8 :: (Sel8 a b, Sel8' a ~ b) => Select (a :-> Full b)
- Sel9 :: (Sel9 a b, Sel9' a ~ b) => Select (a :-> Full b)
- Sel10 :: (Sel10 a b, Sel10' a ~ b) => Select (a :-> Full b)
- Sel11 :: (Sel11 a b, Sel11' a ~ b) => Select (a :-> Full b)
- Sel12 :: (Sel12 a b, Sel12' a ~ b) => Select (a :-> Full b)
- Sel13 :: (Sel13 a b, Sel13' a ~ b) => Select (a :-> Full b)
- Sel14 :: (Sel14 a b, Sel14' a ~ b) => Select (a :-> Full b)
- Sel15 :: (Sel15 a b, Sel15' a ~ b) => Select (a :-> Full b)
- selectPos :: Select a -> Int
Construction
Expressions for constructing tuples
Tup2 :: Tuple (a :-> (b :-> Full (a, b))) | |
Tup3 :: Tuple (a :-> (b :-> (c :-> Full (a, b, c)))) | |
Tup4 :: Tuple (a :-> (b :-> (c :-> (d :-> Full (a, b, c, d))))) | |
Tup5 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> Full (a, b, c, d, e)))))) | |
Tup6 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> Full (a, b, c, d, e, f))))))) | |
Tup7 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> Full (a, b, c, d, e, f, g)))))))) | |
Tup8 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> Full (a, b, c, d, e, f, g, h))))))))) | |
Tup9 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> Full (a, b, c, d, e, f, g, h, i)))))))))) | |
Tup10 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> Full (a, b, c, d, e, f, g, h, i, j))))))))))) | |
Tup11 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> Full (a, b, c, d, e, f, g, h, i, j, k)))))))))))) | |
Tup12 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> (l :-> Full (a, b, c, d, e, f, g, h, i, j, k, l))))))))))))) | |
Tup13 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> (l :-> (m :-> Full (a, b, c, d, e, f, g, h, i, j, k, l, m)))))))))))))) | |
Tup14 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> (l :-> (m :-> (n :-> Full (a, b, c, d, e, f, g, h, i, j, k, l, m, n))))))))))))))) | |
Tup15 :: Tuple (a :-> (b :-> (c :-> (d :-> (e :-> (f :-> (g :-> (h :-> (i :-> (j :-> (k :-> (l :-> (m :-> (n :-> (o :-> Full (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)))))))))))))))) |
Instances
Semantic Tuple Source # | |
StringTree Tuple Source # | |
Defined in Language.Syntactic.Constructs.Tuple | |
Render Tuple Source # | |
Eval Tuple Source # | |
Defined in Language.Syntactic.Constructs.Tuple evaluate :: Tuple a -> Denotation a Source # | |
Equality Tuple Source # | |
Constrained Tuple Source # | |
EvalBind Tuple Source # | |
Optimize Tuple Source # | |
AlphaEq dom dom dom env => AlphaEq Tuple Tuple dom env Source # | |
TupleSat ((Tuple :|| p) :+: dom2) p Source # | |
Defined in Language.Syntactic.Frontend.TupleConstrained | |
TupleSat (Tuple :|| p) p Source # | |
Defined in Language.Syntactic.Frontend.TupleConstrained | |
type Sat Tuple Source # | |
Defined in Language.Syntactic.Constructs.Tuple |
Projection
These families (Sel1'
- Sel15'
) are needed because of the problem
described in:
http://emil-fp.blogspot.com/2011/08/fundeps-weaker-than-type-families.html
Instances
type Sel1' (a, b) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b) = a | |
type Sel1' (a, b, c) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c) = a | |
type Sel1' (a, b, c, d) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d) = a | |
type Sel1' (a, b, c, d, e) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e) = a | |
type Sel1' (a, b, c, d, e, f) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f) = a | |
type Sel1' (a, b, c, d, e, f, g) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g) = a | |
type Sel1' (a, b, c, d, e, f, g, h) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g, h) = a | |
type Sel1' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g, h, i) = a | |
type Sel1' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g, h, i, j) = a | |
type Sel1' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g, h, i, j, k) = a | |
type Sel1' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g, h, i, j, k, l) = a | |
type Sel1' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g, h, i, j, k, l, m) = a | |
type Sel1' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = a | |
type Sel1' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel1' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = a |
Instances
type Sel2' (a, b) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b) = b | |
type Sel2' (a, b, c) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c) = b | |
type Sel2' (a, b, c, d) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d) = b | |
type Sel2' (a, b, c, d, e) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e) = b | |
type Sel2' (a, b, c, d, e, f) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f) = b | |
type Sel2' (a, b, c, d, e, f, g) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g) = b | |
type Sel2' (a, b, c, d, e, f, g, h) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g, h) = b | |
type Sel2' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g, h, i) = b | |
type Sel2' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g, h, i, j) = b | |
type Sel2' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g, h, i, j, k) = b | |
type Sel2' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g, h, i, j, k, l) = b | |
type Sel2' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g, h, i, j, k, l, m) = b | |
type Sel2' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = b | |
type Sel2' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel2' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = b |
Instances
type Sel3' (a, b, c) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c) = c | |
type Sel3' (a, b, c, d) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d) = c | |
type Sel3' (a, b, c, d, e) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e) = c | |
type Sel3' (a, b, c, d, e, f) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f) = c | |
type Sel3' (a, b, c, d, e, f, g) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g) = c | |
type Sel3' (a, b, c, d, e, f, g, h) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g, h) = c | |
type Sel3' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g, h, i) = c | |
type Sel3' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g, h, i, j) = c | |
type Sel3' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g, h, i, j, k) = c | |
type Sel3' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g, h, i, j, k, l) = c | |
type Sel3' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g, h, i, j, k, l, m) = c | |
type Sel3' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = c | |
type Sel3' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel3' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = c |
Instances
type Sel4' (a, b, c, d) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d) = d | |
type Sel4' (a, b, c, d, e) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e) = d | |
type Sel4' (a, b, c, d, e, f) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f) = d | |
type Sel4' (a, b, c, d, e, f, g) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g) = d | |
type Sel4' (a, b, c, d, e, f, g, h) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g, h) = d | |
type Sel4' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g, h, i) = d | |
type Sel4' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g, h, i, j) = d | |
type Sel4' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g, h, i, j, k) = d | |
type Sel4' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g, h, i, j, k, l) = d | |
type Sel4' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g, h, i, j, k, l, m) = d | |
type Sel4' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = d | |
type Sel4' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel4' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = d |
Instances
type Sel5' (a, b, c, d, e) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e) = e | |
type Sel5' (a, b, c, d, e, f) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f) = e | |
type Sel5' (a, b, c, d, e, f, g) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g) = e | |
type Sel5' (a, b, c, d, e, f, g, h) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g, h) = e | |
type Sel5' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g, h, i) = e | |
type Sel5' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g, h, i, j) = e | |
type Sel5' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g, h, i, j, k) = e | |
type Sel5' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g, h, i, j, k, l) = e | |
type Sel5' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g, h, i, j, k, l, m) = e | |
type Sel5' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = e | |
type Sel5' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel5' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = e |
Instances
type Sel6' (a, b, c, d, e, f) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f) = f | |
type Sel6' (a, b, c, d, e, f, g) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g) = f | |
type Sel6' (a, b, c, d, e, f, g, h) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g, h) = f | |
type Sel6' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g, h, i) = f | |
type Sel6' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g, h, i, j) = f | |
type Sel6' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g, h, i, j, k) = f | |
type Sel6' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g, h, i, j, k, l) = f | |
type Sel6' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g, h, i, j, k, l, m) = f | |
type Sel6' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = f | |
type Sel6' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel6' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = f |
Instances
type Sel7' (a, b, c, d, e, f, g) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g) = g | |
type Sel7' (a, b, c, d, e, f, g, h) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g, h) = g | |
type Sel7' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g, h, i) = g | |
type Sel7' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g, h, i, j) = g | |
type Sel7' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g, h, i, j, k) = g | |
type Sel7' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g, h, i, j, k, l) = g | |
type Sel7' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g, h, i, j, k, l, m) = g | |
type Sel7' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = g | |
type Sel7' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel7' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = g |
Instances
type Sel8' (a, b, c, d, e, f, g, h) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel8' (a, b, c, d, e, f, g, h) = h | |
type Sel8' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel8' (a, b, c, d, e, f, g, h, i) = h | |
type Sel8' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel8' (a, b, c, d, e, f, g, h, i, j) = h | |
type Sel8' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel8' (a, b, c, d, e, f, g, h, i, j, k) = h | |
type Sel8' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel8' (a, b, c, d, e, f, g, h, i, j, k, l) = h | |
type Sel8' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel8' (a, b, c, d, e, f, g, h, i, j, k, l, m) = h | |
type Sel8' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel8' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = h | |
type Sel8' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel8' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = h |
Instances
type Sel9' (a, b, c, d, e, f, g, h, i) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel9' (a, b, c, d, e, f, g, h, i) = i | |
type Sel9' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel9' (a, b, c, d, e, f, g, h, i, j) = i | |
type Sel9' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel9' (a, b, c, d, e, f, g, h, i, j, k) = i | |
type Sel9' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel9' (a, b, c, d, e, f, g, h, i, j, k, l) = i | |
type Sel9' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel9' (a, b, c, d, e, f, g, h, i, j, k, l, m) = i | |
type Sel9' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel9' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = i | |
type Sel9' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel9' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = i |
Instances
type Sel10' (a, b, c, d, e, f, g, h, i, j) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel10' (a, b, c, d, e, f, g, h, i, j) = j | |
type Sel10' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel10' (a, b, c, d, e, f, g, h, i, j, k) = j | |
type Sel10' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel10' (a, b, c, d, e, f, g, h, i, j, k, l) = j | |
type Sel10' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel10' (a, b, c, d, e, f, g, h, i, j, k, l, m) = j | |
type Sel10' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel10' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = j | |
type Sel10' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel10' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = j |
Instances
type Sel11' (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel11' (a, b, c, d, e, f, g, h, i, j, k) = k | |
type Sel11' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel11' (a, b, c, d, e, f, g, h, i, j, k, l) = k | |
type Sel11' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel11' (a, b, c, d, e, f, g, h, i, j, k, l, m) = k | |
type Sel11' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel11' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = k | |
type Sel11' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel11' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = k |
Instances
type Sel12' (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel12' (a, b, c, d, e, f, g, h, i, j, k, l) = l | |
type Sel12' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel12' (a, b, c, d, e, f, g, h, i, j, k, l, m) = l | |
type Sel12' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel12' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = l | |
type Sel12' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel12' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = l |
Instances
type Sel13' (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel13' (a, b, c, d, e, f, g, h, i, j, k, l, m) = m | |
type Sel13' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel13' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = m | |
type Sel13' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel13' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = m |
Instances
type Sel14' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel14' (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = n | |
type Sel14' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel14' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = n |
Instances
type Sel15' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Language.Syntactic.Constructs.Tuple type Sel15' (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = o |
Expressions for selecting elements of a tuple
Sel1 :: (Sel1 a b, Sel1' a ~ b) => Select (a :-> Full b) | |
Sel2 :: (Sel2 a b, Sel2' a ~ b) => Select (a :-> Full b) | |
Sel3 :: (Sel3 a b, Sel3' a ~ b) => Select (a :-> Full b) | |
Sel4 :: (Sel4 a b, Sel4' a ~ b) => Select (a :-> Full b) | |
Sel5 :: (Sel5 a b, Sel5' a ~ b) => Select (a :-> Full b) | |
Sel6 :: (Sel6 a b, Sel6' a ~ b) => Select (a :-> Full b) | |
Sel7 :: (Sel7 a b, Sel7' a ~ b) => Select (a :-> Full b) | |
Sel8 :: (Sel8 a b, Sel8' a ~ b) => Select (a :-> Full b) | |
Sel9 :: (Sel9 a b, Sel9' a ~ b) => Select (a :-> Full b) | |
Sel10 :: (Sel10 a b, Sel10' a ~ b) => Select (a :-> Full b) | |
Sel11 :: (Sel11 a b, Sel11' a ~ b) => Select (a :-> Full b) | |
Sel12 :: (Sel12 a b, Sel12' a ~ b) => Select (a :-> Full b) | |
Sel13 :: (Sel13 a b, Sel13' a ~ b) => Select (a :-> Full b) | |
Sel14 :: (Sel14 a b, Sel14' a ~ b) => Select (a :-> Full b) | |
Sel15 :: (Sel15 a b, Sel15' a ~ b) => Select (a :-> Full b) |
Instances
Semantic Select Source # | |
StringTree Select Source # | |
Defined in Language.Syntactic.Constructs.Tuple | |
Render Select Source # | |
Eval Select Source # | |
Defined in Language.Syntactic.Constructs.Tuple evaluate :: Select a -> Denotation a Source # | |
Equality Select Source # | |
Constrained Select Source # | |
EvalBind Select Source # | |
Optimize Select Source # | |
AlphaEq dom dom dom env => AlphaEq Select Select dom env Source # | |
TupleSat ((Select :|| p) :+: dom2) p Source # | |
Defined in Language.Syntactic.Frontend.TupleConstrained | |
TupleSat (Select :|| p) p Source # | |
Defined in Language.Syntactic.Frontend.TupleConstrained | |
type Sat Select Source # | |
Defined in Language.Syntactic.Constructs.Tuple |