heap-console-0.1.0.1: interactively inspect Haskell values at runtime
Safe HaskellNone
LanguageHaskell2010

Heap.Console.Value

Description

Utilities for inspection of Haskell values.

Synopsis

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.

Constructors

forall info. FromValue 

Fields

data Name Source #

Runtime representation of Haskell identifier - can be both of type or value.

Constructors

Name 

Instances

Instances details
Show Name Source # 
Instance details

Defined in Heap.Console.Value

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

conName :: forall a. Data a => a -> Name Source #

Name of given data constructor.

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.

data RepM a Source #

Monad for inspecting representation of Haskell values - see runRepM.

Instances

Instances details
Monad RepM Source # 
Instance details

Defined in Heap.Console.Value

Methods

(>>=) :: RepM a -> (a -> RepM b) -> RepM b #

(>>) :: RepM a -> RepM b -> RepM b #

return :: a -> RepM a #

Functor RepM Source # 
Instance details

Defined in Heap.Console.Value

Methods

fmap :: (a -> b) -> RepM a -> RepM b #

(<$) :: a -> RepM b -> RepM a #

Applicative RepM Source # 
Instance details

Defined in Heap.Console.Value

Methods

pure :: a -> RepM a #

(<*>) :: RepM (a -> b) -> RepM a -> RepM b #

liftA2 :: (a -> b -> c) -> RepM a -> RepM b -> RepM c #

(*>) :: RepM a -> RepM b -> RepM b #

(<*) :: RepM a -> RepM b -> RepM a #

MonadIO RepM Source # 
Instance details

Defined in Heap.Console.Value

Methods

liftIO :: IO a -> RepM a #

Alternative RepM Source # 
Instance details

Defined in Heap.Console.Value

Methods

empty :: RepM a #

(<|>) :: RepM a -> RepM a -> RepM a #

some :: RepM a -> RepM [a] #

many :: RepM a -> RepM [a] #

MonadReader RepOptions RepM Source # 
Instance details

Defined in Heap.Console.Value

Methods

ask :: RepM RepOptions #

local :: (RepOptions -> RepOptions) -> RepM a -> RepM a #

reader :: (RepOptions -> a) -> RepM a #

MonadError String RepM Source # 
Instance details

Defined in Heap.Console.Value

Methods

throwError :: String -> RepM a #

catchError :: RepM a -> (String -> RepM a) -> RepM a #

data RepOptions Source #

Options for representation inspection.

Constructors

RepOptions 

Fields

  • repDepth :: Natural

    Depth of inspection - guards against getting stuck in infinite structures.

  • repStrict :: Bool

    Whether inspection should force thunks along the way.

  • repTypes :: Bool

    Whether printed representations should contain type signatures in ambiguous places - used by prettyRep.

Instances

Instances details
Show RepOptions Source # 
Instance details

Defined in Heap.Console.Value

MonadReader RepOptions RepM Source # 
Instance details

Defined in Heap.Console.Value

Methods

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).

data Value Source #

Lifted Haskell value together with it's Data instance.

Constructors

forall a.Data a => Value a 

Instances

Instances details
Show Value Source # 
Instance details

Defined in Heap.Console.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

valueFromData :: forall a r. Data a => FromValue Value r -> a -> RepM r Source #

Inspects any value with Data instance using given interpretation. Prefer

data Box #

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.

Constructors

Box (Any :: Type) 

Instances

Instances details
Show Box 
Instance details

Defined in GHC.Exts.Heap.Closures

Methods

showsPrec :: Int -> Box -> ShowS #

show :: Box -> String #

showList :: [Box] -> ShowS #

asBox :: a -> Box #

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 Words.

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, with Value as input)

In case of Box, unpacked values are ignored while indexing.

prettyRep :: Either Box Value -> RepM String Source #

Pretty-print given value. In case of Box, record syntax is never shown and (unpacked) fields may be shown as Word#s out of order.