repa-flow-4.2.3.1: Data-parallel data flows.

Safe HaskellNone
LanguageHaskell98

Data.Repa.Flow.Generic.Debug

Contents

Synopsis

More

more Source #

Arguments

:: (States i IO, Nicer a) 
=> i

Index of source in bundle.

-> Sources i IO a

Bundle of sources.

-> IO [Nice a] 

Given a source index and a length, pull enough chunks from the source to build a list of the requested length, and discard the remaining elements in the final chunk.

  • This function is intended for interactive debugging. If you want to retain the rest of the final chunk then use head_i.

more' :: (States i IO, Nicer a) => i -> Int -> Sources i IO a -> IO [Nice a] Source #

Like more but also specify now many elements you want.

More (tabular)

moret Source #

Arguments

:: (States i IO, Nicer [a], Presentable (Nice [a])) 
=> i

Index of source in bundle.

-> Sources i IO a

Bundle of sources.

-> IO () 

Like more, but print results in a tabular form to the console.

moret' :: (States i IO, Nicer [a], Presentable (Nice [a])) => i -> Int -> Sources i IO a -> IO () Source #

Like more', but print results in tabular form to the console.

More (raw)

morer Source #

Arguments

:: States i IO 
=> i

Index of source in bundle.

-> Sources i IO a

Bundle of sources.

-> IO [a] 

Like more, but show elements in their raw format.

morer' :: States i IO => i -> Int -> Sources i IO a -> IO [a] Source #

Like more', but show elements in their raw format.

Nicer

class Nicer a where #

Convert some value to a nice form.

In particular:

  • Nested Arrays are converted to nested lists, so that they are easier to work with on the ghci console.
  • Lists of characters are wrapped into the Str data type, so that they can be pretty printed differently by follow-on processing.

As ghci automatically pretty prints lists, using nice is more fun than trying to show the raw Repa array representations.

Associated Types

type Nice a :: * #

Instances

Nicer Char 

Associated Types

type Nice Char :: * #

Methods

nice :: Char -> Nice Char #

Nicer Double 

Associated Types

type Nice Double :: * #

Methods

nice :: Double -> Nice Double #

Nicer Float 

Associated Types

type Nice Float :: * #

Methods

nice :: Float -> Nice Float #

Nicer Int 

Associated Types

type Nice Int :: * #

Methods

nice :: Int -> Nice Int #

Nicer Int8 

Associated Types

type Nice Int8 :: * #

Methods

nice :: Int8 -> Nice Int8 #

Nicer Int16 

Associated Types

type Nice Int16 :: * #

Methods

nice :: Int16 -> Nice Int16 #

Nicer Int32 

Associated Types

type Nice Int32 :: * #

Methods

nice :: Int32 -> Nice Int32 #

Nicer Int64 

Associated Types

type Nice Int64 :: * #

Methods

nice :: Int64 -> Nice Int64 #

Nicer Word 

Associated Types

type Nice Word :: * #

Methods

nice :: Word -> Nice Word #

Nicer Word8 

Associated Types

type Nice Word8 :: * #

Methods

nice :: Word8 -> Nice Word8 #

Nicer Word16 

Associated Types

type Nice Word16 :: * #

Methods

nice :: Word16 -> Nice Word16 #

Nicer Word32 

Associated Types

type Nice Word32 :: * #

Methods

nice :: Word32 -> Nice Word32 #

Nicer Word64 

Associated Types

type Nice Word64 :: * #

Methods

nice :: Word64 -> Nice Word64 #

Nicer () 

Associated Types

type Nice () :: * #

Methods

nice :: () -> Nice () #

Nicer Date32 

Associated Types

type Nice Date32 :: * #

Methods

nice :: Date32 -> Nice Date32 #

Nicer [Char] 

Associated Types

type Nice [Char] :: * #

Methods

nice :: [Char] -> Nice [Char] #

Nicer [Double] 

Associated Types

type Nice [Double] :: * #

Methods

nice :: [Double] -> Nice [Double] #

Nicer [Float] 

Associated Types

type Nice [Float] :: * #

Methods

nice :: [Float] -> Nice [Float] #

Nicer [Int] 

Associated Types

type Nice [Int] :: * #

Methods

nice :: [Int] -> Nice [Int] #

Nicer [Int8] 

Associated Types

type Nice [Int8] :: * #

Methods

