Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utilities for inspection of Haskell values.
Synopsis
- data FromValue box rep = forall info. FromValue {
- box :: box -> info -> rep
- list :: [rep] -> Maybe box -> info
- string :: [Either box Char] -> Maybe box -> info
- char :: Char -> info
- tuple :: [rep] -> info
- con :: Name -> [Word] -> [rep] -> info
- rec :: Name -> [(String, rep)] -> info
- fun :: info
- thunk :: info
- bytecode :: info
- byteArray :: Word -> [Word] -> info
- mutByteArray :: info
- mVar :: info
- mutVar :: rep -> info
- stmQueue :: info
- integral :: Integer -> PrettyType -> info
- floating :: Double -> PrettyType -> info
- int# :: Int -> info
- word# :: Word -> info
- int64# :: Int64 -> info
- word64# :: Word64 -> info
- addr# :: Int -> info
- float# :: Float -> info
- double# :: Double -> info
- other :: info
- depthLimit :: info
- data Name = Name {}
- conName :: forall a. Data a => a -> Name
- type PrettyType = String
- prettyType :: forall a. Typeable a => PrettyType
- data RepM a
- data RepOptions = RepOptions {}
- runRepM :: RepM a -> RepOptions -> IO (Either String a)
- data Value = forall a.Data a => Value a
- valueFromData :: forall a r. Data a => FromValue Value r -> a -> RepM r
- data Box = Box (Any :: Type)
- asBox :: a -> Box
- boxFromAny :: forall r a. FromValue Box r -> a -> RepM r
- index :: Either Box Value -> Bool -> [String] -> RepM (Either Box Value)
- prettyRep :: Either Box Value -> RepM String
Documentation
data FromValue box rep Source #
Interpretation of Haskell value into representation r
. Allows user to
interpret inspection done by valueFromData
or boxFromAny
as needed.
forall info. FromValue | |
|
Runtime representation of Haskell identifier - can be both of type or value.
type PrettyType = String Source #
Pretty representation of type at runtime - currently just
String
.
prettyType :: forall a. Typeable a => PrettyType Source #
Shows type a
as PrettyType
.
Monad for inspecting representation of Haskell values - see runRepM
.
Instances
Monad RepM Source # | |
Functor RepM Source # | |
Applicative RepM Source # | |
MonadIO RepM Source # | |
Defined in Heap.Console.Value | |
Alternative RepM Source # | |
MonadReader RepOptions RepM Source # | |
Defined in Heap.Console.Value ask :: RepM RepOptions # local :: (RepOptions -> RepOptions) -> RepM a -> RepM a # reader :: (RepOptions -> a) -> RepM a # | |
MonadError String RepM Source # | |
Defined in Heap.Console.Value throwError :: String -> RepM a # |
data RepOptions Source #
Options for representation inspection.
Instances
Show RepOptions Source # | |
Defined in Heap.Console.Value showsPrec :: Int -> RepOptions -> ShowS # show :: RepOptions -> String # showList :: [RepOptions] -> ShowS # | |
MonadReader RepOptions RepM Source # | |
Defined in Heap.Console.Value ask :: RepM RepOptions # local :: (RepOptions -> RepOptions) -> RepM a -> RepM a # reader :: (RepOptions -> a) -> RepM a # |
runRepM :: RepM a -> RepOptions -> IO (Either String a) Source #
Runs action that may make use of inspection of representation of Haskell
values (e.g. using valueFromData
or boxFromAny
).
Lifted Haskell value together with it's Data
instance.
valueFromData :: forall a r. Data a => FromValue Value r -> a -> RepM r Source #
Inspects any value with Data
instance using given interpretation. Prefer
An arbitrary Haskell value in a safe Box. The point is that even
unevaluated thunks can safely be moved around inside the Box, and when
required, e.g. in getBoxedClosureData
, the function knows how far it has
to evaluate the argument.
This takes an arbitrary value and puts it into a box. Note that calls like
asBox (head list)
will put the thunk "head list" into the box, not the element at the head of the list. For that, use careful case expressions:
case list of x:_ -> asBox x
boxFromAny :: forall r a. FromValue Box r -> a -> RepM r Source #
Inspects any lifted value using given interpretation. This function can't
recover some information compared to valueFromData
- specifically, it
never recovers record syntax and unpacked fields are only provided by their
representation using Word
s.
index :: Either Box Value -> Bool -> [String] -> RepM (Either Box Value) Source #
Indexes Haskell value using given "selection" - that is, Bool
determining whether indexing should be always strict and list of indexes to
walk through along the way. Valid indexes are:
- positive integer (e.g.
3
) - position of element in list, tuple or other data constructor - record field name (e.g.
foo
) - name of field in record (only works when given enough information - that is, withValue
as input)
In case of Box
, unpacked values are ignored while indexing.