Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
The Eval
family.
Documentation
type family Eval (e :: Exp a) :: a Source #
Expression evaluator.
Instances
type Eval (Not False) Source # | |
Defined in Fcf.Data.Bool | |
type Eval (Not True) Source # | |
Defined in Fcf.Data.Bool | |
type Eval (Constraints (a ': as) :: Constraint -> Type) Source # | |
Defined in Fcf.Utils | |
type Eval (Constraints ([] :: [Constraint])) Source # | |
Defined in Fcf.Utils | |
type Eval (IsJust (Nothing :: Maybe a) :: Bool -> Type) Source # | |
type Eval (IsJust (Just _a) :: Bool -> Type) Source # | |
type Eval (IsNothing (Nothing :: Maybe a) :: Bool -> Type) Source # | |
type Eval (IsNothing (Just _a) :: Bool -> Type) Source # | |
type Eval (False && b :: Bool -> Type) Source # | |
type Eval (True && b :: Bool -> Type) Source # | |
type Eval (a && True :: Bool -> Type) Source # | |
type Eval (a && False :: Bool -> Type) Source # | |
type Eval (False || b :: Bool -> Type) Source # | |
type Eval (True || b :: Bool -> Type) Source # | |
type Eval (a || False :: Bool -> Type) Source # | |
type Eval (a || True :: Bool -> Type) Source # | |
type Eval (a > b :: Bool -> Type) Source # | |
type Eval (a < b :: Bool -> Type) Source # | |
type Eval (a >= b :: Bool -> Type) Source # | |
type Eval (a <= b :: Bool -> Type) Source # | |
type Eval (Null (a2 ': as) :: Bool -> Type) Source # | |
type Eval (Null ([] :: [a]) :: Bool -> Type) Source # | |
type Eval (a ^ b :: Nat -> Type) Source # | |
type Eval (a * b :: Nat -> Type) Source # | |
type Eval (a - b :: Nat -> Type) Source # | |
type Eval (a + b :: Nat -> Type) Source # | |
type Eval (Length (a2 ': as) :: Nat -> Type) Source # | |
type Eval (Length ([] :: [a]) :: Nat -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Pure x :: a -> Type) Source # | |
Defined in Fcf.Combinators | |
type Eval (Join e :: a -> Type) Source # | |
type Eval (Error msg :: a -> Type) Source # | |
type Eval (TError msg :: a -> Type) Source # | |
type Eval (IsRight (Right _a :: Either a b) :: Bool -> Type) Source # | |
type Eval (IsRight (Left _a :: Either a b) :: Bool -> Type) Source # | |
type Eval (IsLeft (Right _a :: Either a b) :: Bool -> Type) Source # | |
type Eval (IsLeft (Left _a :: Either a b) :: Bool -> Type) Source # | |
type Eval (Elem a2 as :: Bool -> Type) Source # | |
type Eval (Fst ((,) a2 _b) :: a1 -> Type) Source # | |
Defined in Fcf.Data.Common | |
type Eval (Snd ((,) _a b) :: a1 -> Type) Source # | |
Defined in Fcf.Data.Common | |
type Eval (FromMaybe _a (Just b) :: a -> Type) Source # | |
Defined in Fcf.Data.Common | |
type Eval (FromMaybe a2 (Nothing :: Maybe a1) :: a1 -> Type) Source # | |
type Eval (TyEq a b :: Bool -> Type) Source # | |
type Eval (Pure1 f x :: a2 -> Type) Source # | |
Defined in Fcf.Combinators | |
type Eval (k =<< e :: a2 -> Type) Source # | |
type Eval (f <$> e :: a2 -> Type) Source # | |
Defined in Fcf.Combinators | |
type Eval (f <*> e :: a2 -> Type) Source # | |
type Eval (ConstFn a2 _b :: a1 -> Type) Source # | |
Defined in Fcf.Combinators | |
type Eval (f $ a3 :: a2 -> Type) Source # | |
Defined in Fcf.Combinators | |
type Eval (Case ms a :: k -> Type) Source # | |
type Eval (UnBool fal tru True :: a -> Type) Source # | |
type Eval (UnBool fal tru False :: a -> Type) Source # | |
type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) Source # | |
type Eval (Uncurry f ((,) x y) :: a2 -> Type) Source # | |
type Eval (UnMaybe y f (Just x) :: a2 -> Type) Source # | |
type Eval (UnMaybe y f (Nothing :: Maybe a1) :: a2 -> Type) Source # | |
type Eval (Foldr f y (x ': xs) :: a2 -> Type) Source # | |
type Eval (Foldr f y ([] :: [a1]) :: a2 -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (UnList y f xs :: a2 -> Type) Source # | |
type Eval (Pure2 f x y :: a2 -> Type) Source # | |
Defined in Fcf.Combinators | |
type Eval ((f <=< g) x :: a3 -> Type) Source # | |
type Eval (LiftM2 f x y :: a3 -> Type) Source # | |
type Eval (Flip f y x :: a2 -> Type) Source # | |
Defined in Fcf.Combinators | |
type Eval (UnEither f g (Right y :: Either a2 b) :: a1 -> Type) Source # | |
type Eval (UnEither f g (Left x :: Either a2 b) :: a1 -> Type) Source # | |
type Eval (Pure3 f x y z :: a2 -> Type) Source # | |
Defined in Fcf.Combinators | |
type Eval (LiftM3 f x y z :: a4 -> Type) Source # | |
type Eval (Concat lsts :: [a] -> Type) Source # | |
type Eval (Reverse l :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) Source # | |
type Eval (Init (a2 ': ([] :: [a1])) :: Maybe [a1] -> Type) Source # | |
type Eval (Init ([] :: [a]) :: Maybe [a] -> Type) Source # | |
type Eval (Tail (_a ': as) :: Maybe [a] -> Type) Source # | |
type Eval (Tail ([] :: [a]) :: Maybe [a] -> Type) Source # | |
type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) Source # | |
type Eval (Head ([] :: [a]) :: Maybe a -> Type) Source # | |
type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) Source # | |
type Eval (Last (a2 ': ([] :: [a1])) :: Maybe a1 -> Type) Source # | |
type Eval (Last ([] :: [a]) :: Maybe a -> Type) Source # | |
type Eval (Cons a2 as :: [a1] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval ((x ': xs) ++ ys :: [a] -> Type) Source # | |
type Eval (([] :: [a]) ++ ys :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Filter p (a2 ': as) :: [a1] -> Type) Source # | |
type Eval (Filter _p ([] :: [a]) :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Replicate n a2 :: [a1] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Take n as :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Drop n as :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (TakeWhile p (x ': xs) :: [a] -> Type) Source # | |
type Eval (TakeWhile p ([] :: [a]) :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (DropWhile p (x ': xs) :: [a] -> Type) Source # | |
type Eval (DropWhile p ([] :: [a]) :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) Source # | |
type Eval (FindIndex _p ([] :: [a]) :: Maybe Nat -> Type) Source # | |
type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) Source # | |
type Eval (Find _p ([] :: [a]) :: Maybe a -> Type) Source # | |
type Eval (Zip as bs :: [(a, b)] -> Type) Source # | |
type Eval (Unfoldr f c :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (ConcatMap f lst :: [a2] -> Type) Source # | |
type Eval (SetIndex n a' as :: [k] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Lookup a as :: Maybe b -> Type) Source # | |
type Eval (Map f (a2 ': as) :: [b] -> Type) Source # | |
type Eval (Map f ([] :: [a]) :: [b] -> Type) Source # | |
Defined in Fcf.Classes | |
type Eval (Map f (Just a3) :: Maybe a2 -> Type) Source # | |
type Eval (Map f (Nothing :: Maybe a) :: Maybe b -> Type) Source # | |
type Eval (ZipWith f (a2 ': as) (b2 ': bs) :: [c] -> Type) Source # | |
type Eval (ZipWith _f _as ([] :: [b]) :: [c] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (ZipWith _f ([] :: [a]) _bs :: [c] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Unzip as :: ([a], [b]) -> Type) Source # | |
type Eval (Cons2 ((,) a3 b) ((,) as bs) :: ([a2], [a1]) -> Type) Source # | |
type Eval (Map f (Right a3 :: Either a2 a1) :: Either a2 b -> Type) Source # | |
type Eval (Map f (Left x :: Either a2 a1) :: Either a2 b -> Type) Source # | |
type Eval (Map f ((,) x a2) :: (k2, k1) -> Type) Source # | |
type Eval ((f *** f') ((,) b2 b'2) :: (k2, k1) -> Type) Source # | |
type Eval (Bimap f g (Right y :: Either a b1) :: Either a' b2 -> Type) Source # | |
type Eval (Bimap f g (Left x :: Either a1 b) :: Either a2 b' -> Type) Source # | |
type Eval (Bimap f g ((,) x y) :: (k2, k1) -> Type) Source # | |
type Eval (Map f ((,,) x y a2) :: (k2, k3, k1) -> Type) Source # | |
type Eval (Map f ((,,,) x y z a2) :: (k2, k3, k4, k1) -> Type) Source # | |
type Eval (Map f ((,,,,) x y z w a2) :: (k2, k3, k4, k5, k1) -> Type) Source # | |