2015-12-22 20:53:31 +03:00
module ArbitraryTerm where
2016-02-04 21:59:33 +03:00
import Category
2015-12-22 20:53:31 +03:00
import Control.Comonad.Cofree
import Control.Monad
2016-03-15 18:17:47 +03:00
import Data.Functor.Both
2016-01-06 19:56:58 +03:00
import qualified Data.OrderedMap as Map
2015-12-22 20:53:31 +03:00
import qualified Data.List as List
import qualified Data.Set as Set
2016-03-15 18:17:47 +03:00
import Data.Text.Arbitrary ( )
import Diff
2016-03-31 00:33:07 +03:00
import Info
2016-03-15 18:17:47 +03:00
import Line
import Patch
2016-03-15 18:46:09 +03:00
import Prelude hiding ( fst , snd )
2016-03-15 18:17:47 +03:00
import Range
import Source hiding ( ( ++ ) )
import Syntax
2015-12-22 20:53:31 +03:00
import GHC.Generics
2016-03-15 18:17:47 +03:00
import Term
2015-12-22 20:53:31 +03:00
import Test.QuickCheck hiding ( Fixed )
2015-12-22 20:54:01 +03:00
newtype ArbitraryTerm a annotation = ArbitraryTerm ( annotation , Syntax a ( ArbitraryTerm a annotation ) )
2015-12-22 20:53:31 +03:00
deriving ( Show , Eq , Generic )
unTerm :: ArbitraryTerm a annotation -> Term a annotation
unTerm = unfold unpack
where unpack ( ArbitraryTerm ( annotation , syntax ) ) = ( annotation , syntax )
instance ( Eq a , Eq annotation , Arbitrary a , Arbitrary annotation ) => Arbitrary ( ArbitraryTerm a annotation ) where
2016-03-11 17:22:17 +03:00
arbitrary = scale ( ` div ` 2 ) $ sized ( \ x -> boundedTerm x x ) -- first indicates the cube of the max length of lists, second indicates the cube of the max depth of the tree
2015-12-22 20:53:31 +03:00
where boundedTerm maxLength maxDepth = ArbitraryTerm <$> ( ( , ) <$> arbitrary <*> boundedSyntax maxLength maxDepth )
boundedSyntax _ maxDepth | maxDepth <= 0 = liftM Leaf arbitrary
boundedSyntax maxLength maxDepth = frequency
[ ( 12 , liftM Leaf arbitrary ) ,
( 1 , liftM Indexed $ take maxLength <$> listOf ( smallerTerm maxLength maxDepth ) ) ,
( 1 , liftM Fixed $ take maxLength <$> listOf ( smallerTerm maxLength maxDepth ) ) ,
2015-12-22 20:54:01 +03:00
( 1 , liftM ( Keyed . Map . fromList ) $ take maxLength <$> listOf ( arbitrary >>= ( \ x -> ( , ) x <$> smallerTerm maxLength maxDepth ) ) ) ]
2015-12-22 20:53:31 +03:00
smallerTerm maxLength maxDepth = boundedTerm ( div maxLength 3 ) ( div maxDepth 3 )
shrink term @ ( ArbitraryTerm ( annotation , syntax ) ) = ( ++ ) ( subterms term ) $ filter ( /= term ) $
ArbitraryTerm <$> ( ( , ) <$> shrink annotation <*> case syntax of
Leaf a -> Leaf <$> shrink a
Indexed i -> Indexed <$> ( List . subsequences i >>= recursivelyShrink )
Fixed f -> Fixed <$> ( List . subsequences f >>= recursivelyShrink )
Keyed k -> Keyed . Map . fromList <$> ( List . subsequences ( Map . toList k ) >>= recursivelyShrink ) )
data CategorySet = A | B | C | D deriving ( Eq , Show )
instance Categorizable CategorySet where
2016-02-09 22:43:13 +03:00
categories A = Set . fromList [ Other " a " ]
categories B = Set . fromList [ Other " b " ]
categories C = Set . fromList [ Other " c " ]
categories D = Set . fromList [ Other " d " ]
2015-12-22 20:53:31 +03:00
instance Arbitrary CategorySet where
arbitrary = elements [ A , B , C , D ]
2016-03-15 18:17:47 +03:00
instance Arbitrary a => Arbitrary ( Both a ) where
arbitrary = pure ( curry Both ) <*> arbitrary <*> arbitrary
2016-03-15 18:46:09 +03:00
shrink b = both <$> ( shrink ( fst b ) ) <*> ( shrink ( snd b ) )
2016-03-15 18:17:47 +03:00
instance Arbitrary a => Arbitrary ( Line a ) where
arbitrary = oneof [ Line <$> arbitrary , Closed <$> arbitrary ]
2016-03-15 18:46:05 +03:00
shrink line = ( ` lineMap ` line ) . const <$> shrinkList shrink ( unLine line )
2016-03-15 18:17:47 +03:00
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 )