pragmatic-show-0.1.0.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

Description

 

Synopsis

Documentation

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 # 

Methods

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

show :: Bool -> String Source #

showList :: [Bool] -> ShowS Source #

Show Char Source # 

Methods

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

show :: Char -> String Source #

showList :: [Char] -> ShowS Source #

Show Double Source # 

Methods

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

show :: Double -> String Source #

showList :: [Double] -> ShowS Source #

Show Float Source # 

Methods

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

show :: Float -> String Source #

showList :: [Float] -> ShowS Source #

Show Int Source # 

Methods

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

show :: Int -> String Source #

showList :: [Int] -> ShowS Source #

Show Int8 Source # 

Methods

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

show :: Int8 -> String Source #

showList :: [Int8] -> ShowS Source #

Show Int16 Source # 

Methods

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

show :: Int16 -> String Source #

showList :: [Int16] -> ShowS Source #

Show Int32 Source # 

Methods

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

show :: Int32 -> String Source #

showList :: [Int32] -> ShowS Source #

Show Int64 Source # 

Methods

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

show :: Int64 -> String Source #

showList :: [Int64] -> ShowS Source #

Show Integer Source # 

Methods

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

show :: Integer -> String Source #

showList :: [Integer] -> ShowS Source #

Show Natural Source # 

Methods

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

show :: Natural -> String Source #

showList :: [Natural] -> ShowS Source #

Show Ordering Source # 

Methods

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

show :: Ordering -> String Source #

showList :: [Ordering] -> ShowS Source #

Show Word Source # 

Methods

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

show :: Word -> String Source #

showList :: [Word] -> ShowS Source #

Show Word8 Source # 

Methods

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

show :: Word8 -> String Source #

showList :: [Word8] -> ShowS Source #

Show Word16 Source # 

Methods

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

show :: Word16 -> String Source #

showList :: [Word16] -> ShowS Source #

Show Word32 Source # 

Methods

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

show :: Word32 -> String Source #

showList :: [Word32] -> ShowS Source #

Show Word64 Source # 

Methods

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

show :: Word64 -> String Source #

showList :: [Word64] -> ShowS Source #

Show CallStack Source # 

Methods

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

show :: CallStack -> String Source #

showList :: [CallStack] -> ShowS Source #

Show SomeTypeRep Source # 

Methods

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

show :: SomeTypeRep -> String Source #

showList :: [SomeTypeRep] -> ShowS Source #

Show () Source # 

Methods

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

show :: () -> String Source #

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

Show TyCon Source # 

Methods

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

show :: TyCon -> String Source #

showList :: [TyCon] -> ShowS Source #

Show Module Source # 

Methods

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

show :: Module -> String Source #

showList :: [Module] -> ShowS Source #

Show SrcLoc Source # 

Methods

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

show :: SrcLoc -> String Source #

showList :: [SrcLoc] -> ShowS Source #

Show Fingerprint Source # 

Methods

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

show :: Fingerprint -> String Source #

showList :: [Fingerprint] -> ShowS Source #

Show SomeAsyncException Source # 

Methods

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

show :: SomeAsyncException -> String Source #

showList :: [SomeAsyncException] -> ShowS Source #

Show IOException Source # 

Methods

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

show :: IOException -> String Source #

showList :: [IOException] -> ShowS Source #

Show Deadlock Source # 

Methods

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

show :: Deadlock -> String Source #

showList :: [Deadlock] -> ShowS Source #

Show CompactionFailed Source # 

Methods

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

show :: CompactionFailed -> String Source #

showList :: [CompactionFailed] -> ShowS Source #

Show BlockedIndefinitelyOnSTM Source # 

Methods

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

show :: BlockedIndefinitelyOnSTM -> String Source #

showList :: [BlockedIndefinitelyOnSTM] -> ShowS Source #

Show BlockedIndefinitelyOnMVar Source # 

Methods

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

show :: BlockedIndefinitelyOnMVar -> String Source #

showList :: [BlockedIndefinitelyOnMVar] -> ShowS Source #

Show AsyncException Source # 

Methods

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

show :: AsyncException -> String Source #

