Safe Haskell | None |
---|---|
Language | Haskell98 |
- succOnlyForNumbers :: Bool
- last' :: a -> [a] -> a
- tail :: [a] -> [a]
- gcd :: Integral t => t -> t -> t
- enumFromThenTo :: (Enum t2, Enum t1, Enum t, Enum b) => t2 -> t1 -> t -> [b]
- initialize :: IO ()
- init075 :: IO ()
- inittv1 :: IO ()
- mall :: ProgramGenerator pg => pg
- mlist :: ProgramGenerator pg => pg
- mlist' :: ProgramGenerator pg => pg
- mnat :: ProgramGenerator pg => pg
- mlistnat :: ProgramGenerator pg => pg
- mnat_nc :: ProgramGenerator pg => pg
- mnatural :: ProgramGenerator pg => pg
- mlistnatural :: ProgramGenerator pg => pg
- hd :: [a] -> Maybe a
- mb :: [Primitive]
- mb' :: [Primitive]
- nat :: [Primitive]
- natural :: [Primitive]
- nat' :: [Primitive]
- nat'woPred :: [Primitive]
- natural' :: [Primitive]
- plusInt :: [Primitive]
- plusInteger :: [Primitive]
- list'' :: [Primitive]
- list' :: [Primitive]
- list :: [Primitive]
- bool :: [Primitive]
- boolean :: [Primitive]
- intinst :: [Primitive]
- list1 :: [Primitive]
- list1' :: [Primitive]
- list2 :: [Primitive]
- list3 :: [Primitive]
- list3' :: [Primitive]
- nats :: [Primitive]
- tuple :: [Primitive]
- tuple' :: [Primitive]
- rich :: [Primitive]
- rich' :: [Primitive]
- debug :: [Primitive]
- nat_para :: Integral i => i -> a -> (i -> a -> a) -> a
- nat_cata :: Integral i => i -> a -> (a -> a) -> a
- list_para :: [b] -> a -> (b -> [b] -> a -> a) -> a
- iF :: Bool -> a -> a -> a
- postprocess :: Exp -> Exp
- byMap :: IntMap (Exp -> Exp -> Exp)
- byEqs :: [(Int, Exp -> Exp -> Exp)]
- byOrds :: [(Int, Exp -> Exp -> Exp)]
- skip :: String -> String -> Exp -> Exp -> Exp
- skipEq :: String -> Exp -> Exp -> Exp
- skipOrd :: String -> Exp -> Exp -> Exp
- appearsIn :: Data a => String -> a -> Bool
- ppLambda :: [Pat] -> Exp -> Exp
- ppv :: Exp -> Exp
- ppopn :: Name -> Name
- ppdrop :: Integer -> Exp -> Exp
- constE :: Exp
- flipE :: Exp
- plusE :: Exp
- dropE :: Exp
- reverseE :: Exp
- lengthE :: Exp
- sumE :: Exp
- productE :: Exp
- procSucc :: Integer -> Exp -> Exp
- postprocessQ :: Exp -> ExpQ
- exploit :: (Typeable a, Filtrable a) => Bool -> (a -> Bool) -> IO ()
- newtype Partial a = Part {
- undef :: a
- undefs :: [((HValue, Exp, Type), (HValue, Exp, Type))]
- by1_head :: Partial a -> [a] -> a
- (--#!!) :: Partial a -> [a] -> Int -> a
- prelPartial :: [(HValue, Exp, Type)]
- newtype Equivalence a = Eq {}
- eq :: Eq a => Equivalence a
- by1_eqMaybe :: Equivalence a -> Equivalence (Maybe a)
- eqMaybeBy :: (t1 -> t -> Bool) -> Maybe t1 -> Maybe t -> Bool
- by1_eqList :: Equivalence a -> Equivalence [a]
- eqListBy :: (t1 -> t -> Bool) -> [t1] -> [t] -> Bool
- by2_eqEither :: Equivalence a -> Equivalence b -> Equivalence (Either a b)
- eqEitherBy :: (t3 -> t2 -> Bool) -> (t1 -> t -> Bool) -> Either t3 t1 -> Either t2 t -> Bool
- by2_eqPair :: Equivalence a -> Equivalence b -> Equivalence (a, b)
- eqPairBy :: (t3 -> t2 -> Bool) -> (t1 -> t -> Bool) -> (t3, t1) -> (t2, t) -> Bool
- eqs :: [(HValue, Exp, Type)]
- prelEqRelated :: [[(HValue, Exp, Type)]]
- dataListEqRelated :: [[(HValue, Exp, Type)]]
- (--#/=) :: Equivalence a -> a -> a -> Bool
- by1_elem :: Equivalence a -> a -> [a] -> Bool
- by1_group :: Equivalence a -> [a] -> [[a]]
- by1_nub :: Equivalence a -> [a] -> [a]
- by1_isPrefixOf :: Equivalence a -> [a] -> [a] -> Bool
- by1_isSuffixOf :: Equivalence a -> [a] -> [a] -> Bool
- by1_isInfixOf :: Equivalence a -> [a] -> [a] -> Bool
- by1_stripPrefix :: Equivalence a -> [a] -> [a] -> Maybe [a]
- by1_lookup :: Equivalence a -> a -> (->) [(a, b)] (Maybe b)
- newtype Ordered a = Ord {
- by1_compare :: a -> a -> Ordering
- cmp :: Ord a => Ordered a
- by1_cmpMaybe :: Ordered a -> Ordered (Maybe a)
- compareMaybeBy :: (t1 -> t -> Ordering) -> Maybe t1 -> Maybe t -> Ordering
- by1_cmpList :: Ordered a -> Ordered [a]
- compareListBy :: (t1 -> t -> Ordering) -> [t1] -> [t] -> Ordering
- by2_cmpEither :: Ordered a -> Ordered b -> Ordered (Either a b)
- compareEitherBy :: (t3 -> t2 -> Ordering) -> (t1 -> t -> Ordering) -> Either t3 t1 -> Either t2 t -> Ordering
- by2_cmpPair :: Ordered a -> Ordered b -> Ordered (a, b)
- comparePairBy :: (t3 -> t2 -> Ordering) -> (t1 -> t -> Ordering) -> (t3, t1) -> (t2, t) -> Ordering
- ords :: [(HValue, Exp, Type)]
- prelOrdRelated :: [[(HValue, Exp, Type)]]
- dataListOrdRelated :: [[(HValue, Exp, Type)]]
- (--#<=) :: Ordered t -> t -> t -> Bool
- (--#<) :: Ordered t -> t -> t -> Bool
- by1_max :: Ordered t -> t -> t -> t
- by1_min :: Ordered t -> t -> t -> t
- by1_sort :: Ordered t -> [t] -> [t]
- intinst1 :: [(HValue, Exp, Type)]
- intpartials :: [(HValue, Exp, Type)]
- intinst2 :: [(HValue, Exp, Type)]
- reallyall :: ProgramGenerator pg => pg
- nrnds :: Num a => [a]
- generator :: TFGen
- mix :: ProgramGenerator pg => pg
- poormix :: ProgramGenerator pg => pg
- soso :: [Primitive]
- ra :: ProgramGenerator pg => pg
- mx :: ProgramGenerator pg => pg
- pgfull :: ProgGenSF
- pgfulls :: [ProgGenSF]
- mkPgFull :: IO ProgGenSF
- mkPgTotal :: IO ProgGenSF
- mkDebugPg :: IO ProgGenSF
- deb :: [[(HValue, Exp, Type)]]
- pgfullIO :: IO ProgGenSFIORef
- full :: [[(HValue, Exp, Type)]]
- clspartialss :: [(Primitive, Primitive)]
- tupartialss :: [[(Primitive, Primitive)]]
- tupartialssNormal :: [[(Primitive, Primitive)]]
- literals :: [[(HValue, Exp, Type)]]
- fromPrelude :: [[Primitive]]
- fromDataList :: [[(HValue, Exp, Type)]]
- fromDataChar :: [[(HValue, Exp, Type)]]
- fromDataMaybe :: [[(HValue, Exp, Type)]]
- pgWithDoubleRatio :: ProgGenSF
- pgWithDoubleRatios :: [ProgGenSF]
- withDoubleRatio :: [[(HValue, Exp, Type)]]
- pgWithRatio :: ProgGenSF
- pgWithRatios :: [ProgGenSF]
- pgRatio :: ProgGenSF
- pgRatios :: [ProgGenSF]
- withRatio :: [[(HValue, Exp, Type)]]
- ratioCls :: [(HValue, Exp, Type)]
- fromPrelRatio :: [[(HValue, Exp, Type)]]
- fromDataRatio :: [[(HValue, Exp, Type)]]
- pgWithDouble :: ProgGenSF
- pgWithDoubles :: [ProgGenSF]
- mkPgWithDouble :: IO ProgGenSF
- withDouble :: [[(HValue, Exp, Type)]]
- doubleCls :: [(HValue, Exp, Type)]
- fromPrelDouble :: [[(HValue, Exp, Type)]]
- module MagicHaskeller
Documentation
initialize :: IO () Source #
mall :: ProgramGenerator pg => pg Source #
mlist :: ProgramGenerator pg => pg Source #
mlist' :: ProgramGenerator pg => pg Source #
mnat :: ProgramGenerator pg => pg Source #
mlistnat :: ProgramGenerator pg => pg Source #
mnat_nc :: ProgramGenerator pg => pg Source #
mnatural :: ProgramGenerator pg => pg Source #
mlistnatural :: ProgramGenerator pg => pg Source #
nat'woPred :: [Primitive] Source #
plusInteger :: [Primitive] Source #
postprocess :: Exp -> Exp Source #
postprocess
replaces uncommon functions like catamorphisms with well-known functions.
postprocessQ :: Exp -> ExpQ Source #
eq :: Eq a => Equivalence a Source #
by1_eqMaybe :: Equivalence a -> Equivalence (Maybe a) Source #
by1_eqList :: Equivalence a -> Equivalence [a] Source #
by2_eqEither :: Equivalence a -> Equivalence b -> Equivalence (Either a b) Source #
eqEitherBy :: (t3 -> t2 -> Bool) -> (t1 -> t -> Bool) -> Either t3 t1 -> Either t2 t -> Bool Source #
by2_eqPair :: Equivalence a -> Equivalence b -> Equivalence (a, b) Source #
(--#/=) :: Equivalence a -> a -> a -> Bool Source #
by1_elem :: Equivalence a -> a -> [a] -> Bool Source #
by1_group :: Equivalence a -> [a] -> [[a]] Source #
by1_nub :: Equivalence a -> [a] -> [a] Source #
by1_isPrefixOf :: Equivalence a -> [a] -> [a] -> Bool Source #
by1_isSuffixOf :: Equivalence a -> [a] -> [a] -> Bool Source #
by1_isInfixOf :: Equivalence a -> [a] -> [a] -> Bool Source #
by1_stripPrefix :: Equivalence a -> [a] -> [a] -> Maybe [a] Source #
by1_lookup :: Equivalence a -> a -> (->) [(a, b)] (Maybe b) Source #
by1_cmpList :: Ordered a -> Ordered [a] Source #
compareListBy :: (t1 -> t -> Ordering) -> [t1] -> [t] -> Ordering Source #
compareEitherBy :: (t3 -> t2 -> Ordering) -> (t1 -> t -> Ordering) -> Either t3 t1 -> Either t2 t -> Ordering Source #
comparePairBy :: (t3 -> t2 -> Ordering) -> (t1 -> t -> Ordering) -> (t3, t1) -> (t2, t) -> Ordering Source #
reallyall :: ProgramGenerator pg => pg Source #
mix :: ProgramGenerator pg => pg Source #
poormix :: ProgramGenerator pg => pg Source #
ra :: ProgramGenerator pg => pg Source #
mx :: ProgramGenerator pg => pg Source #
clspartialss :: [(Primitive, Primitive)] Source #
tupartialss :: [[(Primitive, Primitive)]] Source #
tupartialssNormal :: [[(Primitive, Primitive)]] Source #
fromPrelude :: [[Primitive]] Source #
pgWithRatios :: [ProgGenSF] Source #
pgWithDoubles :: [ProgGenSF] Source #
module MagicHaskeller