Safe Haskell | None |
---|---|
Language | Haskell2010 |
Many of the common things we want to do with String like structures are just properties of MonoFoldable. This module provides a classes for MonoFoldables that contain Char as Stringlike structures.
The motivation here is to have re-usable functions abstracted over common things we get from Foldable.
The reason we can't just use the mono-traversable package, is that it's ByteString instances are MonoFoldables containing Word8
, an the goal here is to normalize the API around Char.
For example:
isFiveChars :: FoldableString s => s -> Bool isFiveChars s = length s == 5
Which will work with all 5 string types
The motivation here is to have re-usable functions abstracted over common things we get from Foldable.
For example:
isFiveChars :: FoldableString s => s -> Bool isFiveChars s = length s == 5
Which will work with all 5 string types. .
- module Data.MonoTraversable
- class FunctorString s where
- class FoldableString s where
- class (FunctorString s, FoldableString s) => TraverseString s where
Documentation
module Data.MonoTraversable
class FunctorString s where Source #
MonoFunctor containing Char
class FoldableString s where Source #
MonoFoldable containing Char
foldMap :: (Char -> s) -> s -> s Source #
foldMap :: (MonoFoldable s, Element s ~ Char, Monoid s) => (Char -> s) -> s -> s Source #
foldr :: (Char -> a -> a) -> a -> s -> a Source #
foldr :: (MonoFoldable s, Element s ~ Char) => (Char -> a -> a) -> a -> s -> a Source #
foldl' :: (a -> Char -> a) -> a -> s -> a Source #
foldl' :: (MonoFoldable s, Element s ~ Char) => (a -> Char -> a) -> a -> s -> a Source #
all :: (Char -> Bool) -> s -> Bool Source #
all :: (MonoFoldable s, Element s ~ Char) => (Char -> Bool) -> s -> Bool Source #
any :: (Char -> Bool) -> s -> Bool Source #
any :: (MonoFoldable s, Element s ~ Char) => (Char -> Bool) -> s -> Bool Source #
null :: MonoFoldable s => s -> Bool Source #
length :: MonoFoldable s => s -> Int Source #
elem :: Char -> s -> Bool Source #
elem :: (MonoFoldable s, Element s ~ Char) => Char -> s -> Bool Source #
maximum :: (MonoFoldable s, Element s ~ Char) => s -> Char Source #
minimum :: (MonoFoldable s, Element s ~ Char) => s -> Char Source #
class (FunctorString s, FoldableString s) => TraverseString s where Source #
MonoTraversable containing Char
traverse :: Applicative f => (Char -> f Char) -> s -> f s Source #
traverse :: (MonoTraversable s, Element s ~ Char, Applicative f) => (Char -> f Char) -> s -> f s Source #