showList :: [AsyncException] -> ShowS Source #

Show AssertionFailed Source # 

Methods

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

show :: AssertionFailed -> String Source #

showList :: [AssertionFailed] -> ShowS Source #

Show ArrayException Source # 

Methods

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

show :: ArrayException -> String Source #

showList :: [ArrayException] -> ShowS Source #

Show AllocationLimitExceeded Source # 

Methods

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

show :: AllocationLimitExceeded -> String Source #

showList :: [AllocationLimitExceeded] -> ShowS Source #

Show MaskingState Source # 

Methods

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

show :: MaskingState -> String Source #

showList :: [MaskingState] -> ShowS Source #

Show SomeException Source # 

Methods

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

show :: SomeException -> String Source #

showList :: [SomeException] -> ShowS Source #

Show ErrorCall Source # 

Methods

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

show :: ErrorCall -> String Source #

showList :: [ErrorCall] -> ShowS Source #

Show ArithException Source # 

Methods

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

show :: ArithException -> String Source #

showList :: [ArithException] -> ShowS Source #

Show TypeError Source # 

Methods

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

show :: TypeError -> String Source #

showList :: [TypeError] -> ShowS Source #

Show RecUpdError Source # 

Methods

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

show :: RecUpdError -> String Source #

showList :: [RecUpdError] -> ShowS Source #

Show RecSelError Source # 

Methods

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

show :: RecSelError -> String Source #

showList :: [RecSelError] -> ShowS Source #

Show RecConError Source # 

Methods

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

show :: RecConError -> String Source #

showList :: [RecConError] -> ShowS Source #

Show PatternMatchFail Source # 

Methods

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

show :: PatternMatchFail -> String Source #

showList :: [PatternMatchFail] -> ShowS Source #

Show NonTermination Source # 

Methods

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

show :: NonTermination -> String Source #

showList :: [NonTermination] -> ShowS Source #

Show NoMethodError Source # 

Methods

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

show :: NoMethodError -> String Source #

showList :: [NoMethodError] -> ShowS Source #

Show NestedAtomically Source # 

Methods

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

show :: NestedAtomically -> String Source #

showList :: [NestedAtomically] -> ShowS Source #

Show GeneralCategory Source # 

Methods

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

show :: GeneralCategory -> String Source #

showList :: [GeneralCategory] -> ShowS Source #

Show Number Source # 

Methods

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

show :: Number -> String Source #

showList :: [Number] -> ShowS Source #

Show Lexeme Source # 

Methods

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

show :: Lexeme -> String Source #

showList :: [Lexeme] -> ShowS Source #

Show CMode Source # 

Methods

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

show :: CMode -> String Source #

showList :: [CMode] -> ShowS Source #

Show CInt Source # 

Methods

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

show :: CInt -> String Source #

showList :: [CInt] -> ShowS Source #

Show IOMode Source # 

Methods

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

show :: IOMode -> String Source #

showList :: [IOMode] -> ShowS Source #

Show NewlineMode Source # 

Methods

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

show :: NewlineMode -> String Source #

showList :: [NewlineMode] -> ShowS Source #

Show Newline Source # 

Methods

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

show :: Newline -> String Source #

showList :: [Newline] -> ShowS Source #

Show Handle Source # 

Methods

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

show :: Handle -> String Source #

showList :: [Handle] -> ShowS Source #

Show BufferMode Source # 

Methods

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

show :: BufferMode -> String Source #

showList :: [BufferMode] -> ShowS Source #

Show HandlePosn Source # 

Methods

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

show :: HandlePosn -> String Source #

showList :: [HandlePosn] -> ShowS Source #

Show TextEncoding Source # 

Methods

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

show :: TextEncoding -> String Source #

showList :: [TextEncoding] -> ShowS Source #

Show SeekMode Source # 

Methods

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

show :: SeekMode -> String Source #

showList :: [SeekMode] -> ShowS Source #

Show IOErrorType Source # 

Methods

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

show :: IOErrorType -> String Source #

showList :: [IOErrorType] -> ShowS Source #

Show ExitCode Source # 

Methods

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

show :: ExitCode -> String Source #

