mirror of
https://github.com/github/semantic.git
synced 2024-12-28 09:21:35 +03:00
Merge branch 'master' into substructural-diffing
This commit is contained in:
commit
c7c1161310
@ -17,7 +17,6 @@ library
|
||||
, Alignment
|
||||
, Category
|
||||
, Data.Align.Generic
|
||||
, Data.Bifunctor.Symmetrical
|
||||
, Data.Blob
|
||||
, Data.Error
|
||||
, Data.Functor.Both
|
||||
|
@ -1,18 +0,0 @@
|
||||
module Data.Bifunctor.Symmetrical where
|
||||
|
||||
import Data.Bifunctor
|
||||
import Data.These
|
||||
import Data.Tuple (swap)
|
||||
|
||||
class Bifunctor s => Symmetrical s where
|
||||
mirror :: s a b -> s b a
|
||||
|
||||
|
||||
instance Symmetrical (,) where
|
||||
mirror = swap
|
||||
|
||||
instance Symmetrical Either where
|
||||
mirror = either Right Left
|
||||
|
||||
instance Symmetrical These where
|
||||
mirror = these That This (flip These)
|
@ -4,7 +4,6 @@ module Diff where
|
||||
import Data.Aeson
|
||||
import Data.Bifoldable
|
||||
import Data.Bifunctor
|
||||
import Data.Bifunctor.Symmetrical
|
||||
import Data.Bitraversable
|
||||
import Data.Foldable (toList)
|
||||
import Data.Functor.Classes
|
||||
@ -145,10 +144,6 @@ instance (Show1 syntax, Show ann1, Show ann2, Show recur) => Show (DiffF syntax
|
||||
instance Functor syntax => Bifunctor (Diff syntax) where
|
||||
bimap f g = go where go = Diff . trimap f g go . unDiff
|
||||
|
||||
instance Functor syntax => Symmetrical (Diff syntax) where
|
||||
mirror (Diff (Patch p)) = Diff (Patch (mirror (bimap (fmap mirror) (fmap mirror) p)))
|
||||
mirror (Diff (Merge m)) = Diff (Merge (bimap mirror mirror m))
|
||||
|
||||
instance Foldable syntax => Bifoldable (Diff syntax) where
|
||||
bifoldMap f g = go where go = trifoldMap f g go . unDiff
|
||||
|
||||
|
@ -11,7 +11,6 @@ import Data.Aeson
|
||||
import Data.Align
|
||||
import Data.Bifoldable
|
||||
import Data.Bifunctor
|
||||
import Data.Bifunctor.Symmetrical
|
||||
import Data.Bitraversable
|
||||
import Data.Functor.Classes
|
||||
import Data.JSON.Fields
|
||||
@ -48,9 +47,6 @@ instance Bifunctor Patch where
|
||||
bimap _ g (Insert b) = Insert (g b)
|
||||
bimap f g (Replace a b) = Replace (f a) (g b)
|
||||
|
||||
instance Symmetrical Patch where
|
||||
mirror = patch Insert Delete (flip Replace)
|
||||
|
||||
instance Bifoldable Patch where
|
||||
bifoldMap f _ (Delete a) = f a
|
||||
bifoldMap _ g (Insert b) = g b
|
||||
|
@ -205,15 +205,15 @@ runParser Options{..} blob@Blob{..} = go
|
||||
logTiming "ts ast parse" $
|
||||
liftIO ((Right <$> parseToAST language blob) `catchError` (pure . Left . toException)) >>= either throwError pure
|
||||
AssignmentParser parser assignment -> do
|
||||
ast <- go parser `catchError` \ err -> writeLog Error "failed parsing" blobFields >> throwError err
|
||||
ast <- go parser `catchError` \ err -> writeLog Error "failed parsing" (("tag", "parse") : blobFields) >> throwError err
|
||||
logTiming "assign" $ case Assignment.assign blobSource assignment ast of
|
||||
Left err -> do
|
||||
let formatted = Error.formatError optionsPrintSource (optionsIsTerminal && optionsEnableColour) blob err
|
||||
writeLog Error formatted blobFields
|
||||
writeLog Error formatted (("tag", "assign") : blobFields)
|
||||
throwError (toException err)
|
||||
Right term -> do
|
||||
for_ (errors term) $ \ err ->
|
||||
writeLog Warning (Error.formatError optionsPrintSource (optionsIsTerminal && optionsEnableColour) blob err) blobFields
|
||||
writeLog Warning (Error.formatError optionsPrintSource (optionsIsTerminal && optionsEnableColour) blob err) (("tag", "assign") : blobFields)
|
||||
pure term
|
||||
TreeSitterParser tslanguage -> logTiming "ts parse" $ liftIO (treeSitterParser tslanguage blob)
|
||||
MarkdownParser -> logTiming "cmark parse" $ pure (cmarkParser blobSource)
|
||||
|
Loading…
Reference in New Issue
Block a user