Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal module defining the core machinery of configurable pretty-printing.
We introduce an internal module, because most users won't need stuff like
DefaultPrettyBy
, so
it doesn't make much sense to export that from the top-level module. But
DefaultPrettyBy
can
still can be useful occasionally and there are some docs explaining details of the implementation
(see e.g.
DispatchPrettyDefaultBy
), hence it's exported from here.
Versioning is not affected by the fact that the module is called "Internal", i.e. we track changes using the usual PVP.
Synopsis
-
class
PrettyBy
config a
where
- prettyBy :: config -> a -> Doc ann
- prettyListBy :: config -> [a] -> Doc ann
- type family HasPrettyDefaults config :: Bool
-
newtype
IgnorePrettyConfig
a =
IgnorePrettyConfig
{
- unIgnorePrettyConfig :: a
- data AttachPrettyConfig config a = AttachPrettyConfig !config !a
- withAttachPrettyConfig :: config -> (( forall a. a -> AttachPrettyConfig config a) -> r) -> r
- defaultPrettyFunctorBy :: ( Functor f, Pretty (f ( AttachPrettyConfig config a))) => config -> f a -> Doc ann
- defaultPrettyBifunctorBy :: ( Bifunctor f, Pretty (f ( AttachPrettyConfig config a) ( AttachPrettyConfig config b))) => config -> f a b -> Doc ann
- type family StarsOfHead (target :: Symbol ) (a :: Type ) :: Type where ...
-
class
StarsOfHead
target a ~ k =>
DispatchDefaultFor
target k config a
where
- dispatchDefaultFor :: config -> a -> Doc ann
-
class
DispatchDefaultFor
target (
StarsOfHead
target a) config a =>
DefaultFor
target config a
where
- defaultFor :: config -> a -> Doc ann
- data AttachDefaultPrettyConfig config a = AttachDefaultPrettyConfig !config !a
-
class
DefaultPrettyBy
config a
where
- defaultPrettyBy :: config -> a -> Doc ann
- defaultPrettyListBy :: config -> [a] -> Doc ann
-
class
NonDefaultPrettyBy
config a
where
- nonDefaultPrettyBy :: config -> a -> Doc ann
- nonDefaultPrettyListBy :: config -> [a] -> Doc ann
- type PrettyDefaultBy config = DispatchPrettyDefaultBy ( NonStuckHasPrettyDefaults config) config
-
newtype
PrettyCommon
a =
PrettyCommon
{
- unPrettyCommon :: a
- type family ThrowOnStuck err (b :: Bool ) :: Bool where ...
- type family HasPrettyDefaultsStuckError config :: Bool where ...
- type NonStuckHasPrettyDefaults config = ThrowOnStuck ( HasPrettyDefaultsStuckError config) ( HasPrettyDefaults config)
-
class
HasPrettyDefaults
config ~ b =>
DispatchPrettyDefaultBy
(b ::
Bool
) config a
where
- dispatchPrettyDefaultBy :: config -> a -> Doc ann
- dispatchPrettyDefaultListBy :: config -> [a] -> Doc ann
-
newtype
PrettyAny
a =
PrettyAny
{
- unPrettyAny :: a
Documentation
class PrettyBy config a where Source #
A class for pretty-printing values in a configurable manner.
A basic example:
>>>
data Case = UpperCase | LowerCase
>>>
data D = D
>>>
instance PrettyBy Case D where prettyBy UpperCase D = "D"; prettyBy LowerCase D = "d"
>>>
prettyBy UpperCase D
D>>>
prettyBy LowerCase D
d
The library provides instances for common types like
Integer
or
Bool
, so you can't define
your own
PrettyBy SomeConfig Integer
instance. And for the same reason you should not define
instances like
PrettyBy SomeAnotherConfig a
for universally quantified
a
, because such an
instance would overlap with the existing ones. Take for example
>>>
data ViaShow = ViaShow
>>>
instance Show a => PrettyBy ViaShow a where prettyBy ViaShow = pretty . show
with such an instance
prettyBy ViaShow (1 :: Int)
throws an error about overlapping instances:
• Overlapping instances for PrettyBy ViaShow Int arising from a use of ‘prettyBy’ Matching instances: instance PrettyDefaultBy config Int => PrettyBy config Int instance [safe] Show a => PrettyBy ViaShow a
There's a
newtype
provided specifically for the purpose of defining a
PrettyBy
instance for
any
a
:
PrettyAny
. Read its docs for details on when you might want to use it.
The
PrettyBy
instance for common types is defined in a way that allows to override default
pretty-printing behaviour, read the docs of
HasPrettyDefaults
for details.
Nothing
prettyBy :: config -> a -> Doc ann Source #
Pretty-print a value of type
a
the way a
config
specifies it.
The default implementation of
prettyBy
is in terms of
pretty
,
defaultPrettyFunctorBy
or
defaultPrettyBifunctorBy
depending on the kind of the data type that you're providing
an instance for. For example, the default implementation of
prettyBy
for a monomorphic type
is going to be "ignore the config and call
pretty
over the value":
>>>
newtype N = N Int deriving newtype (Pretty)
>>>
instance PrettyBy () N
>>>
prettyBy () (N 42)
42
The default implementation of
prettyBy
for a
Functor
is going to be in terms of
defaultPrettyFunctorBy
:
>>>
newtype N a = N a deriving stock (Functor) deriving newtype (Pretty)
>>>
instance PrettyBy () a => PrettyBy () (N a)
>>>
prettyBy () (N (42 :: Int))
42
It's fine for the data type to have a phantom parameter as long as the data type is still a
Functor
(i.e. the parameter has to be of kind
Type
). Then
defaultPrettyFunctorBy
is used
again:
>>>
newtype N a = N Int deriving stock (Functor) deriving newtype (Pretty)
>>>
instance PrettyBy () (N b)
>>>
prettyBy () (N 42)
42
If the data type has a single parameter of any other kind, then it's not a functor and so
like in the monomorphic case
pretty
is used:
>>>
newtype N (b :: Bool) = N Int deriving newtype (Pretty)
>>>
instance PrettyBy () (N b)
>>>
prettyBy () (N 42)
42
Same applies to a data type with two parameters: if both the parameters are of kind
Type
,
then the data type is assumed to be a
Bifunctor
and hence
defaultPrettyBifunctorBy
is
used. If the right parameter is of kind
Type
and the left parameter is of any other kind,
then we fallback to assuming the data type is a
Functor
and defining
prettyBy
as
defaultPrettyFunctorBy
. If both the parameters are not of kind
Type
, we fallback to
implementing
prettyBy
in terms of
pretty
like in the monomorphic case.
Note that in all those cases a
Pretty
instance for the data type has to already exist,
so that we can derive a
PrettyBy
one in terms of it. If it doesn't exist or if your data
type is not supported (for example, if it has three or more parameters of kind
Type
), then
you'll need to provide the implementation manually.
default prettyBy :: DefaultFor "prettyBy" config a => config -> a -> Doc ann Source #
prettyListBy :: config -> [a] -> Doc ann Source #
prettyListBy
is used to define the default
PrettyBy
instance for
[a]
and
NonEmpty a
.
In normal circumstances only the
prettyBy
function is used.
The default implementation of
prettyListBy
is in terms of
defaultPrettyFunctorBy
.
default prettyListBy :: config -> [a] -> Doc ann Source #
Instances
PrettyDefaultBy config Char => PrettyBy config Char Source # |
By default a
|
PrettyDefaultBy config Text => PrettyBy config Text Source # |
An instance for lazy
|
PrettyDefaultBy config Text => PrettyBy config Text Source # |
Automatically converts all newlines to
|
PrettyDefaultBy config Double => PrettyBy config Double Source # |
|
PrettyDefaultBy config Float => PrettyBy config Float Source # |
|
PrettyDefaultBy config Word64 => PrettyBy config Word64 Source # | |
PrettyDefaultBy config Word32 => PrettyBy config Word32 Source # | |
PrettyDefaultBy config Word16 => PrettyBy config Word16 Source # | |
PrettyDefaultBy config Word8 => PrettyBy config Word8 Source # | |
PrettyDefaultBy config Word => PrettyBy config Word Source # | |
PrettyDefaultBy config Int64 => PrettyBy config Int64 Source # | |
PrettyDefaultBy config Int32 => PrettyBy config Int32 Source # | |
PrettyDefaultBy config Int16 => PrettyBy config Int16 Source # | |
PrettyDefaultBy config Int8 => PrettyBy config Int8 Source # | |
PrettyDefaultBy config Int => PrettyBy config Int Source # |
|
PrettyDefaultBy config Integer => PrettyBy config Integer Source # |
|
PrettyDefaultBy config Natural => PrettyBy config Natural Source # |
|
PrettyDefaultBy config Bool => PrettyBy config Bool Source # |
|
PrettyDefaultBy config () => PrettyBy config () Source # |
The argument is not used:
|
Defined in Text.PrettyBy.Internal |
|
PrettyDefaultBy config Void => PrettyBy config Void Source # |
|
PrettyDefaultBy config a => PrettyBy config ( PrettyCommon a) Source # | |
Defined in Text.PrettyBy.Internal prettyBy :: config -> PrettyCommon a -> Doc ann Source # prettyListBy :: config -> [ PrettyCommon a] -> Doc ann Source # |
|
Pretty a => PrettyBy config ( IgnorePrettyConfig a) Source # |
|
Defined in Text.PrettyBy.Internal prettyBy :: config -> IgnorePrettyConfig a -> Doc ann Source # prettyListBy :: config -> [ IgnorePrettyConfig a] -> Doc ann Source # |
|
PrettyDefaultBy config ( Maybe a) => PrettyBy config ( Maybe a) Source # |
By default a
|
PrettyDefaultBy config ( NonEmpty a) => PrettyBy config ( NonEmpty a) Source # |
|
PrettyDefaultBy config [a] => PrettyBy config [a] Source # |
|
Defined in Text.PrettyBy.Internal |
|
PrettyDefaultBy config ( Identity a) => PrettyBy config ( Identity a) Source # |
|
PrettyDefaultBy config (a, b) => PrettyBy config (a, b) Source # |
|
Defined in Text.PrettyBy.Internal |
|
PrettyDefaultBy config ( Const a b) => PrettyBy config ( Const a b) Source # |
Non-polykinded, because
|
PrettyDefaultBy config (a, b, c) => PrettyBy config (a, b, c) Source # |
|
Defined in Text.PrettyBy.Internal |
type family HasPrettyDefaults config :: Bool Source #
Determines whether a pretty-printing config allows default pretty-printing for types that support it. I.e. it's possible to create a new config and get access to pretty-printing for all types supporting default pretty-printing just by providing the right type instance. Example:
>>>
data DefCfg = DefCfg
>>>
type instance HasPrettyDefaults DefCfg = 'True
>>>
prettyBy DefCfg (['a', 'b', 'c'], (1 :: Int), Just True)
(abc, 1, True)
The set of types supporting default pretty-printing is determined by the
prettyprinter
library: whatever
there
has a
Pretty
instance also supports default pretty-printing
in this library and the behavior of
pretty x
and
prettyBy config_with_defaults x
must
be identical when
x
is one of such types.
It is possible to override default pretty-printing. For this you need to specify that
HasPrettyDefaults
is
'False
for your config and then define a
NonDefaultPrettyBy config
instance for each of the types supporting default pretty-printing that you want to pretty-print
values of. Note that once
HasPrettyDefaults
is specified to be
'False
,
all defaults are lost
for your config, so you can't override default pretty-printing for one
type and keep the defaults for all the others. I.e. if you have
>>>
data NonDefCfg = NonDefCfg
>>>
type instance HasPrettyDefaults NonDefCfg = 'False
then you have no defaults available and an attempt to pretty-print a value of a type supporting default pretty-printing
prettyBy NonDefCfg True
results in a type error:
• No instance for (NonDefaultPrettyBy NonDef Bool) arising from a use of ‘prettyBy’
As the error suggests you need to provide a
NonDefaultPrettyBy
instance explicitly:
>>>
instance NonDefaultPrettyBy NonDefCfg Bool where nonDefaultPrettyBy _ b = if b then "t" else "f"
>>>
prettyBy NonDefCfg True
t
It is also possible not to provide any implementation for
nonDefaultPrettyBy
, in which case
it defaults to being the default pretty-printing for the given type. This can be useful to
recover default pretty-printing for types pretty-printing of which you don't want to override:
>>>
instance NonDefaultPrettyBy NonDefCfg Int
>>>
prettyBy NonDefCfg (42 :: Int)
42
Look into
test/NonDefault.hs
for an extended example.
We could give the user more fine-grained control over what defaults to override instead of requiring to explicitly provide all the instances whenever there's a need to override any default behavior, but that would complicate the library even more, so we opted for not doing that at the moment.
Note that you can always override default behavior by wrapping a type in
newtype
and
providing a
PrettyBy config_name
instance for that
newtype
.
Also note that if you want to extend the set of types supporting default pretty-printing
it's not enough to provide a
Pretty
instance for your type (such logic is hardly expressible
in present day Haskell). Read the docs of
DefaultPrettyBy
for how to extend the set of types
supporting default pretty-printing.
Instances
type HasPrettyDefaults () Source # |
|
Defined in Text.PrettyBy.Internal |
newtype IgnorePrettyConfig a Source #
A newtype wrapper around
a
whose point is to provide a
PrettyBy config
instance
for anything that has a
Pretty
instance.
Instances
Pretty a => PrettyBy config ( IgnorePrettyConfig a) Source # |
|
Defined in Text.PrettyBy.Internal prettyBy :: config -> IgnorePrettyConfig a -> Doc ann Source # prettyListBy :: config -> [ IgnorePrettyConfig a] -> Doc ann Source # |
data AttachPrettyConfig config a Source #
A config together with some value. The point is to provide a
Pretty
instance
for anything that has a
PrettyBy config
instance.
AttachPrettyConfig !config !a |
Instances
PrettyBy config a => Pretty ( AttachPrettyConfig config a) Source # |
|
Defined in Text.PrettyBy.Internal pretty :: AttachPrettyConfig config a -> Doc ann Source # prettyList :: [ AttachPrettyConfig config a] -> Doc ann Source # |
withAttachPrettyConfig :: config -> (( forall a. a -> AttachPrettyConfig config a) -> r) -> r Source #
Pass
AttachPrettyConfig config
to the continuation.
defaultPrettyFunctorBy :: ( Functor f, Pretty (f ( AttachPrettyConfig config a))) => config -> f a -> Doc ann Source #
defaultPrettyBifunctorBy :: ( Bifunctor f, Pretty (f ( AttachPrettyConfig config a) ( AttachPrettyConfig config b))) => config -> f a b -> Doc ann Source #
type family StarsOfHead (target :: Symbol ) (a :: Type ) :: Type where ... Source #
Return the longest sequence of
Type
in the kind (right-to-left) of the head of an application.
(but no longer than
Type -> Type -> Type
, because we can't support longer ones in
DispatchDefaultFor
).
StarsOfHead target ((f :: Type -> Type -> Type -> Type ) a b c) = TypeError (((' Text "Automatic derivation of \8216" :<>: ' Text target) :<>: ' Text "\8217") :$$: ' Text "is not possible for data types that receive three and more arguments of kind \8216Type\8217") | |
StarsOfHead _ ((f :: k -> Type -> Type -> Type ) a b c) = Type -> Type -> Type | |
StarsOfHead _ ((f :: Type -> Type -> Type ) a b) = Type -> Type -> Type | |
StarsOfHead _ ((f :: k -> Type -> Type ) a b) = Type -> Type | |
StarsOfHead _ ((f :: Type -> Type ) a) = Type -> Type | |
StarsOfHead _ ((f :: k -> Type ) a) = Type | |
StarsOfHead _ a = Type |
class StarsOfHead target a ~ k => DispatchDefaultFor target k config a where Source #
This allows us to have different default implementations for
prettyBy
and
defaultPrettyBy
depending on whether
a
is a monomorphic type or a
Functor
or a
Bifunctor
. Read the docs of
prettyBy
for details.
dispatchDefaultFor :: config -> a -> Doc ann Source #
Instances
( StarsOfHead target a ~ Type , Pretty a) => DispatchDefaultFor target Type config a Source # | |
Defined in Text.PrettyBy.Internal dispatchDefaultFor :: config -> a -> Doc ann Source # |
|
( StarsOfHead target fab ~ (k1 -> k2 -> Type ), fab ~ f a b, Bifunctor f, Pretty (f ( AttachPrettyConfig config a) ( AttachPrettyConfig config b))) => DispatchDefaultFor target (k1 -> k2 -> Type ) config fab Source # | |
Defined in Text.PrettyBy.Internal dispatchDefaultFor :: config -> fab -> Doc ann Source # |
|
( StarsOfHead target fa ~ (k -> Type ), fa ~ f a, Functor f, Pretty (f ( AttachPrettyConfig config a))) => DispatchDefaultFor target (k -> Type ) config fa Source # | |
Defined in Text.PrettyBy.Internal dispatchDefaultFor :: config -> fa -> Doc ann Source # |
class DispatchDefaultFor target ( StarsOfHead target a) config a => DefaultFor target config a where Source #
Introducing a class just for the nice name of the method and in case the defaulting machinery somehow blows up in the user's face.
defaultFor :: config -> a -> Doc ann Source #
Instances
DispatchDefaultFor target ( StarsOfHead target a) config a => DefaultFor target config a Source # | |
Defined in Text.PrettyBy.Internal defaultFor :: config -> a -> Doc ann Source # |
data AttachDefaultPrettyConfig config a Source #
Same as
AttachPrettyConfig
, but for providing a
Pretty
instance for anything that has
a
DefaultPrettyBy
instance. Needed for the default implementation of
defaultPrettyListBy
.
AttachDefaultPrettyConfig !config !a |
Instances
DefaultPrettyBy config a => Pretty ( AttachDefaultPrettyConfig config a) Source # | |
Defined in Text.PrettyBy.Internal pretty :: AttachDefaultPrettyConfig config a -> Doc ann Source # prettyList :: [ AttachDefaultPrettyConfig config a] -> Doc ann Source # |
class DefaultPrettyBy config a where Source #
A class for pretty-printing values is some default manner. Basic example:
>>>
data D = D
>>>
instance PrettyBy () D where prettyBy () D = "D"
>>>
defaultPrettyBy () (Just D)
D
DefaultPrettyBy
and
PrettyBy
are mutually recursive in a sense:
PrettyBy
delegates
to
DefaultPrettyBy
(provided the config supports defaults) when given a value of a type
supporting default pretty-printing and
DefaultPrettyBy
delegates back to
PrettyBy
for
elements of a polymorphic container.
It is possible to extend the set of types supporting default pretty-printing. If you have a
newtype
wrapping a type that already supports default pretty-printing, then "registering"
that
newtype
amounts to making a standalone newtype-deriving declaration:
>>>
newtype AlsoInt = AlsoInt Int
>>>
deriving newtype instance PrettyDefaultBy config Int => PrettyBy config AlsoInt
>>>
prettyBy () (AlsoInt 42)
42
Note that you have to use standalone deriving as
newtype AlsoInt = AlsoInt Int deriving newtype (PrettyBy config)
doesn't please GHC.
It's also good practice to preserve coherence of
Pretty
and
PrettyBy
, so I'd also add
deriving newtype (Pretty)
to the definition of
AlsoInt
, even though it's not necessary.
When you want to extend the set of types supporting default pretty-printing with a data type
that is a
data
rather than a
newtype
, you can directly implement
DefaultPrettyBy
and
and via-derive
PrettyBy
:
>>>
data D = D
>>>
instance DefaultPrettyBy config D where defaultPrettyBy _ D = "D"
>>>
deriving via PrettyCommon D instance PrettyDefaultBy config D => PrettyBy config D
>>>
prettyBy () D
D
But since it's best to preserve coherence of
Pretty
and
PrettyBy
for types supporting
default pretty-printing, it's recommended (not mandatory) to define a
Pretty
instance and
anyclass-derive
DefaultPrettyBy
in terms of it:
>>>
data D = D
>>>
instance Pretty D where pretty D = "D"
>>>
instance DefaultPrettyBy config D
>>>
deriving via PrettyCommon D instance PrettyDefaultBy config D => PrettyBy config D
>>>
prettyBy () [D, D, D]
[D, D, D]
Note that
DefaultPrettyBy
is specifically designed to handle
all
configs in its instances,
i.e. you only specify a data type in a
DefaultPrettyBy
instance and leave
config
universally
quantified. This is because default pretty-printing behavior should be the same for all configs
supporting default pretty-printing (it's the default after all). If you want to override the
defaults, read the docs of
HasPrettyDefaults
.
Since
config
in a
DefaultPrettyBy
instance is meant to be universally quantified,
defaultPrettyBy
(the main method of
DefaultPrettyBy
) has to ignore the config in the
monomorphic case as it can't use it in any way anyway, i.e. in the monomorphic case
defaultPrettyBy
has the exact same info as simple
pretty
, which is another reason to
anyclass-derive
DefaultPrettyBy
in terms of
Pretty
.
Like in the case of
prettyBy
, the default implementation of
defaultPrettyBy
for a
Functor
is
defaultPrettyFunctorBy
(and for a
Bifunctor
--
defaultPrettyBifunctorBy
):
>>>
data Twice a = Twice a a deriving stock (Functor)
>>>
instance Pretty a => Pretty (Twice a) where pretty (Twice x y) = pretty x <+> "&" <+> pretty y
>>>
instance PrettyBy config a => DefaultPrettyBy config (Twice a)
>>>
deriving via PrettyCommon (Twice a) instance PrettyDefaultBy config (Twice a) => PrettyBy config (Twice a)
>>>
prettyBy () (Twice True False)
True & False
Since preserving coherence of
Pretty
and
PrettyBy
is only a good practice and not
mandatory, it's fine not to provide an instance for
Pretty
. Then a
DefaultPrettyBy
can be
implemented directly:
>>>
data Twice a = Twice a a
>>>
instance PrettyBy config a => DefaultPrettyBy config (Twice a) where defaultPrettyBy config (Twice x y) = prettyBy config x <+> "&" <+> prettyBy config y
>>>
deriving via PrettyCommon (Twice a) instance PrettyDefaultBy config (Twice a) => PrettyBy config (Twice a)
>>>
prettyBy () (Twice True False)
True & False
But make sure that if both a
Pretty
and a
DefaultPrettyBy
instances exist, then they're in
sync.
Nothing
defaultPrettyBy :: config -> a -> Doc ann Source #
Pretty-print a value of type
a
in some default manner.
The default implementation works equally to the one of
prettyBy
.
default defaultPrettyBy :: DefaultFor "defaultPrettyBy" config a => config -> a -> Doc ann Source #
defaultPrettyListBy :: config -> [a] -> Doc ann Source #
defaultPrettyListBy
to
prettyListBy
is what
defaultPrettyBy
to
prettyBy
.
The default implementation is "pretty-print the spine of a list the way
pretty
does that
and pretty-print the elements using
defaultPrettyBy
".
default defaultPrettyListBy :: config -> [a] -> Doc ann Source #
Instances
class NonDefaultPrettyBy config a where Source #
A class for overriding default pretty-printing behavior for types having it.
Read the docs of
HasPrettyDefaults
for how to use the class.
Nothing
nonDefaultPrettyBy :: config -> a -> Doc ann Source #
Pretty-print a value of a type supporting default pretty-printing in a possibly
non-default way. The "possibly" is due to
nonDefaultPrettyBy
having a default
implementation as
defaultPrettyBy
. See docs for
HasPrettyDefaults
for details.
default nonDefaultPrettyBy :: DefaultPrettyBy config a => config -> a -> Doc ann Source #
nonDefaultPrettyListBy :: config -> [a] -> Doc ann Source #
nonDefaultPrettyListBy
to
prettyListBy
is what
nonDefaultPrettyBy
to
prettyBy
.
Analogously, the default implementation is
defaultPrettyListBy
.
default nonDefaultPrettyListBy :: DefaultPrettyBy config a => config -> [a] -> Doc ann Source #
type PrettyDefaultBy config = DispatchPrettyDefaultBy ( NonStuckHasPrettyDefaults config) config Source #
PrettyDefaultBy config a
is the same thing as
PrettyBy config a
, when
a
supports
default pretty-printing. Thus
PrettyDefaultBy config a
and
PrettyBy config a
are
interchangeable constraints for such types, but the latter throws an annoying
"this makes type inference for inner bindings fragile" warning, unlike the former.
PrettyDefaultBy config a
reads as "
a
supports default pretty-printing and can be
pretty-printed via
config
in either default or non-default manner depending on whether
config
supports default pretty-printing".
newtype PrettyCommon a Source #
A newtype wrapper defined for its
PrettyBy
instance that allows to via-derive a
PrettyBy
instance for a type supporting default pretty-printing.
Instances
PrettyDefaultBy config a => PrettyBy config ( PrettyCommon a) Source # | |
Defined in Text.PrettyBy.Internal prettyBy :: config -> PrettyCommon a -> Doc ann Source # prettyListBy :: config -> [ PrettyCommon a] -> Doc ann Source # |
type family ThrowOnStuck err (b :: Bool ) :: Bool where ... Source #
Throw
err
when
b
is stuck.
ThrowOnStuck _ ' True = ' True | |
ThrowOnStuck _ ' False = ' False | |
ThrowOnStuck err _ = err |
type family HasPrettyDefaultsStuckError config :: Bool where ... Source #
The error thrown when
HasPrettyDefaults config
is stuck.
HasPrettyDefaultsStuckError config = TypeError (((((((((((((' Text "No \8217HasPrettyDefaults\8217 is specified for " :<>: ' ShowType config) :$$: ' Text "Either you're trying to derive an instance, in which case you have to use") :$$: ' Text " standalone deriving and need to explicitly put a \8216PrettyDefaultBy config\8217") :$$: ' Text " constraint in the instance context for each type in your data type") :$$: ' Text " that supports default pretty-printing") :$$: ' Text "Or you're trying to pretty-print a value of a type supporting default") :$$: ' Text " pretty-printing using a config, for which \8216HasPrettyDefaults\8217 is not specified.") :$$: ' Text " If the config is a bound type variable, then you need to add") :$$: ' Text " \8216HasPrettyDefaults <config_variable_name> ~ 'True\8217") :$$: ' Text " to the context.") :$$: ' Text " If the config is a data type, then you need to add") :$$: ' Text " \8216type instance HasPrettyDefaults <config_name> = 'True\8217") :$$: ' Text " at the top level.") |
type NonStuckHasPrettyDefaults config = ThrowOnStuck ( HasPrettyDefaultsStuckError config) ( HasPrettyDefaults config) Source #
A version of
HasPrettyDefaults
that is never stuck: it either immediately evaluates
to a
Bool
or fails with a
TypeError
.
class HasPrettyDefaults config ~ b => DispatchPrettyDefaultBy (b :: Bool ) config a where Source #
DispatchPrettyDefaultBy
is a class for dispatching on
HasPrettyDefaults config
:
if it's
'True
, then
dispatchPrettyDefaultBy
is instantiated as
defaultPrettyBy
,
otherwise as
nonDefaultPrettyBy
(and similarly for
dispatchPrettyDefaultListBy
).
I.e. depending on whether a config allows to pretty-print values using default
pretty-printing, either the default or non-default pretty-printing strategy is used.
dispatchPrettyDefaultBy :: config -> a -> Doc ann Source #
dispatchPrettyDefaultListBy :: config -> [a] -> Doc ann Source #
Instances
( HasPrettyDefaults config ~ ' False , NonDefaultPrettyBy config a) => DispatchPrettyDefaultBy ' False config a Source # | |
Defined in Text.PrettyBy.Internal dispatchPrettyDefaultBy :: config -> a -> Doc ann Source # dispatchPrettyDefaultListBy :: config -> [a] -> Doc ann Source # |
|
( HasPrettyDefaults config ~ ' True , DefaultPrettyBy config a) => DispatchPrettyDefaultBy ' True config a Source # | |
Defined in Text.PrettyBy.Internal dispatchPrettyDefaultBy :: config -> a -> Doc ann Source # dispatchPrettyDefaultListBy :: config -> [a] -> Doc ann Source # |
A
newtype
wrapper around
a
provided for the purporse of defining
PrettyBy
instances
handling any
a
. For example you can wrap values with the
PrettyAny
constructor directly
like in this last line of
>>>
data ViaShow = ViaShow
>>>
instance Show a => PrettyBy ViaShow (PrettyAny a) where prettyBy ViaShow = pretty . show . unPrettyAny
>>>
prettyBy ViaShow $ PrettyAny True
True
or you can use the type to via-derive instances:
>>>
data D = D deriving stock (Show)
>>>
deriving via PrettyAny D instance PrettyBy ViaShow D
>>>
prettyBy ViaShow D
D
One important use case is handling sum-type configs. For example having two configs you can
define their sum and derive
PrettyBy
for the unified config in terms of its components:
>>>
data UpperCase = UpperCase
>>>
data LowerCase = LowerCase
>>>
data Case = CaseUpperCase UpperCase | CaseLowerCase LowerCase
>>>
instance (PrettyBy UpperCase a, PrettyBy LowerCase a) => PrettyBy Case (PrettyAny a) where prettyBy (CaseUpperCase upper) = prettyBy upper . unPrettyAny; prettyBy (CaseLowerCase lower) = prettyBy lower . unPrettyAny
Then having a data type implementing both
PrettyBy UpperCase
and
PrettyBy LowerCase
you can
derive
PrettyBy Case
for that data type:
>>>
data D = D
>>>
instance PrettyBy UpperCase D where prettyBy UpperCase D = "D"
>>>
instance PrettyBy LowerCase D where prettyBy LowerCase D = "d"
>>>
deriving via PrettyAny D instance PrettyBy Case D
>>>
prettyBy UpperCase D
D>>>
prettyBy LowerCase D
d
Look into
test/Universal.hs
for an extended example.
PrettyAny | |
|