mirror of
https://github.com/github/semantic.git
synced 2024-11-25 02:58:36 +03:00
Merge branch 'master' into one-header-per-file
This commit is contained in:
commit
da3f04100e
@ -29,6 +29,7 @@ library
|
||||
, Diff
|
||||
, Diffing
|
||||
, DiffOutput
|
||||
, Info
|
||||
, Interpreter
|
||||
, Language
|
||||
, Line
|
||||
|
@ -25,6 +25,7 @@ import Data.Monoid
|
||||
import qualified Data.OrderedMap as Map
|
||||
import qualified Data.Text as T
|
||||
import Diff
|
||||
import Info
|
||||
import Line
|
||||
import Patch
|
||||
import Prelude hiding (fst, snd)
|
||||
@ -63,7 +64,7 @@ splitPatchByLines sources patch = wrapTermInPatch <$> splitAndFoldTerm (unPatch
|
||||
-- | Split a term comprised of an Info & Syntax up into one `outTerm` (abstracted by an alignment function & constructor) per line in `Source`.
|
||||
splitAbstractedTerm :: (Applicative f, Coalescent (f (Line (Maybe (Identity outTerm), Range))), Coalescent (f (Line (Maybe (T.Text, outTerm), Range))), Foldable f, TotalCrosswalk f) => (Info -> Syntax leaf outTerm -> outTerm) -> f (Source Char) -> f Info -> Syntax leaf (Adjoined (f (Line (outTerm, Range)))) -> Adjoined (f (Line (outTerm, Range)))
|
||||
splitAbstractedTerm makeTerm sources infos syntax = case syntax of
|
||||
Leaf a -> tsequenceL (pure mempty) $ fmap <$> ((\ categories -> fmap (\ range -> (makeTerm (Info range categories) (Leaf a), range))) <$> (Diff.categories <$> infos)) <*> (linesInRangeOfSource <$> (characterRange <$> infos) <*> sources)
|
||||
Leaf a -> tsequenceL (pure mempty) $ fmap <$> ((\ categories -> fmap (\ range -> (makeTerm (Info range categories) (Leaf a), range))) <$> (Info.categories <$> infos)) <*> (linesInRangeOfSource <$> (characterRange <$> infos) <*> sources)
|
||||
Indexed children -> adjoinChildren sources infos (constructor (Indexed . fmap runIdentity)) (Identity <$> children)
|
||||
Fixed children -> adjoinChildren sources infos (constructor (Fixed . fmap runIdentity)) (Identity <$> children)
|
||||
Keyed children -> adjoinChildren sources infos (constructor (Keyed . Map.fromList)) (Map.toList children)
|
||||
@ -74,7 +75,7 @@ adjoinChildren :: (Copointed c, Functor c, Applicative f, Coalescent (f (Line (M
|
||||
adjoinChildren sources infos constructor children = wrap <$> leadingContext <> lines
|
||||
where (lines, next) = foldr (childLines sources) (mempty, end <$> ranges) children
|
||||
ranges = characterRange <$> infos
|
||||
categories = Diff.categories <$> infos
|
||||
categories = Info.categories <$> infos
|
||||
leadingContext = tsequenceL (pure mempty) $ makeContextLines <$> (linesInRangeOfSource <$> (Range <$> (start <$> ranges) <*> next) <*> sources)
|
||||
wrap = (wrapLineContents <$> (makeBranchTerm constructor <$> categories <*> next) <*>)
|
||||
makeBranchTerm constructor categories next children = let range = unionRangesFrom (rangeAt next) $ Prelude.snd <$> children in
|
||||
|
11
src/Diff.hs
11
src/Diff.hs
@ -1,11 +1,8 @@
|
||||
module Diff where
|
||||
|
||||
import Category
|
||||
import Control.Monad.Free
|
||||
import Data.Functor.Both
|
||||
import Data.Set
|
||||
import Patch
|
||||
import Range
|
||||
import Syntax
|
||||
import Term
|
||||
|
||||
@ -13,14 +10,6 @@ import Term
|
||||
data Annotated a annotation f = Annotated { annotation :: !annotation, syntax :: !(Syntax a f) }
|
||||
deriving (Functor, Eq, Show, Foldable)
|
||||
|
||||
-- | An annotation for a source file, including the source range and semantic
|
||||
-- | categories.
|
||||
data Info = Info { characterRange :: !Range, categories :: !(Set Category) }
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance Categorizable Info where
|
||||
categories = Diff.categories
|
||||
|
||||
-- | An annotated series of patches of terms.
|
||||
type Diff a annotation = Free (Annotated a (Both annotation)) (Patch (Term a annotation))
|
||||
|
||||
|
@ -1,6 +1,6 @@
|
||||
module Diffing where
|
||||
|
||||
import Diff
|
||||
import Info
|
||||
import Interpreter
|
||||
import Language
|
||||
import Parser
|
||||
|
13
src/Info.hs
Normal file
13
src/Info.hs
Normal file
@ -0,0 +1,13 @@
|
||||
module Info where
|
||||
|
||||
import Category
|
||||
import Data.Set
|
||||
import Range
|
||||
|
||||
-- | An annotation for a source file, including the source range and semantic
|
||||
-- | categories.
|
||||
data Info = Info { characterRange :: !Range, categories :: !(Set Category) }
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance Categorizable Info where
|
||||
categories = Info.categories
|
@ -1,7 +1,7 @@
|
||||
module Parser where
|
||||
|
||||
import Category
|
||||
import Diff
|
||||
import Info
|
||||
import Range
|
||||
import Syntax
|
||||
import Term
|
||||
|
@ -2,6 +2,7 @@ module Renderer where
|
||||
|
||||
import Data.Functor.Both
|
||||
import Diff
|
||||
import Info
|
||||
import Source
|
||||
|
||||
-- | A function that will render a diff, given the two source files.
|
||||
|
@ -17,6 +17,7 @@ import Data.OrderedMap hiding (fromList)
|
||||
import qualified Data.Text as T
|
||||
import Data.Vector hiding (toList)
|
||||
import Diff
|
||||
import Info
|
||||
import Line
|
||||
import Range
|
||||
import Renderer
|
||||
|
@ -6,6 +6,7 @@ module Renderer.Patch (
|
||||
|
||||
import Alignment
|
||||
import Diff
|
||||
import Info
|
||||
import Line
|
||||
import Prelude hiding (fst, snd)
|
||||
import qualified Prelude
|
||||
|
@ -10,6 +10,7 @@ import Data.Functor.Both
|
||||
import Data.Monoid
|
||||
import qualified Data.Text.Lazy as TL
|
||||
import Diff
|
||||
import Info
|
||||
import Line
|
||||
import Prelude hiding (div, head, span, fst, snd)
|
||||
import qualified Prelude
|
||||
|
@ -14,6 +14,7 @@ import Data.Adjoined
|
||||
import Data.Copointed
|
||||
import Data.Functor.Both as Both
|
||||
import Diff
|
||||
import Info
|
||||
import qualified Data.Maybe as Maybe
|
||||
import Data.Functor.Identity
|
||||
import Line
|
||||
|
@ -9,6 +9,7 @@ import qualified Data.List as List
|
||||
import qualified Data.Set as Set
|
||||
import Data.Text.Arbitrary ()
|
||||
import Diff
|
||||
import Info
|
||||
import Line
|
||||
import Patch
|
||||
import Prelude hiding (fst, snd)
|
||||
|
@ -6,7 +6,7 @@ import Syntax
|
||||
import Control.Comonad.Cofree
|
||||
import Control.Monad.Free
|
||||
import Patch
|
||||
import Diff
|
||||
import Info
|
||||
import Category
|
||||
import Test.Hspec
|
||||
|
||||
|
@ -1,12 +1,13 @@
|
||||
module PatchOutputSpec where
|
||||
|
||||
import Control.Monad.Free
|
||||
import Data.Functor.Both
|
||||
import Diff
|
||||
import Renderer.Patch
|
||||
import Info
|
||||
import Range
|
||||
import Renderer.Patch
|
||||
import Source
|
||||
import Syntax
|
||||
import Control.Monad.Free
|
||||
import Test.Hspec
|
||||
|
||||
spec :: Spec
|
||||
|
Loading…
Reference in New Issue
Block a user