1
1
mirror of https://github.com/github/semantic.git synced 2024-12-29 18:06:14 +03:00

Move the other arbitrary instances into ArbitraryTerm.

This commit is contained in:
Rob Rix 2016-03-15 11:17:47 -04:00
parent 86f41d4ce8
commit 01f817a77e
2 changed files with 30 additions and 24 deletions

View File

@ -6,7 +6,7 @@ import Test.QuickCheck hiding (Fixed)
import Data.Text.Arbitrary ()
import Alignment
import ArbitraryTerm ()
import ArbitraryTerm (arbitraryLeaf)
import Control.Arrow
import Control.Comonad.Cofree
import Control.Monad.Free hiding (unfold)
@ -26,25 +26,6 @@ import qualified Source
import SplitDiff
import Syntax
instance Arbitrary a => Arbitrary (Both a) where
arbitrary = pure (curry Both) <*> arbitrary <*> arbitrary
instance Arbitrary a => Arbitrary (Line a) where
arbitrary = oneof [ Line <$> arbitrary, Closed <$> arbitrary ]
instance Arbitrary a => Arbitrary (Patch a) where
arbitrary = oneof [
Insert <$> arbitrary,
Delete <$> arbitrary,
Replace <$> arbitrary <*> arbitrary ]
instance Arbitrary a => Arbitrary (Source a) where
arbitrary = Source.fromList <$> arbitrary
arbitraryLeaf :: Gen (Source Char, Info, Syntax (Source Char) f)
arbitraryLeaf = toTuple <$> arbitrary
where toTuple string = (string, Info (Range 0 $ length string) mempty, Leaf string)
spec :: Spec
spec = parallel $ do
describe "splitDiffByLines" $ do

View File

@ -1,16 +1,22 @@
module ArbitraryTerm where
import Category
import Syntax
import Term
import Control.Comonad.Cofree
import Control.Monad
import Data.Functor.Both
import qualified Data.OrderedMap as Map
import qualified Data.List as List
import qualified Data.Set as Set
import GHC.Generics
import Test.QuickCheck hiding (Fixed)
import Data.Text.Arbitrary ()
import Diff
import Line
import Patch
import Range
import Source hiding ((++))
import Syntax
import GHC.Generics
import Term
import Test.QuickCheck hiding (Fixed)
newtype ArbitraryTerm a annotation = ArbitraryTerm (annotation, Syntax a (ArbitraryTerm a annotation))
deriving (Show, Eq, Generic)
@ -46,3 +52,22 @@ instance Categorizable CategorySet where
instance Arbitrary CategorySet where
arbitrary = elements [ A, B, C, D ]
instance Arbitrary a => Arbitrary (Both a) where
arbitrary = pure (curry Both) <*> arbitrary <*> arbitrary
instance Arbitrary a => Arbitrary (Line a) where
arbitrary = oneof [ Line <$> arbitrary, Closed <$> arbitrary ]
instance Arbitrary a => Arbitrary (Patch a) where
arbitrary = oneof [
Insert <$> arbitrary,
Delete <$> arbitrary,
Replace <$> arbitrary <*> arbitrary ]
instance Arbitrary a => Arbitrary (Source a) where
arbitrary = Source.fromList <$> arbitrary
arbitraryLeaf :: Gen (Source Char, Info, Syntax (Source Char) f)
arbitraryLeaf = toTuple <$> arbitrary
where toTuple string = (string, Info (Range 0 $ length string) mempty, Leaf string)