1
1
mirror of https://github.com/github/semantic.git synced 2024-11-28 10:15:55 +03:00

Merge remote-tracking branch 'origin/master' into repl-effect

This commit is contained in:
Patrick Thomson 2018-10-30 15:58:00 -04:00
commit cb54dd7aed
7 changed files with 14 additions and 9 deletions

View File

@ -41,7 +41,6 @@ library
, Control.Abstract.Evaluator
, Control.Abstract.Heap
, Control.Abstract.Hole
, Control.Abstract.Matching
, Control.Abstract.Modules
, Control.Abstract.Primitive
, Control.Abstract.PythonPackage
@ -51,7 +50,8 @@ library
-- Effects
, Control.Effect.Interpose
, Control.Effect.REPL
-- Rewriting
-- Matching and rewriting DSLs
, Control.Matching
, Control.Rewriting
-- Datatypes for abstract interpretation
, Data.Abstract.Address.Hole

View File

@ -1,6 +1,6 @@
{-# LANGUAGE GADTs, TypeOperators #-}
module Control.Abstract.Matching
module Control.Matching
( Matcher
, TermMatcher
, target
@ -9,6 +9,7 @@ module Control.Abstract.Matching
, matchM
, narrow
, narrow'
, purely
, succeeds
, fails
, runMatcher
@ -71,6 +72,10 @@ target = Target
ensure :: (t -> Bool) -> Matcher t ()
ensure f = target >>= \c -> guard (f c)
-- | Promote a pure function to a 'Matcher'.
purely :: (a -> b) -> Matcher a b
purely f = fmap f target
-- | 'matchm' takes a modification function and a new matcher action the target parameter of which
-- is the result of the modification function. If the modification function returns 'Just' when
-- applied to the current 'target', the given matcher is executed with the result of that 'Just'

View File

@ -74,7 +74,7 @@ import Data.Profunctor
import qualified Data.Sum as Sum hiding (apply)
import Data.Text (pack)
import Control.Abstract.Matching (Matcher, stepMatcher)
import Control.Matching (Matcher, stepMatcher)
import Data.History as History
import Data.Term

View File

@ -8,7 +8,7 @@ module Matching.Core
import Prologue
import Control.Abstract.Matching
import Control.Matching
import qualified Data.Syntax.Literal as Literal
import Data.Term

View File

@ -9,7 +9,7 @@ import Control.Category
import qualified Data.ByteString.Char8 as BC
import Text.Show.Pretty (pPrint)
import Control.Abstract.Matching
import Control.Matching
import Control.Rewriting hiding (fromMatcher, target)
import Data.Blob
import Data.File

View File

@ -8,7 +8,7 @@ import qualified Data.ByteString as B
import Data.Either
import Data.Text (Text)
import Control.Abstract.Matching as Matching
import Control.Matching as Matching
import Control.Rewriting as Rewriting
import Data.History as History
import qualified Data.Source as Source
@ -21,7 +21,7 @@ import Reprinting.Pipeline
onTrees :: ( Literal.TextElement :< syn
, Literal.KeyValue :< syn
, Apply Functor syn
, term ~ Term (Sum syn) History
, term ~ Term (Sum syn) History
) => Rewrite (env, term) (Literal.Hash term)
onTrees = do
Literal.Hash els <- Rewriting.target

View File

@ -2,7 +2,7 @@
module Matching.Go.Spec (spec) where
import Control.Abstract.Matching
import Control.Matching
import Data.Abstract.Module
import Data.List
import Data.Sum