| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Debug.Variables
Contents
Description
Module for debugging Haskell programs. To use, take the functions that you are interested in debugging, e.g.:
module QuickSort(quicksort) where
import Data.List
quicksort :: Ord a => [a] -> [a]
quicksort [] = []
quicksort (x:xs) = quicksort lt ++ [x] ++ quicksort gt
where (lt, gt) = partition (<= x) xsTurn on the TemplateHaskell and ViewPatterns extensions, import Debug,
indent your code and place it under a call to debug, e.g.:
{-# LANGUAGE TemplateHaskell, ViewPatterns, PartialTypeSignatures #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
module QuickSort(quicksort) where
import Data.List
import Debug
debug [d|
quicksort :: Ord a => [a] -> [a]
quicksort [] = []
quicksort (x:xs) = quicksort lt ++ [x] ++ quicksort gt
where (lt, gt) = partition (<= x) xs
|]We can now run our debugger with:
$ ghci QuickSort.hs GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling QuickSort ( QuickSort.hs, interpreted ) Ok, 1 module loaded. *QuickSort> quicksort "haskell" "aehklls" *QuickSort> debugView
The final call to debugView starts a web browser to view the recorded information.
Alternatively call debugSave to write the web page to a known location.
For more ways to view the result (e.g. producing JSON) or record traces (without using
TemplateHaskell) see Debug.DebugTrace.
- debug :: Q [Dec] -> Q [Dec]
- debugClear :: IO ()
- debugRun :: IO a -> IO a
- debugPrint :: IO ()
- debugJSON :: IO String
- debugView :: IO ()
- debugSave :: FilePath -> IO ()
- data DebugTrace = DebugTrace {}
- getDebugTrace :: IO DebugTrace
- funInfo :: Show a => Function -> (Call -> a) -> a
- fun :: Show a => String -> (Call -> a) -> a
- var :: Show a => Call -> String -> a -> a
Documentation
debugClear :: IO () Source #
Clear all debug information. Useful when working in ghci to reset
any previous debugging work and reduce the amount of output.
debugRun :: IO a -> IO a Source #
Run a computation and open a browser window showing observed function calls.
main = debugRun $ do
...
debugPrint :: IO () Source #
Print information about the observed function calls to stdout,
in a human-readable format.
debugJSON :: IO String Source #
Obtain information about observed functions in JSON format. The JSON format is not considered a stable part of the interface, more presented as a back door to allow exploration of alternative views.
debugSave :: FilePath -> IO () Source #
Save information about observed functions to the specified file, in HTML format.
getDebugTrace :: IO DebugTrace Source #
Returns all the information about the observed function accumulated so far in the variables.
Recording
fun :: Show a => String -> (Call -> a) -> a Source #
Called under a lambda with a function name to provide a unique context for a particular call, e.g.:
tracedAdd x y = fun "add" $ \t -> var t "x" x + var t "y" y
This function involves giving identity to function calls, so is unsafe, and will only work under a lambda.