Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
debugTrace :: String -> a -> a Source #
anaM' :: (Monad m, Corecursive t, x ~ Base t, Traversable x) => (a -> m (Base t a)) -> a -> m t Source #
Instances
newtype FunctionIndex Source #
Instances
Instances
class BasicBase g where Source #
Instances
BasicBase AbortExprF Source # | |
Defined in Telomare.Possible | |
BasicBase StuckExprF Source # | |
Defined in Telomare.Possible | |
BasicBase SuperExprF Source # | |
Defined in Telomare.Possible | |
BasicBase UnsizedExprF Source # | |
Defined in Telomare.Possible |
class StuckBase g where Source #
Instances
StuckBase AbortExprF Source # | |
Defined in Telomare.Possible | |
StuckBase StuckExprF Source # | |
Defined in Telomare.Possible | |
StuckBase SuperExprF Source # | |
Defined in Telomare.Possible | |
StuckBase UnsizedExprF Source # | |
Defined in Telomare.Possible |
class SuperBase g where Source #
embedP :: SuperPositionF x -> g x Source #
extractP :: g x -> Maybe (SuperPositionF x) Source #
Instances
SuperBase SuperExprF Source # | |
Defined in Telomare.Possible embedP :: SuperPositionF x -> SuperExprF x Source # extractP :: SuperExprF x -> Maybe (SuperPositionF x) Source # | |
SuperBase UnsizedExprF Source # | |
Defined in Telomare.Possible embedP :: SuperPositionF x -> UnsizedExprF x Source # extractP :: UnsizedExprF x -> Maybe (SuperPositionF x) Source # |
class AbortBase g where Source #
embedA :: AbortableF x -> g x Source #
extractA :: g x -> Maybe (AbortableF x) Source #
Instances
AbortBase AbortExprF Source # | |
Defined in Telomare.Possible embedA :: AbortableF x -> AbortExprF x Source # extractA :: AbortExprF x -> Maybe (AbortableF x) Source # | |
AbortBase SuperExprF Source # | |
Defined in Telomare.Possible embedA :: AbortableF x -> SuperExprF x Source # extractA :: SuperExprF x -> Maybe (AbortableF x) Source # | |
AbortBase UnsizedExprF Source # | |
Defined in Telomare.Possible embedA :: AbortableF x -> UnsizedExprF x Source # extractA :: UnsizedExprF x -> Maybe (AbortableF x) Source # |
class UnsizedBase g where Source #
embedU :: UnsizedRecursionF x -> g x Source #
extractU :: g x -> Maybe (UnsizedRecursionF x) Source #
Instances
UnsizedBase UnsizedExprF Source # | |
Defined in Telomare.Possible embedU :: UnsizedRecursionF x -> UnsizedExprF x Source # extractU :: UnsizedExprF x -> Maybe (UnsizedRecursionF x) Source # |
pattern SuperFW :: SuperBase g => SuperPositionF x -> g x Source #
pattern AbortFW :: AbortBase g => AbortableF x -> g x Source #
pattern UnsizedFW :: UnsizedBase g => UnsizedRecursionF x -> g x Source #
pattern UnsizedEE :: (Base g ~ f, UnsizedBase f, Recursive g) => UnsizedRecursionF g -> g Source #
superEE :: (Base g ~ f, SuperBase f, Corecursive g) => SuperPositionF g -> g Source #
abortEE :: (Base g ~ f, AbortBase f, Corecursive g) => AbortableF g -> g Source #
unsizedEE :: (Base g ~ f, UnsizedBase f, Corecursive g) => UnsizedRecursionF g -> g Source #
fillFunction :: (Base g ~ f, BasicBase f, Corecursive g) => g -> g -> g Source #
gateSwitch :: (Base g ~ f, BasicBase f, Corecursive g) => g -> g -> g -> g Source #
basicStep :: (Base g ~ f, BasicBase f, Corecursive g, Recursive g) => (f g -> g) -> f g -> g Source #
basicStepM :: (Base g ~ f, BasicBase f, Traversable f, Corecursive g, Recursive g, PrettyPrintable g, Monad m) => (f (m g) -> m g) -> f (m g) -> m g Source #
transformNoDeferM :: (Base g ~ f, StuckBase f, Monad m, Recursive g) => (f (m g) -> m g) -> g -> m g Source #
stuckStep :: (Base a ~ f, StuckBase f, BasicBase f, Recursive a, Corecursive a, PrettyPrintable a) => (f a -> a) -> f a -> a Source #
stuckStepM :: (Base a ~ f, Traversable f, StuckBase f, BasicBase f, Recursive a, Corecursive a, PrettyPrintable a, Monad m) => (f (m a) -> m a) -> f (m a) -> m a Source #
evalBottomUp :: (Base t ~ f, BasicBase f, StuckBase f, Corecursive t, Recursive t, Recursive t) => (Base t t -> t) -> t -> t Source #
superStep :: (Base a ~ f, BasicBase f, SuperBase f, Recursive a, Corecursive a, PrettyPrintable a) => (a -> a -> a) -> (f a -> a) -> (f a -> a) -> f a -> a Source #
superStepM :: (Base a ~ f, Traversable f, BasicBase f, SuperBase f, Recursive a, Corecursive a, PrettyPrintable a, Monad m) => (a -> a -> a) -> (f (m a) -> m a) -> (f (m a) -> m a) -> f (m a) -> m a Source #
abortStep :: (Base a ~ f, BasicBase f, StuckBase f, AbortBase f, Recursive a, Corecursive a) => (f a -> a) -> f a -> a Source #
abortStepM :: (Base a ~ f, Traversable f, BasicBase f, StuckBase f, AbortBase f, Recursive a, Corecursive a, Monad m) => (f (m a) -> m a) -> f (m a) -> m a Source #
anyFunctionStep :: (Base a ~ f, BasicBase f, SuperBase f, Recursive a, Corecursive a) => (f a -> a) -> f a -> a Source #
anyFunctionStepM :: (Base a ~ f, Traversable f, BasicBase f, SuperBase f, Recursive a, Corecursive a, Monad m) => (f (m a) -> m a) -> f (m a) -> m a Source #
newtype SizedRecursion Source #
Instances
Monoid SizedRecursion Source # | |
Defined in Telomare.Possible mempty :: SizedRecursion Source # mappend :: SizedRecursion -> SizedRecursion -> SizedRecursion Source # mconcat :: [SizedRecursion] -> SizedRecursion Source # | |
Semigroup SizedRecursion Source # | |
Defined in Telomare.Possible (<>) :: SizedRecursion -> SizedRecursion -> SizedRecursion Source # sconcat :: NonEmpty SizedRecursion -> SizedRecursion Source # stimes :: Integral b => b -> SizedRecursion -> SizedRecursion Source # | |
PrettyPrintable1 (StrictAccum SizedRecursion) Source # | |
Defined in Telomare.Possible showP1 :: PrettyPrintable a => StrictAccum SizedRecursion a -> State Int String Source # | |
PrettyPrintable1 ((,) SizedRecursion) Source # | |
Defined in Telomare.Possible showP1 :: PrettyPrintable a => (SizedRecursion, a) -> State Int String Source # |
data StrictAccum a x Source #
StrictAccum !a x |
Instances
unsizedStepM :: (Base a ~ f, Traversable f, BasicBase f, StuckBase f, SuperBase f, AbortBase f, UnsizedBase f, Recursive a, Corecursive a, Eq a, PrettyPrintable a) => Int -> (f (StrictAccum SizedRecursion a) -> StrictAccum SizedRecursion a) -> (f (StrictAccum SizedRecursion a) -> StrictAccum SizedRecursion a) -> f (StrictAccum SizedRecursion a) -> StrictAccum SizedRecursion a Source #
Instances
Foldable VoidF Source # | |
Defined in Telomare.Possible fold :: Monoid m => VoidF m -> m Source # foldMap :: Monoid m => (a -> m) -> VoidF a -> m Source # foldMap' :: Monoid m => (a -> m) -> VoidF a -> m Source # foldr :: (a -> b -> b) -> b -> VoidF a -> b Source # foldr' :: (a -> b -> b) -> b -> VoidF a -> b Source # foldl :: (b -> a -> b) -> b -> VoidF a -> b Source # foldl' :: (b -> a -> b) -> b -> VoidF a -> b Source # foldr1 :: (a -> a -> a) -> VoidF a -> a Source # foldl1 :: (a -> a -> a) -> VoidF a -> a Source # toList :: VoidF a -> [a] Source # null :: VoidF a -> Bool Source # length :: VoidF a -> Int Source # elem :: Eq a => a -> VoidF a -> Bool Source # maximum :: Ord a => VoidF a -> a Source # minimum :: Ord a => VoidF a -> a Source # | |
Eq1 VoidF Source # | |
Show1 VoidF Source # | |
Traversable VoidF Source # | |
Functor VoidF Source # | |
PrettyPrintable1 VoidF Source # | |
Defined in Telomare.Possible |
data SuperPositionF f Source #
Instances
data AbortableF f Source #
Instances
mergeBasic :: (Base x ~ f, BasicBase f, Eq x, Corecursive x, Recursive x) => (x -> x -> x) -> x -> x -> x Source #
mergeSuper :: (Base x ~ f, SuperBase f, Eq x, Corecursive x, Recursive x) => (x -> x -> x) -> (x -> x -> x) -> x -> x -> x Source #
mergeAbort :: (Base x ~ f, AbortBase f, Eq x, Corecursive x, Recursive x) => (x -> x -> x) -> x -> x -> x Source #
mergeUnknown :: (Base x ~ f, SuperBase f, Eq x, Corecursive x, Recursive x) => x -> x -> x Source #
data UnsizedRecursionF f Source #
RecursionTestF UnsizedRecursionToken f | |
UnsizedStubF UnsizedRecursionToken f | |
SizingWrapperF UnsizedRecursionToken f | |
SizeStageF UnsizedRecursionToken Int f |
Instances
data StuckExprF f Source #
StuckExprB (PartExprF f) | |
StuckExprS (StuckF f) |
Instances
type StuckExpr = Fix StuckExprF Source #
data UnsizedExprF f Source #
UnsizedExprB (PartExprF f) | |
UnsizedExprS (StuckF f) | |
UnsizedExprP (SuperPositionF f) | |
UnsizedExprA (AbortableF f) | |
UnsizedExprU (UnsizedRecursionF f) |
Instances
type UnsizedExpr = Fix UnsizedExprF Source #
data SuperExprF f Source #
SuperExprB (PartExprF f) | |
SuperExprS (StuckF f) | |
SuperExprA (AbortableF f) | |
SuperExprP (SuperPositionF f) |
Instances
type SuperExpr = Fix SuperExprF Source #
data AbortExprF f Source #
AbortExprB (PartExprF f) | |
AbortExprS (StuckF f) | |
AbortExprA (AbortableF f) |
Instances
type AbortExpr = Fix AbortExprF Source #
term3ToUnsizedExpr :: Int -> Term3 -> UnsizedExpr Source #
data SizedResult Source #
Instances
Semigroup SizedResult Source # | |
Defined in Telomare.Possible (<>) :: SizedResult -> SizedResult -> SizedResult Source # sconcat :: NonEmpty SizedResult -> SizedResult Source # stimes :: Integral b => b -> SizedResult -> SizedResult Source # | |
Show SizedResult Source # | |
Defined in Telomare.Possible | |
Eq SizedResult Source # | |
Defined in Telomare.Possible (==) :: SizedResult -> SizedResult -> Bool Source # (/=) :: SizedResult -> SizedResult -> Bool Source # | |
Ord SizedResult Source # | |
Defined in Telomare.Possible compare :: SizedResult -> SizedResult -> Ordering Source # (<) :: SizedResult -> SizedResult -> Bool Source # (<=) :: SizedResult -> SizedResult -> Bool Source # (>) :: SizedResult -> SizedResult -> Bool Source # (>=) :: SizedResult -> SizedResult -> Bool Source # max :: SizedResult -> SizedResult -> SizedResult Source # min :: SizedResult -> SizedResult -> SizedResult Source # |
newtype MonoidList a Source #
MonoidList | |
|
Instances
Semigroup a => Monoid (MonoidList a) Source # | |
Defined in Telomare.Possible mempty :: MonoidList a Source # mappend :: MonoidList a -> MonoidList a -> MonoidList a Source # mconcat :: [MonoidList a] -> MonoidList a Source # | |
Semigroup a => Semigroup (MonoidList a) Source # | |
Defined in Telomare.Possible (<>) :: MonoidList a -> MonoidList a -> MonoidList a Source # sconcat :: NonEmpty (MonoidList a) -> MonoidList a Source # stimes :: Integral b => b -> MonoidList a -> MonoidList a Source # |
capMain :: (Base g ~ f, BasicBase f, StuckBase f, SuperBase f, Recursive g, Corecursive g) => g -> g Source #
isClosure :: (Base g ~ f, BasicBase f, StuckBase f, SuperBase f, Recursive g, Corecursive g) => g -> Bool Source #
convertToF :: (Base g ~ f, BasicBase f, StuckBase f, Traversable f, Corecursive g) => IExpr -> g Source #
convertFromF :: (Base g ~ f, TelomareLike g, BasicBase f, StuckBase f, Traversable f, Recursive g) => g -> Maybe IExpr Source #
term4toAbortExpr :: (Base g ~ f, BasicBase f, StuckBase f, AbortBase f, Corecursive g) => Term4 -> g Source #
abortExprToTerm4 :: (Base g ~ f, BasicBase f, StuckBase f, AbortBase f, Foldable f, Recursive g) => g -> Either IExpr Term4 Source #
evalA :: (Maybe IExpr -> Maybe IExpr -> Maybe IExpr) -> Maybe IExpr -> Term4 -> Maybe IExpr Source #