Skip to content

Commit

Permalink
Add support por callsPrimitive family
Browse files Browse the repository at this point in the history
  • Loading branch information
flbulgarelli committed Feb 4, 2023
1 parent 27827f1 commit 7095aea
Show file tree
Hide file tree
Showing 7 changed files with 87 additions and 3 deletions.
35 changes: 35 additions & 0 deletions spec/ExpectationsCompilerSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -300,6 +300,41 @@ spec = do
run (py "x['y'] = 10") "*" "UsesGetAt" `shouldBe` False
run (py "x['y'] = 10") "*" "UsesSetAt" `shouldBe` True

it "works with primitive operators call in py - single matcher" $ do
run (py "len('hello')") "*" "CallsSize" `shouldBe` True
run (py "len('hello')") "*" "CallsSize:WithLiteral" `shouldBe` True
run (py "len('hello')") "*" "CallsSize:WithString:\"hello\"" `shouldBe` True
run (py "len('hello')") "*" "CallsSize:WithString:\"baz\"" `shouldBe` False

it "works with primitive operators call in py - two basic matchers" $ do
run (py "x[0]") "*" "CallsGetAt" `shouldBe` True

run (py "x[0]") "*" "CallsGetAt:WithAnything" `shouldBe` True
run (py "x[0]") "*" "CallsGetAt:WithLiteral" `shouldBe` False

run (py "x[0]") "*" "CallsGetAt:WithAnything:WithAnything" `shouldBe` True
run (py "x[0]") "*" "CallsGetAt:WithNonliteral:WithAnything" `shouldBe` True
run (py "x[0]") "*" "CallsGetAt:WithNonliteral:WithLiteral" `shouldBe` True

it "works with primitive operators call in py - two matchers with args" $ do
run (py "x[0]") "*" "CallsGetAt:WithAnything:WithLiteral" `shouldBe` True
run (py "x[0]") "*" "CallsGetAt:WithAnything:WithNumber:0" `shouldBe` True
run (py "x[0]") "*" "CallsGetAt:WithAnything:WithNumber:2" `shouldBe` False
run (py "x[0]") "*" "CallsSetAt:WithAnything:WithNumber:0" `shouldBe` False

it "works with primitive operators call in py - three matchers" $ do
run (py "x[0] = 9") "*" "CallsGetAt:WithAnything:WithNumber:0" `shouldBe` False
run (py "x[0] = 9") "*" "CallsSetAt:WithAnything:WithNumber:5" `shouldBe` False
run (py "x[0] = 9") "*" "CallsSetAt:WithAnything:WithNumber:0" `shouldBe` True

run (py "x[0] = 9") "*" "CallsSetAt:WithAnything:WithNumber:0:WithNumber:9" `shouldBe` True
run (py "x[0] = 9") "*" "CallsSetAt:WithAnything:WithNumber:0:WithNumber:0" `shouldBe` False

run (py "x['y'] = 10") "*" "CallsGetAt:WithAnything:WithString:\"y\"" `shouldBe` False
run (py "x['y'] = 10") "*" "CallsSetAt:WithAnything:WithString:\"j\"" `shouldBe` False
run (py "x['y'] = 10") "*" "CallsSetAt:WithAnything:WithString:\"y\"" `shouldBe` True
run (py "x['y'] = 10") "*" "CallsSetAt:WithAnything:WithString:\"y\":WithNumber:10" `shouldBe` True

it "works with primitive operators essence with ast" $ do
run (Primitive Equal) "*" "IsEqual" `shouldBe` True
run (Primitive NotEqual) "*" "IsEqual" `shouldBe` False
Expand Down
27 changes: 27 additions & 0 deletions spec/GenericSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -254,6 +254,33 @@ spec = do
it "is False when using a matcher that does not match" $ do
(callsMatching (with . isNumber $ 1) anyone) (hs "f = g 2") `shouldBe` False

