Copyright | (c) 2020 Kowainik |
---|---|
License | MPL-2.0 |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
The Trial
Data Structure is a Either
-like structure that keeps
events history inside. The data type allows to keep track of the
Fatality
level of each such event entry (Warning
or Error
).
Trial
has two constructors:
Fiasco
: stores the list of events with the explicitFatality
level; at least one event has levelError
Result
: stores the final result and the list of events where each event has implicitFatality
levelWarning
trial
implements the composable interface for creating and combining
values of type Trial
, so the history of all events is stored
inside. Fundamental algebraic instances provide the following main
features:
Semigroup
: take the lastResult
and combine all events.Applicative
: returnFiasco
, if at least one value ifFiasco
, combine all events.Alternative
: return firstResult
, also combine all events for allTrial
s before thisResult
.
Synopsis
- data Trial e a
- type TaggedTrial tag a = Trial tag (tag, a)
- data Fatality
- pattern Warning :: Fatality
- pattern Error :: Fatality
- fiasco :: e -> Trial e a
- fiascos :: NonEmpty e -> Trial e a
- result :: e -> a -> Trial e a
- alt :: Trial e a -> Trial e a -> Trial e a
- isFiasco :: Trial e a -> Bool
- isResult :: Trial e a -> Bool
- whenResult :: Applicative f => x -> Trial e a -> ([e] -> a -> f x) -> f x
- whenResult_ :: Applicative f => Trial e a -> ([e] -> a -> f ()) -> f ()
- whenFiasco :: Applicative f => x -> Trial e a -> ([(Fatality, e)] -> f x) -> f x
- whenFiasco_ :: Applicative f => Trial e a -> ([(Fatality, e)] -> f ()) -> f ()
- pattern FiascoL :: [(Fatality, e)] -> Trial e a
- pattern ResultL :: [e] -> a -> Trial e a
- getTrialInfo :: Trial e a -> ([(Fatality, e)], Maybe a)
- fiascoErrors :: Trial e a -> [e]
- fiascoWarnings :: Trial e a -> [e]
- resultWarnings :: Trial e a -> [e]
- anyWarnings :: Trial e a -> [e]
- dlistToList :: DList a -> [a]
- maybeToTrial :: e -> Maybe a -> Trial e a
- trialToMaybe :: Trial e a -> Maybe a
- eitherToTrial :: Either e a -> Trial e a
- trialToEither :: Monoid e => Trial e a -> Either e a
- withTag :: tag -> Trial tag a -> TaggedTrial tag a
- unTag :: TaggedTrial tag a -> Trial tag a
- fiascoOnEmpty :: (IsString tag, Semigroup tag, Foldable f) => tag -> tag -> f a -> TaggedTrial tag (f a)
- prettyFatality :: (Semigroup str, IsString str) => Fatality -> str
- prettyTrial :: (Show a, Semigroup e, IsString e) => Trial e a -> e
- prettyTrialWith :: (Semigroup e, IsString e) => (a -> String) -> Trial e a -> e
- prettyTaggedTrial :: (Show a, Semigroup e, IsString e) => TaggedTrial e a -> e
- prettyTaggedTrialWith :: (Semigroup e, IsString e) => (a -> String) -> TaggedTrial e a -> e
- data Phase (e :: Type)
- type family (phase :: Phase (e :: Type)) :- field where ...
- type family (phase :: Phase (tag :: Type)) ::- field where ...
Data structures
Trial
is a data type that stores history of all events happened
with a value. In addition, each event is associated with the
Fatality
level that indicates whether the event is fatal or not.
API provided by trial
guarantees the following property:
- If the final value is
Fiasco
, it is either an empty list or a list with at least one event with theFatality
levelError
.
Since: 0.0.0.0
Fiasco (DList (Fatality, e)) | Stores list of events with the explicit |
Result (DList e) a | Store list of events and the final result. |
Instances
Bitraversable Trial Source # | Since: 0.0.0.0 |
Defined in Trial bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Trial a b -> f (Trial c d) # | |
Bifoldable Trial Source # | Since: 0.0.0.0 |
Bifunctor Trial Source # | Since: 0.0.0.0 |
(HasField label r (Trial tag (tag, a)), IsString tag, Semigroup tag, KnownSymbol label) => IsLabel label (r -> Trial tag a) Source # | Convenient instance to convert record fields of type
Since: 0.0.0.0 |
Functor (Trial e) Source # | Since: 0.0.0.0 |
Applicative (Trial e) Source # | Combine two
Since: 0.0.0.0 |
Alternative (Trial e) Source # | Return the first
See Since: 0.0.0.0 |
(Eq e, Eq a) => Eq (Trial e a) Source # | |
(Show e, Show a) => Show (Trial e a) Source # | |
Semigroup (Trial e a) Source # | Combine two Let's create some default values:
And here is how combination of those values look like:
Since: 0.0.0.0 |
type TaggedTrial tag a = Trial tag (tag, a) Source #
In addition to usual Trial
capabilities, TaggedTrial
allows
attaching a tag
to the resulting value, so you can track which event
helped to obtain a value.
Since: 0.0.0.0
Fatality
Severity of the event in history.
Error
: fatal error that led to the finalFiasco
Warning
: non-essential error, which didn't affect the result
You can't create values of type Fatality
, you can only pattern-match
on them. Trial
smart constructors and instances take care of
assigning proper Fatality
values.
Use Warning
and Error
Pattern Synonyms to pattern match on
Fatality
:
>>>
:{
showFatality :: Fatality -> String showFatality Warning = "Warning" showFatality Error = "Error" :}
Since: 0.0.0.0
Instances
Bounded Fatality Source # | |
Enum Fatality Source # | |
Eq Fatality Source # | |
Show Fatality Source # | |
Smart constructors
Combinators
alt :: Trial e a -> Trial e a -> Trial e a infixl 3 Source #
Alternative implementation of the Alternative
instance for
Trial
. Return the first Result
. Otherwise, append two histories in
both Fiasco
s. both Fiasco
s.
>>>
fiasco "No info" `alt` pure 42
Result (fromList []) 42>>>
pure 42 `alt` result "Something" 10
Result (fromList []) 42>>>
fiasco "No info" `alt` fiasco "Some info"
Fiasco (fromList [(E,"No info"),(E,"Some info")])
Since: 0.0.0.0
whenResult :: Applicative f => x -> Trial e a -> ([e] -> a -> f x) -> f x Source #
Applies the given action to Trial
if it is Result
and returns the
value. In case of Fiasco
the default value is returned.
>>>
whenResult "bar" (fiasco "foo") (\es a -> "success!" <$ (print a >> print es))
"bar"
>>>
whenResult "bar" (result "res" 42) (\es a -> "success!" <$ (print a >> print es))
42 ["res"] "success!"
Since: 0.0.0.0
whenResult_ :: Applicative f => Trial e a -> ([e] -> a -> f ()) -> f () Source #
Applies given action to the Trial
content if it is Result
.
Similar to whenResult
but the default value is ()
.
>>>
whenResult_ (fiasco "foo") (\es a -> print a >> print es)
>>>
whenResult_ (result "res" 42) (\es a -> print a >> print es)
42 ["res"]
Since: 0.0.0.0
whenFiasco :: Applicative f => x -> Trial e a -> ([(Fatality, e)] -> f x) -> f x Source #
whenFiasco_ :: Applicative f => Trial e a -> ([(Fatality, e)] -> f ()) -> f () Source #
Applies given action to the Trial
content if it is Fiasco
.
Similar to whenFiasco
but the default value is ()
.
>>>
whenFiasco_ (result "res" 42) print
>>>
whenFiasco_ (fiasco "foo") print
[(E,"foo")]
Since: 0.0.0.0
Work with Lists
Trial
stores list of events as DList
internally for efficient
appending. But when pattern-matching on the final value, it's more
convenient to work directly with lists. FiascoL
and ResultL
are
Pattern Synonyms for working with lists. It's recommended to use them
only once at the end, since conversion from DList
to list takes some
time.
>>>
:{
foo :: Trial String Int -> String foo (FiascoL []) = "Fiasco list is empty" foo (ResultL [] _) = "Result list is empty" foo _ = "Other case" :}
>>>
foo empty
"Fiasco list is empty">>>
foo $ pure 42
"Result list is empty">>>
foo $ result "Something" 42
"Other case"
pattern FiascoL :: [(Fatality, e)] -> Trial e a Source #
Uni-directional Pattern Synonym for Fiasco
that allows
pattern-matching directly on lists.
Since: 0.0.0.0
pattern ResultL :: [e] -> a -> Trial e a Source #
Uni-directional Pattern Synonym for Result
that allows
pattern-matching directly on lists.
Since: 0.0.0.0
fiascoErrors :: Trial e a -> [e] Source #
fiascoWarnings :: Trial e a -> [e] Source #
resultWarnings :: Trial e a -> [e] Source #
anyWarnings :: Trial e a -> [e] Source #
dlistToList :: DList a -> [a] Source #
Helper function to convert DList
to list.
Since: 0.0.0.0
Maybe
combinators
maybeToTrial :: e -> Maybe a -> Trial e a Source #
Convert Maybe
to Trial
but assigning Error
Fatality
when
the value is Nothing
.
>>>
maybeToTrial "No default" (Just 10)
Result (fromList []) 10>>>
maybeToTrial "No default" Nothing
Fiasco (fromList [(E,"No default")])
Functions maybeToTrial
and trialToMaybe
satisfy property:
trialToMaybe
.maybeToTrial
e ≡id
Since: 0.0.0.0
trialToMaybe :: Trial e a -> Maybe a Source #
Either
combinators
eitherToTrial :: Either e a -> Trial e a Source #
Convert Either
to Trial
by assigning Fatality
Warning
to
a Left
value.
>>>
eitherToTrial (Right 42)
Result (fromList []) 42>>>
eitherToTrial (Left "Missing value")
Fiasco (fromList [(E,"Missing value")])
Functions eitherToTrial
and trialToEither
satisfy property:
trialToEither
.eitherToTrial
≡id
Since: 0.0.0.0
Tag
withTag :: tag -> Trial tag a -> TaggedTrial tag a Source #
Tag a Trial
.
>>>
withTag "Answer" $ pure 42
Result (fromList []) ("Answer",42)>>>
withTag "Answer" $ fiasco "No answer"
Fiasco (fromList [(E,"No answer")])
Since: 0.0.0.0
unTag :: TaggedTrial tag a -> Trial tag a Source #
Untag a Trial
by adding a tag
to a history of events.
>>>
unTag $ pure ("Chosen randomly",5)
Result (fromList ["Chosen randomly"]) 5>>>
unTag $ fiasco "No random"
Fiasco (fromList [(E,"No random")])
Since: 0.0.0.0
:: (IsString tag, Semigroup tag, Foldable f) | |
=> tag | Tag |
-> tag | Field name |
-> f a | Container of elements |
-> TaggedTrial tag (f a) |
Tag a value with a given tag, and add a message to events using
tag and a name if the given Foldable
is null
.
When used like this:
fiascoOnEmpty "CLI" "port" someList
it's equivalent to the following:
withTag
"CLI" $ case someList of [] ->fiasco
"No CLI option specified for: port" xs -> pure xs
Since: 0.0.0.0
Pretty printing
prettyFatality :: (Semigroup str, IsString str) => Fatality -> str Source #
prettyTrial :: (Show a, Semigroup e, IsString e) => Trial e a -> e Source #
Colourful pretty-printing of Trial
.
Since: 0.0.0.0
prettyTrialWith :: (Semigroup e, IsString e) => (a -> String) -> Trial e a -> e Source #
Similar to prettyTrial
, but accepts a function to show Result in the
provided way.
Since: 0.0.0.0
prettyTaggedTrial :: (Show a, Semigroup e, IsString e) => TaggedTrial e a -> e Source #
Colourful pretty-printing of TaggedTrial
. Similar to
prettyTrial
, but also prints the resulting tag
for Result
.
Since: 0.0.0.0
prettyTaggedTrialWith :: (Semigroup e, IsString e) => (a -> String) -> TaggedTrial e a -> e Source #
Similar to prettyTaggedTrial
, but accepts a function to show the Result
in the provided way.
Since: 0.0.0.0
Configuration helpers
trial
introduced some additional data types and type families for adding phase notion to your data types.
This approach is especially useful when you have a data type with many fields and the goal is to roll up the Trial
data type to the one with pure fields.
In this case you can have two options:
Use two separate data types:
data MyType = MyType { mtField1 ::
Int
, ... data PartialMyType = PartialMyType { pmtField1 ::Trial
String
Int
, ... finalise :: PartialMyType -> Maybe MyTypeUse
Phase
notion together with:-
type family:data MyType (p :: Phase String) = MyType { mtField1 :: p :-
Int
, ... finalise :: MyType 'Partial -> Maybe (MyType 'Final)And this will have the same effect
See the usage example in the trial-example
package:
data Phase (e :: Type) Source #
The phase of the configurations.
This type is parametrised by the e
(error) type of the Trial
data type.
It is a phantom parameter.
So it could easily be used in the following way: Phase Text
.
Since: 0.0.0.0
type family (phase :: Phase (e :: Type)) :- field where ... infixl 3 Source #