safe-coloured-text-0.2.0.0: Safely output coloured text
Safe HaskellNone
LanguageHaskell2010

Text.Colour

Description

Safe Coloured Text

This module is responsible for defining, building, and rendering coloured text.

The text to be coloured is Text, but the rendered text, while technically still (probably) valid Utf8, will be a ByteString builder.

Synopsis

Building chunks

chunk :: Text -> Chunk Source #

Turn a text into a plain chunk, without any styling

data Chunk Source #

Instances

Instances details
Eq Chunk Source # 
Instance details

Defined in Text.Colour.Chunk

Methods

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

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

Show Chunk Source # 
Instance details

Defined in Text.Colour.Chunk

Methods

showsPrec :: Int -> Chunk -> ShowS #

show :: Chunk -> String #

showList :: [Chunk] -> ShowS #

IsString Chunk Source # 
Instance details

Defined in Text.Colour.Chunk

Methods

fromString :: String -> Chunk #

Generic Chunk Source # 
Instance details

Defined in Text.Colour.Chunk

Associated Types

type Rep Chunk :: Type -> Type #

Methods

from :: Chunk -> Rep Chunk x #

to :: Rep Chunk x -> Chunk #

Validity Chunk Source # 
Instance details

Defined in Text.Colour.Chunk

Methods

validate :: Chunk -> Validation #

type Rep Chunk Source # 
Instance details

Defined in Text.Colour.Chunk

