text-display-0.0.5.0: A typeclass for user-facing output
Copyright© Hécate Moonlight 2021
LicenseMIT
Maintainerhecate@glitchbra.in
Stabilitystable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Text.Display.Core

Description

Core Display typeclass and instances

Synopsis

Documentation

class Display a where Source #

A typeclass for user-facing output.

Since: 0.0.1.0

Minimal complete definition

displayBuilder | displayPrec

Methods

displayBuilder :: a -> Builder Source #

Implement this method to describe how to convert your value to Builder.

displayList :: [a] -> Builder Source #

The method displayList is provided to allow for a specialised way to render lists of a certain value. This is used to render the list of Char as a string of characters enclosed in double quotes, rather than between square brackets and separated by commas.

Example

import qualified Data.Text.Lazy.Builder as TB

instance Display Char where
  displayBuilder c = TB.fromText $ T.singleton c
  displayList cs = TB.fromText $ T.pack cs

instance (Display a) => Display [a] where
  -- In this instance, 'displayBuilder' is defined in terms of 'displayList', which for most types
  -- is defined as the default written in the class declaration.
  -- But when a ~ Char, there is an explicit implementation that is selected instead, which
  -- provides the rendering of the character string between double quotes.
  displayBuilder = displayList

How implementations are selected

displayBuilder ([1,2,3] :: [Int])
→ displayBuilder @[Int] = displayBuilderList @Int
→ Default `displayList`

displayBuilder ("abc" :: [Char])
→ displayBuilder @[Char] = displayBuilderList @Char
→ Custom `displayList`

displayPrec Source #

Arguments

:: Int

The precedence level passed in by the surrounding context

-> a 
-> Builder 

The method displayPrec allows you to write instances that require nesting. The precedence parameter can be thought of as a suggestion coming from the surrounding context for how tightly to bind. If the precedence parameter is higher than the precedence of the operator (or constructor, function, etc.) being displayed, then that suggests that the output will need to be surrounded in parentheses in order to bind tightly enough (see displayParen).

For example, if an operator constructor is being displayed, then the precedence requirement for its arguments will be the precedence of the operator. Meaning, if the argument binds looser than the surrounding operator, then it will require parentheses.

Note that function/constructor application has an effective precedence of 10.

Examples

instance (Display a) => Display (Maybe a) where
  -- In this instance, we define 'displayPrec' rather than 'displayBuilder' as we need to decide
  -- whether or not to surround ourselves in parentheses based on the surrounding context.
  -- If the precedence parameter is higher than 10 (the precedence of constructor application)
  -- then we indeed need to surround ourselves in parentheses to avoid malformed outputs
  -- such as @Just Just 5@.
  -- We then set the precedence parameter of the inner 'displayPrec' to 11, as even
  -- constructor application is not strong enough to avoid parentheses.
  displayPrec _ Nothing = "Nothing"
  displayPrec prec (Just a) = displayParen (prec > 10) $ "Just " <> displayPrec 11 a
data Pair a b = a :*: b
infix 5 :*: -- arbitrary choice of precedence
instance (Display a, Display b) => Display (Pair a b) where
  displayPrec prec (a :*: b) = displayParen (prec > 5) $ displayPrec 6 a <> " :*: " <> displayPrec 6 b

Instances

Instances details
Display Void Source #

Since: 0.0.3.0

Instance details

Defined in Data.Text.Display.Core

Display SomeException Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display IOException Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Int16 Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Int32 Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Int64 Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Int8 Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Word16 Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Word32 Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Word64 Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Word8 Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

CannotDisplayByteStrings => Display ByteString Source #

🚫 You should not try to display strict ByteStrings!

💡 Always provide an explicit encoding. Use decodeUtf8' or decodeUtf8With to convert from UTF-8

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

CannotDisplayByteStrings => Display ByteString Source #

🚫 You should not try to display lazy ByteStrings!

