Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data structures and functions for managing a single element in a
CommaSeparated
structure.
Synopsis
- data Elem f ws a = Elem {
- _elemVal :: a
- _elemTrailing :: f (Comma, ws)
- class HasElem c f ws a | c -> f ws a where
- elem :: Lens' c (Elem f ws a)
- elemTrailing :: Lens' c (f (Comma, ws))
- elemVal :: Lens' c a
- data Comma = Comma
- _ElemTrailingIso :: (Monoid ws, Monoid ws') => Iso (Elem Identity ws a) (Elem Identity ws' a') (Elem Maybe ws a) (Elem Maybe ws' a')
- parseComma :: CharParsing f => f Comma
- parseCommaTrailingMaybe :: CharParsing f => f ws -> f (Maybe (Comma, ws))
Types
Data type to represent a single element in a CommaSeparated
list. Carries
information about it's own trailing whitespace. Denoted by the f
.
Elem | |
|
Instances
Traversable f => Bitraversable (Elem f) Source # | |
Defined in Waargonaut.Types.CommaSep.Elem bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> Elem f a b -> f0 (Elem f c d) # | |
Foldable f => Bifoldable (Elem f) Source # | |
Functor f => Bifunctor (Elem f) Source # | |
Functor (Elem f ws) Source # | |
(Monoid ws, Applicative f) => Applicative (Elem f ws) Source # | |
Foldable (Elem f ws) Source # | |
Defined in Waargonaut.Types.CommaSep.Elem fold :: Monoid m => Elem f ws m -> m # foldMap :: Monoid m => (a -> m) -> Elem f ws a -> m # foldMap' :: Monoid m => (a -> m) -> Elem f ws a -> m # foldr :: (a -> b -> b) -> b -> Elem f ws a -> b # foldr' :: (a -> b -> b) -> b -> Elem f ws a -> b # foldl :: (b -> a -> b) -> b -> Elem f ws a -> b # foldl' :: (b -> a -> b) -> b -> Elem f ws a -> b # foldr1 :: (a -> a -> a) -> Elem f ws a -> a # foldl1 :: (a -> a -> a) -> Elem f ws a -> a # toList :: Elem f ws a -> [a] # length :: Elem f ws a -> Int # elem :: Eq a => a -> Elem f ws a -> Bool # maximum :: Ord a => Elem f ws a -> a # minimum :: Ord a => Elem f ws a -> a # | |
Traversable (Elem f ws) Source # | |
Defined in Waargonaut.Types.CommaSep.Elem | |
(Eq1 f, Eq ws, Eq a) => Eq (Elem f ws a) Source # | |
(Show1 f, Show ws, Show a) => Show (Elem f ws a) Source # | |
HasElem (Elem f ws a) f ws a Source # | |
class HasElem c f ws a | c -> f ws a where Source #
Typeclass for things that contain a single Elem
structure.
Unary type to represent a comma.
_ElemTrailingIso :: (Monoid ws, Monoid ws') => Iso (Elem Identity ws a) (Elem Identity ws' a') (Elem Maybe ws a) (Elem Maybe ws' a') Source #
Iso
between an Elem
that is not on the trailing element and one that is.
Parse
parseComma :: CharParsing f => f Comma Source #
Parse a single comma (,)
parseCommaTrailingMaybe :: CharParsing f => f ws -> f (Maybe (Comma, ws)) Source #
Parse an optional comma and its trailing whitespace.
>>>
testparse (parseCommaTrailingMaybe parseWhitespace) ", "
Right (Just (Comma,WS [Space]))
>>>
testparse (parseCommaTrailingMaybe parseWhitespace) " , "
Right Nothing
>>>
testparse (parseCommaTrailingMaybe parseWhitespace) ",, "
Right (Just (Comma,WS []))