MagicHaskeller-0.9.6.4.4: Automatic inductive functional programmer by systematic search

Safe HaskellNone
LanguageHaskell98

MagicHaskeller.Classification

Documentation

class Search m => SStrategy m where Source

Methods

sfilter :: Relation r => (k -> k -> r) -> (Int -> Int) -> m ([k], e) -> m ([k], e) Source

ofilter :: Relation r => (k -> k -> r) -> m (k, e) -> m (k, e) Source

arbitraries :: Arbitrary a => [a] Source

arbs :: Arbitrary a => Int -> StdGen -> [a] Source

(/~) :: [a] -> (a -> a -> Bool) -> [[a]] Source

nubSortBy :: (a -> a -> Ordering) -> [a] -> [a] Source

nubSortByBot :: (a -> a -> Maybe Ordering) -> [a] -> [a] Source

(/<) :: [a] -> (a -> a -> Ordering) -> [[a]] Source

(/<?) :: [a] -> (a -> a -> Maybe Ordering) -> [[a]] Source

class Eq rel => Relation rel where Source

Minimal complete definition

(/), appendWithBy, diffBy, cEQ

Methods

fromListBy :: (k -> k -> rel) -> [k] -> [k] Source

fromListByDB :: (k -> k -> rel) -> [(k, Int)] -> [(k, Int)] Source

(/) :: [k] -> (k -> k -> rel) -> [[k]] Source

appendWithBy :: (k -> k -> k) -> (k -> k -> rel) -> [k] -> [k] -> [k] Source

diffBy :: (k -> k -> rel) -> [k] -> [k] -> [k] Source

cEQ :: rel Source

appendQuotientsBy :: Relation rel => (k -> k -> rel) -> [[k]] -> [[k]] -> [[k]] Source

appendRepresentativesBy :: Relation rel => (k -> k -> rel) -> [k] -> [k] -> [k] Source

unionWithBy :: (a -> a -> a) -> (a -> a -> Bool) -> [a] -> [a] -> [a] Source

randomTestFilter :: (SStrategy m, Filtrable a) => (Int -> Int) -> m (e, a) -> m (e, a) Source

unsafeRandomTestFilter Source

Arguments

:: (SStrategy m, Filtrable a) 
=> Maybe Int

microsecs until timeout

-> (Int -> Int) 
-> m (e, a) 
-> m (e, a) 

mapFst :: (t -> t1) -> (t, t2) -> (t1, t2) Source

class Filtrable a where Source

Methods

filt :: SStrategy m => (Int -> Int) -> m (a, e) -> m e Source

filtFun :: (SStrategy m, Arbitrary b) => (Int -> Int) -> m (b -> a, e) -> m e Source

unsafeFilt :: SStrategy m => Maybe Int -> (Int -> Int) -> m (a, e) -> m e Source

unsafeFiltFun :: (SStrategy m, Arbitrary b) => Maybe Int -> (Int -> Int) -> m (b -> a, e) -> m e Source

Instances

Filtrable Double Source 
Ord a => Filtrable a Source 
(RealFloat a, Ord a) => Filtrable (Complex a) Source 
(Arbitrary a, Filtrable r) => Filtrable (a -> r) Source 

filtNullary :: (SStrategy m, Relation r) => (k -> k -> r) -> (Int -> Int) -> m (k, e) -> m e Source

filtUnary :: (Arbitrary a, Relation r, SStrategy f) => (k -> k -> r) -> (Int -> Int) -> f (a -> k, b) -> f b Source

ofilterMx :: Relation r => (k -> k -> r) -> Matrix (k, e) -> Matrix (k, e) Source

ofilterDB :: Relation rel => (k -> k -> rel) -> DBound (k, e) -> DBound (k, e) Source

cumulativeRepresentatives :: Relation rel => [a -> a -> rel] -> Matrix a -> Matrix a Source

representatives :: Relation rel => [a -> a -> rel] -> Matrix a -> Matrix a Source

unscanlByList :: Relation r => [k -> k -> r] -> Matrix k -> Matrix k Source

sfilterMx :: Relation r => (k -> k -> r) -> (Int -> Int) -> Matrix ([k], e) -> Matrix ([k], e) Source

liftRelation :: Relation r => (k -> k -> r) -> Int -> ([k], e) -> ([k], e) -> r Source

liftRel :: (Eq a, Num a, Relation rel) => (t -> t1 -> rel) -> a -> [t] -> [t1] -> rel Source

sfilterDB :: Relation rel => (k -> k -> rel) -> (Int -> Int) -> DBound ([k], e) -> DBound ([k], e) Source

cumulativeQuotients :: Relation rel => [k -> k -> rel] -> Matrix k -> Matrix [k] Source