1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 00:42:33 +03:00

Rename Sequenceable to Mergeable.

This commit is contained in:
Rob Rix 2016-07-22 17:38:10 -04:00
parent 0b85a1826d
commit 9ae7f52e8f
6 changed files with 34 additions and 34 deletions

View File

@ -21,8 +21,8 @@ library
, Data.Functor.Both
, Data.RandomWalkSimilarity
, Data.Record
, Data.Sequenceable
, Data.Sequenceable.Generic
, Data.Mergeable
, Data.Mergeable.Generic
, Data.These.Arbitrary
, Diff
, Diff.Arbitrary

18
src/Data/Mergeable.hs Normal file
View File

@ -0,0 +1,18 @@
{-# LANGUAGE DefaultSignatures #-}
module Data.Mergeable where
import Data.Mergeable.Generic
import GHC.Generics
import Prologue
-- Classes
class Functor t => Mergeable t where
sequenceAlt :: Alternative f => t (f a) -> f (t a)
default sequenceAlt :: (Generic1 t, GMergeable (Rep1 t), Alternative f) => t (f a) -> f (t a)
sequenceAlt = genericSequenceAlt
-- Instances
instance Mergeable [] where sequenceAlt = gsequenceAlt

View File

@ -1,42 +1,42 @@
{-# LANGUAGE TypeOperators #-}
module Data.Sequenceable.Generic where
module Data.Mergeable.Generic where
import GHC.Generics
import Prologue
-- Classes
class GSequenceable t where
class GMergeable t where
gsequenceAlt :: Alternative f => t (f a) -> f (t a)
genericSequenceAlt :: (Generic1 t, GSequenceable (Rep1 t), Alternative f) => t (f a) -> f (t a)
genericSequenceAlt :: (Generic1 t, GMergeable (Rep1 t), Alternative f) => t (f a) -> f (t a)
genericSequenceAlt = fmap to1 . gsequenceAlt . from1
-- Instances
instance GSequenceable U1 where
instance GMergeable U1 where
gsequenceAlt _ = pure U1
instance GSequenceable Par1 where
instance GMergeable Par1 where
gsequenceAlt (Par1 a) = Par1 <$> a
instance GSequenceable (K1 i c) where
instance GMergeable (K1 i c) where
gsequenceAlt (K1 a) = pure (K1 a)
instance GSequenceable f => GSequenceable (Rec1 f) where
instance GMergeable f => GMergeable (Rec1 f) where
gsequenceAlt (Rec1 a) = Rec1 <$> gsequenceAlt a
instance GSequenceable f => GSequenceable (M1 i c f) where
instance GMergeable f => GMergeable (M1 i c f) where
gsequenceAlt (M1 a) = M1 <$> gsequenceAlt a
instance (GSequenceable f, GSequenceable g) => GSequenceable (f :+: g) where
instance (GMergeable f, GMergeable g) => GMergeable (f :+: g) where
gsequenceAlt (L1 a) = L1 <$> gsequenceAlt a
gsequenceAlt (R1 b) = R1 <$> gsequenceAlt b
instance (GSequenceable f, GSequenceable g) => GSequenceable (f :*: g) where
instance (GMergeable f, GMergeable g) => GMergeable (f :*: g) where
gsequenceAlt (a :*: b) = (:*:) <$> gsequenceAlt a <*> gsequenceAlt b
instance GSequenceable [] where
instance GMergeable [] where
gsequenceAlt (x:xs) = ((:) <$> x <|> pure identity) <*> gsequenceAlt xs
gsequenceAlt [] = pure []

View File

@ -1,18 +0,0 @@
{-# LANGUAGE DefaultSignatures #-}
module Data.Sequenceable where
import Data.Sequenceable.Generic
import GHC.Generics
import Prologue
-- Classes
class Functor t => Sequenceable t where
sequenceAlt :: Alternative f => t (f a) -> f (t a)
default sequenceAlt :: (Generic1 t, GSequenceable (Rep1 t), Alternative f) => t (f a) -> f (t a)
sequenceAlt = genericSequenceAlt
-- Instances
instance Sequenceable [] where sequenceAlt = gsequenceAlt

View File

@ -5,7 +5,7 @@ module Diff where
import Prologue
import Data.Functor.Foldable as Foldable
import Data.Functor.Both as Both
import Data.Sequenceable
import Data.Mergeable
import Patch
import Syntax
import Term

View File

@ -1,7 +1,7 @@
{-# LANGUAGE DeriveAnyClass #-}
module Syntax where
import Data.Sequenceable
import Data.Mergeable
import GHC.Generics
import Prologue
import Test.QuickCheck hiding (Fixed)
@ -17,7 +17,7 @@ data Syntax
| Indexed [f]
-- | An ordered branch of child nodes, expected to be of fixed length in the grammar, e.g. a binary operator & its operands.
| Fixed [f]
deriving (Eq, Foldable, Functor, Generic, Generic1, Ord, Sequenceable, Show, Traversable)
deriving (Eq, Foldable, Functor, Generic, Generic1, Ord, Mergeable, Show, Traversable)
-- Instances