Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Profunctor.Product.Examples
Synopsis
- newtype Replicator r f a b = Replicator (r -> f b)
- replicateT :: Default (Replicator r f) b b => r -> f b
- newtype Take a z b = Take ([a] -> Maybe ([a], b))
- takeT :: Default (Take a) b b => [a] -> Maybe b
- newtype Traverse f a b = Traverse {
- runTraverse :: a -> f b
- traverseT :: Default (Traverse f) a b => a -> f b
- type Sequence = Traverse
- sequenceT :: Default (Sequence f) a b => a -> f b
- newtype Zipper a b = Zipper {}
- cl_map :: Default Zipper a b => (b -> r) -> a -> [r]
Documentation
newtype Replicator r f a b Source #
Constructors
Replicator (r -> f b) |
Instances
Functor f => Profunctor (Replicator r f) Source # | |
Defined in Data.Profunctor.Product.Examples Methods dimap :: (a -> b) -> (c -> d) -> Replicator r f b c -> Replicator r f a d # lmap :: (a -> b) -> Replicator r f b c -> Replicator r f a c # rmap :: (b -> c) -> Replicator r f a b -> Replicator r f a c # (#.) :: forall a b c q. Coercible c b => q b c -> Replicator r f a b -> Replicator r f a c # (.#) :: forall a b c q. Coercible b a => Replicator r f b c -> q a b -> Replicator r f a c # | |
Applicative f => ProductProfunctor (Replicator r f) Source # | |
Defined in Data.Profunctor.Product.Examples Methods purePP :: b -> Replicator r f a b Source # (****) :: Replicator r f a (b -> c) -> Replicator r f a b -> Replicator r f a c Source # empty :: Replicator r f () () Source # (***!) :: Replicator r f a b -> Replicator r f a' b' -> Replicator r f (a, a') (b, b') Source # | |
Applicative f => Default (Replicator (f b) f) b b Source # | |
Defined in Data.Profunctor.Product.Examples Methods def :: Replicator (f b) f b b Source # | |
Functor f => Functor (Replicator r f a) Source # | |
Defined in Data.Profunctor.Product.Examples Methods fmap :: (a0 -> b) -> Replicator r f a a0 -> Replicator r f a b # (<$) :: a0 -> Replicator r f a b -> Replicator r f a a0 # | |
Applicative f => Applicative (Replicator r f a) Source # | |
Defined in Data.Profunctor.Product.Examples Methods pure :: a0 -> Replicator r f a a0 # (<*>) :: Replicator r f a (a0 -> b) -> Replicator r f a a0 -> Replicator r f a b # liftA2 :: (a0 -> b -> c) -> Replicator r f a a0 -> Replicator r f a b -> Replicator r f a c # (*>) :: Replicator r f a a0 -> Replicator r f a b -> Replicator r f a b # (<*) :: Replicator r f a a0 -> Replicator r f a b -> Replicator r f a a0 # |
replicateT :: Default (Replicator r f) b b => r -> f b Source #
A higher-order generalisation of replicate
. For
example
foo :: IO (String, String, String) foo = replicateT getLine
> foo Hello world ! ("Hello","world","!")
Instances
Profunctor (Take a) Source # | |
Defined in Data.Profunctor.Product.Examples Methods dimap :: (a0 -> b) -> (c -> d) -> Take a b c -> Take a a0 d # lmap :: (a0 -> b) -> Take a b c -> Take a a0 c # rmap :: (b -> c) -> Take a a0 b -> Take a a0 c # (#.) :: forall a0 b c q. Coercible c b => q b c -> Take a a0 b -> Take a a0 c # (.#) :: forall a0 b c q. Coercible b a0 => Take a b c -> q a0 b -> Take a a0 c # | |
ProductProfunctor (Take a) Source # | |
Default (Take a) z a Source # | |
Defined in Data.Profunctor.Product.Examples | |
Functor (Take a z) Source # | |
Applicative (Take a z) Source # | |
Defined in Data.Profunctor.Product.Examples |
takeT :: Default (Take a) b b => [a] -> Maybe b Source #
A type safe generalisation of take
. For example
> let count = [1..] :: [Int] > takeT count :: Maybe (Int, Int) Just (1,2) > takeT count :: Maybe (Int, Int, (Int, (Int, Int), Int, Int), Const Int Bool, Identity (Int, Int), Tagged String Int) Just (1,2,(3,(4,5),6,7),Const 8,Identity (9,10),Tagged 11)
newtype Traverse f a b Source #
Constructors
Traverse | |
Fields
|
Instances
Functor f => Profunctor (Traverse f) Source # | |
Defined in Data.Profunctor.Product.Examples Methods dimap :: (a -> b) -> (c -> d) -> Traverse f b c -> Traverse f a d # lmap :: (a -> b) -> Traverse f b c -> Traverse f a c # rmap :: (b -> c) -> Traverse f a b -> Traverse f a c # (#.) :: forall a b c q. Coercible c b => q b c -> Traverse f a b -> Traverse f a c # (.#) :: forall a b c q. Coercible b a => Traverse f b c -> q a b -> Traverse f a c # | |
Applicative f => ProductProfunctor (Traverse f) Source # | |
Default (Traverse f) (f a) a Source # | |
Defined in Data.Profunctor.Product.Examples | |
Functor f => Functor (Traverse f a) Source # | |
Applicative f => Applicative (Traverse f a) Source # | |
Defined in Data.Profunctor.Product.Examples Methods pure :: a0 -> Traverse f a a0 # (<*>) :: Traverse f a (a0 -> b) -> Traverse f a a0 -> Traverse f a b # liftA2 :: (a0 -> b -> c) -> Traverse f a a0 -> Traverse f a b -> Traverse f a c # (*>) :: Traverse f a a0 -> Traverse f a b -> Traverse f a b # (<*) :: Traverse f a a0 -> Traverse f a b -> Traverse f a a0 # |
traverseT :: Default (Traverse f) a b => a -> f b Source #
Use sequenceT
instead. It has a better name.
Instances
Profunctor Zipper Source # | |
Defined in Data.Profunctor.Product.Examples Methods dimap :: (a -> b) -> (c -> d) -> Zipper b c -> Zipper a d # lmap :: (a -> b) -> Zipper b c -> Zipper a c # rmap :: (b -> c) -> Zipper a b -> Zipper a c # (#.) :: forall a b c q. Coercible c b => q b c -> Zipper a b -> Zipper a c # (.#) :: forall a b c q. Coercible b a => Zipper b c -> q a b -> Zipper a c # | |
ProductProfunctor Zipper Source # | |
a ~ b => Default Zipper [a] b Source # | |
Defined in Data.Profunctor.Product.Examples | |
Functor (Zipper a) Source # | |
Applicative (Zipper a) Source # | |
Defined in Data.Profunctor.Product.Examples |