hspec-tidy-formatter-0.1.0.0: A custom hspec formatter for easy-to-read terminal output.
LicenseMIT
Safe HaskellNone
LanguageGHC2021

Test.Hspec.TidyFormatter.Internal.Parts

Description

The mise-en-place utility set needed for a readable, declarative implementation of Test.Hspec.TidyFormatter -- in the dress of a small, general annotated-sequence module.

The Parts type expresses ordered annotated sequences. It is expected to be useful primarily in its Silenceable specialization.

The Silenceable type, together with utility functions and instances, can be useful as an abstraction over sequences of pairs of pure values and effect-modifying functions.

Synopsis

Documentation

>>> import Data.Monoid (Sum)

Type

newtype Parts ann b Source #

An ordered sequence of elements where each element consists of an annotation and a label.

This type is a thin newtype wrapper over [(a,b)], and usefully different from that bare type in nuance only: in Parts, the first tuple component (the annotation) is assumed to be meaningful only together with the second tuple component (the label). Therefore, Parts have no utility functions or instances that allow combining over only the annotations of a Parts - hence the lack of (Bi)Foldable and (Bi)Traversable. Parts instead offers up to (Bi)Functor, Semigroup and Monoid; all of which retains the structural pairing of annotations and labels. For combining over the (ann,b) pairs (elements) of a Parts, foldParts and interpret are provided instead.

Further, the justification of a Parts type could be claimed to rely solely on its specialization to the Silenceable type.

Constructors

Parts [(ann, b)] 

Instances

Instances details
Bifunctor Parts Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

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

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

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

Functor (Parts ann) Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

fmap :: (a -> b) -> Parts ann a -> Parts ann b #

(<$) :: a -> Parts ann b -> Parts ann a #

(Monoid ann, IsString b) => IsString (Parts ann b) Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

fromString :: String -> Parts ann b #

Monoid (Parts ann b) Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

mempty :: Parts ann b #

mappend :: Parts ann b -> Parts ann b -> Parts ann b #

mconcat :: [Parts ann b] -> Parts ann b #

Semigroup (Parts ann b) Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

(<>) :: Parts ann b -> Parts ann b -> Parts ann b #

sconcat :: NonEmpty (Parts ann b) -> Parts ann b #

stimes :: Integral b0 => b0 -> Parts ann b -> Parts ann b #

(Read ann, Read b) => Read (Parts ann b) Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

readsPrec :: Int -> ReadS (Parts ann b) #

readList :: ReadS [Parts ann b] #

readPrec :: ReadPrec (Parts ann b) #

readListPrec :: ReadPrec [Parts ann b] #

(Show ann, Show b) => Show (Parts ann b) Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

showsPrec :: Int -> Parts ann b -> ShowS #

show :: Parts ann b -> String #

showList :: [Parts ann b] -> ShowS #

(Eq ann, Eq b) => Eq (Parts ann b) Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

(==) :: Parts ann b -> Parts ann b -> Bool #

(/=) :: Parts ann b -> Parts ann b -> Bool #

(Ord ann, Ord b) => Ord (Parts ann b) Source # 
Instance details

Defined in Test.Hspec.TidyFormatter.Internal.Parts

Methods

compare :: Parts ann b -> Parts ann b -> Ordering #

(<) :: Parts ann b -> Parts ann b -> Bool #

(<=) :: Parts ann b -> Parts ann b -> Bool #

(>) :: Parts ann b -> Parts ann b -> Bool #

(>=) :: Parts ann b -> Parts ann b -> Bool #

max :: Parts ann b -> Parts ann b -> Parts ann b #

min :: Parts ann b -> Parts ann b -> Parts ann b #

Create

Examples:

>>> singleton [] "a" :: Parts [Int] String
Parts [([],"a")]
>>> string "a" :: Parts [Int] String
Parts [([],"a")]
>>> p = singleton [] "a" :: Parts [Int] String
>>> :seti -XOverloadedStrings
>>> p <> "b"
Parts [([],"a"),([],"b")]

singleton :: ann -> b -> Parts ann b Source #

value :: Monoid ann => b -> Parts ann b Source #

Embed a value annotated with mempty.

string :: (Monoid ann, IsString b) => String -> Parts ann b Source #

Embed a string literal annotated with mempty.

empty :: Parts ann b Source #

Modify

maybeEmpty :: Maybe (Parts ann b) -> Parts ann b Source #

