preview-0.1.0.4: The method of previewing data (instead of wholly show-ing it)

Safe HaskellNone
LanguageHaskell2010

Data.Preview

Synopsis

Documentation

class Preview a where Source #

Conversion of values to short readable strings. Preview allows defining short and readable representations of potentially huge data structures that can be used in logs for example. E.g. the Preview instance for lists may only print the values at the beginning of the list and omit the rest.

Minimal complete definition

previewsPrec

Methods

previewsPrec :: Int -> a -> String -> String Source #

Create a preview String for the given value.

previewsPrec should satisfy the law

previewsPrec d x r ++ s == previewsPrec d x (r ++ s)

Instances

Preview Bool Source # 
Preview Char Source # 
Preview Int Source # 

Methods

previewsPrec :: Int -> Int -> String -> String Source #

Preview Int32 Source # 
Preview Int64 Source # 
Preview Word8 Source # 
Preview Word64 Source # 
Preview () Source # 

Methods

previewsPrec :: Int -> () -> String -> String Source #

Preview Text Source # 
Preview a => Preview [a] Source # 

Methods

previewsPrec :: Int -> [a] -> String -> String Source #

Preview a => Preview (Maybe a) Source # 

Methods

previewsPrec :: Int -> Maybe a -> String -> String Source #

Preview a => Preview (Option a) Source # 

Methods

previewsPrec :: Int -> Option a -> String -> String Source #

Preview a => Preview (Fail a) Source # 

Methods

previewsPrec :: Int -> Fail a -> String -> String Source #

Preview a => Preview (StrictList a) Source # 
(Preview a, Preview b) => Preview (Either a b) Source # 

Methods

previewsPrec :: Int -> Either a b -> String -> String Source #

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

Methods

previewsPrec :: Int -> (a, b) -> String -> String Source #

(Preview k, Preview v) => Preview (Map k v) Source # 

Methods

previewsPrec :: Int -> Map k v -> String -> String Source #

(Preview a, Preview b) => Preview (Pair a b) Source # 

Methods

previewsPrec :: Int -> Pair a b -> String -> String Source #

(Preview a, Preview b) => Preview (Choice a b) Source # 

Methods

previewsPrec :: Int -> Choice a b -> String -> String Source #

(Preview k, Preview v) => Preview (OSMap k v) Source # 

Methods

previewsPrec :: Int -> OSMap k v -> String -> String Source #

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

Methods

previewsPrec :: Int -> (a, b, c) -> String -> String Source #

previewList :: Preview a => Int -> [a] -> String -> String Source #

showKv :: Show a => String -> a -> String -> String Source #

pprMapping :: (Ppr a, Ppr b) => [(a, b)] -> Doc Source #

previewsPrecMapping :: (Preview k, Preview v) => t -> [(k, v)] -> String -> String Source #

class Ppr a where Source #

Minimal complete definition

ppr

Methods

ppr :: a -> Doc Source #

pprMany :: Foldable f => f a -> Doc Source #

Instances

Ppr Bool Source # 

Methods

ppr :: Bool -> Doc Source #

pprMany :: Foldable f => f Bool -> Doc Source #

Ppr Char Source # 

Methods

ppr :: Char -> Doc Source #

pprMany :: Foldable f => f Char -> Doc Source #

Ppr Double Source # 

Methods

ppr :: Double -> Doc Source #

pprMany :: Foldable f => f Double -> Doc Source #

Ppr Int Source # 

Methods

ppr :: Int -> Doc Source #

pprMany :: Foldable f => f Int -> Doc Source #

Ppr Int32 Source # 

Methods

ppr :: Int32 -> Doc Source #

pprMany :: Foldable f => f Int32 -> Doc Source #

Ppr Int64 Source # 

Methods

ppr :: Int64 -> Doc Source #

pprMany :: Foldable f => f Int64 -> Doc Source #

Ppr Integer Source # 

Methods

ppr :: Integer -> Doc Source #

pprMany :: Foldable f => f Integer -> Doc Source #

