2016-04-04 22:01:47 +03:00
{- # LANGUAGE FlexibleInstances # -}
2016-04-22 19:54:50 +03:00
{- # OPTIONS_GHC - fno - warn - orphans # -}
2015-12-22 20:53:31 +03:00
module ArbitraryTerm where
2016-02-04 21:59:33 +03:00
import Category
2016-04-04 22:01:47 +03:00
import Data.Bifunctor.Join
2016-03-15 18:17:47 +03:00
import Data.Functor.Both
2016-05-27 16:35:26 +03:00
import Data.Functor.Foldable
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 ( )
2016-04-26 21:14:31 +03:00
import Data.These
2016-03-31 00:33:07 +03:00
import Info
2016-03-15 18:17:47 +03:00
import Patch
2016-05-26 19:58:04 +03:00
import Prologue hiding ( fst , snd )
2016-03-15 18:17:47 +03:00
import Range
import Source hiding ( ( ++ ) )
import Syntax
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
2016-05-04 22:15:25 +03:00
where unpack ( ArbitraryTerm ( annotation , syntax ) ) = annotation :< syntax
2015-12-22 20:53:31 +03:00
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 )
2016-04-26 21:18:59 +03:00
boundedSyntax _ maxDepth | maxDepth <= 0 = Leaf <$> arbitrary
2015-12-22 20:53:31 +03:00
boundedSyntax maxLength maxDepth = frequency
2016-04-26 21:18:59 +03:00
[ ( 12 , Leaf <$> arbitrary ) ,
( 1 , Indexed . take maxLength <$> listOf ( smallerTerm maxLength maxDepth ) ) ,
( 1 , Fixed . take maxLength <$> listOf ( smallerTerm maxLength maxDepth ) ) ,
( 1 , 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 )
2016-04-26 21:20:02 +03:00
shrink term @ ( ArbitraryTerm ( annotation , syntax ) ) = ( subterms term ++ ) $ filter ( /= term ) $
2015-12-22 20:53:31 +03:00
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
2016-04-04 22:01:47 +03:00
instance Arbitrary a => Arbitrary ( Join ( , ) a ) where
2016-04-04 21:53:09 +03:00
arbitrary = both <$> arbitrary <*> arbitrary
2016-04-15 04:56:07 +03:00
shrink b = both <$> shrink ( fst b ) <*> shrink ( snd b )
2016-03-15 18:17:47 +03:00
2016-04-26 21:14:31 +03:00
instance ( Arbitrary a , Arbitrary b ) => Arbitrary ( These a b ) where
arbitrary = oneof [ This <$> arbitrary
, That <$> arbitrary
, These <$> arbitrary <*> arbitrary ]
2016-04-26 21:17:36 +03:00
shrink = these ( fmap This . shrink ) ( fmap That . shrink ) ( \ a b -> ( This <$> shrink a ) ++ ( That <$> shrink b ) ++ ( These <$> shrink a <*> shrink b ) )
2016-04-26 21:14:31 +03:00
2016-04-26 21:17:43 +03:00
instance Arbitrary a => Arbitrary ( Join These a ) where
arbitrary = Join <$> arbitrary
shrink ( Join a ) = Join <$> shrink a
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
2016-04-12 11:54:32 +03:00
where toTuple string = ( string , Info ( Range 0 $ length string ) mempty 1 , Leaf string )