morley-1.20.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Util.MismatchError

Description

Helper utilities for rendering mismatch-type errors.

For cases where it's useful to get a diff-style mismatch report, i.e. where types can be rendered multi-line, a few override instances are needed.

The diff is produced by printing the types in a multiline format, then computing the line diff with the standard algorithm (as implemented by the Diff package).

In general, assuming the type in question is T, those instances can look like this:

instance Buildable (MismatchError T) where
  build = buildRenderDocExtended

instance RenderDoc (MismatchError T) where
  renderDoc ctx = renderDocDiff ctx . fmap Prettier

The fmap Prettier part is only required to enable multi-line rendering.

Additionally, if there's a need to show mismatch errors for lists, the following instance can be used:

instance RenderDoc (MismatchError [T]) where
  renderDoc ctx = renderDocDiffList ctx . (fmap . fmap) Prettier
Synopsis

Documentation

data MismatchError a Source #

A helper record datatype representing a mismatch between two values of some type. One is assumed to be in some sense the "expected" value, the other one is assumed to be the "actual" value.

Constructors

MkMismatchError 

Fields

Instances

Instances details
Foldable MismatchError Source # 
Instance details

Defined in Morley.Util.MismatchError

Methods

fold :: Monoid m => MismatchError m -> m #

foldMap :: Monoid m => (a -> m) -> MismatchError a -> m #

foldMap' :: Monoid m => (a -> m) -> MismatchError a -> m #

foldr :: (a -> b -> b) -> b -> MismatchError a -> b #

foldr' :: (a -> b -> b) -> b -> MismatchError a -> b #

foldl :: (b -> a -> b) -> b -> MismatchError a -> b #

foldl' :: (b -> a -> b) -> b -> MismatchError a -> b #

foldr1 :: (a -> a -> a) -> MismatchError a -> a #

foldl1 :: (a -> a -> a) -> MismatchError a -> a #

toList :: MismatchError a -> [a] #

null :: MismatchError a -> Bool #

length :: MismatchError a -> Int #

elem :: Eq a => a -> MismatchError a -> Bool #

maximum :: Ord a => MismatchError a -> a #

minimum :: Ord a => MismatchError a -> a #

sum :: Num a => MismatchError a -> a #

product :: Num a => MismatchError a -> a #

Functor MismatchError Source # 
Instance details

Defined in Morley.Util.MismatchError

Methods

fmap :: (a -> b) -> MismatchError a -> MismatchError b #

(<$) :: a -> MismatchError b -> MismatchError a #

Generic (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

Associated Types

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

Show a => Show (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

NFData a => NFData (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

Methods

rnf :: MismatchError a -> () #

Eq a => Eq (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

Buildable (MismatchError T) 
Instance details

Defined in Morley.Michelson.Typed.T

Methods

build :: MismatchError T -> Doc

buildList :: [MismatchError T] -> Doc

Buildable (MismatchError Ty) 
Instance details

Defined in Morley.Michelson.Untyped.Type

Methods

build :: MismatchError Ty -> Doc

buildList :: [MismatchError Ty] -> Doc

Buildable (MismatchError [T]) 
Instance details

Defined in Morley.Michelson.Typed.T

Methods

build :: MismatchError [T] -> Doc

buildList :: [MismatchError [T]] -> Doc

Buildable a => Buildable (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

Methods

build :: MismatchError a -> Doc

buildList :: [MismatchError a] -> Doc

Container (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

Associated Types

type Element (MismatchError a) #

Methods

toList :: MismatchError a -> [Element (MismatchError a)] #

null :: MismatchError a -> Bool #

foldr :: (Element (MismatchError a) -> b -> b) -> b -> MismatchError a -> b #

foldl :: (b -> Element (MismatchError a) -> b) -> b -> MismatchError a -> b #

foldl' :: (b -> Element (MismatchError a) -> b) -> b -> MismatchError a -> b #

length :: MismatchError a -> Int #

elem :: Element (MismatchError a) -> MismatchError a -> Bool #

foldMap :: Monoid m => (Element (MismatchError a) -> m) -> MismatchError a -> m #

fold :: MismatchError a -> Element (MismatchError a) #

foldr' :: (Element (MismatchError a) -> b -> b) -> b -> MismatchError a -> b #

notElem :: Element (MismatchError a) -> MismatchError a -> Bool #

all :: (Element (MismatchError a) -> Bool) -> MismatchError a -> Bool #

any :: (Element (MismatchError a) -> Bool) -> MismatchError a -> Bool #

and :: MismatchError a -> Bool #

or :: MismatchError a -> Bool #

find :: (Element (MismatchError a) -> Bool) -> MismatchError a -> Maybe (Element (MismatchError a)) #

safeHead :: MismatchError a -> Maybe (Element (MismatchError a)) #

safeMaximum :: MismatchError a -> Maybe (Element (MismatchError a)) #

safeMinimum :: MismatchError a -> Maybe (Element (MismatchError a)) #

safeFoldr1 :: (Element (MismatchError a) -> Element (MismatchError a) -> Element (MismatchError a)) -> MismatchError a -> Maybe (Element (MismatchError a)) #

safeFoldl1 :: (Element (MismatchError a) -> Element (MismatchError a) -> Element (MismatchError a)) -> MismatchError a -> Maybe (Element (MismatchError a)) #

type Rep (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

type Rep (MismatchError a) = D1 ('MetaData "MismatchError" "Morley.Util.MismatchError" "morley-1.20.0-inplace" 'False) (C1 ('MetaCons "MkMismatchError" 'PrefixI 'True) (S1 ('MetaSel ('Just "meExpected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "meActual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))
type Element (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

type Element (MismatchError a) = ElementDefault (MismatchError a)

buildDocDiff :: Buildable a => MismatchError a -> Doc Source #

Render a mismatch error with a diff.

This is intended to be used with types for which RenderDoc outputs multiline Doc.

buildDocDiffList :: Buildable a => MismatchError [a] -> Doc Source #

Render a mismatch error of lists with a diff.

This is intended to be used with types for which RenderDoc outputs multiline Doc.