MagicHaskeller-0.9.6.7: Automatic inductive functional programmer by systematic search

Safe HaskellNone
LanguageHaskell98

MagicHaskeller.IOGenerator

Synopsis

Documentation

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

arbs :: Arbitrary a => Int -> TFGen -> [a] Source #

showIOPairsWithFormsHTML Source #

Arguments

:: String

CGI.myPath, which is usually "cgi-binMagicHaskeller.cgi"

-> String

predicate before escaping single quotes

-> String 
-> [ShownIOPair] 
-> String 

nubOn :: Eq a => (b -> a) -> [b] -> [b] Source #

nubSortedOn :: Ord a => (b -> a) -> [b] -> [b] Source #

nubSortedOn' :: Ord a => (b -> a) -> [b] -> [b] Source #

type AnnShowS Source #

Arguments

 = (String -> String)

annotater

-> String 
-> String 

showsInputs :: Foldable t => t ((a -> a) -> [Char] -> [Char]) -> [Char] -> [Char] Source #

class IOGenerator a where Source #

Minimal complete definition

generateIOPairs

generateIOPairsLitNum :: (Num a, Ord a, Show a, IOGenerator b) => [a] -> (a -> b) -> [ShownIOPair] Source #

class ShowArbitrary a where Source #

ShowArbitrary is a variant of Arbitrary for presenting I/O example pairs. It uses everythingF for generating printable functions. Here `good presentation' is more important than `good randomness'.

Minimal complete definition

showArbitraries

Methods

showArbitraries :: [(AnnShowS, a)] Source #

Instances

ShowArbitrary Bool Source # 
ShowArbitrary Char Source # 
ShowArbitrary Double Source # 
ShowArbitrary Float Source # 
ShowArbitrary Int Source # 
ShowArbitrary Integer Source # 
ShowArbitrary Ordering Source # 
ShowArbitrary () Source # 

Methods

showArbitraries :: [(AnnShowS, ())] Source #

ShowArbitrary a => ShowArbitrary [a] Source # 

Methods

showArbitraries :: [(AnnShowS, [a])] Source #

ShowArbitrary a => ShowArbitrary (Maybe a) Source # 
(Integral i, Random i, Show i) => ShowArbitrary (Ratio i) Source # 
(Typeable * a, Typeable * b) => ShowArbitrary (a -> b) Source # 

Methods

showArbitraries :: [(AnnShowS, a -> b)] Source #

(ShowArbitrary a, ShowArbitrary b) => ShowArbitrary (Either a b) Source # 
(ShowArbitrary a, ShowArbitrary b) => ShowArbitrary (a, b) Source # 

Methods

showArbitraries :: [(AnnShowS, (a, b))] Source #

(ShowArbitrary a, ShowArbitrary b, ShowArbitrary c) => ShowArbitrary (a, b, c) Source # 

Methods

showArbitraries :: [(AnnShowS, (a, b, c))] Source #

sas :: Show a => (a -> Bool) -> [a] -> [(AnnShowS, a)] Source #

sasNum :: (Show a, Arbitrary a, Num a, Ord a) => [(AnnShowS, a)] Source #

sasFalse :: Show a => [a] -> [(AnnShowS, a)] Source #

sasIntegral :: (Show a, Arbitrary a, Integral a, Ord a) => [(AnnShowS, a)] Source #

mapSA :: [Char] -> (t2 -> t1) -> (t -> String -> [Char], t2) -> (t -> ShowS, t1) Source #

skip :: Int -> [a] -> [a] Source #

chopBy :: [Int] -> [a] -> [[a]] Source #

cvt :: [(AnnShowS, a)] -> (AnnShowS, [a]) Source #

showsList :: [(a -> a) -> [Char] -> [Char]] -> (a -> a) -> ShowS Source #

generateIOPairsFun :: (Ord a, Show a, Arbitrary a, IOGenerator b) => Bool -> (a -> b) -> [ShownIOPair] Source #

uniqSort :: Ord a => [a] -> [a] Source #

class NearEq a where Source #

Minimal complete definition

(~=)

Methods

(~=) :: a -> a -> Bool infix 4 Source #

Instances

NearEq Bool Source # 

Methods

(~=) :: Bool -> Bool -> Bool Source #

NearEq Char Source # 

Methods

(~=) :: Char -> Char -> Bool Source #

NearEq Double Source # 

Methods

(~=) :: Double -> Double -> Bool Source #

NearEq Float Source # 

Methods

(~=) :: Float -> Float -> Bool Source #

NearEq Int Source # 

Methods

(~=) :: Int -> Int -> Bool Source #

NearEq Integer Source # 

Methods

(~=) :: Integer -> Integer -> Bool Source #

NearEq Ordering Source # 

Methods

(~=) :: Ordering -> Ordering -> Bool Source #

NearEq () Source # 

Methods

(~=) :: () -> () -> Bool Source #

NearEq a => NearEq [a] Source # 

Methods

(~=) :: [a] -> [a] -> Bool Source #

NearEq a => NearEq (Maybe a) Source # 

Methods

(~=) :: Maybe a -> Maybe a -> Bool Source #

(NearEq i, Integral i) => NearEq (Ratio i) Source # 

Methods

(~=) :: Ratio i -> Ratio i -> Bool Source #

(NearEq a, NearEq b) => NearEq (Either a b) Source # 

Methods

(~=) :: Either a b -> Either a b -> Bool Source #

(NearEq a, NearEq b) => NearEq (a, b) Source # 

Methods

(~=) :: (a, b) -> (a, b) -> Bool Source #

(NearEq a, NearEq b, NearEq c) => NearEq (a, b, c) Source # 

Methods

(~=) :: (a, b, c) -> (a, b, c) -> Bool Source #