💡 Always provide an explicit encoding. Use decodeUtf8' or decodeUtf8With to convert from UTF-8

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Text Source #

Strict Text

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Text Source #

Lazy Text

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Integer Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display () Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Bool Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Char Source #

displayList is overloaded, so that when the Display [a] instance calls displayList, we end up with a nice string instead of a list of chars between brackets.

>>> display [1, 2, 3]
"[1,2,3]"
>>> display ['h', 'e', 'l', 'l', 'o']
"hello"

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Double Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Float Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Int Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display Word Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Integral e => Display (DisplayDecimal e) Source # 
Instance details

Defined in Data.Text.Display.Core

RealFloat e => Display (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

Show e => Display (ShowInstance e) Source #

This wrapper allows you to rely on a pre-existing Show instance in order to derive Display from it.

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

(AssertNoSumRecordInstance Display a, Generic a, GDisplay1 (Rep a)) => Display (RecordInstance a) Source #

We leverage the AssertNoSum type family to prevent consumers from deriving instances for sum types. Sum types should use a manual instance or derive one via ShowInstance.

Since: 0.0.5.0

Instance details

Defined in Data.Text.Display.Generic

Display a => Display (NonEmpty a) Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display a => Display (Maybe a) Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Display a => Display [a] Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

KnownSymbol str => Display (OpaqueInstance str a) Source #

This wrapper allows you to create an opaque instance for your type, useful for redacting sensitive content like tokens or passwords.

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

CannotDisplayBareFunctions => Display (a -> b) Source #

🚫 You should not try to display functions!

💡 Write a 'newtype' wrapper that represents your domain more accurately. If you are not consciously trying to use display on a function, make sure that you are not missing an argument somewhere.

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Methods

displayBuilder :: (a -> b) -> Builder Source #

displayList :: [a -> b] -> Builder Source #

displayPrec :: Int -> (a -> b) -> Builder Source #

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

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Methods

displayBuilder :: (a, b) -> Builder Source #

displayList :: [(a, b)] -> Builder Source #

displayPrec :: Int -> (a, b) -> Builder Source #

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

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Methods

displayBuilder :: (a, b, c) -> Builder Source #

displayList :: [(a, b, c)] -> Builder Source #

displayPrec :: Int -> (a, b, c) -> Builder Source #

(Display a, Display b, Display c, Display d) => Display (a, b, c, d) Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Methods

displayBuilder :: (a, b, c, d) -> Builder Source #

displayList :: [(a, b, c, d)] -> Builder Source #

displayPrec :: Int -> (a, b, c, d) -> Builder Source #

display :: Display a => a -> Text Source #

Convert a value to a readable Text.

Examples

>>> display 3
"3"
>>> display True
"True"

Since: 0.0.1.0

type family CannotDisplayBareFunctions :: Constraint where ... Source #

Since: 0.0.1.0

Equations

CannotDisplayBareFunctions = TypeError ((('Text "\128683 You should not try to display functions!" ':$$: 'Text "\128161 Write a 'newtype' wrapper that represents your domain more accurately.") ':$$: 'Text " If you are not consciously trying to use `display` on a function,") ':$$: 'Text " make sure that you are not missing an argument somewhere.") 

type family CannotDisplayByteStrings :: Constraint where ... Source #

Equations

CannotDisplayByteStrings = TypeError (('Text "\128683 You should not try to display ByteStrings!" ':$$: 'Text "\128161 Always provide an explicit encoding") ':$$: 'Text "Use 'Data.Text.Encoding.decodeUtf8'' or 'Data.Text.Encoding.decodeUtf8With' to convert from UTF-8") 

displayParen :: Bool -> Builder -> Builder Source #

A utility function that surrounds the given Builder with parentheses when the Bool parameter is True. Useful for writing instances that may require nesting. See the displayPrec documentation for more information.

Since: 0.0.1.0

newtype OpaqueInstance (str :: Symbol) (a :: Type) Source #

This wrapper allows you to create an opaque instance for your type, useful for redacting sensitive content like tokens or passwords.

Example

data UserToken = UserToken UUID
 deriving Display
   via (OpaqueInstance "[REDACTED]" UserToken)
display $ UserToken "7a01d2ce-31ff-11ec-8c10-5405db82c3cd"
"[REDACTED]"

Since: 0.0.1.0

Constructors

Opaque a 

Instances

Instances details
KnownSymbol str => Display (OpaqueInstance str a) Source #

This wrapper allows you to create an opaque instance for your type, useful for redacting sensitive content like tokens or passwords.

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

newtype ShowInstance (a :: Type) Source #

This wrapper allows you to rely on a pre-existing Show instance in order to derive Display from it.

Example

data AutomaticallyDerived = AD
 -- We derive 'Show'
 deriving stock Show
 -- We take advantage of the 'Show' instance to derive 'Display' from it
 deriving Display
   via (ShowInstance AutomaticallyDerived)

Since: 0.0.1.0

Constructors

ShowInstance a 

Instances

Instances details
Show a => Show (ShowInstance a) Source #

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

Show e => Display (ShowInstance e) Source #

This wrapper allows you to rely on a pre-existing Show instance in order to derive Display from it.

Since: 0.0.1.0

Instance details

Defined in Data.Text.Display.Core

newtype DisplayDecimal e Source #

Constructors

DisplayDecimal e 

Instances

Instances details
Enum e => Enum (DisplayDecimal e) Source # 
Instance details

Defined in Data.Text.Display.Core

Num e => Num (DisplayDecimal e) Source # 
Instance details

Defined in Data.Text.Display.Core

Integral e => Integral (DisplayDecimal e) Source # 
Instance details

Defined in Data.Text.Display.Core

Real e => Real (DisplayDecimal e) Source # 
Instance details

Defined in Data.Text.Display.Core

Eq e => Eq (DisplayDecimal e) Source # 
Instance details

Defined in Data.Text.Display.Core

Ord e => Ord (DisplayDecimal e) Source # 
Instance details

Defined in Data.Text.Display.Core

Integral e => Display (DisplayDecimal e) Source # 
Instance details

Defined in Data.Text.Display.Core

newtype DisplayRealFloat e Source #

Constructors

DisplayRealFloat e 

Instances

Instances details
Floating e => Floating (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

RealFloat e => RealFloat (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

Num e => Num (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

Fractional e => Fractional (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

Real e => Real (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

RealFrac e => RealFrac (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

Eq e => Eq (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

Ord e => Ord (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

RealFloat e => Display (DisplayRealFloat e) Source # 
Instance details

Defined in Data.Text.Display.Core

A “Lawless Typeclass”

The Display typeclass does not contain any law. This is a controversial choice for some people, but the truth is that there are not any laws to ask of the consumer that are not already enforced by the type system and the internals of the Text type.

"🚫 You should not try to display functions!"

Sometimes, when using the library, you may encounter this message:

• 🚫 You should not try to display functions!
  💡 Write a 'newtype' wrapper that represents your domain more accurately.
     If you are not consciously trying to use `display` on a function,
     make sure that you are not missing an argument somewhere.

The display library does not allow the definition and usage of Display on bare function types ((a -> b)). Experience and time have shown that due to partial application being baked in the language, many users encounter a partial application-related error message when a simple missing argument to a function is the root cause.

There may be legitimate uses of a Display instance on a function type. But these usages are extremely dependent on their domain of application. That is why it is best to wrap them in a newtype that can better express and enforce the domain.

"🚫 You should not try to display ByteStrings!"

An arbitrary ByteStrings cannot be safely converted to text without prior knowledge of its encoding.

As such, in order to avoid dangerously blind conversions, it is recommended to use a specialised function such as decodeUtf8' or decodeUtf8With if you wish to turn a UTF8-encoded ByteString to Text.