text-display-0.0.5.0: A typeclass for user-facing output
Copyright© Jonathan Lorimer 2023
LicenseMIT
Maintainerjonathanlorimer@pm.me
Stabilitystable
Safe HaskellNone
LanguageHaskell2010

Data.Text.Display.Generic

Description

Generic machinery for automatically deriving display instances for record types

Synopsis

Documentation

class GDisplay1 f where Source #

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.

Since: 0.0.5.0

Methods

gdisplayBuilder1 :: f p -> Builder Source #

Instances

Instances details
GDisplay1 (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Text.Display.Generic

GDisplay1 (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Text.Display.Generic

(GDisplay1 a, GDisplay1 b) => GDisplay1 (a :*: b) Source # 
Instance details

Defined in Data.Text.Display.Generic

Methods

gdisplayBuilder1 :: (a :*: b) p -> Builder Source #

(GDisplay1 a, GDisplay1 b) => GDisplay1 (a :+: b) Source # 
Instance details

Defined in Data.Text.Display.Generic

Methods

gdisplayBuilder1 :: (a :+: b) p -> Builder Source #

Display c => GDisplay1 (K1 i c :: Type -> Type) Source #

This is the most important instance, it can be considered as the "base case". It requires a non-generic Display instance. All this generic machinery can be conceptualized as distributing these displayBuilder calls across a product type.

Instance details

Defined in Data.Text.Display.Generic

Methods

gdisplayBuilder1 :: K1 i c p -> Builder Source #

(Constructor c, GDisplay1 f) => GDisplay1 (M1 C c f) Source # 
Instance details

Defined in Data.Text.Display.Generic

Methods

gdisplayBuilder1 :: M1 C c f p -> Builder Source #

GDisplay1 f => GDisplay1 (M1 D s f) Source # 
Instance details

Defined in Data.Text.Display.Generic

Methods

gdisplayBuilder1 :: M1 D s f p -> Builder Source #

(Selector s, GDisplay1 f) => GDisplay1 (M1 S s f) Source # 
Instance details

Defined in Data.Text.Display.Generic

Methods

gdisplayBuilder1 :: M1 S s f p -> Builder Source #

newtype RecordInstance a Source #

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]
  }

Since: 0.0.5.0

Constructors

RecordInstance 

Fields

Instances

Instances details
Generic a => Generic (RecordInstance a) Source # 
Instance details

Defined in Data.Text.Display.Generic

Associated Types

type Rep (RecordInstance a) :: Type -> Type #

(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

type Rep (RecordInstance a) Source # 
Instance details

Defined in Data.Text.Display.Generic

type Rep (RecordInstance a) = Rep a

type family HasSum f where ... Source #

This type family is lifted from generic-data. We use it to prevent the user from deriving a RecordInstance for sum types

Since: 0.0.5.0

Equations

HasSum V1 = 'False 
HasSum U1 = 'False 
HasSum (K1 i c) = 'False 
HasSum (M1 i c f) = HasSum f 
HasSum (f :*: g) = HasSum f || HasSum g 
HasSum (f :+: g) = 'True 

class Assert (pred :: Bool) (msg :: ErrorMessage) Source #

Instances

Instances details
(TypeError msg :: ()) ~ '() => Assert 'False msg Source # 
Instance details

Defined in Data.Text.Display.Generic

Assert 'True msg Source # 
Instance details

Defined in Data.Text.Display.Generic

type AssertNoSumRecordInstance (constraint :: Type -> Constraint) a = Assert (Not (HasSum (Rep a))) ((((('Text "\128683 Cannot derive " ':<>: 'ShowType constraint) ':<>: 'Text " instance for ") ':<>: 'ShowType a) ':<>: 'Text " via RecordInstance due to sum type") ':$$: 'Text "\128161 Sum types should use a manual instance or derive one via ShowInstance.") Source #

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)

Since: 0.0.5.0