-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A typeclass for user-facing output -- -- The Display typeclass provides a solution for user-facing -- output that does not have to abide by the rules of the Show typeclass. @package text-display @version 1.0.0.0 -- | Core Display typeclass and instances module Data.Text.Display.Core -- | A typeclass for user-facing output. class Display a -- | Implement this method to describe how to convert your value to -- Builder. displayBuilder :: Display a => a -> Builder -- | 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 = Builder.fromText $ Text.pack $ Text.singleton c
--     displayList cs = Builder.fromText $ Text.pack $ Text.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`
--   
displayList :: Display a => [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
--   
displayPrec :: Display a => Int -> a -> Builder -- | Convert a value to a readable Text. -- --

Examples

-- --
--   >>> display 3
--   "3"
--   
-- --
--   >>> display True
--   "True"
--   
display :: Display a => a -> Text type family CannotDisplayBareFunctions :: Constraint type family CannotDisplayByteStrings :: Constraint -- | 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. displayParen :: Bool -> Builder -> Builder -- | 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]"
--   
newtype OpaqueInstance (str :: Symbol) (a :: Type) Opaque :: a -> OpaqueInstance (str :: Symbol) (a :: Type) -- | 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)
--   
newtype ShowInstance (a :: Type) ShowInstance :: a -> ShowInstance (a :: Type) newtype DisplayDecimal e DisplayDecimal :: e -> DisplayDecimal e newtype DisplayRealFloat e DisplayRealFloat :: e -> DisplayRealFloat e instance GHC.Show.Show a => GHC.Show.Show (Data.Text.Display.Core.ShowInstance a) instance GHC.Classes.Eq e => GHC.Classes.Eq (Data.Text.Display.Core.DisplayDecimal e) instance GHC.Num.Num e => GHC.Num.Num (Data.Text.Display.Core.DisplayDecimal e) instance GHC.Classes.Ord e => GHC.Classes.Ord (Data.Text.Display.Core.DisplayDecimal e) instance GHC.Enum.Enum e => GHC.Enum.Enum (Data.Text.Display.Core.DisplayDecimal e) instance GHC.Real.Real e => GHC.Real.Real (Data.Text.Display.Core.DisplayDecimal e) instance GHC.Real.Integral e => GHC.Real.Integral (Data.Text.Display.Core.DisplayDecimal e) instance GHC.Float.Floating e => GHC.Float.Floating (Data.Text.Display.Core.DisplayRealFloat e) instance GHC.Real.Fractional e => GHC.Real.Fractional (Data.Text.Display.Core.DisplayRealFloat e) instance GHC.Num.Num e => GHC.Num.Num (Data.Text.Display.Core.DisplayRealFloat e) instance GHC.Classes.Eq e => GHC.Classes.Eq (Data.Text.Display.Core.DisplayRealFloat e) instance GHC.Classes.Ord e => GHC.Classes.Ord (Data.Text.Display.Core.DisplayRealFloat e) instance GHC.Real.Real e => GHC.Real.Real (Data.Text.Display.Core.DisplayRealFloat e) instance GHC.Real.RealFrac e => GHC.Real.RealFrac (Data.Text.Display.Core.DisplayRealFloat e) instance GHC.Float.RealFloat e => GHC.Float.RealFloat (Data.Text.Display.Core.DisplayRealFloat e) instance Data.Text.Display.Core.Display () instance Data.Text.Display.Core.Display GHC.Base.Void instance Data.Text.Display.Core.Display GHC.Types.Bool instance Data.Text.Display.Core.Display GHC.Types.Double instance Data.Text.Display.Core.Display GHC.Types.Float instance Data.Text.Display.Core.Display GHC.Types.Int instance Data.Text.Display.Core.Display GHC.Int.Int8 instance Data.Text.Display.Core.Display GHC.Int.Int16 instance Data.Text.Display.Core.Display GHC.Int.Int32 instance Data.Text.Display.Core.Display GHC.Int.Int64 instance Data.Text.Display.Core.Display GHC.Num.Integer.Integer instance Data.Text.Display.Core.Display GHC.Types.Word instance Data.Text.Display.Core.Display GHC.Word.Word8 instance Data.Text.Display.Core.Display GHC.Word.Word16 instance Data.Text.Display.Core.Display GHC.Word.Word32 instance Data.Text.Display.Core.Display GHC.Word.Word64 instance Data.Text.Display.Core.Display GHC.IO.Exception.IOException instance Data.Text.Display.Core.Display GHC.Exception.Type.SomeException instance GHC.Float.RealFloat e => Data.Text.Display.Core.Display (Data.Text.Display.Core.DisplayRealFloat e) instance GHC.Real.Integral e => Data.Text.Display.Core.Display (Data.Text.Display.Core.DisplayDecimal e) instance GHC.Show.Show e => Data.Text.Display.Core.Display (Data.Text.Display.Core.ShowInstance e) instance GHC.TypeLits.KnownSymbol str => Data.Text.Display.Core.Display (Data.Text.Display.Core.OpaqueInstance str a) instance Data.Text.Display.Core.CannotDisplayByteStrings => Data.Text.Display.Core.Display Data.ByteString.Internal.Type.StrictByteString instance Data.Text.Display.Core.CannotDisplayByteStrings => Data.Text.Display.Core.Display Data.ByteString.Lazy.Internal.LazyByteString instance Data.Text.Display.Core.CannotDisplayBareFunctions => Data.Text.Display.Core.Display (a -> b) instance Data.Text.Display.Core.Display GHC.Types.Char instance Data.Text.Display.Core.Display Data.Text.Internal.Lazy.Text instance Data.Text.Display.Core.Display Data.Text.Internal.Text instance Data.Text.Display.Core.Display a => Data.Text.Display.Core.Display [a] instance Data.Text.Display.Core.Display a => Data.Text.Display.Core.Display (GHC.Base.NonEmpty a) instance Data.Text.Display.Core.Display a => Data.Text.Display.Core.Display (GHC.Maybe.Maybe a) instance (Data.Text.Display.Core.Display a, Data.Text.Display.Core.Display b) => Data.Text.Display.Core.Display (a, b) instance (Data.Text.Display.Core.Display a, Data.Text.Display.Core.Display b, Data.Text.Display.Core.Display c) => Data.Text.Display.Core.Display (a, b, c) instance (Data.Text.Display.Core.Display a, Data.Text.Display.Core.Display b, Data.Text.Display.Core.Display c, Data.Text.Display.Core.Display d) => Data.Text.Display.Core.Display (a, b, c, d) -- | Generic machinery for automatically deriving display instances for -- record types module Data.Text.Display.Generic -- | Generic typeclass machinery for inducting on the structure of the -- type, such that we can thread Display instances through the -- structure of the type. The primary use case is for implementing -- RecordInstance, which does this "threading" for record fields. -- This machinery does, crucially, depend on child types (i.e. the type -- of a record field) having a Display instance. class GDisplay1 f gdisplayBuilder1 :: GDisplay1 f => f p -> Builder gdisplayBuilderDefault :: (Generic a, GDisplay1 (Rep a)) => a -> Builder -- | This wrapper allows you to create an Display instance for a -- record, so long as all the record fields have a Display -- instance as well. -- --

Example

-- --
--   data Password = Password
--    deriving Display
--      via (OpaqueInstance "[REDACTED]" Password)
--   
-- --
--   data MyRecord =
--      MyRecord
--        { fieldA :: String
--        , fieldB :: Maybe String
--        , fieldC :: Int
--        , pword :: Password
--        }
--        deriving stock (Generic)
--        deriving (Display) via (RecordInstance MyRecord)
--   
-- --
--   putStrLn . Data.Text.unpack . display $ MyRecord "hello" (Just "world") 22 Password
--   
-- --
--   MyRecord
--     { fieldA = hello
--     , fieldB = Just world
--     , fieldC = 22
--     , pword = [REDACTED]
--     }
--   
newtype RecordInstance a RecordInstance :: a -> RecordInstance a [unDisplayProduct] :: RecordInstance a -> a -- | This type family is lifted from generic-data. We use it to prevent the -- user from deriving a RecordInstance for sum types type family HasSum f class Assert (pred :: Bool) (msg :: ErrorMessage) -- | Constraint to prevent misuse of RecordInstance deriving via -- mechanism. -- --

Example

-- --
--   data MySum = A | B | C deriving stock (Generic) deriving (Display) via (RecordInstance MySum)
--   
-- --
--   • 🚫 Cannot derive Display instance for MySum via RecordInstance due to sum type
--     💡 Sum types should use a manual instance or derive one via ShowInstance.
--   • When deriving the instance for (Display MySum)
--   
type AssertNoSumRecordInstance (constraint :: Type -> Constraint) a = Assert (Not (HasSum (Rep a))) ('Text "🚫 Cannot derive " ':<>: 'ShowType constraint ':<>: 'Text " instance for " ':<>: 'ShowType a ':<>: 'Text " via RecordInstance due to sum type" ':$$: 'Text "💡 Sum types should use a manual instance or derive one via ShowInstance.") instance (Data.Text.Display.Generic.AssertNoSumRecordInstance Data.Text.Display.Core.Display a, GHC.Generics.Generic a, Data.Text.Display.Generic.GDisplay1 (GHC.Generics.Rep a)) => Data.Text.Display.Core.Display (Data.Text.Display.Generic.RecordInstance a) instance Data.Text.Display.Generic.Assert 'GHC.Types.True msg instance ((TypeError ...) GHC.Types.~ '()) => Data.Text.Display.Generic.Assert 'GHC.Types.False msg instance GHC.Generics.Generic a => GHC.Generics.Generic (Data.Text.Display.Generic.RecordInstance a) instance Data.Text.Display.Generic.GDisplay1 GHC.Generics.V1 instance Data.Text.Display.Generic.GDisplay1 GHC.Generics.U1 instance Data.Text.Display.Core.Display c => Data.Text.Display.Generic.GDisplay1 (GHC.Generics.K1 i c) instance (GHC.Generics.Constructor c, Data.Text.Display.Generic.GDisplay1 f) => Data.Text.Display.Generic.GDisplay1 (GHC.Generics.M1 GHC.Generics.C c f) instance (GHC.Generics.Selector s, Data.Text.Display.Generic.GDisplay1 f) => Data.Text.Display.Generic.GDisplay1 (GHC.Generics.M1 GHC.Generics.S s f) instance Data.Text.Display.Generic.GDisplay1 f => Data.Text.Display.Generic.GDisplay1 (GHC.Generics.M1 GHC.Generics.D s f) instance (Data.Text.Display.Generic.GDisplay1 a, Data.Text.Display.Generic.GDisplay1 b) => Data.Text.Display.Generic.GDisplay1 (a GHC.Generics.:*: b) instance (Data.Text.Display.Generic.GDisplay1 a, Data.Text.Display.Generic.GDisplay1 b) => Data.Text.Display.Generic.GDisplay1 (a GHC.Generics.:+: b) -- | Use display to produce user-facing text module Data.Text.Display -- | Convert a value to a readable Text. -- --

Examples

-- --
--   >>> display 3
--   "3"
--   
-- --
--   >>> display True
--   "True"
--   
display :: Display a => a -> Text -- | A typeclass for user-facing output. class Display a -- | Implement this method to describe how to convert your value to -- Builder. displayBuilder :: Display a => a -> Builder -- | 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 = Builder.fromText $ Text.pack $ Text.singleton c
--     displayList cs = Builder.fromText $ Text.pack $ Text.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`
--   
displayList :: Display a => [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
--   
displayPrec :: Display a => Int -> a -> Builder -- | 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)
--   
newtype ShowInstance (a :: Type) ShowInstance :: a -> ShowInstance (a :: Type) -- | 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]"
--   
newtype OpaqueInstance (str :: Symbol) (a :: Type) Opaque :: a -> OpaqueInstance (str :: Symbol) (a :: Type) -- | This wrapper allows you to create an Display instance for a -- record, so long as all the record fields have a Display -- instance as well. -- --

Example

-- --
--   data Password = Password
--    deriving Display
--      via (OpaqueInstance "[REDACTED]" Password)
--   
-- --
--   data MyRecord =
--      MyRecord
--        { fieldA :: String
--        , fieldB :: Maybe String
--        , fieldC :: Int
--        , pword :: Password
--        }
--        deriving stock (Generic)
--        deriving (Display) via (RecordInstance MyRecord)
--   
-- --
--   putStrLn . Data.Text.unpack . display $ MyRecord "hello" (Just "world") 22 Password
--   
-- --
--   MyRecord
--     { fieldA = hello
--     , fieldB = Just world
--     , fieldC = 22
--     , pword = [REDACTED]
--     }
--   
newtype RecordInstance a RecordInstance :: a -> RecordInstance a [unDisplayProduct] :: RecordInstance a -> a -- | 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. displayParen :: Bool -> Builder -> Builder