showList :: [ExitCode] -> ShowS Source #

Show WordPtr Source # 

Methods

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

show :: WordPtr -> String Source #

showList :: [WordPtr] -> ShowS Source #

Show IntPtr Source # 

Methods

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

show :: IntPtr -> String Source #

showList :: [IntPtr] -> ShowS Source #

Show CWchar Source # 

Methods

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

show :: CWchar -> String Source #

showList :: [CWchar] -> ShowS Source #

Show CUShort Source # 

Methods

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

show :: CUShort -> String Source #

showList :: [CUShort] -> ShowS Source #

Show CUSeconds Source # 

Methods

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

show :: CUSeconds -> String Source #

showList :: [CUSeconds] -> ShowS Source #

Show CULong Source # 

Methods

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

show :: CULong -> String Source #

showList :: [CULong] -> ShowS Source #

Show CULLong Source # 

Methods

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

show :: CULLong -> String Source #

showList :: [CULLong] -> ShowS Source #

Show CUIntPtr Source # 

Methods

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

show :: CUIntPtr -> String Source #

showList :: [CUIntPtr] -> ShowS Source #

Show CUIntMax Source # 

Methods

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

show :: CUIntMax -> String Source #

showList :: [CUIntMax] -> ShowS Source #

Show CUInt Source # 

Methods

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

show :: CUInt -> String Source #

showList :: [CUInt] -> ShowS Source #

Show CUChar Source # 

Methods

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

show :: CUChar -> String Source #

showList :: [CUChar] -> ShowS Source #

Show CTime Source # 

Methods

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

show :: CTime -> String Source #

showList :: [CTime] -> ShowS Source #

Show CSize Source # 

Methods

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

show :: CSize -> String Source #

showList :: [CSize] -> ShowS Source #

Show CSigAtomic Source # 

Methods

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

show :: CSigAtomic -> String Source #

showList :: [CSigAtomic] -> ShowS Source #

Show CShort Source # 

Methods

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

show :: CShort -> String Source #

showList :: [CShort] -> ShowS Source #

Show CSUSeconds Source # 

Methods

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

show :: CSUSeconds -> String Source #

showList :: [CSUSeconds] -> ShowS Source #

Show CSChar Source # 

Methods

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

show :: CSChar -> String Source #

showList :: [CSChar] -> ShowS Source #

Show CPtrdiff Source # 

Methods

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

show :: CPtrdiff -> String Source #

showList :: [CPtrdiff] -> ShowS Source #

Show CLong Source # 

Methods

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

show :: CLong -> String Source #

showList :: [CLong] -> ShowS Source #

Show CLLong Source # 

Methods

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

show :: CLLong -> String Source #

showList :: [CLLong] -> ShowS Source #

Show CIntPtr Source # 

Methods

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

show :: CIntPtr -> String Source #

showList :: [CIntPtr] -> ShowS Source #

Show CIntMax Source # 

Methods

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

show :: CIntMax -> String Source #

showList :: [CIntMax] -> ShowS Source #

Show CFloat Source # 

Methods

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

show :: CFloat -> String Source #

showList :: [CFloat] -> ShowS Source #

Show CDouble Source # 

Methods

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

show :: CDouble -> String Source #

showList :: [CDouble] -> ShowS Source #

Show CClock Source # 

Methods

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

show :: CClock -> String Source #

showList :: [CClock] -> ShowS Source #

Show CChar Source # 

Methods

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

show :: CChar -> String Source #

showList :: [CChar] -> ShowS Source #

Show CBool Source # 

Methods

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

show :: CBool -> String Source #

showList :: [CBool] -> ShowS Source #

Show SomeNat Source # 

Methods

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

show :: SomeNat -> String Source #

showList :: [SomeNat] -> ShowS Source #

Show SomeSymbol Source # 

Methods

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

show :: SomeSymbol -> String Source #

showList :: [SomeSymbol] -> ShowS Source #

Show SourceUnpackedness Source # 

Methods

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

show :: SourceUnpackedness -> String Source #

showList :: [SourceUnpackedness] -> ShowS Source #

Show SourceStrictness Source # 

Methods

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

