Skip to content

Commit

Permalink
Format with fourmolu
Browse files Browse the repository at this point in the history
  • Loading branch information
github-actions committed Apr 11, 2024
1 parent 28ea26b commit daf9f2d
Show file tree
Hide file tree
Showing 4 changed files with 32 additions and 22 deletions.
2 changes: 1 addition & 1 deletion library/Booster/Pattern/UnifiedMatcher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Data.Either.Extra
import Data.List.NonEmpty as NE (NonEmpty, fromList)
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Sequence (Seq, pattern (:<|), pattern (:|>), (><))
import Data.Sequence (Seq, (><), pattern (:<|), pattern (:|>))
import Data.Sequence qualified as Seq

import Data.Set (Set)
Expand Down
27 changes: 16 additions & 11 deletions unit-tests/Test/Booster/Pattern/MatchFun.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE QuasiQuotes #-}

{- |
Copyright : (c) Runtime Verification, 2022
License : BSD-3-Clause
Expand All @@ -7,8 +8,8 @@ module Test.Booster.Pattern.MatchFun (
test_match_fun,
) where

import Data.Map qualified as Map
import Data.List.NonEmpty qualified as NE
import Data.Map qualified as Map
import Test.Tasty
import Test.Tasty.HUnit

Expand Down Expand Up @@ -50,11 +51,13 @@ symbols =
, let pat = app con1 [var "X" someSort]
subj = app f1 [var "Y" someSort]
in test "constructor and function" pat subj $
MatchIndeterminate $ NE.singleton (pat, subj)
MatchIndeterminate $
NE.singleton (pat, subj)
, let pat = app f1 [var "X" someSort]
subj = app con1 [var "Y" someSort]
in test "function and constructor" pat subj $
MatchIndeterminate $ NE.singleton (pat, subj)
MatchIndeterminate $
NE.singleton (pat, subj)
, let x = var "X" someSort
d = dv differentSort "something"
pat = app con1 [x]
Expand Down Expand Up @@ -143,11 +146,13 @@ varsAndValues =
, let v = var "X" someSort
d = dv someSort ""
in test "dv matching a var (on RHS): indeterminate" d v $
MatchIndeterminate $ NE.singleton (d, v)
MatchIndeterminate $
NE.singleton (d, v)
, let d = dv someSort ""
f = app f1 [d]
in test "dv matching a function call (on RHS): indeterminate" d f $
MatchIndeterminate $ NE.singleton (d, f)
MatchIndeterminate $
NE.singleton (d, f)
, let d = dv someSort ""
c = app con1 [d]
in test "dv matching a constructor (on RHS): fail" d c $
Expand Down Expand Up @@ -183,7 +188,7 @@ andTerms =
"And-term on the right, indeterminate"
d
(AndTerm fa fb)
(MatchIndeterminate $ NE.singleton (d ,AndTerm fa fb))
(MatchIndeterminate $ NE.singleton (d, AndTerm fa fb))
]

kmapTerms :: TestTree
Expand Down Expand Up @@ -229,10 +234,10 @@ kmapTerms =
)
, -- pattern has more assocs than subject
test
"Extra concrete key in pattern, no rest in subject: fail on rest"
concreteKMapWithTwoItems
concreteKMapWithOneItem
(failed $ KeyNotFound [trm| \dv{SortTestKMapKey{}}("key2")|] emptyKMap)
"Extra concrete key in pattern, no rest in subject: fail on rest"
concreteKMapWithTwoItems
concreteKMapWithOneItem
(failed $ KeyNotFound [trm| \dv{SortTestKMapKey{}}("key2")|] emptyKMap)
, -- cases with disjoint keys
test
"Variable key ~= concrete key (and common element) without rest: match key"
Expand Down Expand Up @@ -300,7 +305,7 @@ success assocs =
]

failed :: FailReason -> MatchResult
failed = MatchFailed
failed = MatchFailed

errors :: String -> Term -> Term -> TestTree
errors name pat subj =
Expand Down
18 changes: 12 additions & 6 deletions unit-tests/Test/Booster/Pattern/MatchRule.hs
Original file line number Diff line number Diff line change
Expand Up @@ -432,13 +432,19 @@ internalMaps =
"Fails to match {\"key\" |-> \"value\", A |-> \"value2\"} with {\"key\" |-> \"value\", ...REST}"
concreteAndSymbolicKMapWithTwoItems
concreteKMapWithOneItemAndRest
(failed $ DifferentSymbols ( KMap
testKMapDefinition
[( [trm| A:SortTestKMapKey{}|]
, [trm| \dv{SortTestKMapItem{}}("value2") |]
( failed $
DifferentSymbols
( KMap
testKMapDefinition
[
( [trm| A:SortTestKMapKey{}|]
, [trm| \dv{SortTestKMapItem{}}("value2") |]
)
]
Nothing
)
]
Nothing) (KMap testKMapDefinition [] (Just [trm| REST:SortTestKMap{}|])))
(KMap testKMapDefinition [] (Just [trm| REST:SortTestKMap{}|]))
)
, test
"Can match {\"f()\" |-> \"value\", ...REST} with {\"f()\" |-> B}"
functionKMapWithOneItemAndRest
Expand Down
7 changes: 3 additions & 4 deletions unit-tests/Test/Booster/Pattern/Rewrite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -346,13 +346,12 @@ callsError :: TestTree
callsError =
testGroup
"Calls error when there are unexpected situations"
[ testCase "on wrong argument count in a symbol application" $
[ testCase "on wrong argument count in a symbol application" $
runRewrite
[trm| kCell{}( kseq{}( inj{SomeSort{}, SortKItem{}}( con1{}( \dv{SomeSort{}}("thing"), \dv{SomeSort{}}("thing"), \dv{SomeSort{}}("thing") ) ), C:SortK{}) ) |]
>>= \case
[trm| kCell{}( kseq{}( inj{SomeSort{}, SortKItem{}}( con1{}( \dv{SomeSort{}}("thing"), \dv{SomeSort{}}("thing"), \dv{SomeSort{}}("thing") ) ), C:SortK{}) ) |]
>>= \case
(_, RewriteAborted InternalMatchError{} _) -> pure ()
_ -> assertFailure "success"

]

getsStuckOnFailures :: TestTree
Expand Down

0 comments on commit daf9f2d

Please sign in to comment.