pragmatic-show-0.1.2.1: Alternative Show class that gives shorter view if possible.

Copyright(c) Justus Sagemüller 2017
LicenseGPL v3
Maintainer(@) jsagemue $ uni-koeln.de
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Show.Pragmatic

Contents

Description

 
Synopsis

Replacement for the standard class

class Show a where Source #

A drop-in replacement for Show. The behaviour is mostly the same: the result of show should be valid Haskell code, and reading back such a value should give the original value – but, unlike in Show, we don't require this in an exact sense, i.e. read (show x) == x is not necessarily fulfilled.

Notably for floating-point values, we allow a slight deviation if it considerably shortens the shown representation: for example, 0.90000004 :: Float, which can easily come up as the result of a computation which should in principle be exactly 0.9, is shown as 0.9 instead. We do however not commit to any particular fixed precision; it depends on the type and the order of magnitude which amount of rounding is appropriate. See the test suite for some examples.

Minimal complete definition

showsPrec | show

Methods

showsPrec :: Int -> a -> ShowS Source #

show :: a -> String Source #

showList :: [a] -> ShowS Source #

Instances
Show Bool Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Char Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Double Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Float Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Int Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Int8 Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Int16 Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Int32 Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Int64 Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Integer Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Natural Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Ordering Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Word Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Word8 Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Word16 Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Word32 Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Word64 Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CallStack Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SomeTypeRep Source # 
Instance details

Defined in Text.Show.Pragmatic

Show () Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> () -> ShowS Source #

show :: () -> String Source #

showList :: [()] -> ShowS Source #

Show TyCon Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Module Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Handle Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Void Source # 
Instance details

Defined in Text.Show.Pragmatic

Show StaticPtrInfo Source # 
Instance details

Defined in Text.Show.Pragmatic

Show DataType Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Constr Source # 
Instance details

Defined in Text.Show.Pragmatic

Show DataRep Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ConstrRep Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Fixity Source # 
Instance details

Defined in Text.Show.Pragmatic

Show GiveGCStats Source # 
Instance details

Defined in Text.Show.Pragmatic

Show GCFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ConcFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show MiscFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show DebugFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show DoCostCentres Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CCFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show DoHeapProfile Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ProfFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show DoTrace Source # 
Instance details

Defined in Text.Show.Pragmatic

Show TraceFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show TickyFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ParFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show RTSFlags Source # 
Instance details

Defined in Text.Show.Pragmatic

Show RTSStats Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Version Source # 
Instance details

Defined in Text.Show.Pragmatic

Show HandlePosn Source # 
Instance details

Defined in Text.Show.Pragmatic

Show FileLockingNotSupported Source # 
Instance details

Defined in Text.Show.Pragmatic

Show FdKey Source # 
Instance details

Defined in Text.Show.Pragmatic

Show PatternMatchFail Source # 
Instance details

Defined in Text.Show.Pragmatic

Show RecSelError Source # 
Instance details

Defined in Text.Show.Pragmatic

Show RecConError Source # 
Instance details

Defined in Text.Show.Pragmatic

Show RecUpdError Source # 
Instance details

Defined in Text.Show.Pragmatic

Show NoMethodError Source # 
Instance details

Defined in Text.Show.Pragmatic

Show TypeError Source # 
Instance details

Defined in Text.Show.Pragmatic

Show NonTermination Source # 
Instance details

Defined in Text.Show.Pragmatic

Show NestedAtomically Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ThreadId Source # 
Instance details

Defined in Text.Show.Pragmatic

Show BlockReason Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ThreadStatus Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Dynamic Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Event Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Lifetime Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CDev Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CIno Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CMode Source # 
Instance details

Defined in Text.Show.Pragmatic

Show COff Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CPid Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CSsize Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CGid Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CNlink Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CUid Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CCc Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CSpeed Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CTcflag Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CRLim Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CBlkSize Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CBlkCnt Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CClockId Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CFsBlkCnt Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CFsFilCnt Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CId Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CKey Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CTimer Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Fd Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CodingFailureMode Source # 
Instance details

Defined in Text.Show.Pragmatic

Show BlockedIndefinitelyOnMVar Source # 
Instance details

Defined in Text.Show.Pragmatic

Show BlockedIndefinitelyOnSTM Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Deadlock Source # 
Instance details

Defined in Text.Show.Pragmatic

Show AllocationLimitExceeded Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CompactionFailed Source # 
Instance details

Defined in Text.Show.Pragmatic

Show AssertionFailed Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SomeAsyncException Source # 
Instance details

Defined in Text.Show.Pragmatic

Show AsyncException Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ArrayException Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ExitCode Source # 
Instance details

Defined in Text.Show.Pragmatic

