uni-util-2.2.1.0: Utilities for the uniform workbench

Util.Dynamics

Description

A wrapper for the new GHC (and Hugs) Dynamic module. The main improvement over the original Dynamic module is that we provide flavours of TypeableXXXX for kinds with arguments other than *, a feature used by DisplayView.

Synopsis

Documentation

class Typeable a where

The class Typeable allows a concrete representation of a type to be calculated.

Methods

typeOf :: a -> TypeRep

Takes a value of type a and returns a concrete representation of that type. The value of the argument should be ignored by any instance of Typeable, so that it is safe to pass undefined as the argument.

Instances

Typeable Bool 
Typeable Char 
Typeable Double 
Typeable Float 
Typeable Int 
Typeable Int8 
Typeable Int16 
Typeable Int32 
Typeable Int64 
Typeable Integer 
Typeable Ordering 
Typeable RealWorld 
Typeable Word 
Typeable Word8 
Typeable Word16 
Typeable Word32 
Typeable Word64 
Typeable () 
Typeable Handle 
Typeable Handle__ 
Typeable PatternMatchFail 
Typeable RecSelError 
Typeable RecConError 
Typeable RecUpdError 
Typeable NoMethodError 
Typeable NonTermination 
Typeable NestedAtomically 
Typeable ThreadId 
Typeable BlockedIndefinitelyOnMVar 
Typeable BlockedIndefinitelyOnSTM 
Typeable Deadlock 
Typeable AssertionFailed 
Typeable AsyncException 
Typeable ArrayException 
Typeable ExitCode 
Typeable WordPtr 
Typeable IntPtr 
Typeable Dynamic 
Typeable CChar 
Typeable CSChar 
Typeable CUChar 
Typeable CShort 
Typeable CUShort 
Typeable CInt 
Typeable CUInt 
Typeable CLong 
Typeable CULong 
Typeable CLLong 
Typeable CULLong 
Typeable CFloat 
Typeable CDouble 
Typeable CPtrdiff 
Typeable CSize 
Typeable CWchar 
Typeable CSigAtomic 
Typeable CClock 
Typeable CTime 
Typeable CIntPtr 
Typeable CUIntPtr 
Typeable CIntMax 
Typeable CUIntMax 
Typeable IOException 
Typeable SomeException 
Typeable ErrorCall 
Typeable ArithException 
Typeable TypeRep 
Typeable TyCon 
Typeable ByteString 
Typeable ServiceEntry 
Typeable ProtocolEntry 
Typeable HostEntry 
Typeable NetworkEntry 
Typeable SocketStatus 
Typeable Socket 
Typeable SocketOption 
Typeable SocketType 
Typeable ShutdownCmd 
Typeable AddrInfoFlag 
Typeable AddrInfo 
Typeable NameInfoFlag 
Typeable PortNumber 
Typeable SockAddr 
Typeable FallOutExcep 
Typeable FromStringExcep 
Typeable AtomString 
Typeable UniqueStringSource 
Typeable ICStringLen 
(Typeable1_1 ty, Typeable1 typeArg) => Typeable (ty typeArg) 
(Typeable1 s, Typeable a) => Typeable (s a)

One Typeable instance for all Typeable1 instances

data TypeRep

A concrete representation of a (monomorphic) type. TypeRep supports reasonably efficient equality.

toDyn :: Typeable a => a -> DynSource

fromDynamicWE :: Typeable a => Dyn -> WithError aSource

Like fromDynamic but provides an error message indicating what types are getting confused.

dynCast :: (Typeable a, Typeable b) => String -> a -> bSource

mkTypeRep :: String -> String -> TypeRepSource

Construct a TypeRep for a type or type constructor with no arguments. The first string should be the module name, the second that of the type.

class Typeable1_1 ty whereSource

Methods

typeOf1_1 :: Typeable1 typeArg => ty typeArg -> TypeRepSource

Instances

(Typeable2_11 ty, Typeable1 typeArg1) => Typeable1_1 (ty typeArg1) 

class Typeable2_11 ty whereSource

Methods

typeOf2_11 :: (Typeable1 typeArg1, Typeable1 typeArg2) => ty typeArg1 typeArg2 -> TypeRepSource

Instances

(Typeable3_111 ty, Typeable1 typeArg1) => Typeable2_11 (ty typeArg1) 

class Typeable3_111 ty whereSource

Methods

typeOf3_111 :: (Typeable1 typeArg1, Typeable1 typeArg2, Typeable1 typeArg3) => ty typeArg1 typeArg2 typeArg3 -> TypeRepSource

Instances

(Typeable4_0111 ty, Typeable ty1) => Typeable3_111 (ty ty1) 

class Typeable4_0111 ty whereSource

Methods

typeOf4_0111 :: (Typeable ty1, Typeable1 typeArg1, Typeable1 typeArg2, Typeable1 typeArg3) => ty ty1 typeArg1 typeArg2 typeArg3 -> TypeRepSource

Instances

(Typeable5_00111 ty, Typeable ty1) => Typeable4_0111 (ty ty1) 

class Typeable5_00111 ty whereSource

Methods

typeOf5_00111 :: (Typeable ty1, Typeable ty2, Typeable1 typeArg1, Typeable1 typeArg2, Typeable1 typeArg3) => ty ty1 ty2 typeArg1 typeArg2 typeArg3 -> TypeRepSource

Instances

(Typeable6_000111 ty, Typeable ty1) => Typeable5_00111 (ty ty1) 

class Typeable6_000111 ty whereSource

Methods

typeOf6_000111 :: (Typeable ty1, Typeable ty2, Typeable ty3, Typeable1 typeArg1, Typeable1 typeArg2, Typeable1 typeArg3) => ty ty1 ty2 ty3 typeArg1 typeArg2 typeArg3 -> TypeRepSource