mapAnn :: (ann -> ann') -> Parts ann b -> Parts ann' b Source #

Map annotations.

mapAnn == first

with :: Parts ann b -> (ann -> ann') -> Parts ann' b infixl 7 Source #

Flipped mapAnn.

Examples:

>>> p = string "ab" :: Parts [Int] String
>>> p
Parts [([],"ab")]
>>> p `with` (++[1])
Parts [([1],"ab")]

The high precedence of the operator variant means it binds tighter than e.g. <>, which is inteded to facilitate constructs such as:

>>> :seti -XOverloadedStrings
>>> :{
let parts :: Parts (Sum Int) String
    parts =    "a" `with` (+1)
            <> "b" `with` (+2)
in  parts
:}
Parts [(Sum {getSum = 1},"a"),(Sum {getSum = 2},"b")]

(Note: above, the IsString instance promotes the string literals to Parts, initializing the annotation to mempty == 'Sum 0'.)

Fold

foldParts Source #

Arguments

:: ((ann, b) -> acc -> acc)

combine

-> acc

initial aggregate

-> Parts ann b 
-> acc 

Right-fold a Parts.

Parts . foldParts (:) [] == id

Interpret

interpret Source #

Arguments

:: (ann -> b -> c)

interpreting one element

-> (c -> acc -> acc)

adding an interpretation to the aggregate

-> acc

initial aggregate

-> Parts ann b

the Parts to interpret

-> acc

returned interpretation

Interpret an annotated sequence by applying a function to each element and combine the results.

interpret (,)                == foldParts
Parts . interpret (,) (:) [] == id

Examples:

>>> parts = singleton 'a' 1 <> singleton 'b' 2
>>> interpret (,) (:) [] parts
[('a',1),('b',2)]
>>> :seti -XOverloadedStrings
>>> import Data.Monoid (Endo(..))
>>> interp  = interpret (\ann -> appEndo ann . putStr) (>>) (pure ())
>>> bold    = putStr "\ESC[1m"
>>> stop    = putStr "\ESC[0m"
>>> asBold  = Endo $ \x -> bold >> x >> stop
>>> interp $ "plain, " <> "bold" `with` (<> asBold)
<prints "plain, bold" with "bold" bold-formatted>

Parts with Silenceable elements

The Silenceable specialization of Parts have annotations that describe how to transform the effect of emitting the label it is paired with. This allows embedding per-element effectfully-predicated include/suppress decisions in the annotations. The decisions are effectuated at interpretation time.

type Silenceable (m :: Type -> Type) b = Parts (Endo (m ())) b Source #

Conditionals

These transformations are semantically meaningful, and in a way that aligns with the function names, if later interpreted with run, e.g. run putStr.

Labels remain pure, inspectable and fmap-able; instances remain lawful.

Note: upon interpretation,

  • effectful predicates will run for each element
  • conditionals nested on the same element have short-circuiting behaviour

when' Source #

Arguments

:: Monad m 
=> m Bool 
-> Silenceable m b

to include if True (else nothing)

-> Silenceable m b 

Conditional inclusion.

Transform each annotation so that, when interpreted as a wrapper around the element’s action, the element’s effects are only run if the effectful predicate evaluates to True.

whenA Source #

Arguments

:: Applicative f 
=> Bool 
-> Silenceable f b

to include if True (else nothing)

-> Silenceable f b 

Conditional inclusion based on a pure predicate.

onlyIf :: Monad m => Silenceable m b -> m Bool -> Silenceable m b infixl 7 Source #

Flipped when'.

Example:

>>> import Data.Monoid (Endo(..))
>>> import Data.Char (toUpper)
>>> upper  = fmap toUpper
>>> interp = interpret (\ann -> appEndo ann . putStr) (>>) (pure ())
>>> yes    = string "yes" `onlyIf` (pure True )
>>> no     = string "no"  `onlyIf` (pure False)
>>> ok     = upper <$> (yes <> no <> string ".")
>>> interp ok
YES.

ifThenElse Source #

Arguments

:: Monad m 
=> m Bool 
-> Silenceable m b

to include if True

-> Silenceable m b

to include if False

-> Silenceable m b 

Binary choice.

At interpretation, the monadic condition will be run twice (for every element).

The expectation that exactly one of the arguments will have all its elements included and the other have all its elements suppressed will hold if the same Bool is returned every time the effectful condition is run.

Interpret

run Source #

Arguments

:: Monad m 
=> (b -> m ())

emitting a label

-> Silenceable m b

the Silenceable to interpret

-> m ()

returned interpretation

Interpret by emitting each label with the given function, then applying the annotation, and combining with >>.

Note: this function is basically interpret, but with some type specialization, some defaults and an adjusted API shape.