Ppr Word8 Source # 

Methods

ppr :: Word8 -> Doc Source #

pprMany :: Foldable f => f Word8 -> Doc Source #

Ppr Word64 Source # 

Methods

ppr :: Word64 -> Doc Source #

pprMany :: Foldable f => f Word64 -> Doc Source #

Ppr () Source # 

Methods

ppr :: () -> Doc Source #

pprMany :: Foldable f => f () -> Doc Source #

Ppr Text Source # 

Methods

ppr :: Text -> Doc Source #

pprMany :: Foldable f => f Text -> Doc Source #

Ppr Doc Source # 

Methods

ppr :: Doc -> Doc Source #

pprMany :: Foldable f => f Doc -> Doc Source #

Ppr a => Ppr [a] Source # 

Methods

ppr :: [a] -> Doc Source #

pprMany :: Foldable f => f [a] -> Doc Source #

Ppr a => Ppr (Maybe a) Source # 

Methods

ppr :: Maybe a -> Doc Source #

pprMany :: Foldable f => f (Maybe a) -> Doc Source #

Ppr a => Ppr (Set a) Source # 

Methods

ppr :: Set a -> Doc Source #

pprMany :: Foldable f => f (Set a) -> Doc Source #

Ppr a => Ppr (Option a) Source # 

Methods

ppr :: Option a -> Doc Source #

pprMany :: Foldable f => f (Option a) -> Doc Source #

Ppr a => Ppr (Fail a) Source # 

Methods

ppr :: Fail a -> Doc Source #

pprMany :: Foldable f => f (Fail a) -> Doc Source #

Ppr a => Ppr (StrictList a) Source # 

Methods

ppr :: StrictList a -> Doc Source #

pprMany :: Foldable f => f (StrictList a) -> Doc Source #

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

Methods

ppr :: (a, b) -> Doc Source #

pprMany :: Foldable f => f (a, b) -> Doc Source #

(Ppr a, Ppr b) => Ppr (Map a b) Source # 

Methods

ppr :: Map a b -> Doc Source #

pprMany :: Foldable f => f (Map a b) -> Doc Source #

(Ppr a, Ppr b) => Ppr (Pair a b) Source # 

Methods

ppr :: Pair a b -> Doc Source #

pprMany :: Foldable f => f (Pair a b) -> Doc Source #

(Ppr a, Ppr b) => Ppr (Choice a b) Source # 

Methods

ppr :: Choice a b -> Doc Source #

pprMany :: Foldable f => f (Choice a b) -> Doc Source #

(Ppr k, Ppr v) => Ppr (OSMap k v) Source # 

Methods

ppr :: OSMap k v -> Doc Source #

pprMany :: Foldable f => f (OSMap k v) -> Doc Source #

(Ppr k, Ppr v) => Ppr (USMap k v) Source # 

Methods

ppr :: USMap k v -> Doc Source #

pprMany :: Foldable f => f (USMap k v) -> Doc Source #

class Ppr' k where Source #

Minimal complete definition

ppr'

Methods

ppr' :: Ppr a => k a -> Doc Source #

data Doc :: * #

The abstract type of documents. A Doc represents a set of layouts. A Doc with no occurrences of Union or NoDoc represents just one layout.

Instances

Eq Doc 

Methods

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

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

Show Doc 

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

IsString Doc 

Methods

fromString :: String -> Doc #

Generic Doc 

Associated Types

type Rep Doc :: * -> * #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Semigroup Doc 

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Monoid Doc 

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

NFData Doc 

Methods

rnf :: Doc -> () #

Ppr Doc Source # 

Methods

ppr :: Doc -> Doc Source #

pprMany :: Foldable f => f Doc -> Doc Source #

type Rep Doc 
type Rep Doc = D1 (MetaData "Doc" "Text.PrettyPrint.HughesPJ" "pretty-1.1.3.3" True) (C1 (MetaCons "Doc" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ()))))

pretty :: Ppr a => a -> String Source #

prettyText :: Ppr a => a -> Text Source #