show :: SourceStrictness -> String Source #

showList :: [SourceStrictness] -> ShowS Source #

Show Fixity Source # 

Methods

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

show :: Fixity -> String Source #

showList :: [Fixity] -> ShowS Source #

Show DecidedStrictness Source # 

Methods

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

show :: DecidedStrictness -> String Source #

showList :: [DecidedStrictness] -> ShowS Source #

Show Associativity Source # 

Methods

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

show :: Associativity -> String Source #

showList :: [Associativity] -> ShowS Source #

Show Any Source # 

Methods

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

show :: Any -> String Source #

showList :: [Any] -> ShowS Source #

Show All Source # 

Methods

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

show :: All -> String Source #

showList :: [All] -> ShowS Source #

Show CodingProgress Source # 

Methods

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

show :: CodingProgress -> String Source #

showList :: [CodingProgress] -> ShowS Source #

Show CodingFailureMode Source # 

Methods

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

show :: CodingFailureMode -> String Source #

showList :: [CodingFailureMode] -> ShowS Source #

Show FileLockingNotSupported Source # 

Methods

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

show :: FileLockingNotSupported -> String Source #

showList :: [FileLockingNotSupported] -> ShowS Source #

Show StaticPtrInfo Source # 

Methods

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

show :: StaticPtrInfo -> String Source #

showList :: [StaticPtrInfo] -> ShowS Source #

Show Fd Source # 

Methods

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

show :: Fd -> String Source #

showList :: [Fd] -> ShowS Source #

Show CUid Source # 

Methods

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

show :: CUid -> String Source #

showList :: [CUid] -> ShowS Source #

Show CTimer Source # 

Methods

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

show :: CTimer -> String Source #

showList :: [CTimer] -> ShowS Source #

Show CTcflag Source # 

Methods

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

show :: CTcflag -> String Source #

showList :: [CTcflag] -> ShowS Source #

Show CSsize Source # 

Methods

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

show :: CSsize -> String Source #

showList :: [CSsize] -> ShowS Source #

Show CSpeed Source # 

Methods

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

show :: CSpeed -> String Source #

showList :: [CSpeed] -> ShowS Source #

Show CRLim Source # 

Methods

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

show :: CRLim -> String Source #

showList :: [CRLim] -> ShowS Source #

Show CPid Source # 

Methods

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

show :: CPid -> String Source #

showList :: [CPid] -> ShowS Source #

Show COff Source # 

Methods

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

show :: COff -> String Source #

showList :: [COff] -> ShowS Source #

Show CNlink Source # 

Methods

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

show :: CNlink -> String Source #

showList :: [CNlink] -> ShowS Source #

Show CKey Source # 

Methods

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

show :: CKey -> String Source #

showList :: [CKey] -> ShowS Source #

Show CIno Source # 

Methods

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

show :: CIno -> String Source #

showList :: [CIno] -> ShowS Source #

Show CId Source # 

Methods

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

show :: CId -> String Source #

showList :: [CId] -> ShowS Source #

Show CGid Source # 

Methods

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

show :: CGid -> String Source #

showList :: [CGid] -> ShowS Source #

Show CFsFilCnt Source # 

Methods

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

show :: CFsFilCnt -> String Source #

showList :: [CFsFilCnt] -> ShowS Source #

Show CFsBlkCnt Source # 

Methods

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

show :: CFsBlkCnt -> String Source #

showList :: [CFsBlkCnt] -> ShowS Source #

Show CDev Source # 

Methods

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

show :: CDev -> String Source #

showList :: [CDev] -> ShowS Source #

Show CClockId Source # 

Methods

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

show :: CClockId -> String Source #

showList :: [CClockId] -> ShowS Source #

Show CCc Source # 

Methods

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

show :: CCc -> String Source #

showList :: [CCc] -> ShowS Source #

Show CBlkSize Source # 

Methods

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

show :: CBlkSize -> String Source #

showList :: [CBlkSize] -> ShowS Source #

Show CBlkCnt Source # 

Methods

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

show :: CBlkCnt -> String Source #

showList :: [CBlkCnt] -> ShowS Source #

Show FdKey Source # 

Methods

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