Show IOErrorType Source # 
Instance details

Defined in Text.Show.Pragmatic

Show BufferMode Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Newline Source # 
Instance details

Defined in Text.Show.Pragmatic

Show NewlineMode Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SeekMode Source # 
Instance details

Defined in Text.Show.Pragmatic

Show TextEncoding Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CodingProgress Source # 
Instance details

Defined in Text.Show.Pragmatic

Show MaskingState Source # 
Instance details

Defined in Text.Show.Pragmatic

Show IOException Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ErrorCall Source # 
Instance details

Defined in Text.Show.Pragmatic

Show ArithException Source # 
Instance details

Defined in Text.Show.Pragmatic

Show All Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Any Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Fixity Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Associativity Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SourceUnpackedness Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SourceStrictness Source # 
Instance details

Defined in Text.Show.Pragmatic

Show DecidedStrictness Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SomeSymbol Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SomeNat Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CChar Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CSChar Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CUChar Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CShort Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CUShort Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CInt Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CUInt Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CLong Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CULong Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CLLong Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CULLong Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CBool Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CFloat Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CDouble Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CPtrdiff Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CSize Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CWchar Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CSigAtomic Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CClock Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CTime Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CUSeconds Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CSUSeconds Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CIntPtr Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CUIntPtr Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CIntMax Source # 
Instance details

Defined in Text.Show.Pragmatic

Show CUIntMax Source # 
Instance details

Defined in Text.Show.Pragmatic

Show WordPtr Source # 
Instance details

Defined in Text.Show.Pragmatic

Show IntPtr Source # 
Instance details

Defined in Text.Show.Pragmatic

Show IOMode Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Fingerprint Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Lexeme Source # 
Instance details

Defined in Text.Show.Pragmatic

Show Number Source # 
Instance details

Defined in Text.Show.Pragmatic

Show GeneralCategory Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SrcLoc Source # 
Instance details

Defined in Text.Show.Pragmatic

Show SomeException Source # 
Instance details

Defined in Text.Show.Pragmatic

Show IntSet Source # 
Instance details

Defined in Text.Show.Pragmatic

Show a => Show [a] Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> [a] -> ShowS Source #

show :: [a] -> String Source #

showList :: [[a]] -> ShowS Source #

(Integral i, Show i) => Show (Ratio i) Source # 
Instance details

Defined in Text.Show.Pragmatic

Show (Complex Double) Source # 
Instance details

Defined in Text.Show.Pragmatic

Show (Complex Float) Source # 
Instance details

Defined in Text.Show.Pragmatic

Show b => Show (IntMap b) Source # 
Instance details

Defined in Text.Show.Pragmatic

Show a => Show (Tree a) Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> Tree a -> ShowS Source #

show :: Tree a -> String Source #

showList :: [Tree a] -> ShowS Source #

(Show a, Ord a) => Show (Seq a) Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> Seq a -> ShowS Source #

show :: Seq a -> String Source #

showList :: [Seq a] -> ShowS Source #

(Show a, Ord a) => Show (Set a) Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> Set a -> ShowS Source #

show :: Set a -> String Source #

showList :: [Set a] -> ShowS Source #

(Show a, Show b) => Show (a, b) Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> (a, b) -> ShowS Source #

show :: (a, b) -> String Source #

showList :: [(a, b)] -> ShowS Source #

(Show a, Ord a, Show b) => Show (Map a b) Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> Map a b -> ShowS Source #

show :: Map a b -> String Source #

showList :: [Map a b] -> ShowS Source #

(Show a, Show b, Show c) => Show (a, b, c) Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> (a, b, c) -> ShowS Source #

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

showList :: [(a, b, c)] -> ShowS Source #

(Show a, Show b, Show c, Show d) => Show (a, b, c, d) Source # 
Instance details

Defined in Text.Show.Pragmatic

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS Source #

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

showList :: [(a, b, c, d)] -> ShowS Source #

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

Utility (unstable)

ltdPrecShowsPrec :: RealFloat n => Int -> Int -> n -> ShowS Source #

ltdPrecShowsPrec prcn displays floating-point values with a precision of at least prcn digits. That does not mean it will necessarily display that many digits, rather it tries to always choose the shortest representation with the required precision.

showsPrecWithSharedPrecision Source #

Arguments

:: (ShowMagnitudeRangeLimited n, RealFloat sn, Traversable list) 
=> (n -> sn)

Magnitude-function. Should be a norm.

-> Int

Precision of the type, in significant decimals. This will be used to trim the length of all entries to match the expected numerical uncertainty of the biggest one.

-> Int

Precedence of the enclosing context in which the values are to be shown.

-> list n

Values to show

-> list ShowS

Individual values' string representation.