MagicHaskeller-0.9.6.7: Automatic inductive functional programmer by systematic search

Safe HaskellNone
LanguageHaskell98

MagicHaskeller.Classification

Documentation

class Search m => SStrategy m where Source #

Minimal complete definition

sfilter, ofilter

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 #

Instances

SStrategy DBound Source # 

Methods

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

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

SStrategy Matrix Source # 

Methods

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

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

arbitraries :: Arbitrary a => [a] Source #

arbs :: Arbitrary a => Int -> TFGen -> [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 #

Instances

Relation Bool Source # 

Methods

fromListBy :: (k -> k -> Bool) -> [k] -> [k] Source #

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

(/) :: [k] -> (k -> k -> Bool) -> [[k]] Source #

appendWithBy :: (k -> k -> k) -> (k -> k -> Bool) -> [k] -> [k] -> [k] Source #

diffBy :: (k -> k -> Bool) -> [k] -> [k] -> [k] Source #

cEQ :: Bool Source #

Relation Ordering Source # 

Methods

fromListBy :: (k -> k -> Ordering) -> [k] -> [k] Source #

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

(/) :: [k] -> (k -> k -> Ordering) -> [[k]] Source #

appendWithBy :: (k -> k -> k) -> (k -> k -> Ordering) -> [k] -> [k] -> [k] Source #

diffBy :: (k -> k -> Ordering) -> [k] -> [k] -> [k] Source #

cEQ :: Ordering Source #

Relation (Maybe Ordering) Source # 

Methods

fromListBy :: (k -> k -> Maybe Ordering) -> [k] -> [k] Source #

fromListByDB :: (k -> k -> Maybe Ordering) -> [(k, Int)] -> [(k, Int)] Source #

(/) :: [k] -> (k -> k -> Maybe Ordering) -> [[k]] Source #

appendWithBy :: (k -> k -> k) -> (k -> k -> Maybe Ordering) -> [k] -> [k] -> [k] Source #

diffBy :: (k -> k -> Maybe Ordering) -> [k] -> [k] -> [k] Source #

cEQ :: Maybe Ordering 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 :: (t2 -> t1) -> (t2, t) -> (t1, t) Source #

class Filtrable a where Source #

Minimal complete definition

filt, filtFun, unsafeFilt, unsafeFiltFun

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 # 

Methods

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

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

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

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

Ord a => Filtrable a 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 #

(RealFloat a, Ord a) => Filtrable (Complex a) Source # 

Methods

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

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

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

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

(Arbitrary a, Filtrable r) => Filtrable (a -> r) Source # 

Methods

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

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

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

unsafeFiltFun :: (SStrategy m, Arbitrary b) => Maybe Int -> (Int -> Int) -> m (b -> a -> r, e) -> m e 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 t, Relation t1, Num t) => (t3 -> t2 -> t1) -> t -> [t3] -> [t2] -> t1 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 #