GHood-0.0.7: A graphical viewer for Hood

CopyrightLicense : BSD3
Maintainerhpacheco@di.uminho.pt
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Debug.Observe

Contents

Description

GHood: A graphical viewer for Hood

Created a cabal library package. Improved the search for the GHood.jar file, that is bundled with the library. Changed from Literate Haskell to plain Haskell for better haddock documentation support.

Hugo Pacheco, November 2008

Added ObserveM. Adapted imports to use GHC's hierarchical libraries.

Alcino Cunha, February 2004

Modified version of Hood/Observe.lhs to match GHood, the Graphical Haskell Object Observation Debugger, which is distributed as a Java class file archive GHood.jar. [Apart from two new hooks, modifications are at the end]

Claus Reinke, December 2000

The file is part of the Haskell Object Observation Debugger, (HOOD) July 2000 release. Actually this is all of this version of HOOD, apart from the documentation and examples...

HOOD is a small post-mortem debugger for the lazy functional language Haskell. It is based on the concept of observation of intermediate data structures, rather than the more traditional stepping and variable examination paradigm used by imperative language debuggers.

Copyright (c) Andy Gill, 1992-2000

Synopsis

Documentation

observe :: Observable a => String -> a -> a Source #

Our principle function and class

newtype Observer Source #

Contains a forall typed observe (if supported).

Constructors

O (forall a. Observable a => String -> a -> a) 

type Observing a = a -> a Source #

class Observable a where Source #

Minimal complete definition

observer

Methods

observer :: a -> Parent -> a Source #

This reveals the name of a specific constructor. and gets ready to explain the sub-components. We put the context second so we can do eta-reduction with some of our definitions.

observers :: String -> (Observer -> a) -> a Source #

This used used to group several observer instances together.

Instances

Observable Bool Source # 
Observable Char Source # 
Observable Double Source # 
Observable Float Source # 
Observable Int Source # 
Observable Integer Source # 
Observable () Source # 

Methods

observer :: () -> Parent -> () Source #

observers :: String -> (Observer -> ()) -> () Source #

Observable IOError Source # 
Observable a => Observable [a] Source # 

Methods

observer :: [a] -> Parent -> [a] Source #

observers :: String -> (Observer -> [a]) -> [a] Source #

Observable a => Observable (Maybe a) Source # 

Methods

observer :: Maybe a -> Parent -> Maybe a Source #

observers :: String -> (Observer -> Maybe a) -> Maybe a Source #

Observable a => Observable (IO a) Source # 

Methods

observer :: IO a -> Parent -> IO a Source #

observers :: String -> (Observer -> IO a) -> IO a Source #

(Observable a, Observable b) => Observable (a -> b) Source # 

Methods

observer :: (a -> b) -> Parent -> a -> b Source #

observers :: String -> (Observer -> a -> b) -> a -> b Source #

(Observable a, Observable b) => Observable (Either a b) Source # 

Methods

observer :: Either a b -> Parent -> Either a b Source #

observers :: String -> (Observer -> Either a b) -> Either a b Source #

(Observable a, Observable b) => Observable (a, b) Source # 

Methods

observer :: (a, b) -> Parent -> (a, b) Source #

observers :: String -> (Observer -> (a, b)) -> (a, b) Source #

(Ix a, Observable a, Observable b) => Observable (Array a b) Source # 

Methods

observer :: Array a b -> Parent -> Array a b Source #

observers :: String -> (Observer -> Array a b) -> Array a b Source #

(Observable a, Observable b, Observable c) => Observable (a, b, c) Source # 

Methods

observer :: (a, b, c) -> Parent -> (a, b, c) Source #

observers :: String -> (Observer -> (a, b, c)) -> (a, b, c) Source #

(Observable a, Observable b, Observable c, Observable d) => Observable (a, b, c, d) Source # 

Methods

observer :: (a, b, c, d) -> Parent -> (a, b, c, d) Source #

observers :: String -> (Observer -> (a, b, c, d)) -> (a, b, c, d) Source #

(Observable a, Observable b, Observable c, Observable d, Observable e) => Observable (a, b, c, d, e) Source # 

Methods

observer :: (a, b, c, d, e) -> Parent -> (a, b, c, d, e) Source #

observers :: String -> (Observer -> (a, b, c, d, e)) -> (a, b, c, d, e) Source #

runO :: IO a -> IO () Source #

Runs observe ridden code.

printO :: Show a => a -> IO () Source #

Runs and prints observe ridden code.

putStrO :: String -> IO () Source #

Prints a string during observation.

newtype ObserverM a Source #

A simple state monad for placing numbers on sub-observations.

Constructors

ObserverM 

Fields

Instances

Monad ObserverM Source # 

Methods

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

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

return :: a -> ObserverM a #

fail :: String -> ObserverM a #

Functor ObserverM Source # 

Methods

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

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

Applicative ObserverM Source # 

Methods

pure :: a -> ObserverM a #

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

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

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

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

For advanced users, that want to render their own datatypes.

(<<) :: Observable a => ObserverM (a -> b) -> a -> ObserverM b infixl 9 Source #

the infix (<<) is a shortcut for constructor arguments.

thunk :: Observable a => a -> ObserverM a Source #

thunk is for marking suspensions.

send :: String -> ObserverM a -> Parent -> a Source #

Sends a packet to the observation agent.

observeBase :: Show a => a -> Parent -> a Source #

The strictness (by using seq) is the same as the pattern matching done on other constructors. We evaluate to WHNF, and not further.

Observe a base type

observeOpaque :: String -> a -> Parent -> a Source #

Observe a base type as an opaque string.

data Parent Source #

Parent book-keeping information.

Constructors

Parent 

Fields

Instances

For users that want to write their own render drivers.

debugO :: IO a -> IO [CDS] Source #

Debugs observe ridden code.

data CDS Source #

Instances

Eq CDS Source # 

Methods

(==) :: CDS -> CDS -> Bool #

(/=) :: CDS -> CDS -> Bool #

Ord CDS Source # 

Methods

compare :: CDS -> CDS -> Ordering #

(<) :: CDS -> CDS -> Bool #

(<=) :: CDS -> CDS -> Bool #

(>) :: CDS -> CDS -> Bool #

(>=) :: CDS -> CDS -> Bool #

max :: CDS -> CDS -> CDS #

min :: CDS -> CDS -> CDS #

Show CDS Source # 

Methods

showsPrec :: Int -> CDS -> ShowS #

show :: CDS -> String #

showList :: [CDS] -> ShowS #

type CDSSet = [CDS] Source #