1
1
mirror of https://github.com/github/semantic.git synced 2024-12-20 21:31:48 +03:00
semantic/test/Rewriting/Python/Spec.hs
2018-12-11 17:21:39 -05:00

40 lines
1.4 KiB
Haskell

{-# LANGUAGE TypeFamilies, TypeOperators #-}
module Rewriting.Python.Spec (spec) where
import Control.Arrow
import Control.Rewriting
import Data.Abstract.Module
import Data.List
import Data.Sum
import qualified Data.Syntax.Declaration as Decl
import qualified Data.Syntax.Literal as Lit
import qualified Data.Syntax.Statement as Stmt
import Data.Text (Text)
import SpecHelpers
-- This gets the Text contents of all integers
docstringMatcher :: ( Decl.Function :< fs
, [] :< fs
, Lit.TextElement :< fs
, term ~ Term (Sum fs) ann
) => Rewrite term (TermF Decl.Function ann term)
docstringMatcher =
narrowF <* (enter Decl.functionBody
>>> narrow @[]
>>> mhead
>>> narrow @Lit.TextElement
>>> ensure Lit.isTripleQuoted)
spec :: Spec
spec = describe "matching/python" $ do
it "matches top-level docstrings" $ do
parsed <- parseFile pythonParser "test/fixtures/python/matching/docstrings.py"
let matched = recursively @[] docstringMatcher parsed
length matched `shouldBe` 2
it "matches docstrings recursively" $ do
parsed <- parseFile pythonParser "test/fixtures/python/matching/docstrings_nested.py"
let matched = recursively @[] docstringMatcher parsed
length matched `shouldBe` 3