describe "callsPrimitive" $ do
it "is True on direct usage in entry point" $ do
callsPrimitive GetAt (py3 "x[5]") `shouldBe` True
callsPrimitive SetAt (py3 "x[5] = 0") `shouldBe` True
callsPrimitive Slice (py3 "x[5:6]") `shouldBe` True
callsPrimitive Size (py3 "len(x)") `shouldBe` True

it "is False if there is no usage" $ do
callsPrimitive SetAt (py3 "x[5]") `shouldBe` False
callsPrimitive Slice (py3 "x[5] = 0") `shouldBe` False
callsPrimitive Size (py3 "x[5:6]") `shouldBe` False
callsPrimitive GetAt (py3 "len(x)") `shouldBe` False

it "is True when using a matcher that matches" $ do
(callsPrimitiveMatching (with . isString $ "hello") Size) (py3 "len('hello')") `shouldBe` True
(callsPrimitiveMatching (with isLiteral) Size) (py3 "len('hello')") `shouldBe` True
(callsPrimitiveMatching (with isLiteral) Size) (py3 "len([])") `shouldBe` True
(callsPrimitiveMatching (withEvery [isAnything, isAnything, isNumber 0]) SetAt) (py3 "x['i'] = 0") `shouldBe` True
(callsPrimitiveMatching (withEvery [isAnything, isString "i", isNumber 0]) SetAt) (py3 "x['i'] = 0") `shouldBe` True

it "is False when using a matcher that does not match" $ do
(callsPrimitiveMatching (with . isString $ "hello") Size) (py3 "len('bye!!')") `shouldBe` False
(callsPrimitiveMatching (with isLiteral) Size) (py3 "len(greet)") `shouldBe` False
(callsPrimitiveMatching (with . isString $ "hello") Size) (py3 "len([])") `shouldBe` False
(callsPrimitiveMatching (withEvery [isAnything, isAnything, isNumber 0]) SetAt) (py3 "x['i'] = 5") `shouldBe` False
(callsPrimitiveMatching (withEvery [isAnything, isString "i", isNumber 0]) SetAt) (py3 "x['j'] = 0") `shouldBe` False

describe "usesLogic" $ do
it "is when it is used" $ do
usesLogic (hs "f x y = x || y") `shouldBe` True
Expand Down
5 changes: 4 additions & 1 deletion src/Language/Mulang/Analyzer/EdlQueryCompiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import Language.Mulang.Consult (Consult)
import Language.Mulang.Counter (plus)
import Language.Mulang.Inspector.Primitive (atLeast, atMost, exactly)
import Language.Mulang.Inspector.Literal (isNil, isNumber, isBool, isChar, isString, isSymbol, isSelf, isLiteral)
import Language.Mulang.Analyzer.Synthesizer (decodeIsInspection, decodeUsageInspection, decodeDeclarationInspection)
import Language.Mulang.Analyzer.Synthesizer (decodeIsInspection, decodeCallsInspection, decodeUsageInspection, decodeDeclarationInspection)

import qualified Language.Mulang.Edl.Expectation as E

Expand Down Expand Up @@ -93,6 +93,7 @@ compileCounter = f
f "UsesSwitch" m = plainMatching countSwitches m
f "UsesWhile" m = plainMatching countWhiles m
f "UsesYield" m = plainMatching countYiels m
f (primitiveCalls -> Just p) m = plainMatching (\m -> countPrimitiveCalls m p) m
f (primitiveUsage -> Just p) E.Unmatching = plain (countUsesPrimitive p)
f _ _ = Nothing

Expand Down Expand Up @@ -183,6 +184,7 @@ compileInspection = f
f "UsesType" E.Unmatching = bound usesType
f "UsesWhile" m = plainMatching usesWhileMatching m
f "UsesYield" m = plainMatching usesYieldMatching m
f (primitiveCalls -> Just p) m = plainMatching (\m -> callsPrimitiveMatching m p) m
f (primitiveDeclaration -> Just p) E.Unmatching = plain (declaresPrimitive p)
f (primitiveUsage -> Just p) E.Unmatching = plain (usesPrimitive p)
f (primitiveEssence -> Just p) E.Unmatching = plain (isPrimitive p)
Expand All @@ -191,6 +193,7 @@ compileInspection = f
primitiveEssence = decodeIsInspection
primitiveUsage = decodeUsageInspection
primitiveDeclaration = decodeDeclarationInspection
primitiveCalls = decodeCallsInspection

