type-prelude-0.1: Partial port of prelude to the type level. Requires GHC 7.6.1.

Safe HaskellNone

Prelude.Type.Value

Contents

Synopsis

Documentation

data T a Source

Proxy Type

Constructors

T 

Instances

(Value k a t, Show t) => Show (T k a) 

type Proxy = TSource

Values and Main

class Value a t | k -> t whereSource

Convert a type to a value

Methods

value :: T a -> tSource

Instances

Value Bool False Bool 
Value Bool True Bool 
Value Ordering LT Ordering 
Value Ordering EQ Ordering 
Value Ordering GT Ordering 
Typeable t => Value * t TypeRep 
SingI Nat t => Value Nat t Integer 
SingI Symbol t => Value Symbol t String 
Value () () () 
Value Integer Zeros Integer 
Value Integer Ones Integer 
Value Integer i Integer => Value Integer (Zero i) Integer 
Value Integer i Integer => Value Integer (One i) Integer 
Value [k] ([] k) [a] 
Value (Maybe k) (Nothing k) (Maybe t) 
Value k a t => Value (Maybe k) (Just k a) (Maybe t) 
(Value k x y, Value [k] xs [y]) => Value [k] (: k x xs) [y] 
(c a, Value k a t) => Value (k -> Constraint) c t 
Value k1 a t => Value (Either k k1) (Right k k1 a) (Either s t) 
Value k a t => Value (Either k k1) (Left k k1 a) (Either t s) 
(Value k a t, Value k1 b u) => Value ((,) k k1) ((,) k k1 a b) (t, u) 
(Value k a t, Value k1 b u, Value k2 c v) => Value ((,,) k k1 k2) ((,,) k k1 k2 a b c) (t, u, v) 
(Value k a t, Value k1 b u, Value k2 c v, Value k3 d w) => Value ((,,,) k k1 k2 k3) ((,,,) k k1 k2 k3 a b c d) (t, u, v, w) 

type Main = Main'' ()Source

Main

Example Main.hs:

{--} module Main (main) where import Prelude.Type instance Compare '[I 1, I 3] '[I 1, I 2] a => Main a

$ ghc-stage2 Main.hs $ ./Main GT

class Main'' a b | a -> bSource

class Main' m a | m -> a whereSource

Methods

main :: m (T a)Source

Instances

(Show t, Value k a t, Main'' * k () a) => Main' k IO a