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 12, 2024
1 parent 0148d32 commit 2efdf42
Show file tree
Hide file tree
Showing 3 changed files with 29 additions and 29 deletions.
6 changes: 3 additions & 3 deletions 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(..), (><))
import Data.Sequence (Seq (..), (><))
import Data.Sequence qualified as Seq

import Data.Set (Set)
Expand All @@ -36,9 +36,10 @@ import Booster.Pattern.Base
import Booster.Pattern.Util (
checkSymbolIsAc,
freeVariables,
isConcrete,
isConstructorSymbol,
sortOfTerm,
substituteInTerm, isConcrete,
substituteInTerm,
)
import Data.ByteString (ByteString)
import Data.List (partition)
Expand Down Expand Up @@ -554,7 +555,6 @@ matchLists
addIndeterminate surplusLeft surplusRight
{-# INLINE matchLists #-}


------ Internalised Maps
matchMaps :: MatchType -> Term -> Term -> StateT MatchState (Except MatchResult) ()
matchMaps
Expand Down
10 changes: 5 additions & 5 deletions unit-tests/Test/Booster/Pattern/MatchEval.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ import Booster.Pattern.UnifiedMatcher
import Booster.Syntax.Json.Internalise (trm)
import Test.Booster.Fixture

test_match_eval:: TestTree
test_match_eval :: TestTree
test_match_eval =
testGroup
"Equation/simplification matching"
Expand Down Expand Up @@ -235,10 +235,10 @@ kmapTerms =
, -- pattern has more assocs than subject
let patRest = kmap [(dv kmapKeySort "key2", dv kmapElementSort "value2")] Nothing
in test
"Extra concrete key in pattern, no rest in subject: fail on rest"
concreteKMapWithTwoItems
concreteKMapWithOneItem
(failed $ DifferentValues patRest emptyKMap)
"Extra concrete key in pattern, no rest in subject: fail on rest"
concreteKMapWithTwoItems
concreteKMapWithOneItem
(failed $ DifferentValues patRest emptyKMap)
, -- cases with disjoint keys
test
"Variable key ~= concrete key (and common element) without rest: match key"
Expand Down
42 changes: 21 additions & 21 deletions unit-tests/Test/Booster/Pattern/MatchRewrite.hs
Original file line number Diff line number Diff line change
Expand Up @@ -428,27 +428,27 @@ internalMaps =
)
]
)
-- TODO: re-enable once we re-factor the map matching
-- this would not produce a matchign substitution and should therefore fail
-- at match time
-- , test
-- "Fails to match {\"key\" |-> \"value\", A |-> \"value2\"} with {\"key\" |-> \"value\", ...REST}"
-- concreteAndSymbolicKMapWithTwoItems
-- concreteKMapWithOneItemAndRest
-- ( failed $
-- DifferentSymbols
-- ( KMap
-- testKMapDefinition
-- [
-- ( [trm| A:SortTestKMapKey{}|]
-- , [trm| \dv{SortTestKMapItem{}}("value2") |]
-- )
-- ]
-- Nothing
-- )
-- (KMap testKMapDefinition [] (Just [trm| REST:SortTestKMap{}|]))
-- )
, test
, -- TODO: re-enable once we re-factor the map matching
-- this would not produce a matchign substitution and should therefore fail
-- at match time
-- , test
-- "Fails to match {\"key\" |-> \"value\", A |-> \"value2\"} with {\"key\" |-> \"value\", ...REST}"
-- concreteAndSymbolicKMapWithTwoItems
-- concreteKMapWithOneItemAndRest
-- ( failed $
-- DifferentSymbols
-- ( KMap
-- testKMapDefinition
-- [
-- ( [trm| A:SortTestKMapKey{}|]
-- , [trm| \dv{SortTestKMapItem{}}("value2") |]
-- )
-- ]
-- Nothing
-- )
-- (KMap testKMapDefinition [] (Just [trm| REST:SortTestKMap{}|]))
-- )
test
"Can match {\"f()\" |-> \"value\", ...REST} with {\"f()\" |-> B}"
functionKMapWithOneItemAndRest
functionKMapWithOneItem
Expand Down

0 comments on commit 2efdf42

Please sign in to comment.