-- SPDX-FileCopyrightText: 2021 Tocqueville Group
--
-- SPDX-License-Identifier: LicenseRef-MIT-TQ

-- | Internal utilities for unit testing.

module Test.Cleveland.Michelson.Internal.Entrypoints
  ( EPList
  , EPExpected(..)
  , EPActual(..)
  , EPMismatch(.., EPComparisonResultOK)
  , ignoreExtraEntrypoints
  , compareEntrypoints
  , contractMatchesEntrypoints
  , contractCoversEntrypoints
  , testContractEntrypoints
  , assertEPComparisonSuccessful
  , michelsonRoundtripContract
  , michelineRoundtripContract
  ) where

import Data.Aeson (eitherDecode, encode)
import qualified Data.Map as Map
import Fmt (Buildable(..), blockMapF, indentF, nameF, pretty, unlinesF, (+|), (|+))
import Test.HUnit (Assertion, assertFailure)
import Test.Tasty (TestName, TestTree, testGroup)
import Test.Tasty.HUnit (testCase)

import Morley.Micheline (fromExpression, toExpression)
import Morley.Michelson.Parser (MichelsonSource(MSUnspecified))
import Morley.Michelson.Printer (printUntypedContract)
import Morley.Michelson.Runtime (parseExpandContract)
import Morley.Michelson.TypeCheck (TCError, mkSomeParamType)
import Morley.Michelson.Untyped hiding (Contract)
import qualified Morley.Michelson.Untyped as U

-- | Convenience type synonym for a list of pairs of entrypoint names and types
type EPList = [(EpName, U.Ty)]

-- | Newtype wrapper for the expected value in entrypoint comparison
newtype EPExpected a = EPExpected a
  deriving stock (EPExpected a -> EPExpected a -> Bool
(EPExpected a -> EPExpected a -> Bool)
-> (EPExpected a -> EPExpected a -> Bool) -> Eq (EPExpected a)
forall a. Eq a => EPExpected a -> EPExpected a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EPExpected a -> EPExpected a -> Bool
$c/= :: forall a. Eq a => EPExpected a -> EPExpected a -> Bool
== :: EPExpected a -> EPExpected a -> Bool
$c== :: forall a. Eq a => EPExpected a -> EPExpected a -> Bool
Eq, Int -> EPExpected a -> ShowS
[EPExpected a] -> ShowS
EPExpected a -> String
(Int -> EPExpected a -> ShowS)
-> (EPExpected a -> String)
-> ([EPExpected a] -> ShowS)
-> Show (EPExpected a)
forall a. Show a => Int -> EPExpected a -> ShowS
forall a. Show a => [EPExpected a] -> ShowS
forall a. Show a => EPExpected a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EPExpected a] -> ShowS
$cshowList :: forall a. Show a => [EPExpected a] -> ShowS
show :: EPExpected a -> String
$cshow :: forall a. Show a => EPExpected a -> String
showsPrec :: Int -> EPExpected a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> EPExpected a -> ShowS
Show)

-- | Newtype wrapper for the actual value in entrypoint comparison
newtype EPActual a = EPActual a
  deriving stock (EPActual a -> EPActual a -> Bool
(EPActual a -> EPActual a -> Bool)
-> (EPActual a -> EPActual a -> Bool) -> Eq (EPActual a)
forall a. Eq a => EPActual a -> EPActual a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EPActual a -> EPActual a -> Bool
$c/= :: forall a. Eq a => EPActual a -> EPActual a -> Bool
== :: EPActual a -> EPActual a -> Bool
$c== :: forall a. Eq a => EPActual a -> EPActual a -> Bool
Eq, Int -> EPActual a -> ShowS
[EPActual a] -> ShowS
EPActual a -> String
(Int -> EPActual a -> ShowS)
-> (EPActual a -> String)
-> ([EPActual a] -> ShowS)
-> Show (EPActual a)
forall a. Show a => Int -> EPActual a -> ShowS
forall a. Show a => [EPActual a] -> ShowS
forall a. Show a => EPActual a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EPActual a] -> ShowS
$cshowList :: forall a. Show a => [EPActual a] -> ShowS
show :: EPActual a -> String
$cshow :: forall a. Show a => EPActual a -> String
showsPrec :: Int -> EPActual a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> EPActual a -> ShowS
Show)