show :: FdKey -> String Source #

showList :: [FdKey] -> ShowS Source #

Show Lifetime Source # 

Methods

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

show :: Lifetime -> String Source #

showList :: [Lifetime] -> ShowS Source #

Show Event Source # 

Methods

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

show :: Event -> String Source #

showList :: [Event] -> ShowS Source #

Show Dynamic Source # 

Methods

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

show :: Dynamic -> String Source #

showList :: [Dynamic] -> ShowS Source #

Show ThreadStatus Source # 

Methods

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

show :: ThreadStatus -> String Source #

showList :: [ThreadStatus] -> ShowS Source #

Show ThreadId Source # 

Methods

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

show :: ThreadId -> String Source #

showList :: [ThreadId] -> ShowS Source #

Show BlockReason Source # 

Methods

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

show :: BlockReason -> String Source #

showList :: [BlockReason] -> ShowS Source #

Show Version Source # 

Methods

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

show :: Version -> String Source #

showList :: [Version] -> ShowS Source #

Show RTSStats Source # 

Methods

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

show :: RTSStats -> String Source #

showList :: [RTSStats] -> ShowS Source #

Show TraceFlags Source # 

Methods

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

show :: TraceFlags -> String Source #

showList :: [TraceFlags] -> ShowS Source #

Show TickyFlags Source # 

Methods

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

show :: TickyFlags -> String Source #

showList :: [TickyFlags] -> ShowS Source #

Show RTSFlags Source # 

Methods

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

show :: RTSFlags -> String Source #

showList :: [RTSFlags] -> ShowS Source #

Show ProfFlags Source # 

Methods

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

show :: ProfFlags -> String Source #

showList :: [ProfFlags] -> ShowS Source #

Show ParFlags Source # 

Methods

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

show :: ParFlags -> String Source #

showList :: [ParFlags] -> ShowS Source #

Show MiscFlags Source # 

Methods

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

show :: MiscFlags -> String Source #

showList :: [MiscFlags] -> ShowS Source #

Show GiveGCStats Source # 

Methods

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

show :: GiveGCStats -> String Source #

showList :: [GiveGCStats] -> ShowS Source #

Show GCFlags Source # 

Methods

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

show :: GCFlags -> String Source #

showList :: [GCFlags] -> ShowS Source #

Show DoTrace Source # 

Methods

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

show :: DoTrace -> String Source #

showList :: [DoTrace] -> ShowS Source #

Show DoHeapProfile Source # 

Methods

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

show :: DoHeapProfile -> String Source #

showList :: [DoHeapProfile] -> ShowS Source #

Show DoCostCentres Source # 

Methods

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

show :: DoCostCentres -> String Source #

showList :: [DoCostCentres] -> ShowS Source #

Show DebugFlags Source # 

Methods

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

show :: DebugFlags -> String Source #

showList :: [DebugFlags] -> ShowS Source #

Show ConcFlags Source # 

Methods

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

show :: ConcFlags -> String Source #

showList :: [ConcFlags] -> ShowS Source #

Show CCFlags Source # 

Methods

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

show :: CCFlags -> String Source #

showList :: [CCFlags] -> ShowS Source #

Show Fixity Source # 

Methods

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

show :: Fixity -> String Source #

showList :: [Fixity] -> ShowS Source #

Show DataType Source # 

Methods

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

show :: DataType -> String Source #

showList :: [DataType] -> ShowS Source #

Show DataRep Source # 

Methods

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

show :: DataRep -> String Source #

showList :: [DataRep] -> ShowS Source #

Show ConstrRep Source # 

Methods

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

show :: ConstrRep -> String Source #

showList :: [ConstrRep] -> ShowS Source #

Show Constr Source # 

Methods

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

show :: Constr -> String Source #

showList :: [Constr] -> ShowS Source #

Show Void Source # 

Methods

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

show :: Void -> String Source #

showList :: [Void] -> ShowS Source #

Show a => Show [a] Source # 

Methods

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

show :: [a] -> String Source #

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

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

Methods

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

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

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

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

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 # 

Methods

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

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

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

shows :: Show a => a -> ShowS Source #

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.