contextual :: ContextualizedConsult a -> Maybe (ContextualizedBoundConsult a)
contextual = Just . contextualizedBind
Expand Down
3 changes: 2 additions & 1 deletion src/Language/Mulang/Analyzer/ExpectationsCompiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ compileScope _ q = Decontextualize q
compileCQuery :: [String] -> CQuery
compileCQuery [] = compileCQuery ["Parses","*"]
compileCQuery [verb] = compileCQuery [verb,"*"]
compileCQuery [verb,name] | Map.member name nullaryMatchers = compileCQuery [verb,"*",name]
compileCQuery (verb:name:args) | Map.member name nullaryMatchers = compileCQuery (verb:"*":name:args)
compileCQuery (verb:"WithChar":args) = compileCQuery (verb:"*":"WithChar":args)
compileCQuery (verb:"WithNumber":args) = compileCQuery (verb:"*":"WithNumber":args)
compileCQuery (verb:"WithString":args) = compileCQuery (verb:"*":"WithString":args)
Expand Down Expand Up @@ -63,6 +63,7 @@ compileMatcher = matching . f

nullaryMatchers =
Map.fromList [
("WithAnything", IsAnything),
("WithFalse", IsFalse),
("WithLiteral", IsLiteral),
("WithLogic", IsLogic),
Expand Down
4 changes: 4 additions & 0 deletions src/Language/Mulang/Analyzer/Synthesizer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Language.Mulang.Analyzer.Synthesizer (
encodeUsageInspection,
encodeDeclarationInspection,
decodeIsInspection,
decodeCallsInspection,
decodeUsageInspection,
decodeDeclarationInspection,
generateInspectionEncodingRules,
Expand Down Expand Up @@ -40,6 +41,9 @@ encodeInspection prefix = (prefix ++) . show
decodeIsInspection :: Decoder Operator
decodeIsInspection = decodeInspection "Is"

decodeCallsInspection :: Decoder Operator
decodeCallsInspection = decodeInspection "Calls"

decodeUsageInspection :: Decoder Operator
decodeUsageInspection = decodeInspection "Uses"

Expand Down
14 changes: 14 additions & 0 deletions src/Language/Mulang/Inspector/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,10 @@ module Language.Mulang.Inspector.Generic (
assignsMatching,
calls,
callsMatching,
callsPrimitive,
callsPrimitiveMatching,
countCalls,
countPrimitiveCalls,
countFors,
countFunctions,
countIfs,
Expand Down Expand Up @@ -100,6 +103,17 @@ countCalls matcher p = countExpressions f
where f (Call (Reference id) arguments) = p id && matcher arguments
f _ = False

callsPrimitive :: Operator -> Inspection
callsPrimitive = unmatching callsPrimitiveMatching

callsPrimitiveMatching :: Matcher -> Operator -> Inspection
callsPrimitiveMatching matcher = positive . (countPrimitiveCalls matcher)

countPrimitiveCalls :: Matcher -> Operator -> Counter
countPrimitiveCalls matcher o = countExpressions f
where f (Call callee arguments) = isPrimitive o callee && matcher arguments
f _ = False

delegates :: BoundInspection
delegates = decontextualize . delegates'

Expand Down
2 changes: 1 addition & 1 deletion src/Language/Mulang/Inspector/Matcher.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Language.Mulang.Inspector.Primitive (Inspection)

type Matcher = [Expression] -> Bool

-- | Creates a simple matcher that evaluates the given inspection only againts the first of its arguments
-- | Creates a simple matcher that evaluates the given inspection only against the first of its arguments
with :: Inspection -> Matcher
with inspection = inspection . head

Expand Down

0 comments on commit 7095aea

Please sign in to comment.