-- | A pattern syononym for no mismatches
pattern EPComparisonResultOK :: EPMismatch
pattern $mEPComparisonResultOK :: forall r. EPMismatch -> (Void# -> r) -> (Void# -> r) -> r
EPComparisonResultOK <- EPMismatch [] [] []

-- | Entrypoint comparison mismatch report
data EPMismatch = EPMismatch
  { EPMismatch -> EPList
epmmExtra :: EPList
    -- ^ Extraneous entrypoints, i.e. those that exist in the actual contract, but not
    -- in the specification
  , EPMismatch -> EPList
epmmMissing :: EPList
    -- ^ Missing entrypoints, i.e. those that exist in the specification, but not the
    -- actual contract
  , EPMismatch -> [(EpName, (EPExpected Ty, EPActual Ty))]
epmmTypeMismatch :: [(EpName, (EPExpected U.Ty, EPActual U.Ty))]
    -- ^ Entrypoints that exist in both the contract and the specification, but types do not
    -- match.
  } deriving stock (EPMismatch -> EPMismatch -> Bool
(EPMismatch -> EPMismatch -> Bool)
-> (EPMismatch -> EPMismatch -> Bool) -> Eq EPMismatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EPMismatch -> EPMismatch -> Bool
$c/= :: EPMismatch -> EPMismatch -> Bool
== :: EPMismatch -> EPMismatch -> Bool
$c== :: EPMismatch -> EPMismatch -> Bool
Eq, Int -> EPMismatch -> ShowS
[EPMismatch] -> ShowS
EPMismatch -> String
(Int -> EPMismatch -> ShowS)
-> (EPMismatch -> String)
-> ([EPMismatch] -> ShowS)
-> Show EPMismatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EPMismatch] -> ShowS
$cshowList :: [EPMismatch] -> ShowS
show :: EPMismatch -> String
$cshow :: EPMismatch -> String
showsPrec :: Int -> EPMismatch -> ShowS
$cshowsPrec :: Int -> EPMismatch -> ShowS
Show)

instance Buildable EPMismatch where
  build :: EPMismatch -> Builder
