2018-03-27 23:14:30 +03:00
|
|
|
{-# LANGUAGE TypeOperators #-}
|
|
|
|
|
|
|
|
module Matching.Go.Spec (spec) where
|
|
|
|
|
2018-10-30 18:01:28 +03:00
|
|
|
import Control.Matching
|
2018-03-27 23:14:30 +03:00
|
|
|
import Data.Abstract.Module
|
|
|
|
import Data.List
|
2018-05-02 19:00:15 +03:00
|
|
|
import Data.Sum
|
2018-03-27 23:14:30 +03:00
|
|
|
import qualified Data.Syntax.Declaration as Decl
|
|
|
|
import qualified Data.Syntax.Literal as Lit
|
|
|
|
import qualified Data.Syntax.Statement as Stmt
|
2018-05-31 05:32:22 +03:00
|
|
|
import Data.Text (Text)
|
2018-03-27 23:14:30 +03:00
|
|
|
import SpecHelpers
|
|
|
|
|
2018-05-31 05:32:22 +03:00
|
|
|
-- This gets the Text contents of all integers
|
|
|
|
integerMatcher :: (Lit.Integer :< fs) => Matcher (Term (Sum fs) ann) Text
|
2018-11-06 00:56:49 +03:00
|
|
|
integerMatcher = enter Lit.integerContent
|
2018-03-27 23:14:30 +03:00
|
|
|
|
|
|
|
-- This matches all for-loops with its index variable new variable bound to 0,
|
|
|
|
-- e.g. `for i := 0; i < 10; i++`
|
|
|
|
loopMatcher :: ( Stmt.For :< fs
|
|
|
|
, Stmt.Assignment :< fs
|
|
|
|
, Lit.Integer :< fs)
|
|
|
|
=> TermMatcher fs ann
|
|
|
|
loopMatcher = target <* go where
|
2018-11-06 00:56:49 +03:00
|
|
|
go = enter Stmt.forBefore
|
|
|
|
>>> enter Stmt.assignmentValue
|
|
|
|
>>> enter Lit.integerContent
|
Give Control.Matching API better ergonomics.
Given that @tclem and I have found the matcher API frustrating, I've
taken a stab at improving its ergonomics, and I've found some success
in separating composition of matchers from predicate-based narrowing
thereof.
The biggest change here is the elimination of the old `match`
combinator, which proved to be clumsy in that it complected narrowing
and composition. Top-down matching combinators are now written with
the `need` combinator and the `>>>` combinator, which is more readable
and more versatile. Here's a matcher that accepts functions with
Python docstrings:
```haskell
docstringMatcher :: ( Decl.Function :< fs
, [] :< fs
, Lit.TextElement :< fs
, term ~ Term (Sum fs) ann
) => Matcher term term
docstringMatcher = target <*
(need Decl.functionBody
>>> narrow @[]
>>> mhead
>>> narrow @Lit.TextElement
>>> ensure Lit.isTripleQuoted))
```
Pretty readable, right? Each step of the tree regular expression -
choosing function bodies, ensuring said bodies are lists, examining
the first element, and choosing only TextElements containing
triple-quoted strings - is made implicit. The old way would have
looked something like this:
```haskell
docstringMatcher = target <* match Decl.functionBody
$ narrow
$ matchM listToMaybe
$ target <* ensure Lit.isTripleQuoted
```
which is a good deal more disorganized and less flexible
in the quite-common case of applying functions during a
matching pass. Separating the act of composition from
function application is a big win here.
Further comments are inline.
2018-11-03 02:25:29 +03:00
|
|
|
>>> ensure (== "0")
|
|
|
|
|
2018-03-27 23:14:30 +03:00
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = describe "matching/go" $ do
|
|
|
|
it "extracts integers" $ do
|
2018-04-22 17:47:59 +03:00
|
|
|
parsed <- parseFile goParser "test/fixtures/go/matching/integers.go"
|
Give Control.Matching API better ergonomics.
Given that @tclem and I have found the matcher API frustrating, I've
taken a stab at improving its ergonomics, and I've found some success
in separating composition of matchers from predicate-based narrowing
thereof.
The biggest change here is the elimination of the old `match`
combinator, which proved to be clumsy in that it complected narrowing
and composition. Top-down matching combinators are now written with
the `need` combinator and the `>>>` combinator, which is more readable
and more versatile. Here's a matcher that accepts functions with
Python docstrings:
```haskell
docstringMatcher :: ( Decl.Function :< fs
, [] :< fs
, Lit.TextElement :< fs
, term ~ Term (Sum fs) ann
) => Matcher term term
docstringMatcher = target <*
(need Decl.functionBody
>>> narrow @[]
>>> mhead
>>> narrow @Lit.TextElement
>>> ensure Lit.isTripleQuoted))
```
Pretty readable, right? Each step of the tree regular expression -
choosing function bodies, ensuring said bodies are lists, examining
the first element, and choosing only TextElements containing
triple-quoted strings - is made implicit. The old way would have
looked something like this:
```haskell
docstringMatcher = target <* match Decl.functionBody
$ narrow
$ matchM listToMaybe
$ target <* ensure Lit.isTripleQuoted
```
which is a good deal more disorganized and less flexible
in the quite-common case of applying functions during a
matching pass. Separating the act of composition from
function application is a big win here.
Further comments are inline.
2018-11-03 02:25:29 +03:00
|
|
|
let matched = matchRecursively integerMatcher parsed
|
2018-03-27 23:14:30 +03:00
|
|
|
sort matched `shouldBe` ["1", "2", "3"]
|
|
|
|
|
|
|
|
it "counts for loops" $ do
|
2018-04-22 17:47:59 +03:00
|
|
|
parsed <- parseFile goParser "test/fixtures/go/matching/for.go"
|
Give Control.Matching API better ergonomics.
Given that @tclem and I have found the matcher API frustrating, I've
taken a stab at improving its ergonomics, and I've found some success
in separating composition of matchers from predicate-based narrowing
thereof.
The biggest change here is the elimination of the old `match`
combinator, which proved to be clumsy in that it complected narrowing
and composition. Top-down matching combinators are now written with
the `need` combinator and the `>>>` combinator, which is more readable
and more versatile. Here's a matcher that accepts functions with
Python docstrings:
```haskell
docstringMatcher :: ( Decl.Function :< fs
, [] :< fs
, Lit.TextElement :< fs
, term ~ Term (Sum fs) ann
) => Matcher term term
docstringMatcher = target <*
(need Decl.functionBody
>>> narrow @[]
>>> mhead
>>> narrow @Lit.TextElement
>>> ensure Lit.isTripleQuoted))
```
Pretty readable, right? Each step of the tree regular expression -
choosing function bodies, ensuring said bodies are lists, examining
the first element, and choosing only TextElements containing
triple-quoted strings - is made implicit. The old way would have
looked something like this:
```haskell
docstringMatcher = target <* match Decl.functionBody
$ narrow
$ matchM listToMaybe
$ target <* ensure Lit.isTripleQuoted
```
which is a good deal more disorganized and less flexible
in the quite-common case of applying functions during a
matching pass. Separating the act of composition from
function application is a big win here.
Further comments are inline.
2018-11-03 02:25:29 +03:00
|
|
|
let matched = matchRecursively @[] loopMatcher parsed
|
2018-03-27 23:14:30 +03:00
|
|
|
length matched `shouldBe` 2
|