type Rep Chunk = D1 ('MetaData "Chunk" "Text.Colour.Chunk" "safe-coloured-text-0.2.0.0-CYny960IEWDA7ODh5aXbAt" 'False) (C1 ('MetaCons "Chunk" 'PrefixI 'True) ((S1 ('MetaSel ('Just "chunkText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "chunkItalic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "chunkConsoleIntensity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ConsoleIntensity)))) :*: (S1 ('MetaSel ('Just "chunkUnderlining") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Underlining)) :*: (S1 ('MetaSel ('Just "chunkForeground") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Colour)) :*: S1 ('MetaSel ('Just "chunkBackground") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Colour))))))

Styling

Setting colour

Setting non-colour attributes

Colours

data Colour Source #

Instances

Instances details
Eq Colour Source # 
Instance details

Defined in Text.Colour.Chunk

Methods

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

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

Show Colour Source # 
Instance details

Defined in Text.Colour.Chunk

Generic Colour Source # 
Instance details

Defined in Text.Colour.Chunk

Associated Types

type Rep Colour :: Type -> Type #

Methods

from :: Colour -> Rep Colour x #

to :: Rep Colour x -> Colour #

Validity Colour Source # 
Instance details

Defined in Text.Colour.Chunk

type Rep Colour Source # 
Instance details

Defined in Text.Colour.Chunk

8-colour

Dull

Bright

8-bit

color256 :: Word8 -> Colour Source #

Alias for colour256, bloody americans...

colour256 :: Word8 -> Colour Source #

Bulid an 8-bit RGB Colour

This will not be rendered unless With8BitColours is used.

24-bit

colorRGB :: Word8 -> Word8 -> Word8 -> Colour Source #

Alias for colourRGB, bloody americans...

colourRGB :: Word8 -> Word8 -> Word8 -> Colour Source #

Bulid a 24-bit RGB Colour

This will not be rendered unless With24BitColours is used.

Rendering

Rendering chunks to strict bytestring in UTF8

renderChunksUtf8BS :: Foldable f => TerminalCapabilities -> f Chunk -> ByteString Source #

Render chunks directly to a UTF8-encoded Bytestring.

renderChunkUtf8BS :: TerminalCapabilities -> Chunk -> ByteString Source #

Render a chunk directly to a UTF8-encoded Bytestring.

Rendering chunks to lazy bytestring builders in UTF8

renderChunkUtf8BSBuilder :: TerminalCapabilities -> Chunk -> Builder Source #

Render a chunk directly to a UTF8-encoded Bytestring Builder.

Rendering chunks to strict Text

renderChunksText :: Foldable f => TerminalCapabilities -> f Chunk -> Text Source #

Render chunks directly to strict Text.

renderChunkText :: TerminalCapabilities -> Chunk -> Text Source #

Render a chunk directly to strict Text.

Rendering chunks to lazy text

renderChunksLazyText :: Foldable f => TerminalCapabilities -> f Chunk -> Text Source #

Render chunks directly to lazy Text.

renderChunkLazyText :: TerminalCapabilities -> Chunk -> Text Source #

Render a chunk directly to strict Text.

Rendering chunks to lazy text builder

Decrecated rendering chunks to strict bytestring in UTF8

renderChunksBS :: Foldable f => TerminalCapabilities -> f Chunk -> ByteString Source #

Deprecated: Use renderChunksText, or renderChunksUtf8BS if you must.

Deprecated synonym for renderChunksUtf8BS

renderChunkBS :: TerminalCapabilities -> Chunk -> ByteString Source #

Deprecated: Use renderChunkText, or renderChunkUtf8BS if you must.

Deprecated synonym for renderChunkUtf8BS

Deprecated rendering chunks to lazy bytestring builders in UTF8

renderChunks :: Foldable f => TerminalCapabilities -> f Chunk -> Builder Source #

Deprecated: Use renderChunksBuilder, or renderChunksUtf8BSBuilder if you must.

Deprecated synonym for renderChunksUtf8BSBuilder

renderChunk :: TerminalCapabilities -> Chunk -> Builder Source #

Deprecated: Use renderChunkBuilder, or renderChunkUtf8BSBuilder if you must.

Deprecated synonym for renderChunkUtf8BSBuilder

IO

data TerminalCapabilities Source #

Constructors

WithoutColours

No colours

With8Colours

Only 8 colours

With8BitColours

Only 8-bit colours

With24BitColours

All 24-bit colours

Instances

Instances details
Eq TerminalCapabilities Source # 
Instance details

Defined in Text.Colour.Capabilities

Ord TerminalCapabilities Source # 
Instance details

Defined in Text.Colour.Capabilities

Show TerminalCapabilities Source # 
Instance details

Defined in Text.Colour.Capabilities

Generic TerminalCapabilities Source # 
Instance details

Defined in Text.Colour.Capabilities

Associated Types

type Rep TerminalCapabilities :: Type -> Type #

type Rep TerminalCapabilities Source # 
Instance details

Defined in Text.Colour.Capabilities

type Rep TerminalCapabilities = D1 ('MetaData "TerminalCapabilities" "Text.Colour.Capabilities" "safe-coloured-text-0.2.0.0-CYny960IEWDA7ODh5aXbAt" 'False) ((C1 ('MetaCons "WithoutColours" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "With8Colours" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "With8BitColours" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "With24BitColours" 'PrefixI 'False) (U1 :: Type -> Type)))

Outputting chunks directly

putChunksUtf8With :: TerminalCapabilities -> [Chunk] -> IO () Source #

Print a list of chunks to stdout with given TerminalCapabilities.

putChunksLocaleWith :: TerminalCapabilities -> [Chunk] -> IO () Source #

Print a list of chunks to stdout with given TerminalCapabilities in an encoding according to the system's locale.

hPutChunksUtf8With :: TerminalCapabilities -> Handle -> [Chunk] -> IO () Source #

Print a list of chunks to the given Handle with given TerminalCapabilities.

hPutChunksLocaleWith :: TerminalCapabilities -> Handle -> [Chunk] -> IO () Source #

Print a list of chunks to the given Handle with given TerminalCapabilities in an encoding according to the system's locale.

putChunksWith :: TerminalCapabilities -> [Chunk] -> IO () Source #

Deprecated: Use putChunksLocaleWith, or putChunksUtf8With if you must.

Deprecated synonym of putChunksUtf8With

hPutChunksWith :: TerminalCapabilities -> Handle -> [Chunk] -> IO () Source #

Deprecated: Use hPutChunksLocaleWith, or hPutChunksUtf8With if you must.

Deprecated synonym of hPutChunksUtf8With