build EPMismatch
EPComparisonResultOK = Builder
"Entrypoints match specificaton"
  build EPMismatch{[(EpName, (EPExpected Ty, EPActual Ty))]
EPList
epmmTypeMismatch :: [(EpName, (EPExpected Ty, EPActual Ty))]
epmmMissing :: EPList
epmmExtra :: EPList
epmmTypeMismatch :: EPMismatch -> [(EpName, (EPExpected Ty, EPActual Ty))]
epmmMissing :: EPMismatch -> EPList
epmmExtra :: EPMismatch -> EPList
..} = Builder -> Builder -> Builder
nameF Builder
"Entrypoints do not match specification" (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ Int -> Builder -> Builder
indentF Int
2 (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$
    [Builder] -> Builder
forall (f :: * -> *) a. (Foldable f, Buildable a) => f a -> Builder
unlinesF ([Builder] -> Builder) -> [Builder] -> Builder
forall a b. (a -> b) -> a -> b
$ (Builder -> Bool) -> [Builder] -> [Builder]
forall a. (a -> Bool) -> [a] -> [a]
filter (Builder -> Builder -> Bool
forall a. Eq a => a -> a -> Bool
/=Builder
forall a. Monoid a => a
mempty) [Builder
extra, Builder
missing, Builder
typemm]
    where
    extra :: Builder
extra | EPList -> Bool
forall t. Container t => t -> Bool
null EPList
epmmExtra = Builder
forall a. Monoid a => a
mempty
          | Bool
otherwise = Builder -> Builder -> Builder
nameF Builder
"Extraneous entrypoints in the contract" (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ EPList -> Builder
forall t k v.
(IsList t, Item t ~ (k, v), Buildable k, Buildable v) =>
t -> Builder
blockMapF EPList
epmmExtra
    missing :: Builder
missing | EPList -> Bool
forall t. Container t => t -> Bool
null EPList
epmmMissing = Builder
forall a. Monoid a => a
mempty
            | Bool
otherwise = Builder -> Builder -> Builder
nameF Builder
"Missing entrypoints in the contract" (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ EPList -> Builder
forall t k v.
(IsList t, Item t ~ (k, v), Buildable k, Buildable v) =>
t -> Builder
blockMapF EPList
epmmMissing
    typemm :: Builder
typemm | [(EpName, (EPExpected Ty, EPActual Ty))] -> Bool
forall t. Container t => t -> Bool
null [(EpName, (EPExpected Ty, EPActual Ty))]
epmmTypeMismatch = Builder
forall a. Monoid a => a
mempty
           | Bool
otherwise = Builder -> Builder -> Builder
nameF Builder
"Type mismatch in entrypoints" (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ [(EpName, (EPExpected Ty, EPActual Ty))] -> Builder
forall t k v.
(IsList t, Item t ~ (k, v), Buildable k, Buildable v) =>
t -> Builder
blockMapF [(EpName, (EPExpected Ty, EPActual Ty))]
epmmTypeMismatch

instance Buildable (EPExpected Ty, EPActual Ty) where
  build :: (EPExpected Ty, EPActual Ty) -> Builder
build (EPExpected Ty
expected, EPActual Ty
actual) = Builder
"" Builder -> Builder -> Builder
forall b. FromBuilder b => Builder -> Builder -> b
+| EPExpected Ty
expected EPExpected Ty -> Builder -> Builder
forall a b. (Buildable a, FromBuilder b) => a -> Builder -> b
|+ Builder
", " Builder -> Builder -> Builder
forall b. FromBuilder b => Builder -> Builder -> b
+| EPActual Ty
actual EPActual Ty -> Builder -> Builder
forall a b. (Buildable a, FromBuilder b) => a -> Builder -> b
|+ Builder
""

instance Buildable a => Buildable (EPExpected a) where
  build :: EPExpected a -> Builder
build (EPExpected a
x) = Builder -> Builder -> Builder
nameF Builder
"Expected" (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ a -> Builder
forall p. Buildable p => p -> Builder
build a
x

instance Buildable a => Buildable (EPActual a) where
  build :: EPActual a -> Builder
build (EPActual a
x) = Builder -> Builder -> Builder
nameF Builder
"Actual" (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ a -> Builder
forall p. Buildable p => p -> Builder
build a
x

-- | Ignore extraneous entrypoint names in 'EPMismatch'. Essentially sets
-- 'epmmExtra' to @[]@.
ignoreExtraEntrypoints :: EPMismatch -> EPMismatch
ignoreExtraEntrypoints :: EPMismatch -> EPMismatch
ignoreExtraEntrypoints EPMismatch
mm = EPMismatch
mm{ epmmExtra :: EPList
epmmExtra = [] }

-- | Compare two sets of entrypoints. Accepts ordered 'Map's to enforce sorting order.
compareEntrypoints :: EPExpected (Map EpName U.Ty) -> EPActual (Map EpName U.Ty) -> EPMismatch
compareEntrypoints :: EPExpected (Map EpName Ty)
-> EPActual (Map EpName Ty) -> EPMismatch
compareEntrypoints (EPExpected Map EpName Ty
expected) (EPActual Map EpName Ty
actual) = EPMismatch :: EPList
-> EPList -> [(EpName, (EPExpected Ty, EPActual Ty))] -> EPMismatch
EPMismatch{[(EpName, (EPExpected Ty, EPActual Ty))]
EPList
epmmTypeMismatch :: [(EpName, (EPExpected Ty, EPActual Ty))]
epmmMissing :: EPList
epmmExtra :: EPList
epmmTypeMismatch :: [(EpName, (EPExpected Ty, EPActual Ty))]
epmmMissing :: EPList
epmmExtra :: EPList
..}
  where
    epmmExtra :: EPList
epmmExtra = Map EpName Ty -> EPList
forall k a. Map k a -> [(k, a)]
Map.toList (Map EpName Ty -> EPList) -> Map EpName Ty -> EPList
forall a b. (a -> b) -> a -> b
$ Map EpName Ty -> Map EpName Ty -> Map EpName Ty
forall k a b. Ord k => Map k a -> Map k b -> Map k a
Map.difference Map EpName Ty
actual Map EpName Ty
expected
    epmmMissing :: EPList
epmmMissing = Map EpName Ty -> EPList
forall k a. Map k a -> [(k, a)]
Map.toList (Map EpName Ty -> EPList) -> Map EpName Ty -> EPList
forall a b. (a -> b) -> a -> b
$ Map EpName Ty -> Map EpName Ty -> Map EpName Ty
forall k a b. Ord k => Map k a -> Map k b -> Map k a
Map.difference Map EpName Ty
expected Map EpName Ty
actual
    inBoth :: Map EpName (Ty, Ty)
inBoth = (Ty -> Ty -> (Ty, Ty))
-> Map EpName Ty -> Map EpName Ty -> Map EpName (Ty, Ty)
forall k a b c.
Ord k =>
(a -> b -> c) -> Map k a -> Map k b -> Map k c
Map.intersectionWith (,) Map EpName Ty
expected Map EpName Ty
actual
    epmmTypeMismatch :: [(EpName, (EPExpected Ty, EPActual Ty))]
epmmTypeMismatch = Map EpName (EPExpected Ty, EPActual Ty)
-> [(EpName, (EPExpected Ty, EPActual Ty))]
forall k a. Map k a -> [(k, a)]
Map.toList (Map EpName (EPExpected Ty, EPActual Ty)
 -> [(EpName, (EPExpected Ty, EPActual Ty))])
-> Map EpName (EPExpected Ty, EPActual Ty)
-> [(EpName, (EPExpected Ty, EPActual Ty))]
forall a b. (a -> b) -> a -> b
$ ((Ty, Ty) -> (EPExpected Ty, EPActual Ty))
-> Map EpName (Ty, Ty) -> Map EpName (EPExpected Ty, EPActual Ty)
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map ((Ty -> EPExpected Ty)
-> (Ty -> EPActual Ty) -> (Ty, Ty) -> (EPExpected Ty, EPActual Ty)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Ty -> EPExpected Ty
forall a. a -> EPExpected a
EPExpected Ty -> EPActual Ty
forall a. a -> EPActual a
EPActual) (Map EpName (Ty, Ty) -> Map EpName (EPExpected Ty, EPActual Ty))
-> Map EpName (Ty, Ty) -> Map EpName (EPExpected Ty, EPActual Ty)
forall a b. (a -> b) -> a -> b
$ ((Ty, Ty) -> Bool) -> Map EpName (Ty, Ty) -> Map EpName (Ty, Ty)
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter ((Ty -> Ty -> Bool) -> (Ty, Ty) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Ty -> Ty -> Bool
forall a. Eq a => a -> a -> Bool
(/=)) Map EpName (Ty, Ty)
inBoth

-- | Check if the contract exactly matches the given entrypoints. Will report both
-- missing and extraneous entrypoint names, and type mismatches.
contractMatchesEntrypoints :: U.Contract -> Map EpName U.Ty -> Either TCError EPMismatch
contractMatchesEntrypoints :: Contract -> Map EpName Ty -> Either TCError EPMismatch
contractMatchesEntrypoints (Contract -> ParameterType
forall op. Contract' op -> ParameterType
contractParameter -> ParameterType
pt) Map EpName Ty
expected = case ParameterType -> Either TCError SomeParamType
mkSomeParamType ParameterType
pt of
  Right{} -> EPMismatch -> Either TCError EPMismatch
forall a b. b -> Either a b
Right (EPMismatch -> Either TCError EPMismatch)
-> EPMismatch -> Either TCError EPMismatch
forall a b. (a -> b) -> a -> b
$ EPExpected (Map EpName Ty)
-> EPActual (Map EpName Ty) -> EPMismatch
compareEntrypoints (Map EpName Ty -> EPExpected (Map EpName Ty)
forall a. a -> EPExpected a
EPExpected Map EpName Ty
expected) (Map EpName Ty -> EPActual (Map EpName Ty)
forall a. a -> EPActual a
EPActual (Map EpName Ty -> EPActual (Map EpName Ty))
-> Map EpName Ty -> EPActual (Map EpName Ty)
forall a b. (a -> b) -> a -> b
$ ParameterType -> Map EpName Ty
mkEntrypointsMap ParameterType
pt)
  Left TCError
err -> TCError -> Either TCError EPMismatch
forall a b. a -> Either a b
Left TCError
err

-- | Check if the contract contains the entrypoints given in spec (with matching types).
-- Ignores any additional entrypoints present in the contract.
contractCoversEntrypoints :: U.Contract -> Map EpName U.Ty -> Either TCError EPMismatch
contractCoversEntrypoints :: Contract -> Map EpName Ty -> Either TCError EPMismatch
contractCoversEntrypoints = (EPMismatch -> EPMismatch)
-> Either TCError EPMismatch -> Either TCError EPMismatch
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second EPMismatch -> EPMismatch
ignoreExtraEntrypoints (Either TCError EPMismatch -> Either TCError EPMismatch)
-> (Contract -> Map EpName Ty -> Either TCError EPMismatch)
-> Contract
-> Map EpName Ty
-> Either TCError EPMismatch
forall a b c. SuperComposition a b c => a -> b -> c
... Contract -> Map EpName Ty -> Either TCError EPMismatch
contractMatchesEntrypoints

-- | Turn 'Either' 'TCError' 'EPMismatch' into an 'Assertion'
assertEPComparisonSuccessful :: Either TCError EPMismatch -> Assertion
assertEPComparisonSuccessful :: Either TCError EPMismatch -> Assertion
assertEPComparisonSuccessful = \case
  Right EPMismatch
EPComparisonResultOK -> Assertion
forall (f :: * -> *). Applicative f => f ()
pass
  Left TCError
tcerr -> String -> Assertion
forall a. HasCallStack => String -> IO a
assertFailure (String -> Assertion) -> String -> Assertion
forall a b. (a -> b) -> a -> b
$ TCError -> String
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty TCError
tcerr
  Right EPMismatch
mismatch -> String -> Assertion
forall a. HasCallStack => String -> IO a
assertFailure (String -> Assertion) -> String -> Assertion
forall a b. (a -> b) -> a -> b
$ EPMismatch -> String
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty EPMismatch
mismatch

-- | Expect the contract to match with the entrypoints given in spec (with matching types).
-- Comparison is defined by the first argument; use @ignoreExtraEntrypoints@ for cover test,
-- @id@ for match test.
--
-- Also tests if the same holds after Michelson and Micheline roundtrips of the contract.
testContractEntrypoints
  :: (EPMismatch -> EPMismatch)
  -> TestName
  -> U.Contract
  -> Map EpName U.Ty
  -> TestTree
testContractEntrypoints :: (EPMismatch -> EPMismatch)
-> String -> Contract -> Map EpName Ty -> TestTree
testContractEntrypoints EPMismatch -> EPMismatch
compMode String
name Contract
contract Map EpName Ty
spec
  = String -> [TestTree] -> TestTree
testGroup String
name
      [ String -> Assertion -> TestTree
testCase String
"Contract itself" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ (Contract -> Contract) -> Assertion
test Contract -> Contract
forall a. a -> a
id
      , String -> Assertion -> TestTree
testCase String
"After Michelson roundtrip" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ (Contract -> Contract) -> Assertion
test HasCallStack => Contract -> Contract
Contract -> Contract
michelsonRoundtripContract
      , String -> Assertion -> TestTree
testCase String
"After Micheline roundtrip" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ (Contract -> Contract) -> Assertion
test HasCallStack => Contract -> Contract
Contract -> Contract
michelineRoundtripContract
      ]
  where test :: (Contract -> Contract) -> Assertion
test Contract -> Contract
modifier = Either TCError EPMismatch -> Assertion
assertEPComparisonSuccessful (Either TCError EPMismatch -> Assertion)
-> Either TCError EPMismatch -> Assertion
forall a b. (a -> b) -> a -> b
$ (EPMismatch -> EPMismatch)
-> Either TCError EPMismatch -> Either TCError EPMismatch
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second EPMismatch -> EPMismatch
compMode (Either TCError EPMismatch -> Either TCError EPMismatch)
-> Either TCError EPMismatch -> Either TCError EPMismatch
forall a b. (a -> b) -> a -> b
$ Contract -> Map EpName Ty -> Either TCError EPMismatch
contractMatchesEntrypoints (Contract -> Contract
modifier Contract
contract) Map EpName Ty
spec

-- | Round-trip the contract through Michelson text representation.
--
-- This is useful if you're intending to use the contract with Michelson text output and want to
-- check if that output satisfies tests (which /should be/ the same for internal representation
-- and output, but bugs happen)
michelsonRoundtripContract :: HasCallStack => U.Contract -> U.Contract
michelsonRoundtripContract :: Contract -> Contract
michelsonRoundtripContract Contract
contract =
  (ParserException -> Contract)
-> (Contract -> Contract)
-> Either ParserException Contract
-> Contract
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> Contract
forall a. HasCallStack => Text -> a
error (Text -> Contract)
-> (ParserException -> Text) -> ParserException -> Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserException -> Text
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) Contract -> Contract
forall a. a -> a
id (Either ParserException Contract -> Contract)
-> (Text -> Either ParserException Contract) -> Text -> Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MichelsonSource -> Text -> Either ParserException Contract
parseExpandContract MichelsonSource
MSUnspecified (Text -> Either ParserException Contract)
-> (Text -> Text) -> Text -> Either ParserException Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
forall a. ToText a => a -> Text
toText
    (Text -> Contract) -> Text -> Contract
forall a b. (a -> b) -> a -> b
$ Bool -> Contract -> Text
forall op. RenderDoc op => Bool -> Contract' op -> Text
printUntypedContract Bool
True Contract
contract

-- | Round-trip the contract through Micheline JSON representation.
--
-- This is useful if you're intending to use the contract with Micheline JSON output and want to
-- check if that output satisfies tests (which /should be/ the same for internal representation
-- and output, but bugs happen)
michelineRoundtripContract :: HasCallStack => U.Contract -> U.Contract
michelineRoundtripContract :: Contract -> Contract
michelineRoundtripContract Contract
contract =
  (FromExpressionError -> Contract)
-> (Contract -> Contract)
-> Either FromExpressionError Contract
-> Contract
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> Contract
forall a. HasCallStack => Text -> a
error (Text -> Contract)
-> (FromExpressionError -> Text) -> FromExpressionError -> Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FromExpressionError -> Text
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty) Contract -> Contract
forall a. a -> a
id (Either FromExpressionError Contract -> Contract)
-> (Expression -> Either FromExpressionError Contract)
-> Expression
-> Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> Either FromExpressionError Contract
forall a.
FromExpression a =>
Expression -> Either FromExpressionError a
fromExpression
    (Expression -> Either FromExpressionError Contract)
-> (Expression -> Expression)
-> Expression
-> Either FromExpressionError Contract
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Expression)
-> (Expression -> Expression)
-> Either String Expression
-> Expression
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> Expression
forall a. HasCallStack => Text -> a
error (Text -> Expression) -> (String -> Text) -> String -> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. ToText a => a -> Text
toText) Expression -> Expression
forall a. a -> a
id
    (Either String Expression -> Expression)
-> (Expression -> Either String Expression)
-> Expression
-> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String Expression
forall a. FromJSON a => ByteString -> Either String a
eitherDecode (ByteString -> Either String Expression)
-> (Expression -> ByteString)
-> Expression
-> Either String Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expression -> ByteString
forall a. ToJSON a => a -> ByteString
encode
    (Expression -> Contract) -> Expression -> Contract
forall a b. (a -> b) -> a -> b
$ Contract -> Expression
forall a. ToExpression a => a -> Expression
toExpression Contract
contract