Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- newtype CaseFunc (k :: Type -> Constraint) r (xs :: [Type]) = CaseFunc (forall x. k x => x -> r)
- newtype CaseFunc' (k :: Type -> Constraint) (xs :: [Type]) = CaseFunc' (forall x. k x => x -> x)
- newtype CaseFunc1 (k :: Type -> Constraint) (k1 :: (Type -> Type) -> Constraint) (k0 :: Type -> Constraint) r (xs :: [Type]) = CaseFunc1 (forall f x. (k (f x), k1 f, k0 x) => f x -> f r)
- newtype CaseFunc1' (k :: Type -> Constraint) (k1 :: (Type -> Type) -> Constraint) (k0 :: Type -> Constraint) (xs :: [Type]) = CaseFunc1' (forall f x. (k (f x), k1 f, k0 x) => f x -> f x)
Documentation
newtype CaseFunc (k :: Type -> Constraint) r (xs :: [Type]) Source #
This handler stores a polymorphic function that returns a different type.
let y =pick
(5 :: Int) ::Which
'[Int, Bool]switch
y (CaseFunc
@Typeable
(show . typeRep . (pure @Proxy))) `shouldBe` Int
let x = (5 :: Int)./
False./
'X'./
Just 'O'./
(6 :: Int)./
Just 'A'./
nul
afoldr
(:) [] (forMany
(CaseFunc
@Typeable
(show . typeRep . (pure @Proxy))) x) `shouldBe` ["Int", "Bool", "Char", "Maybe Char", "Int", "Maybe Char"]
CaseFunc (forall x. k x => x -> r) |
newtype CaseFunc' (k :: Type -> Constraint) (xs :: [Type]) Source #
This handler stores a polymorphic function that doesn't change the type.
let x = (5 :: Int)./
(6 :: Int8)./
(7 :: Int16)./
(8 :: Int32)./
nil
y = (15 :: Int)./
(16 :: Int8)./
(17 :: Int16)./
(18 :: Int32)./
nil
afmap
(CaseFunc'
@Num
(+10)) x `shouldBe` y
CaseFunc' (forall x. k x => x -> x) |
newtype CaseFunc1 (k :: Type -> Constraint) (k1 :: (Type -> Type) -> Constraint) (k0 :: Type -> Constraint) r (xs :: [Type]) Source #
This handler stores a polymorphic function that work on higher kinds, eg Functor
You may want to use NoContraint for
k@
CaseFunc1 (forall f x. (k (f x), k1 f, k0 x) => f x -> f r) |
newtype CaseFunc1' (k :: Type -> Constraint) (k1 :: (Type -> Type) -> Constraint) (k0 :: Type -> Constraint) (xs :: [Type]) Source #
A varation of CaseFunc
that doesn't change the return type
CaseFunc1' (forall f x. (k (f x), k1 f, k0 x) => f x -> f x) |
Reiterate (CaseFunc1' k k1 k0) xs Source # | |
(k (f x), k1 f, k0 x) => Case (CaseFunc1' k k1 k0) ((:) Type (f x) xs) Source # | |
type CaseResult Type * (CaseFunc1' k k1 k0) (f x) Source # | |