trial-0.0.0.0: Trial Data Structure
Copyright(c) 2020 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Trial

Description

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 explicit Fatality level; at least one event has level Error
  • Result: stores the final result and the list of events where each event has implicit Fatality level Warning

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:

Synopsis

Data structures

data Trial e a Source #

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 the Fatality level Error.

Since: 0.0.0.0

Constructors

Fiasco (DList (Fatality, e))

Stores list of events with the explicit Fatality level.

Result (DList e) a

Store list of events and the final result.

Instances

Instances details
Bitraversable Trial Source #

Since: 0.0.0.0

Instance details

Defined in Trial

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Trial a b -> f (Trial c d) #

Bifoldable Trial Source #

Since: 0.0.0.0

Instance details

Defined in Trial

Methods

bifold :: Monoid m => Trial m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Trial a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Trial a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Trial a b -> c #

Bifunctor Trial Source #

Since: 0.0.0.0

Instance details

Defined in Trial

Methods

bimap :: (a -> b) -> (c -> d) -> Trial a c -> Trial b d #

first :: (a -> b) -> Trial a c -> Trial b c #

second :: (b -> c) -> Trial a b -> Trial a c #

(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 TaggedTrial to Trial by appending field names to the history. This instance automatically combines tags and record field names into human readable message, so the resulting history has more context.

Since: 0.0.0.0

Instance details

Defined in Trial

Methods

fromLabel :: r -> Trial tag a #

Functor (Trial e) Source #

Since: 0.0.0.0

Instance details

Defined in Trial

Methods

fmap :: (a -> b) -> Trial e a -> Trial e b #

(<$) :: a -> Trial e b -> Trial e a #

Applicative (Trial e) Source #

Combine two Trials but recording all Result events inside Fiasco as Warnings.

>>> fiasco "No default" <*> fiasco "No config"
Fiasco (fromList [(E,"No default"),(E,"No config")])
>>> fiasco "No default" *> result "Option deprecated" 10
Fiasco (fromList [(E,"No default"),(W,"Option deprecated")])
>>> (,) <$> result "Redundant" 10 <*> result "No CLI Flag" True
Result (fromList ["Redundant","No CLI Flag"]) (10,True)
>>> result "Option deprecated" 10 *> pure 42
Result (fromList ["Option deprecated"]) 42

Since: 0.0.0.0

Instance details

Defined in Trial

Methods

pure :: a -> Trial e a #

(<*>) :: Trial e (a -> b) -> Trial e a -> Trial e b #

liftA2 :: (a -> b -> c) -> Trial e a -> Trial e b -> Trial e c #

(*>) :: Trial e a -> Trial e b -> Trial e b #

(<*) :: Trial e a -> Trial e b -> Trial e a #

Alternative (Trial e) Source #

Return the first Result with the whole history before it. If both are Fiascos, return Fiascos with the histories combined.

>>> fiasco "No info" <|> pure 42
Result (fromList ["No info"]) 42
>>> pure 42 <|> result "Something" 10
Result (fromList []) 42
>>> fiasco "No info" <|> fiasco "Some info"
Fiasco (fromList [(E,"No info"),(E,"Some info")])

See alt if you want a different behaviour.

Since: 0.0.0.0

Instance details

Defined in Trial

Methods

empty :: Trial e a #

(<|>) :: Trial e a -> Trial e a -> Trial e a #

some :: Trial e a -> Trial e [a] #

many :: Trial e a -> Trial e [a] #

(Eq e, Eq a) => Eq (Trial e a) Source # 
Instance details

Defined in Trial

Methods

(==) :: Trial e a -> Trial e a -> Bool #

(/=) :: Trial e a -> Trial e a -> Bool #

(Show e, Show a) => Show (Trial e a) Source # 
Instance details

Defined in Trial

Methods

showsPrec :: Int -> Trial e a -> ShowS #

show :: Trial e a -> String #

showList :: [Trial e a] -> ShowS #

Semigroup (Trial e a) Source #

Combine two Trial values. Returns Result if at least one argument is Result.

Let's create some default values:

>>> f1 = fiasco "Not initialised..."
>>> f2 = fiasco "Parsing error!"
>>> r1 = result "r1: From CLI" 5
>>> r2 = result "r2: Default" 42

And here is how combination of those values look like:

>>> f1 <> f2
Fiasco (fromList [(E,"Not initialised..."),(E,"Parsing error!")])
>>> f1 <> r1
Result (fromList ["Not initialised...","r1: From CLI"]) 5
>>> f2 <> r2
Result (fromList ["Parsing error!","r2: Default"]) 42
>>> r1 <> r2
Result (fromList ["r1: From CLI","r2: Default"]) 42
>>> f1 <> r1 <> f2 <> r2
Result (fromList ["Not initialised...","r1: From CLI","Parsing error!","r2: Default"]) 42

Since: 0.0.0.0

Instance details

Defined in Trial

Methods

(<>) :: Trial e a -> Trial e a -> Trial e a #

sconcat :: NonEmpty (Trial e a) -> Trial e a #

stimes :: Integral b => b -> Trial e a -> Trial e a #

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

data Fatality Source #

Severity of the event in history.

  • Error: fatal error that led to the final Fiasco
  • 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

Instances details
Bounded Fatality Source # 
Instance details

Defined in Trial

Enum Fatality Source # 
Instance details

Defined in Trial

Eq Fatality Source # 
Instance details

Defined in Trial

Show Fatality Source # 
Instance details

Defined in Trial

pattern Warning :: Fatality Source #

Warning pattern synonym.

Since: 0.0.0.0

pattern Error :: Fatality Source #

Error pattern synonym.

Since: 0.0.0.0

Smart constructors

fiasco :: e -> Trial e a Source #

Smart constructor for Trial. Returns Fiasco with a single event and Error Fatality.

Since: 0.0.0.0

fiascos :: NonEmpty e -> Trial e a Source #

Smart constructor for Trial. Returns Fiasco with a list of events, where each has Fatality Error.

Since: 0.0.0.0

result :: e -> a -> Trial e a Source #

Smart constructor for Trial. Returns Result with a single event of Warning Fatality.

Hint: Use pure to create a Result with an empty list of events.

Since: 0.0.0.0

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 Fiascos. both Fiascos.

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

isFiasco :: Trial e a -> Bool Source #

Predicate on if the given Trial is Fiasco.

>>> isFiasco (fiasco 'e')
True
>>> isFiasco (result 'a' 42)
False

Since: 0.0.0.0

isResult :: Trial e a -> Bool Source #

Predicate on if the given Trial is Result.

>>> isResult (result 'a' 42)
True
>>> isResult (fiasco 'e')
False

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 #

Applies the given action to Trial if it is Fiasco and returns the result. In case of Result the default value is returned.

>>> whenFiasco "bar" (fiasco 42) (\es -> "foo" <$ print es)
[(E,42)]
"foo"
>>> whenFiasco "bar" (result "res" 42) (\es -> "foo" <$ print es)
"bar"

Since: 0.0.0.0

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

getTrialInfo :: Trial e a -> ([(Fatality, e)], Maybe a) Source #

Get the list of Warnings and Errors together with the Maybe Result if applicable.

>>> getTrialInfo $ result "Warning" 42
([(W,"Warning")],Just 42)
>>> getTrialInfo $ fiasco "Error"
([(E,"Error")],Nothing)

Since: 0.0.0.0

fiascoErrors :: Trial e a -> [e] Source #

Returns all Errors in the Fiasco constructor. If the given Trial is Result then returns an empty list instead.

>>> fiascoErrors $ fiasco "One Error"
["One Error"]
>>> fiascoErrors $ result "Warning" 42
[]
>>> fiascoErrors (fiasco "Error" *> result "Warning" 42)
["Error"]

Since: 0.0.0.0

fiascoWarnings :: Trial e a -> [e] Source #

Returns all Warnings in the Fiasco constructor. If the given Trial is Result then returns an empty list instead.

>>> fiascoWarnings $ fiasco "One Error"
[]
>>> fiascoWarnings $ result "Warning" 42
[]
>>> fiascoWarnings (fiasco "Error" *> result "Warning" 42)
["Warning"]

Since: 0.0.0.0

resultWarnings :: Trial e a -> [e] Source #

Returns all Warnings in the Result constructor. If the given Trial is Fiasco then returns an empty list instead.

>>> resultWarnings $ fiasco "One Error"
[]
>>> resultWarnings $ result "Warning" 42
["Warning"]
>>> resultWarnings (fiasco "Error" *> result "Warning" 42)
[]

Since: 0.0.0.0

anyWarnings :: Trial e a -> [e] Source #

Returns all Warnings in the Trial. These includes both warnings in Result of in Fiasco.

>>> anyWarnings $ fiasco "One Error"
[]
>>> anyWarnings $ result "Warning" 42
["Warning"]
>>> anyWarnings (fiasco "Error" *> result "Warning" 42)
["Warning"]

Since: 0.0.0.0

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 #

'Convert Trial to Maybe by losing all history information.

>>> trialToMaybe $ fiasco "Some info"
Nothing
>>> trialToMaybe $ result "From CLI" 3
Just 3

Since: 0.0.0.0

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 . eitherToTrialid

Since: 0.0.0.0

trialToEither :: Monoid e => Trial e a -> Either e a Source #

Convert Trial to Either by concatenating all history events.

>>> trialToEither (result "No info" 42)
Right 42
>>> trialToEither $ fiascos $ "Hello, " :| ["there"]
Left "Hello, there"

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

fiascoOnEmpty Source #

Arguments

:: (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 #

Print aligned and colourful Fatality:

See prettyTrial for examples.

Since: 0.0.0.0

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:

  1. Use two separate data types:

    data MyType = MyType
        { mtField1 :: Int
        , ...
    
    data PartialMyType = PartialMyType
        { pmtField1 :: Trial String Int
        , ...
    
    finalise :: PartialMyType -> Maybe MyType
    
  2. Use 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

Constructors

Partial 
Final 

Instances

Instances details
Eq (Phase e) Source # 
Instance details

Defined in Trial

Methods

(==) :: Phase e -> Phase e -> Bool #

(/=) :: Phase e -> Phase e -> Bool #

Show (Phase e) Source # 
Instance details

Defined in Trial

Methods

showsPrec :: Int -> Phase e -> ShowS #

show :: Phase e -> String #

showList :: [Phase e] -> ShowS #

type family (phase :: Phase (e :: Type)) :- field where ... infixl 3 Source #

Type family to map Phase to the corresponding field for the Trial approach. This is a Higher-Kinded Data approach specialised to custom enumeration.

Since: 0.0.0.0

Equations

('Partial :: Phase e) :- field = Trial e field 
'Final :- field = field 

type family (phase :: Phase (tag :: Type)) ::- field where ... infixl 3 Source #

Type family to map Phase to the corresponding field for the TaggedTrial approach. This is a Higher-Kinded Data approach specialised to custom enumeration.

Since: 0.0.0.0

Equations

('Partial :: Phase tag) ::- field = TaggedTrial tag field 
'Final ::- field = field