nice :: [Int8] -> Nice [Int8] #

Nicer [Int16] 

Associated Types

type Nice [Int16] :: * #

Methods

nice :: [Int16] -> Nice [Int16] #

Nicer [Int32] 

Associated Types

type Nice [Int32] :: * #

Methods

nice :: [Int32] -> Nice [Int32] #

Nicer [Int64] 

Associated Types

type Nice [Int64] :: * #

Methods

nice :: [Int64] -> Nice [Int64] #

Nicer [a] => Nicer [[a]] 

Associated Types

type Nice [[a]] :: * #

Methods

nice :: [[a]] -> Nice [[a]] #

Nicer a => Nicer [Maybe a] 

Associated Types

type Nice [Maybe a] :: * #

Methods

nice :: [Maybe a] -> Nice [Maybe a] #

Nicer [Word8] 

Associated Types

type Nice [Word8] :: * #

Methods

nice :: [Word8] -> Nice [Word8] #

Nicer [Word16] 

Associated Types

type Nice [Word16] :: * #

Methods

nice :: [Word16] -> Nice [Word16] #

Nicer [Word32] 

Associated Types

type Nice [Word32] :: * #

Methods

nice :: [Word32] -> Nice [Word32] #

Nicer [Word64] 

Associated Types

type Nice [Word64] :: * #

Methods

nice :: [Word64] -> Nice [Word64] #

(Nicer a, Nicer b) => Nicer [(a, b)] 

Associated Types

type Nice [(a, b)] :: * #

Methods

nice :: [(a, b)] -> Nice [(a, b)] #

(Nicer a, Nicer b) => Nicer [(:*:) a b] 

Associated Types

type Nice [(:*:) a b] :: * #

Methods

nice :: [a :*: b] -> Nice [a :*: b] #

(Bulk l a, Nicer [a]) => Nicer [Array l a] 

Associated Types

type Nice [Array l a] :: * #

Methods

nice :: [Array l a] -> Nice [Array l a] #

Nicer a => Nicer (Maybe a) 

Associated Types

type Nice (Maybe a) :: * #

Methods

nice :: Maybe a -> Nice (Maybe a) #

(Nicer a, Nicer b) => Nicer (a, b) 

Associated Types

type Nice (a, b) :: * #

Methods

nice :: (a, b) -> Nice (a, b) #

(Nicer a, Nicer b) => Nicer ((:*:) a b) 

Associated Types

type Nice ((:*:) a b) :: * #

Methods

nice :: (a :*: b) -> Nice (a :*: b) #

(Bulk l a, Nicer [a]) => Nicer (Array l a) 

Associated Types

type Nice (Array l a) :: * #

Methods

nice :: Array l a -> Nice (Array l a) #

class Presentable a where #

Convert some value to a form presentable to the user.

Like show but we allow the nesting structure to be preserved so it can be displayed in tabular format.

Instances

Presentable Char 

Methods

present :: Char -> Present #

Presentable Double 

Methods

present :: Double -> Present #

Presentable Float 

Methods

present :: Float -> Present #

Presentable Int 

Methods

present :: Int -> Present #

Presentable Word8 

Methods

present :: Word8 -> Present #

Presentable Word16 

Methods

present :: Word16 -> Present #

Presentable Word32 

Methods

present :: Word32 -> Present #

Presentable Word64 

Methods

present :: Word64 -> Present #

Presentable () 

Methods

present :: () -> Present #

Presentable Str 

Methods

present :: Str -> Present #

Presentable Tok 

Methods

present :: Tok -> Present #

Presentable Date32 

Methods

present :: Date32 -> Present #

Presentable a => Presentable [a] 

Methods

present :: [a] -> Present #

(Presentable a, Presentable b) => Presentable (a, b) 

Methods

present :: (a, b) -> Present #

(Presentable a, Presentable b) => Presentable ((:*:) a b) 

Methods

present :: (a :*: b) -> Present #

(Presentable a, Presentable b, Presentable c) => Presentable (a, b, c) 

Methods

present :: (a, b, c) -> Present #

(Presentable a, Presentable b, Presentable c, Presentable d) => Presentable (a, b, c, d) 

Methods

present :: (a, b, c, d) -> Present #

(Presentable a, Presentable b, Presentable c, Presentable d, Presentable e) => Presentable (a, b, c, d, e) 

Methods

present :: (a, b, c, d, e) -> Present #