Copyright | (C) CSIRO 2017-2018 |
---|---|
License | BSD3 |
Maintainer | George Wilson <george.wilson@data61.csiro.au> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
A sum type for space characters
Synopsis
- data HorizontalSpace
- class AsHorizontalSpace r where
- type Spaces = Vector HorizontalSpace
- single :: Spaces
- manySpaces :: Int -> Spaces
- tab :: Spaces
- spaceToChar :: HorizontalSpace -> Char
- charToSpace :: Char -> Maybe HorizontalSpace
- spacesText :: Prism' Text Spaces
- spacesString :: Prism' String Spaces
- data Spaced a = Spaced {}
- class HasSpaced s t a b | s -> a, t -> b, s b -> t, t a -> s where
- betwixt :: Spaces -> a -> Spaces -> Spaced a
- uniform :: Spaces -> a -> Spaced a
- unspaced :: a -> Spaced a
- removeSpaces :: Spaced a -> Spaced a
Documentation
data HorizontalSpace Source #
HorizontalSpace
is a subset of Char
. To move back and forth betwen
it and Char
, String
, or Text
, use _HorizontalSpace
Instances
Eq HorizontalSpace Source # | |
Defined in Data.Svfactor.Text.Space (==) :: HorizontalSpace -> HorizontalSpace -> Bool # (/=) :: HorizontalSpace -> HorizontalSpace -> Bool # | |
Ord HorizontalSpace Source # | |
Defined in Data.Svfactor.Text.Space compare :: HorizontalSpace -> HorizontalSpace -> Ordering # (<) :: HorizontalSpace -> HorizontalSpace -> Bool # (<=) :: HorizontalSpace -> HorizontalSpace -> Bool # (>) :: HorizontalSpace -> HorizontalSpace -> Bool # (>=) :: HorizontalSpace -> HorizontalSpace -> Bool # max :: HorizontalSpace -> HorizontalSpace -> HorizontalSpace # min :: HorizontalSpace -> HorizontalSpace -> HorizontalSpace # | |
Show HorizontalSpace Source # | |
Defined in Data.Svfactor.Text.Space showsPrec :: Int -> HorizontalSpace -> ShowS # show :: HorizontalSpace -> String # showList :: [HorizontalSpace] -> ShowS # | |
NFData HorizontalSpace Source # | |
Defined in Data.Svfactor.Text.Space rnf :: HorizontalSpace -> () # | |
AsHorizontalSpace HorizontalSpace Source # | |
Defined in Data.Svfactor.Text.Space |
class AsHorizontalSpace r where Source #
Classy prisms for HorizontalSpace
s
_HorizontalSpace :: Prism' r HorizontalSpace Source #
Instances
AsHorizontalSpace Char Source # | |
AsHorizontalSpace HorizontalSpace Source # | |
Defined in Data.Svfactor.Text.Space |
manySpaces :: Int -> Spaces Source #
As many spaces as you'd like
spaceToChar :: HorizontalSpace -> Char Source #
Turn a Space
into a Char
. To go the other way, see charToSpace
charToSpace :: Char -> Maybe HorizontalSpace Source #
Try to turn a Char
into a Space. To go the other way, see spaceToChar
Spaced
is a value with zero or many horizontal spaces around it on
both sides.
Instances
Functor Spaced Source # | |
Applicative Spaced Source # | Appends the right parameter on the inside of the left parameter Spaced " " () " " *> Spaced "\t\t\t" () "\t \t" == Spaced " \t\t\t" () "\t \t " |
Foldable Spaced Source # | |
Defined in Data.Svfactor.Text.Space fold :: Monoid m => Spaced m -> m # foldMap :: Monoid m => (a -> m) -> Spaced a -> m # foldr :: (a -> b -> b) -> b -> Spaced a -> b # foldr' :: (a -> b -> b) -> b -> Spaced a -> b # foldl :: (b -> a -> b) -> b -> Spaced a -> b # foldl' :: (b -> a -> b) -> b -> Spaced a -> b # foldr1 :: (a -> a -> a) -> Spaced a -> a # foldl1 :: (a -> a -> a) -> Spaced a -> a # elem :: Eq a => a -> Spaced a -> Bool # maximum :: Ord a => Spaced a -> a # minimum :: Ord a => Spaced a -> a # | |
Traversable Spaced Source # | |
Eq a => Eq (Spaced a) Source # | |
Ord a => Ord (Spaced a) Source # | |
Defined in Data.Svfactor.Text.Space | |
Show a => Show (Spaced a) Source # | |
Generic (Spaced a) Source # | |
NFData a => NFData (Spaced a) Source # | |
Defined in Data.Svfactor.Text.Space | |
HasSpaced (Spaced a) (Spaced b) a b Source # | |
type Rep (Spaced a) Source # | |
Defined in Data.Svfactor.Text.Space type Rep (Spaced a) = D1 (MetaData "Spaced" "Data.Svfactor.Text.Space" "svfactor-0.1-GDLTyJD8FfREVKdyivwTvx" False) (C1 (MetaCons "Spaced" PrefixI True) (S1 (MetaSel (Just "_before") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Spaces) :*: (S1 (MetaSel (Just "_after") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Spaces) :*: S1 (MetaSel (Just "_value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))) |
class HasSpaced s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #
Classy lenses for Spaced
spaced :: Lens s t (Spaced a) (Spaced b) Source #
after :: s ~ t => Lens s t Spaces Spaces Source #
before :: s ~ t => Lens s t Spaces Spaces Source #
spacedValue :: Lens s t a b Source #
after :: (s ~ t, a ~ b) => Lens s t Spaces Spaces Source #
before :: (s ~ t, a ~ b) => Lens s t Spaces Spaces Source #
spacedValue :: (s ~ t, a ~ b) => Lens s t a b Source #
uniform :: Spaces -> a -> Spaced a Source #
uniform
puts the same spacing both before and after something.
removeSpaces :: Spaced a -> Spaced a Source #
Remove spaces from the argument