{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
module Data.Char.Space(
HorizontalTab
, HasHorizontalTab(..)
, AsHorizontalTab(..)
, parseHorizontalTab
, LineFeed
, HasLineFeed(..)
, AsLineFeed(..)
, parseLineFeed
, VerticalTab
, HasVerticalTab(..)
, AsVerticalTab(..)
, parseVerticalTab
, FormFeed
, HasFormFeed(..)
, AsFormFeed(..)
, parseFormFeed
, CarriageReturn
, HasCarriageReturn(..)
, AsCarriageReturn(..)
, parseCarriageReturn
, Whitespace
, HasWhitespace(..)
, AsWhitespace(..)
, parseWhitespace
, NoBreakSpace
, HasNoBreakSpace(..)
, AsNoBreakSpace(..)
, parseNoBreakSpace
, OghamSpaceMark
, HasOghamSpaceMark(..)
, AsOghamSpaceMark(..)
, parseOghamSpaceMark
, EnQuad
, HasEnQuad(..)
, AsEnQuad(..)
, parseEnQuad
, EmQuad
, HasEmQuad(..)
, AsEmQuad(..)
, parseEmQuad
, EnSpace
, HasEnSpace(..)
, AsEnSpace(..)
, parseEnSpace
, EmSpace
, HasEmSpace(..)
, AsEmSpace(..)
, parseEmSpace
, ThreePerEmSpace
, HasThreePerEmSpace(..)
, AsThreePerEmSpace(..)
, parseThreePerEmSpace
, FourPerEmSpace
, HasFourPerEmSpace(..)
, AsFourPerEmSpace(..)
, parseFourPerEmSpace
, SixPerEmSpace
, HasSixPerEmSpace(..)
, AsSixPerEmSpace(..)
, parseSixPerEmSpace
, FigureSpace
, HasFigureSpace(..)
, AsFigureSpace(..)
, parseFigureSpace
, PunctuationSpace
, HasPunctuationSpace(..)
, AsPunctuationSpace(..)
, parsePunctuationSpace
, ThinSpace
, HasThinSpace(..)
, AsThinSpace(..)
, parseThinSpace
, HairSpace
, HasHairSpace(..)
, AsHairSpace(..)
, parseHairSpace
, NarrowNoBreakSpace
, HasNarrowNoBreakSpace(..)
, AsNarrowNoBreakSpace(..)
, parseNarrowNoBreakSpace
, MediumMathematicalSpace
, HasMediumMathematicalSpace(..)
, AsMediumMathematicalSpace(..)
, parseMediumMathematicalSpace
, IdeographicSpace
, HasIdeographicSpace(..)
, AsIdeographicSpace(..)
, parseIdeographicSpace
, SpaceChar(..)
, HasSpaceChar(..)
, AsSpaceChar(..)
, parseSpaceChar
, IsoLatin1(..)
, HasIsoLatin1(..)
, AsIsoLatin1(..)
, parseIsoLatin1
) where
import Control.Category ( Category(id) )
import Control.Lens ( Prism', prism', (#), Lens' )
import Data.Char ( Char )
import Data.Eq ( Eq((==)) )
import Data.Int ( Int )
import Data.Foldable ( asum )
import Data.Functor ( Functor((<$), fmap) )
import Data.Maybe ( Maybe(Nothing, Just) )
import Data.Monoid ( (<>), Monoid(mempty) )
import Data.Ord ( Ord )
import Data.Semigroup ( Semigroup )
import GHC.Generics ( Generic )
import GHC.Show ( Show )
import Prelude(Integer)
import Text.Parser.Char ( CharParsing(satisfy) )
import Text.Parser.Combinators ( Parsing((<?>)) )
data HorizontalTab = HorizontalTab
deriving (HorizontalTab -> HorizontalTab -> Bool
(HorizontalTab -> HorizontalTab -> Bool)
-> (HorizontalTab -> HorizontalTab -> Bool) -> Eq HorizontalTab
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HorizontalTab -> HorizontalTab -> Bool
$c/= :: HorizontalTab -> HorizontalTab -> Bool
== :: HorizontalTab -> HorizontalTab -> Bool
$c== :: HorizontalTab -> HorizontalTab -> Bool
Eq, Eq HorizontalTab
Eq HorizontalTab
-> (HorizontalTab -> HorizontalTab -> Ordering)
-> (HorizontalTab -> HorizontalTab -> Bool)
-> (HorizontalTab -> HorizontalTab -> Bool)
-> (HorizontalTab -> HorizontalTab -> Bool)
-> (HorizontalTab -> HorizontalTab -> Bool)
-> (HorizontalTab -> HorizontalTab -> HorizontalTab)
-> (HorizontalTab -> HorizontalTab -> HorizontalTab)
-> Ord HorizontalTab
HorizontalTab -> HorizontalTab -> Bool
HorizontalTab -> HorizontalTab -> Ordering
HorizontalTab -> HorizontalTab -> HorizontalTab
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HorizontalTab -> HorizontalTab -> HorizontalTab
$cmin :: HorizontalTab -> HorizontalTab -> HorizontalTab
max :: HorizontalTab -> HorizontalTab -> HorizontalTab
$cmax :: HorizontalTab -> HorizontalTab -> HorizontalTab
>= :: HorizontalTab -> HorizontalTab -> Bool
$c>= :: HorizontalTab -> HorizontalTab -> Bool
> :: HorizontalTab -> HorizontalTab -> Bool
$c> :: HorizontalTab -> HorizontalTab -> Bool
<= :: HorizontalTab -> HorizontalTab -> Bool
$c<= :: HorizontalTab -> HorizontalTab -> Bool
< :: HorizontalTab -> HorizontalTab -> Bool
$c< :: HorizontalTab -> HorizontalTab -> Bool
compare :: HorizontalTab -> HorizontalTab -> Ordering
$ccompare :: HorizontalTab -> HorizontalTab -> Ordering
$cp1Ord :: Eq HorizontalTab
Ord, Int -> HorizontalTab -> ShowS
[HorizontalTab] -> ShowS
HorizontalTab -> String
(Int -> HorizontalTab -> ShowS)
-> (HorizontalTab -> String)
-> ([HorizontalTab] -> ShowS)
-> Show HorizontalTab
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HorizontalTab] -> ShowS
$cshowList :: [HorizontalTab] -> ShowS
show :: HorizontalTab -> String
$cshow :: HorizontalTab -> String
showsPrec :: Int -> HorizontalTab -> ShowS
$cshowsPrec :: Int -> HorizontalTab -> ShowS
Show, (forall x. HorizontalTab -> Rep HorizontalTab x)
-> (forall x. Rep HorizontalTab x -> HorizontalTab)
-> Generic HorizontalTab
forall x. Rep HorizontalTab x -> HorizontalTab
forall x. HorizontalTab -> Rep HorizontalTab x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HorizontalTab x -> HorizontalTab
$cfrom :: forall x. HorizontalTab -> Rep HorizontalTab x
Generic)
class HasHorizontalTab a where
horizontalTab :: Lens' a HorizontalTab
instance HasHorizontalTab HorizontalTab where
horizontalTab :: (HorizontalTab -> f HorizontalTab)
-> HorizontalTab -> f HorizontalTab
horizontalTab = (HorizontalTab -> f HorizontalTab)
-> HorizontalTab -> f HorizontalTab
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasHorizontalTab () where
horizontalTab :: (HorizontalTab -> f HorizontalTab) -> () -> f ()
horizontalTab HorizontalTab -> f HorizontalTab
f ()
x =
(HorizontalTab -> ()) -> f HorizontalTab -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\HorizontalTab
HorizontalTab -> ()
x) (HorizontalTab -> f HorizontalTab
f HorizontalTab
HorizontalTab)
instance Semigroup HorizontalTab where
HorizontalTab
HorizontalTab <> :: HorizontalTab -> HorizontalTab -> HorizontalTab
<> HorizontalTab
HorizontalTab = HorizontalTab
HorizontalTab
instance Monoid HorizontalTab where
mempty :: HorizontalTab
mempty = HorizontalTab
HorizontalTab
class AsHorizontalTab a where
_HorizontalTab :: Prism' a HorizontalTab
_HorizontalTab' :: a
_HorizontalTab' = Tagged HorizontalTab (Identity HorizontalTab)
-> Tagged a (Identity a)
forall a. AsHorizontalTab a => Prism' a HorizontalTab
_HorizontalTab (Tagged HorizontalTab (Identity HorizontalTab)
-> Tagged a (Identity a))
-> HorizontalTab -> a
forall t b. AReview t b -> b -> t
# HorizontalTab
HorizontalTab
instance AsHorizontalTab HorizontalTab where
_HorizontalTab :: p HorizontalTab (f HorizontalTab)
-> p HorizontalTab (f HorizontalTab)
_HorizontalTab = p HorizontalTab (f HorizontalTab)
-> p HorizontalTab (f HorizontalTab)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsHorizontalTab () where
_HorizontalTab :: p HorizontalTab (f HorizontalTab) -> p () (f ())
_HorizontalTab =
(HorizontalTab -> ())
-> (() -> Maybe HorizontalTab) -> Prism' () HorizontalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HorizontalTab
HorizontalTab -> ())
(\() -> HorizontalTab -> Maybe HorizontalTab
forall a. a -> Maybe a
Just HorizontalTab
HorizontalTab)
instance AsHorizontalTab Char where
_HorizontalTab :: p HorizontalTab (f HorizontalTab) -> p Char (f Char)
_HorizontalTab =
(HorizontalTab -> Char)
-> (Char -> Maybe HorizontalTab) -> Prism' Char HorizontalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HorizontalTab
HorizontalTab -> Char
'\9')
(\case
Char
'\9' -> HorizontalTab -> Maybe HorizontalTab
forall a. a -> Maybe a
Just HorizontalTab
HorizontalTab
Char
_ -> Maybe HorizontalTab
forall a. Maybe a
Nothing
)
instance AsHorizontalTab Int where
_HorizontalTab :: p HorizontalTab (f HorizontalTab) -> p Int (f Int)
_HorizontalTab =
(HorizontalTab -> Int)
-> (Int -> Maybe HorizontalTab) -> Prism' Int HorizontalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HorizontalTab
HorizontalTab -> Int
9)
(\case
Int
9 -> HorizontalTab -> Maybe HorizontalTab
forall a. a -> Maybe a
Just HorizontalTab
HorizontalTab
Int
_ -> Maybe HorizontalTab
forall a. Maybe a
Nothing
)
instance AsHorizontalTab Integer where
_HorizontalTab :: p HorizontalTab (f HorizontalTab) -> p Integer (f Integer)
_HorizontalTab =
(HorizontalTab -> Integer)
-> (Integer -> Maybe HorizontalTab) -> Prism' Integer HorizontalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HorizontalTab
HorizontalTab -> Integer
9)
(\case
Integer
9 -> HorizontalTab -> Maybe HorizontalTab
forall a. a -> Maybe a
Just HorizontalTab
HorizontalTab
Integer
_ -> Maybe HorizontalTab
forall a. Maybe a
Nothing
)
parseHorizontalTab ::
CharParsing p =>
p HorizontalTab
parseHorizontalTab :: p HorizontalTab
parseHorizontalTab =
HorizontalTab
HorizontalTab HorizontalTab -> p Char -> p HorizontalTab
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\9') p HorizontalTab -> String -> p HorizontalTab
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"horizontal tab character"
data LineFeed = LineFeed
deriving (LineFeed -> LineFeed -> Bool
(LineFeed -> LineFeed -> Bool)
-> (LineFeed -> LineFeed -> Bool) -> Eq LineFeed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LineFeed -> LineFeed -> Bool
$c/= :: LineFeed -> LineFeed -> Bool
== :: LineFeed -> LineFeed -> Bool
$c== :: LineFeed -> LineFeed -> Bool
Eq, Eq LineFeed
Eq LineFeed
-> (LineFeed -> LineFeed -> Ordering)
-> (LineFeed -> LineFeed -> Bool)
-> (LineFeed -> LineFeed -> Bool)
-> (LineFeed -> LineFeed -> Bool)
-> (LineFeed -> LineFeed -> Bool)
-> (LineFeed -> LineFeed -> LineFeed)
-> (LineFeed -> LineFeed -> LineFeed)
-> Ord LineFeed
LineFeed -> LineFeed -> Bool
LineFeed -> LineFeed -> Ordering
LineFeed -> LineFeed -> LineFeed
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LineFeed -> LineFeed -> LineFeed
$cmin :: LineFeed -> LineFeed -> LineFeed
max :: LineFeed -> LineFeed -> LineFeed
$cmax :: LineFeed -> LineFeed -> LineFeed
>= :: LineFeed -> LineFeed -> Bool
$c>= :: LineFeed -> LineFeed -> Bool
> :: LineFeed -> LineFeed -> Bool
$c> :: LineFeed -> LineFeed -> Bool
<= :: LineFeed -> LineFeed -> Bool
$c<= :: LineFeed -> LineFeed -> Bool
< :: LineFeed -> LineFeed -> Bool
$c< :: LineFeed -> LineFeed -> Bool
compare :: LineFeed -> LineFeed -> Ordering
$ccompare :: LineFeed -> LineFeed -> Ordering
$cp1Ord :: Eq LineFeed
Ord, Int -> LineFeed -> ShowS
[LineFeed] -> ShowS
LineFeed -> String
(Int -> LineFeed -> ShowS)
-> (LineFeed -> String) -> ([LineFeed] -> ShowS) -> Show LineFeed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LineFeed] -> ShowS
$cshowList :: [LineFeed] -> ShowS
show :: LineFeed -> String
$cshow :: LineFeed -> String
showsPrec :: Int -> LineFeed -> ShowS
$cshowsPrec :: Int -> LineFeed -> ShowS
Show, (forall x. LineFeed -> Rep LineFeed x)
-> (forall x. Rep LineFeed x -> LineFeed) -> Generic LineFeed
forall x. Rep LineFeed x -> LineFeed
forall x. LineFeed -> Rep LineFeed x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LineFeed x -> LineFeed
$cfrom :: forall x. LineFeed -> Rep LineFeed x
Generic)
class HasLineFeed a where
lineFeed :: Lens' a LineFeed
instance HasLineFeed LineFeed where
lineFeed :: (LineFeed -> f LineFeed) -> LineFeed -> f LineFeed
lineFeed = (LineFeed -> f LineFeed) -> LineFeed -> f LineFeed
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasLineFeed () where
lineFeed :: (LineFeed -> f LineFeed) -> () -> f ()
lineFeed LineFeed -> f LineFeed
f ()
x =
(LineFeed -> ()) -> f LineFeed -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\LineFeed
LineFeed -> ()
x) (LineFeed -> f LineFeed
f LineFeed
LineFeed)
instance Semigroup LineFeed where
LineFeed
LineFeed <> :: LineFeed -> LineFeed -> LineFeed
<> LineFeed
LineFeed = LineFeed
LineFeed
instance Monoid LineFeed where
mempty :: LineFeed
mempty = LineFeed
LineFeed
class AsLineFeed a where
_LineFeed :: Prism' a LineFeed
_LineFeed' :: a
_LineFeed' = Tagged LineFeed (Identity LineFeed) -> Tagged a (Identity a)
forall a. AsLineFeed a => Prism' a LineFeed
_LineFeed (Tagged LineFeed (Identity LineFeed) -> Tagged a (Identity a))
-> LineFeed -> a
forall t b. AReview t b -> b -> t
# LineFeed
LineFeed
instance AsLineFeed LineFeed where
_LineFeed :: p LineFeed (f LineFeed) -> p LineFeed (f LineFeed)
_LineFeed = p LineFeed (f LineFeed) -> p LineFeed (f LineFeed)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsLineFeed () where
_LineFeed :: p LineFeed (f LineFeed) -> p () (f ())
_LineFeed =
(LineFeed -> ()) -> (() -> Maybe LineFeed) -> Prism' () LineFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\LineFeed
LineFeed -> ())
(\() -> LineFeed -> Maybe LineFeed
forall a. a -> Maybe a
Just LineFeed
LineFeed)
instance AsLineFeed Char where
_LineFeed :: p LineFeed (f LineFeed) -> p Char (f Char)
_LineFeed =
(LineFeed -> Char)
-> (Char -> Maybe LineFeed) -> Prism' Char LineFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\LineFeed
LineFeed -> Char
'\10')
(\case
Char
'\10' -> LineFeed -> Maybe LineFeed
forall a. a -> Maybe a
Just LineFeed
LineFeed
Char
_ -> Maybe LineFeed
forall a. Maybe a
Nothing
)
instance AsLineFeed Int where
_LineFeed :: p LineFeed (f LineFeed) -> p Int (f Int)
_LineFeed =
(LineFeed -> Int) -> (Int -> Maybe LineFeed) -> Prism' Int LineFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\LineFeed
LineFeed -> Int
10)
(\case
Int
10 -> LineFeed -> Maybe LineFeed
forall a. a -> Maybe a
Just LineFeed
LineFeed
Int
_ -> Maybe LineFeed
forall a. Maybe a
Nothing
)
instance AsLineFeed Integer where
_LineFeed :: p LineFeed (f LineFeed) -> p Integer (f Integer)
_LineFeed =
(LineFeed -> Integer)
-> (Integer -> Maybe LineFeed) -> Prism' Integer LineFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\LineFeed
LineFeed -> Integer
10)
(\case
Integer
10 -> LineFeed -> Maybe LineFeed
forall a. a -> Maybe a
Just LineFeed
LineFeed
Integer
_ -> Maybe LineFeed
forall a. Maybe a
Nothing
)
parseLineFeed ::
CharParsing p =>
p LineFeed
parseLineFeed :: p LineFeed
parseLineFeed =
LineFeed
LineFeed LineFeed -> p Char -> p LineFeed
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\10') p LineFeed -> String -> p LineFeed
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"line feed character"
data VerticalTab = VerticalTab
deriving (VerticalTab -> VerticalTab -> Bool
(VerticalTab -> VerticalTab -> Bool)
-> (VerticalTab -> VerticalTab -> Bool) -> Eq VerticalTab
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerticalTab -> VerticalTab -> Bool
$c/= :: VerticalTab -> VerticalTab -> Bool
== :: VerticalTab -> VerticalTab -> Bool
$c== :: VerticalTab -> VerticalTab -> Bool
Eq, Eq VerticalTab
Eq VerticalTab
-> (VerticalTab -> VerticalTab -> Ordering)
-> (VerticalTab -> VerticalTab -> Bool)
-> (VerticalTab -> VerticalTab -> Bool)
-> (VerticalTab -> VerticalTab -> Bool)
-> (VerticalTab -> VerticalTab -> Bool)
-> (VerticalTab -> VerticalTab -> VerticalTab)
-> (VerticalTab -> VerticalTab -> VerticalTab)
-> Ord VerticalTab
VerticalTab -> VerticalTab -> Bool
VerticalTab -> VerticalTab -> Ordering
VerticalTab -> VerticalTab -> VerticalTab
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VerticalTab -> VerticalTab -> VerticalTab
$cmin :: VerticalTab -> VerticalTab -> VerticalTab
max :: VerticalTab -> VerticalTab -> VerticalTab
$cmax :: VerticalTab -> VerticalTab -> VerticalTab
>= :: VerticalTab -> VerticalTab -> Bool
$c>= :: VerticalTab -> VerticalTab -> Bool
> :: VerticalTab -> VerticalTab -> Bool
$c> :: VerticalTab -> VerticalTab -> Bool
<= :: VerticalTab -> VerticalTab -> Bool
$c<= :: VerticalTab -> VerticalTab -> Bool
< :: VerticalTab -> VerticalTab -> Bool
$c< :: VerticalTab -> VerticalTab -> Bool
compare :: VerticalTab -> VerticalTab -> Ordering
$ccompare :: VerticalTab -> VerticalTab -> Ordering
$cp1Ord :: Eq VerticalTab
Ord, Int -> VerticalTab -> ShowS
[VerticalTab] -> ShowS
VerticalTab -> String
(Int -> VerticalTab -> ShowS)
-> (VerticalTab -> String)
-> ([VerticalTab] -> ShowS)
-> Show VerticalTab
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerticalTab] -> ShowS
$cshowList :: [VerticalTab] -> ShowS
show :: VerticalTab -> String
$cshow :: VerticalTab -> String
showsPrec :: Int -> VerticalTab -> ShowS
$cshowsPrec :: Int -> VerticalTab -> ShowS
Show, (forall x. VerticalTab -> Rep VerticalTab x)
-> (forall x. Rep VerticalTab x -> VerticalTab)
-> Generic VerticalTab
forall x. Rep VerticalTab x -> VerticalTab
forall x. VerticalTab -> Rep VerticalTab x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VerticalTab x -> VerticalTab
$cfrom :: forall x. VerticalTab -> Rep VerticalTab x
Generic)
class HasVerticalTab a where
verticalTab :: Lens' a VerticalTab
instance HasVerticalTab VerticalTab where
verticalTab :: (VerticalTab -> f VerticalTab) -> VerticalTab -> f VerticalTab
verticalTab = (VerticalTab -> f VerticalTab) -> VerticalTab -> f VerticalTab
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasVerticalTab () where
verticalTab :: (VerticalTab -> f VerticalTab) -> () -> f ()
verticalTab VerticalTab -> f VerticalTab
f ()
x =
(VerticalTab -> ()) -> f VerticalTab -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\VerticalTab
VerticalTab -> ()
x) (VerticalTab -> f VerticalTab
f VerticalTab
VerticalTab)
instance Semigroup VerticalTab where
VerticalTab
VerticalTab <> :: VerticalTab -> VerticalTab -> VerticalTab
<> VerticalTab
VerticalTab = VerticalTab
VerticalTab
instance Monoid VerticalTab where
mempty :: VerticalTab
mempty = VerticalTab
VerticalTab
class AsVerticalTab a where
_VerticalTab :: Prism' a VerticalTab
_VerticalTab' :: a
_VerticalTab' = Tagged VerticalTab (Identity VerticalTab) -> Tagged a (Identity a)
forall a. AsVerticalTab a => Prism' a VerticalTab
_VerticalTab (Tagged VerticalTab (Identity VerticalTab)
-> Tagged a (Identity a))
-> VerticalTab -> a
forall t b. AReview t b -> b -> t
# VerticalTab
VerticalTab
instance AsVerticalTab VerticalTab where
_VerticalTab :: p VerticalTab (f VerticalTab) -> p VerticalTab (f VerticalTab)
_VerticalTab = p VerticalTab (f VerticalTab) -> p VerticalTab (f VerticalTab)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsVerticalTab () where
_VerticalTab :: p VerticalTab (f VerticalTab) -> p () (f ())
_VerticalTab =
(VerticalTab -> ())
-> (() -> Maybe VerticalTab) -> Prism' () VerticalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\VerticalTab
VerticalTab -> ())
(\() -> VerticalTab -> Maybe VerticalTab
forall a. a -> Maybe a
Just VerticalTab
VerticalTab)
instance AsVerticalTab Char where
_VerticalTab :: p VerticalTab (f VerticalTab) -> p Char (f Char)
_VerticalTab =
(VerticalTab -> Char)
-> (Char -> Maybe VerticalTab) -> Prism' Char VerticalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\VerticalTab
VerticalTab -> Char
'\11')
(\case
Char
'\11' -> VerticalTab -> Maybe VerticalTab
forall a. a -> Maybe a
Just VerticalTab
VerticalTab
Char
_ -> Maybe VerticalTab
forall a. Maybe a
Nothing
)
instance AsVerticalTab Int where
_VerticalTab :: p VerticalTab (f VerticalTab) -> p Int (f Int)
_VerticalTab =
(VerticalTab -> Int)
-> (Int -> Maybe VerticalTab) -> Prism' Int VerticalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\VerticalTab
VerticalTab -> Int
11)
(\case
Int
11 -> VerticalTab -> Maybe VerticalTab
forall a. a -> Maybe a
Just VerticalTab
VerticalTab
Int
_ -> Maybe VerticalTab
forall a. Maybe a
Nothing
)
instance AsVerticalTab Integer where
_VerticalTab :: p VerticalTab (f VerticalTab) -> p Integer (f Integer)
_VerticalTab =
(VerticalTab -> Integer)
-> (Integer -> Maybe VerticalTab) -> Prism' Integer VerticalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\VerticalTab
VerticalTab -> Integer
11)
(\case
Integer
11 -> VerticalTab -> Maybe VerticalTab
forall a. a -> Maybe a
Just VerticalTab
VerticalTab
Integer
_ -> Maybe VerticalTab
forall a. Maybe a
Nothing
)
parseVerticalTab ::
CharParsing p =>
p VerticalTab
parseVerticalTab :: p VerticalTab
parseVerticalTab =
VerticalTab
VerticalTab VerticalTab -> p Char -> p VerticalTab
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\11') p VerticalTab -> String -> p VerticalTab
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"vertical tab character"
data FormFeed = FormFeed
deriving (FormFeed -> FormFeed -> Bool
(FormFeed -> FormFeed -> Bool)
-> (FormFeed -> FormFeed -> Bool) -> Eq FormFeed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormFeed -> FormFeed -> Bool
$c/= :: FormFeed -> FormFeed -> Bool
== :: FormFeed -> FormFeed -> Bool
$c== :: FormFeed -> FormFeed -> Bool
Eq, Eq FormFeed
Eq FormFeed
-> (FormFeed -> FormFeed -> Ordering)
-> (FormFeed -> FormFeed -> Bool)
-> (FormFeed -> FormFeed -> Bool)
-> (FormFeed -> FormFeed -> Bool)
-> (FormFeed -> FormFeed -> Bool)
-> (FormFeed -> FormFeed -> FormFeed)
-> (FormFeed -> FormFeed -> FormFeed)
-> Ord FormFeed
FormFeed -> FormFeed -> Bool
FormFeed -> FormFeed -> Ordering
FormFeed -> FormFeed -> FormFeed
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FormFeed -> FormFeed -> FormFeed
$cmin :: FormFeed -> FormFeed -> FormFeed
max :: FormFeed -> FormFeed -> FormFeed
$cmax :: FormFeed -> FormFeed -> FormFeed
>= :: FormFeed -> FormFeed -> Bool
$c>= :: FormFeed -> FormFeed -> Bool
> :: FormFeed -> FormFeed -> Bool
$c> :: FormFeed -> FormFeed -> Bool
<= :: FormFeed -> FormFeed -> Bool
$c<= :: FormFeed -> FormFeed -> Bool
< :: FormFeed -> FormFeed -> Bool
$c< :: FormFeed -> FormFeed -> Bool
compare :: FormFeed -> FormFeed -> Ordering
$ccompare :: FormFeed -> FormFeed -> Ordering
$cp1Ord :: Eq FormFeed
Ord, Int -> FormFeed -> ShowS
[FormFeed] -> ShowS
FormFeed -> String
(Int -> FormFeed -> ShowS)
-> (FormFeed -> String) -> ([FormFeed] -> ShowS) -> Show FormFeed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormFeed] -> ShowS
$cshowList :: [FormFeed] -> ShowS
show :: FormFeed -> String
$cshow :: FormFeed -> String
showsPrec :: Int -> FormFeed -> ShowS
$cshowsPrec :: Int -> FormFeed -> ShowS
Show, (forall x. FormFeed -> Rep FormFeed x)
-> (forall x. Rep FormFeed x -> FormFeed) -> Generic FormFeed
forall x. Rep FormFeed x -> FormFeed
forall x. FormFeed -> Rep FormFeed x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FormFeed x -> FormFeed
$cfrom :: forall x. FormFeed -> Rep FormFeed x
Generic)
class HasFormFeed a where
formFeed :: Lens' a FormFeed
instance HasFormFeed FormFeed where
formFeed :: (FormFeed -> f FormFeed) -> FormFeed -> f FormFeed
formFeed = (FormFeed -> f FormFeed) -> FormFeed -> f FormFeed
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasFormFeed () where
formFeed :: (FormFeed -> f FormFeed) -> () -> f ()
formFeed FormFeed -> f FormFeed
f ()
x =
(FormFeed -> ()) -> f FormFeed -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FormFeed
FormFeed -> ()
x) (FormFeed -> f FormFeed
f FormFeed
FormFeed)
instance Semigroup FormFeed where
FormFeed
FormFeed <> :: FormFeed -> FormFeed -> FormFeed
<> FormFeed
FormFeed = FormFeed
FormFeed
instance Monoid FormFeed where
mempty :: FormFeed
mempty = FormFeed
FormFeed
class AsFormFeed a where
_FormFeed :: Prism' a FormFeed
_FormFeed' :: a
_FormFeed' = Tagged FormFeed (Identity FormFeed) -> Tagged a (Identity a)
forall a. AsFormFeed a => Prism' a FormFeed
_FormFeed (Tagged FormFeed (Identity FormFeed) -> Tagged a (Identity a))
-> FormFeed -> a
forall t b. AReview t b -> b -> t
# FormFeed
FormFeed
instance AsFormFeed FormFeed where
_FormFeed :: p FormFeed (f FormFeed) -> p FormFeed (f FormFeed)
_FormFeed = p FormFeed (f FormFeed) -> p FormFeed (f FormFeed)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsFormFeed () where
_FormFeed :: p FormFeed (f FormFeed) -> p () (f ())
_FormFeed =
(FormFeed -> ()) -> (() -> Maybe FormFeed) -> Prism' () FormFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FormFeed
FormFeed -> ())
(\() -> FormFeed -> Maybe FormFeed
forall a. a -> Maybe a
Just FormFeed
FormFeed)
instance AsFormFeed Char where
_FormFeed :: p FormFeed (f FormFeed) -> p Char (f Char)
_FormFeed =
(FormFeed -> Char)
-> (Char -> Maybe FormFeed) -> Prism' Char FormFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FormFeed
FormFeed -> Char
'\12')
(\case
Char
'\12' -> FormFeed -> Maybe FormFeed
forall a. a -> Maybe a
Just FormFeed
FormFeed
Char
_ -> Maybe FormFeed
forall a. Maybe a
Nothing
)
instance AsFormFeed Int where
_FormFeed :: p FormFeed (f FormFeed) -> p Int (f Int)
_FormFeed =
(FormFeed -> Int) -> (Int -> Maybe FormFeed) -> Prism' Int FormFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FormFeed
FormFeed -> Int
12)
(\case
Int
12 -> FormFeed -> Maybe FormFeed
forall a. a -> Maybe a
Just FormFeed
FormFeed
Int
_ -> Maybe FormFeed
forall a. Maybe a
Nothing
)
instance AsFormFeed Integer where
_FormFeed :: p FormFeed (f FormFeed) -> p Integer (f Integer)
_FormFeed =
(FormFeed -> Integer)
-> (Integer -> Maybe FormFeed) -> Prism' Integer FormFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FormFeed
FormFeed -> Integer
12)
(\case
Integer
12 -> FormFeed -> Maybe FormFeed
forall a. a -> Maybe a
Just FormFeed
FormFeed
Integer
_ -> Maybe FormFeed
forall a. Maybe a
Nothing
)
parseFormFeed ::
CharParsing p =>
p FormFeed
parseFormFeed :: p FormFeed
parseFormFeed =
FormFeed
FormFeed FormFeed -> p Char -> p FormFeed
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\12') p FormFeed -> String -> p FormFeed
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"form feed character"
data CarriageReturn = CarriageReturn
deriving (CarriageReturn -> CarriageReturn -> Bool
(CarriageReturn -> CarriageReturn -> Bool)
-> (CarriageReturn -> CarriageReturn -> Bool) -> Eq CarriageReturn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CarriageReturn -> CarriageReturn -> Bool
$c/= :: CarriageReturn -> CarriageReturn -> Bool
== :: CarriageReturn -> CarriageReturn -> Bool
$c== :: CarriageReturn -> CarriageReturn -> Bool
Eq, Eq CarriageReturn
Eq CarriageReturn
-> (CarriageReturn -> CarriageReturn -> Ordering)
-> (CarriageReturn -> CarriageReturn -> Bool)
-> (CarriageReturn -> CarriageReturn -> Bool)
-> (CarriageReturn -> CarriageReturn -> Bool)
-> (CarriageReturn -> CarriageReturn -> Bool)
-> (CarriageReturn -> CarriageReturn -> CarriageReturn)
-> (CarriageReturn -> CarriageReturn -> CarriageReturn)
-> Ord CarriageReturn
CarriageReturn -> CarriageReturn -> Bool
CarriageReturn -> CarriageReturn -> Ordering
CarriageReturn -> CarriageReturn -> CarriageReturn
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CarriageReturn -> CarriageReturn -> CarriageReturn
$cmin :: CarriageReturn -> CarriageReturn -> CarriageReturn
max :: CarriageReturn -> CarriageReturn -> CarriageReturn
$cmax :: CarriageReturn -> CarriageReturn -> CarriageReturn
>= :: CarriageReturn -> CarriageReturn -> Bool
$c>= :: CarriageReturn -> CarriageReturn -> Bool
> :: CarriageReturn -> CarriageReturn -> Bool
$c> :: CarriageReturn -> CarriageReturn -> Bool
<= :: CarriageReturn -> CarriageReturn -> Bool
$c<= :: CarriageReturn -> CarriageReturn -> Bool
< :: CarriageReturn -> CarriageReturn -> Bool
$c< :: CarriageReturn -> CarriageReturn -> Bool
compare :: CarriageReturn -> CarriageReturn -> Ordering
$ccompare :: CarriageReturn -> CarriageReturn -> Ordering
$cp1Ord :: Eq CarriageReturn
Ord, Int -> CarriageReturn -> ShowS
[CarriageReturn] -> ShowS
CarriageReturn -> String
(Int -> CarriageReturn -> ShowS)
-> (CarriageReturn -> String)
-> ([CarriageReturn] -> ShowS)
-> Show CarriageReturn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CarriageReturn] -> ShowS
$cshowList :: [CarriageReturn] -> ShowS
show :: CarriageReturn -> String
$cshow :: CarriageReturn -> String
showsPrec :: Int -> CarriageReturn -> ShowS
$cshowsPrec :: Int -> CarriageReturn -> ShowS
Show, (forall x. CarriageReturn -> Rep CarriageReturn x)
-> (forall x. Rep CarriageReturn x -> CarriageReturn)
-> Generic CarriageReturn
forall x. Rep CarriageReturn x -> CarriageReturn
forall x. CarriageReturn -> Rep CarriageReturn x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CarriageReturn x -> CarriageReturn
$cfrom :: forall x. CarriageReturn -> Rep CarriageReturn x
Generic)
class HasCarriageReturn a where
carriageReturn :: Lens' a CarriageReturn
instance HasCarriageReturn CarriageReturn where
carriageReturn :: (CarriageReturn -> f CarriageReturn)
-> CarriageReturn -> f CarriageReturn
carriageReturn = (CarriageReturn -> f CarriageReturn)
-> CarriageReturn -> f CarriageReturn
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasCarriageReturn () where
carriageReturn :: (CarriageReturn -> f CarriageReturn) -> () -> f ()
carriageReturn CarriageReturn -> f CarriageReturn
f ()
x =
(CarriageReturn -> ()) -> f CarriageReturn -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CarriageReturn
CarriageReturn -> ()
x) (CarriageReturn -> f CarriageReturn
f CarriageReturn
CarriageReturn)
instance Semigroup CarriageReturn where
CarriageReturn
CarriageReturn <> :: CarriageReturn -> CarriageReturn -> CarriageReturn
<> CarriageReturn
CarriageReturn = CarriageReturn
CarriageReturn
instance Monoid CarriageReturn where
mempty :: CarriageReturn
mempty = CarriageReturn
CarriageReturn
class AsCarriageReturn a where
_CarriageReturn :: Prism' a CarriageReturn
_CarriageReturn' :: a
_CarriageReturn' = Tagged CarriageReturn (Identity CarriageReturn)
-> Tagged a (Identity a)
forall a. AsCarriageReturn a => Prism' a CarriageReturn
_CarriageReturn (Tagged CarriageReturn (Identity CarriageReturn)
-> Tagged a (Identity a))
-> CarriageReturn -> a
forall t b. AReview t b -> b -> t
# CarriageReturn
CarriageReturn
instance AsCarriageReturn CarriageReturn where
_CarriageReturn :: p CarriageReturn (f CarriageReturn)
-> p CarriageReturn (f CarriageReturn)
_CarriageReturn = p CarriageReturn (f CarriageReturn)
-> p CarriageReturn (f CarriageReturn)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsCarriageReturn () where
_CarriageReturn :: p CarriageReturn (f CarriageReturn) -> p () (f ())
_CarriageReturn =
(CarriageReturn -> ())
-> (() -> Maybe CarriageReturn) -> Prism' () CarriageReturn
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\CarriageReturn
CarriageReturn -> ())
(\() -> CarriageReturn -> Maybe CarriageReturn
forall a. a -> Maybe a
Just CarriageReturn
CarriageReturn)
instance AsCarriageReturn Char where
_CarriageReturn :: p CarriageReturn (f CarriageReturn) -> p Char (f Char)
_CarriageReturn =
(CarriageReturn -> Char)
-> (Char -> Maybe CarriageReturn) -> Prism' Char CarriageReturn
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\CarriageReturn
CarriageReturn -> Char
'\13')
(\case
Char
'\13' -> CarriageReturn -> Maybe CarriageReturn
forall a. a -> Maybe a
Just CarriageReturn
CarriageReturn
Char
_ -> Maybe CarriageReturn
forall a. Maybe a
Nothing
)
instance AsCarriageReturn Int where
_CarriageReturn :: p CarriageReturn (f CarriageReturn) -> p Int (f Int)
_CarriageReturn =
(CarriageReturn -> Int)
-> (Int -> Maybe CarriageReturn) -> Prism' Int CarriageReturn
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\CarriageReturn
CarriageReturn -> Int
13)
(\case
Int
13 -> CarriageReturn -> Maybe CarriageReturn
forall a. a -> Maybe a
Just CarriageReturn
CarriageReturn
Int
_ -> Maybe CarriageReturn
forall a. Maybe a
Nothing
)
instance AsCarriageReturn Integer where
_CarriageReturn :: p CarriageReturn (f CarriageReturn) -> p Integer (f Integer)
_CarriageReturn =
(CarriageReturn -> Integer)
-> (Integer -> Maybe CarriageReturn)
-> Prism' Integer CarriageReturn
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\CarriageReturn
CarriageReturn -> Integer
13)
(\case
Integer
13 -> CarriageReturn -> Maybe CarriageReturn
forall a. a -> Maybe a
Just CarriageReturn
CarriageReturn
Integer
_ -> Maybe CarriageReturn
forall a. Maybe a
Nothing
)
parseCarriageReturn ::
CharParsing p =>
p CarriageReturn
parseCarriageReturn :: p CarriageReturn
parseCarriageReturn =
CarriageReturn
CarriageReturn CarriageReturn -> p Char -> p CarriageReturn
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\13') p CarriageReturn -> String -> p CarriageReturn
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"carriage return character"
data Whitespace = Whitespace
deriving (Whitespace -> Whitespace -> Bool
(Whitespace -> Whitespace -> Bool)
-> (Whitespace -> Whitespace -> Bool) -> Eq Whitespace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Whitespace -> Whitespace -> Bool
$c/= :: Whitespace -> Whitespace -> Bool
== :: Whitespace -> Whitespace -> Bool
$c== :: Whitespace -> Whitespace -> Bool
Eq, Eq Whitespace
Eq Whitespace
-> (Whitespace -> Whitespace -> Ordering)
-> (Whitespace -> Whitespace -> Bool)
-> (Whitespace -> Whitespace -> Bool)
-> (Whitespace -> Whitespace -> Bool)
-> (Whitespace -> Whitespace -> Bool)
-> (Whitespace -> Whitespace -> Whitespace)
-> (Whitespace -> Whitespace -> Whitespace)
-> Ord Whitespace
Whitespace -> Whitespace -> Bool
Whitespace -> Whitespace -> Ordering
Whitespace -> Whitespace -> Whitespace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Whitespace -> Whitespace -> Whitespace
$cmin :: Whitespace -> Whitespace -> Whitespace
max :: Whitespace -> Whitespace -> Whitespace
$cmax :: Whitespace -> Whitespace -> Whitespace
>= :: Whitespace -> Whitespace -> Bool
$c>= :: Whitespace -> Whitespace -> Bool
> :: Whitespace -> Whitespace -> Bool
$c> :: Whitespace -> Whitespace -> Bool
<= :: Whitespace -> Whitespace -> Bool
$c<= :: Whitespace -> Whitespace -> Bool
< :: Whitespace -> Whitespace -> Bool
$c< :: Whitespace -> Whitespace -> Bool
compare :: Whitespace -> Whitespace -> Ordering
$ccompare :: Whitespace -> Whitespace -> Ordering
$cp1Ord :: Eq Whitespace
Ord, Int -> Whitespace -> ShowS
[Whitespace] -> ShowS
Whitespace -> String
(Int -> Whitespace -> ShowS)
-> (Whitespace -> String)
-> ([Whitespace] -> ShowS)
-> Show Whitespace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Whitespace] -> ShowS
$cshowList :: [Whitespace] -> ShowS
show :: Whitespace -> String
$cshow :: Whitespace -> String
showsPrec :: Int -> Whitespace -> ShowS
$cshowsPrec :: Int -> Whitespace -> ShowS
Show, (forall x. Whitespace -> Rep Whitespace x)
-> (forall x. Rep Whitespace x -> Whitespace) -> Generic Whitespace
forall x. Rep Whitespace x -> Whitespace
forall x. Whitespace -> Rep Whitespace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Whitespace x -> Whitespace
$cfrom :: forall x. Whitespace -> Rep Whitespace x
Generic)
class HasWhitespace a where
whitespace :: Lens' a Whitespace
instance HasWhitespace Whitespace where
whitespace :: (Whitespace -> f Whitespace) -> Whitespace -> f Whitespace
whitespace = (Whitespace -> f Whitespace) -> Whitespace -> f Whitespace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasWhitespace () where
whitespace :: (Whitespace -> f Whitespace) -> () -> f ()
whitespace Whitespace -> f Whitespace
f ()
x =
(Whitespace -> ()) -> f Whitespace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Whitespace
Whitespace -> ()
x) (Whitespace -> f Whitespace
f Whitespace
Whitespace)
instance Semigroup Whitespace where
Whitespace
Whitespace <> :: Whitespace -> Whitespace -> Whitespace
<> Whitespace
Whitespace = Whitespace
Whitespace
instance Monoid Whitespace where
mempty :: Whitespace
mempty = Whitespace
Whitespace
class AsWhitespace a where
_Whitespace :: Prism' a Whitespace
_Whitespace' :: a
_Whitespace' = Tagged Whitespace (Identity Whitespace) -> Tagged a (Identity a)
forall a. AsWhitespace a => Prism' a Whitespace
_Whitespace (Tagged Whitespace (Identity Whitespace) -> Tagged a (Identity a))
-> Whitespace -> a
forall t b. AReview t b -> b -> t
# Whitespace
Whitespace
instance AsWhitespace Whitespace where
_Whitespace :: p Whitespace (f Whitespace) -> p Whitespace (f Whitespace)
_Whitespace = p Whitespace (f Whitespace) -> p Whitespace (f Whitespace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsWhitespace () where
_Whitespace :: p Whitespace (f Whitespace) -> p () (f ())
_Whitespace =
(Whitespace -> ())
-> (() -> Maybe Whitespace) -> Prism' () Whitespace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\Whitespace
Whitespace -> ())
(\() -> Whitespace -> Maybe Whitespace
forall a. a -> Maybe a
Just Whitespace
Whitespace)
instance AsWhitespace Char where
_Whitespace :: p Whitespace (f Whitespace) -> p Char (f Char)
_Whitespace =
(Whitespace -> Char)
-> (Char -> Maybe Whitespace) -> Prism' Char Whitespace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\Whitespace
Whitespace -> Char
'\32')
(\case
Char
'\32' -> Whitespace -> Maybe Whitespace
forall a. a -> Maybe a
Just Whitespace
Whitespace
Char
_ -> Maybe Whitespace
forall a. Maybe a
Nothing
)
instance AsWhitespace Int where
_Whitespace :: p Whitespace (f Whitespace) -> p Int (f Int)
_Whitespace =
(Whitespace -> Int)
-> (Int -> Maybe Whitespace) -> Prism' Int Whitespace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\Whitespace
Whitespace -> Int
32)
(\case
Int
32 -> Whitespace -> Maybe Whitespace
forall a. a -> Maybe a
Just Whitespace
Whitespace
Int
_ -> Maybe Whitespace
forall a. Maybe a
Nothing
)
instance AsWhitespace Integer where
_Whitespace :: p Whitespace (f Whitespace) -> p Integer (f Integer)
_Whitespace =
(Whitespace -> Integer)
-> (Integer -> Maybe Whitespace) -> Prism' Integer Whitespace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\Whitespace
Whitespace -> Integer
32)
(\case
Integer
32 -> Whitespace -> Maybe Whitespace
forall a. a -> Maybe a
Just Whitespace
Whitespace
Integer
_ -> Maybe Whitespace
forall a. Maybe a
Nothing
)
parseWhitespace ::
CharParsing p =>
p Whitespace
parseWhitespace :: p Whitespace
parseWhitespace =
Whitespace
Whitespace Whitespace -> p Char -> p Whitespace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\32') p Whitespace -> String -> p Whitespace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"whitespace character"
data NoBreakSpace = NoBreakSpace
deriving (NoBreakSpace -> NoBreakSpace -> Bool
(NoBreakSpace -> NoBreakSpace -> Bool)
-> (NoBreakSpace -> NoBreakSpace -> Bool) -> Eq NoBreakSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NoBreakSpace -> NoBreakSpace -> Bool
$c/= :: NoBreakSpace -> NoBreakSpace -> Bool
== :: NoBreakSpace -> NoBreakSpace -> Bool
$c== :: NoBreakSpace -> NoBreakSpace -> Bool
Eq, Eq NoBreakSpace
Eq NoBreakSpace
-> (NoBreakSpace -> NoBreakSpace -> Ordering)
-> (NoBreakSpace -> NoBreakSpace -> Bool)
-> (NoBreakSpace -> NoBreakSpace -> Bool)
-> (NoBreakSpace -> NoBreakSpace -> Bool)
-> (NoBreakSpace -> NoBreakSpace -> Bool)
-> (NoBreakSpace -> NoBreakSpace -> NoBreakSpace)
-> (NoBreakSpace -> NoBreakSpace -> NoBreakSpace)
-> Ord NoBreakSpace
NoBreakSpace -> NoBreakSpace -> Bool
NoBreakSpace -> NoBreakSpace -> Ordering
NoBreakSpace -> NoBreakSpace -> NoBreakSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NoBreakSpace -> NoBreakSpace -> NoBreakSpace
$cmin :: NoBreakSpace -> NoBreakSpace -> NoBreakSpace
max :: NoBreakSpace -> NoBreakSpace -> NoBreakSpace
$cmax :: NoBreakSpace -> NoBreakSpace -> NoBreakSpace
>= :: NoBreakSpace -> NoBreakSpace -> Bool
$c>= :: NoBreakSpace -> NoBreakSpace -> Bool
> :: NoBreakSpace -> NoBreakSpace -> Bool
$c> :: NoBreakSpace -> NoBreakSpace -> Bool
<= :: NoBreakSpace -> NoBreakSpace -> Bool
$c<= :: NoBreakSpace -> NoBreakSpace -> Bool
< :: NoBreakSpace -> NoBreakSpace -> Bool
$c< :: NoBreakSpace -> NoBreakSpace -> Bool
compare :: NoBreakSpace -> NoBreakSpace -> Ordering
$ccompare :: NoBreakSpace -> NoBreakSpace -> Ordering
$cp1Ord :: Eq NoBreakSpace
Ord, Int -> NoBreakSpace -> ShowS
[NoBreakSpace] -> ShowS
NoBreakSpace -> String
(Int -> NoBreakSpace -> ShowS)
-> (NoBreakSpace -> String)
-> ([NoBreakSpace] -> ShowS)
-> Show NoBreakSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NoBreakSpace] -> ShowS
$cshowList :: [NoBreakSpace] -> ShowS
show :: NoBreakSpace -> String
$cshow :: NoBreakSpace -> String
showsPrec :: Int -> NoBreakSpace -> ShowS
$cshowsPrec :: Int -> NoBreakSpace -> ShowS
Show, (forall x. NoBreakSpace -> Rep NoBreakSpace x)
-> (forall x. Rep NoBreakSpace x -> NoBreakSpace)
-> Generic NoBreakSpace
forall x. Rep NoBreakSpace x -> NoBreakSpace
forall x. NoBreakSpace -> Rep NoBreakSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NoBreakSpace x -> NoBreakSpace
$cfrom :: forall x. NoBreakSpace -> Rep NoBreakSpace x
Generic)
class HasNoBreakSpace a where
noBreakSpace :: Lens' a NoBreakSpace
instance HasNoBreakSpace NoBreakSpace where
noBreakSpace :: (NoBreakSpace -> f NoBreakSpace) -> NoBreakSpace -> f NoBreakSpace
noBreakSpace = (NoBreakSpace -> f NoBreakSpace) -> NoBreakSpace -> f NoBreakSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasNoBreakSpace () where
noBreakSpace :: (NoBreakSpace -> f NoBreakSpace) -> () -> f ()
noBreakSpace NoBreakSpace -> f NoBreakSpace
f ()
x =
(NoBreakSpace -> ()) -> f NoBreakSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\NoBreakSpace
NoBreakSpace -> ()
x) (NoBreakSpace -> f NoBreakSpace
f NoBreakSpace
NoBreakSpace)
instance Semigroup NoBreakSpace where
NoBreakSpace
NoBreakSpace <> :: NoBreakSpace -> NoBreakSpace -> NoBreakSpace
<> NoBreakSpace
NoBreakSpace = NoBreakSpace
NoBreakSpace
instance Monoid NoBreakSpace where
mempty :: NoBreakSpace
mempty = NoBreakSpace
NoBreakSpace
class AsNoBreakSpace a where
_NoBreakSpace :: Prism' a NoBreakSpace
_NoBreakSpace' :: a
_NoBreakSpace' = Tagged NoBreakSpace (Identity NoBreakSpace)
-> Tagged a (Identity a)
forall a. AsNoBreakSpace a => Prism' a NoBreakSpace
_NoBreakSpace (Tagged NoBreakSpace (Identity NoBreakSpace)
-> Tagged a (Identity a))
-> NoBreakSpace -> a
forall t b. AReview t b -> b -> t
# NoBreakSpace
NoBreakSpace
instance AsNoBreakSpace NoBreakSpace where
_NoBreakSpace :: p NoBreakSpace (f NoBreakSpace) -> p NoBreakSpace (f NoBreakSpace)
_NoBreakSpace = p NoBreakSpace (f NoBreakSpace) -> p NoBreakSpace (f NoBreakSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsNoBreakSpace () where
_NoBreakSpace :: p NoBreakSpace (f NoBreakSpace) -> p () (f ())
_NoBreakSpace =
(NoBreakSpace -> ())
-> (() -> Maybe NoBreakSpace) -> Prism' () NoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NoBreakSpace
NoBreakSpace -> ())
(\() -> NoBreakSpace -> Maybe NoBreakSpace
forall a. a -> Maybe a
Just NoBreakSpace
NoBreakSpace)
instance AsNoBreakSpace Char where
_NoBreakSpace :: p NoBreakSpace (f NoBreakSpace) -> p Char (f Char)
_NoBreakSpace =
(NoBreakSpace -> Char)
-> (Char -> Maybe NoBreakSpace) -> Prism' Char NoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NoBreakSpace
NoBreakSpace -> Char
'\160')
(\case
Char
'\160' -> NoBreakSpace -> Maybe NoBreakSpace
forall a. a -> Maybe a
Just NoBreakSpace
NoBreakSpace
Char
_ -> Maybe NoBreakSpace
forall a. Maybe a
Nothing
)
instance AsNoBreakSpace Int where
_NoBreakSpace :: p NoBreakSpace (f NoBreakSpace) -> p Int (f Int)
_NoBreakSpace =
(NoBreakSpace -> Int)
-> (Int -> Maybe NoBreakSpace) -> Prism' Int NoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NoBreakSpace
NoBreakSpace -> Int
160)
(\case
Int
160 -> NoBreakSpace -> Maybe NoBreakSpace
forall a. a -> Maybe a
Just NoBreakSpace
NoBreakSpace
Int
_ -> Maybe NoBreakSpace
forall a. Maybe a
Nothing
)
instance AsNoBreakSpace Integer where
_NoBreakSpace :: p NoBreakSpace (f NoBreakSpace) -> p Integer (f Integer)
_NoBreakSpace =
(NoBreakSpace -> Integer)
-> (Integer -> Maybe NoBreakSpace) -> Prism' Integer NoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NoBreakSpace
NoBreakSpace -> Integer
160)
(\case
Integer
160 -> NoBreakSpace -> Maybe NoBreakSpace
forall a. a -> Maybe a
Just NoBreakSpace
NoBreakSpace
Integer
_ -> Maybe NoBreakSpace
forall a. Maybe a
Nothing
)
parseNoBreakSpace ::
CharParsing p =>
p NoBreakSpace
parseNoBreakSpace :: p NoBreakSpace
parseNoBreakSpace =
NoBreakSpace
NoBreakSpace NoBreakSpace -> p Char -> p NoBreakSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\160') p NoBreakSpace -> String -> p NoBreakSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"no break space character"
data OghamSpaceMark = OghamSpaceMark
deriving (OghamSpaceMark -> OghamSpaceMark -> Bool
(OghamSpaceMark -> OghamSpaceMark -> Bool)
-> (OghamSpaceMark -> OghamSpaceMark -> Bool) -> Eq OghamSpaceMark
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OghamSpaceMark -> OghamSpaceMark -> Bool
$c/= :: OghamSpaceMark -> OghamSpaceMark -> Bool
== :: OghamSpaceMark -> OghamSpaceMark -> Bool
$c== :: OghamSpaceMark -> OghamSpaceMark -> Bool
Eq, Eq OghamSpaceMark
Eq OghamSpaceMark
-> (OghamSpaceMark -> OghamSpaceMark -> Ordering)
-> (OghamSpaceMark -> OghamSpaceMark -> Bool)
-> (OghamSpaceMark -> OghamSpaceMark -> Bool)
-> (OghamSpaceMark -> OghamSpaceMark -> Bool)
-> (OghamSpaceMark -> OghamSpaceMark -> Bool)
-> (OghamSpaceMark -> OghamSpaceMark -> OghamSpaceMark)
-> (OghamSpaceMark -> OghamSpaceMark -> OghamSpaceMark)
-> Ord OghamSpaceMark
OghamSpaceMark -> OghamSpaceMark -> Bool
OghamSpaceMark -> OghamSpaceMark -> Ordering
OghamSpaceMark -> OghamSpaceMark -> OghamSpaceMark
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OghamSpaceMark -> OghamSpaceMark -> OghamSpaceMark
$cmin :: OghamSpaceMark -> OghamSpaceMark -> OghamSpaceMark
max :: OghamSpaceMark -> OghamSpaceMark -> OghamSpaceMark
$cmax :: OghamSpaceMark -> OghamSpaceMark -> OghamSpaceMark
>= :: OghamSpaceMark -> OghamSpaceMark -> Bool
$c>= :: OghamSpaceMark -> OghamSpaceMark -> Bool
> :: OghamSpaceMark -> OghamSpaceMark -> Bool
$c> :: OghamSpaceMark -> OghamSpaceMark -> Bool
<= :: OghamSpaceMark -> OghamSpaceMark -> Bool
$c<= :: OghamSpaceMark -> OghamSpaceMark -> Bool
< :: OghamSpaceMark -> OghamSpaceMark -> Bool
$c< :: OghamSpaceMark -> OghamSpaceMark -> Bool
compare :: OghamSpaceMark -> OghamSpaceMark -> Ordering
$ccompare :: OghamSpaceMark -> OghamSpaceMark -> Ordering
$cp1Ord :: Eq OghamSpaceMark
Ord, Int -> OghamSpaceMark -> ShowS
[OghamSpaceMark] -> ShowS
OghamSpaceMark -> String
(Int -> OghamSpaceMark -> ShowS)
-> (OghamSpaceMark -> String)
-> ([OghamSpaceMark] -> ShowS)
-> Show OghamSpaceMark
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OghamSpaceMark] -> ShowS
$cshowList :: [OghamSpaceMark] -> ShowS
show :: OghamSpaceMark -> String
$cshow :: OghamSpaceMark -> String
showsPrec :: Int -> OghamSpaceMark -> ShowS
$cshowsPrec :: Int -> OghamSpaceMark -> ShowS
Show, (forall x. OghamSpaceMark -> Rep OghamSpaceMark x)
-> (forall x. Rep OghamSpaceMark x -> OghamSpaceMark)
-> Generic OghamSpaceMark
forall x. Rep OghamSpaceMark x -> OghamSpaceMark
forall x. OghamSpaceMark -> Rep OghamSpaceMark x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OghamSpaceMark x -> OghamSpaceMark
$cfrom :: forall x. OghamSpaceMark -> Rep OghamSpaceMark x
Generic)
class HasOghamSpaceMark a where
oghamSpaceMark :: Lens' a OghamSpaceMark
instance HasOghamSpaceMark OghamSpaceMark where
oghamSpaceMark :: (OghamSpaceMark -> f OghamSpaceMark)
-> OghamSpaceMark -> f OghamSpaceMark
oghamSpaceMark = (OghamSpaceMark -> f OghamSpaceMark)
-> OghamSpaceMark -> f OghamSpaceMark
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasOghamSpaceMark () where
oghamSpaceMark :: (OghamSpaceMark -> f OghamSpaceMark) -> () -> f ()
oghamSpaceMark OghamSpaceMark -> f OghamSpaceMark
f ()
x =
(OghamSpaceMark -> ()) -> f OghamSpaceMark -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\OghamSpaceMark
OghamSpaceMark -> ()
x) (OghamSpaceMark -> f OghamSpaceMark
f OghamSpaceMark
OghamSpaceMark)
instance Semigroup OghamSpaceMark where
OghamSpaceMark
OghamSpaceMark <> :: OghamSpaceMark -> OghamSpaceMark -> OghamSpaceMark
<> OghamSpaceMark
OghamSpaceMark = OghamSpaceMark
OghamSpaceMark
instance Monoid OghamSpaceMark where
mempty :: OghamSpaceMark
mempty = OghamSpaceMark
OghamSpaceMark
class AsOghamSpaceMark a where
_OghamSpaceMark :: Prism' a OghamSpaceMark
_OghamSpaceMark' :: a
_OghamSpaceMark' = Tagged OghamSpaceMark (Identity OghamSpaceMark)
-> Tagged a (Identity a)
forall a. AsOghamSpaceMark a => Prism' a OghamSpaceMark
_OghamSpaceMark (Tagged OghamSpaceMark (Identity OghamSpaceMark)
-> Tagged a (Identity a))
-> OghamSpaceMark -> a
forall t b. AReview t b -> b -> t
# OghamSpaceMark
OghamSpaceMark
instance AsOghamSpaceMark OghamSpaceMark where
_OghamSpaceMark :: p OghamSpaceMark (f OghamSpaceMark)
-> p OghamSpaceMark (f OghamSpaceMark)
_OghamSpaceMark = p OghamSpaceMark (f OghamSpaceMark)
-> p OghamSpaceMark (f OghamSpaceMark)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsOghamSpaceMark () where
_OghamSpaceMark :: p OghamSpaceMark (f OghamSpaceMark) -> p () (f ())
_OghamSpaceMark =
(OghamSpaceMark -> ())
-> (() -> Maybe OghamSpaceMark) -> Prism' () OghamSpaceMark
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\OghamSpaceMark
OghamSpaceMark -> ())
(\() -> OghamSpaceMark -> Maybe OghamSpaceMark
forall a. a -> Maybe a
Just OghamSpaceMark
OghamSpaceMark)
instance AsOghamSpaceMark Char where
_OghamSpaceMark :: p OghamSpaceMark (f OghamSpaceMark) -> p Char (f Char)
_OghamSpaceMark =
(OghamSpaceMark -> Char)
-> (Char -> Maybe OghamSpaceMark) -> Prism' Char OghamSpaceMark
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\OghamSpaceMark
OghamSpaceMark -> Char
'\5760')
(\case
Char
'\5760' -> OghamSpaceMark -> Maybe OghamSpaceMark
forall a. a -> Maybe a
Just OghamSpaceMark
OghamSpaceMark
Char
_ -> Maybe OghamSpaceMark
forall a. Maybe a
Nothing
)
instance AsOghamSpaceMark Int where
_OghamSpaceMark :: p OghamSpaceMark (f OghamSpaceMark) -> p Int (f Int)
_OghamSpaceMark =
(OghamSpaceMark -> Int)
-> (Int -> Maybe OghamSpaceMark) -> Prism' Int OghamSpaceMark
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\OghamSpaceMark
OghamSpaceMark -> Int
5760)
(\case
Int
5760 -> OghamSpaceMark -> Maybe OghamSpaceMark
forall a. a -> Maybe a
Just OghamSpaceMark
OghamSpaceMark
Int
_ -> Maybe OghamSpaceMark
forall a. Maybe a
Nothing
)
instance AsOghamSpaceMark Integer where
_OghamSpaceMark :: p OghamSpaceMark (f OghamSpaceMark) -> p Integer (f Integer)
_OghamSpaceMark =
(OghamSpaceMark -> Integer)
-> (Integer -> Maybe OghamSpaceMark)
-> Prism' Integer OghamSpaceMark
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\OghamSpaceMark
OghamSpaceMark -> Integer
5760)
(\case
Integer
5760 -> OghamSpaceMark -> Maybe OghamSpaceMark
forall a. a -> Maybe a
Just OghamSpaceMark
OghamSpaceMark
Integer
_ -> Maybe OghamSpaceMark
forall a. Maybe a
Nothing
)
parseOghamSpaceMark ::
CharParsing p =>
p OghamSpaceMark
parseOghamSpaceMark :: p OghamSpaceMark
parseOghamSpaceMark =
OghamSpaceMark
OghamSpaceMark OghamSpaceMark -> p Char -> p OghamSpaceMark
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\5760') p OghamSpaceMark -> String -> p OghamSpaceMark
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"ogham space mark character"
data EnQuad = EnQuad
deriving (EnQuad -> EnQuad -> Bool
(EnQuad -> EnQuad -> Bool)
-> (EnQuad -> EnQuad -> Bool) -> Eq EnQuad
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnQuad -> EnQuad -> Bool
$c/= :: EnQuad -> EnQuad -> Bool
== :: EnQuad -> EnQuad -> Bool
$c== :: EnQuad -> EnQuad -> Bool
Eq, Eq EnQuad
Eq EnQuad
-> (EnQuad -> EnQuad -> Ordering)
-> (EnQuad -> EnQuad -> Bool)
-> (EnQuad -> EnQuad -> Bool)
-> (EnQuad -> EnQuad -> Bool)
-> (EnQuad -> EnQuad -> Bool)
-> (EnQuad -> EnQuad -> EnQuad)
-> (EnQuad -> EnQuad -> EnQuad)
-> Ord EnQuad
EnQuad -> EnQuad -> Bool
EnQuad -> EnQuad -> Ordering
EnQuad -> EnQuad -> EnQuad
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnQuad -> EnQuad -> EnQuad
$cmin :: EnQuad -> EnQuad -> EnQuad
max :: EnQuad -> EnQuad -> EnQuad
$cmax :: EnQuad -> EnQuad -> EnQuad
>= :: EnQuad -> EnQuad -> Bool
$c>= :: EnQuad -> EnQuad -> Bool
> :: EnQuad -> EnQuad -> Bool
$c> :: EnQuad -> EnQuad -> Bool
<= :: EnQuad -> EnQuad -> Bool
$c<= :: EnQuad -> EnQuad -> Bool
< :: EnQuad -> EnQuad -> Bool
$c< :: EnQuad -> EnQuad -> Bool
compare :: EnQuad -> EnQuad -> Ordering
$ccompare :: EnQuad -> EnQuad -> Ordering
$cp1Ord :: Eq EnQuad
Ord, Int -> EnQuad -> ShowS
[EnQuad] -> ShowS
EnQuad -> String
(Int -> EnQuad -> ShowS)
-> (EnQuad -> String) -> ([EnQuad] -> ShowS) -> Show EnQuad
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnQuad] -> ShowS
$cshowList :: [EnQuad] -> ShowS
show :: EnQuad -> String
$cshow :: EnQuad -> String
showsPrec :: Int -> EnQuad -> ShowS
$cshowsPrec :: Int -> EnQuad -> ShowS
Show, (forall x. EnQuad -> Rep EnQuad x)
-> (forall x. Rep EnQuad x -> EnQuad) -> Generic EnQuad
forall x. Rep EnQuad x -> EnQuad
forall x. EnQuad -> Rep EnQuad x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnQuad x -> EnQuad
$cfrom :: forall x. EnQuad -> Rep EnQuad x
Generic)
class HasEnQuad a where
enQuad :: Lens' a EnQuad
instance HasEnQuad EnQuad where
enQuad :: (EnQuad -> f EnQuad) -> EnQuad -> f EnQuad
enQuad = (EnQuad -> f EnQuad) -> EnQuad -> f EnQuad
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasEnQuad () where
enQuad :: (EnQuad -> f EnQuad) -> () -> f ()
enQuad EnQuad -> f EnQuad
f ()
x =
(EnQuad -> ()) -> f EnQuad -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\EnQuad
EnQuad -> ()
x) (EnQuad -> f EnQuad
f EnQuad
EnQuad)
instance Semigroup EnQuad where
EnQuad
EnQuad <> :: EnQuad -> EnQuad -> EnQuad
<> EnQuad
EnQuad = EnQuad
EnQuad
instance Monoid EnQuad where
mempty :: EnQuad
mempty = EnQuad
EnQuad
class AsEnQuad a where
_EnQuad :: Prism' a EnQuad
_EnQuad' :: a
_EnQuad' = Tagged EnQuad (Identity EnQuad) -> Tagged a (Identity a)
forall a. AsEnQuad a => Prism' a EnQuad
_EnQuad (Tagged EnQuad (Identity EnQuad) -> Tagged a (Identity a))
-> EnQuad -> a
forall t b. AReview t b -> b -> t
# EnQuad
EnQuad
instance AsEnQuad EnQuad where
_EnQuad :: p EnQuad (f EnQuad) -> p EnQuad (f EnQuad)
_EnQuad = p EnQuad (f EnQuad) -> p EnQuad (f EnQuad)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsEnQuad () where
_EnQuad :: p EnQuad (f EnQuad) -> p () (f ())
_EnQuad =
(EnQuad -> ()) -> (() -> Maybe EnQuad) -> Prism' () EnQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnQuad
EnQuad -> ())
(\() -> EnQuad -> Maybe EnQuad
forall a. a -> Maybe a
Just EnQuad
EnQuad)
instance AsEnQuad Char where
_EnQuad :: p EnQuad (f EnQuad) -> p Char (f Char)
_EnQuad =
(EnQuad -> Char) -> (Char -> Maybe EnQuad) -> Prism' Char EnQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnQuad
EnQuad -> Char
'\8192')
(\case
Char
'\8192' -> EnQuad -> Maybe EnQuad
forall a. a -> Maybe a
Just EnQuad
EnQuad
Char
_ -> Maybe EnQuad
forall a. Maybe a
Nothing
)
instance AsEnQuad Int where
_EnQuad :: p EnQuad (f EnQuad) -> p Int (f Int)
_EnQuad =
(EnQuad -> Int) -> (Int -> Maybe EnQuad) -> Prism' Int EnQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnQuad
EnQuad -> Int
8192)
(\case
Int
8192 -> EnQuad -> Maybe EnQuad
forall a. a -> Maybe a
Just EnQuad
EnQuad
Int
_ -> Maybe EnQuad
forall a. Maybe a
Nothing
)
instance AsEnQuad Integer where
_EnQuad :: p EnQuad (f EnQuad) -> p Integer (f Integer)
_EnQuad =
(EnQuad -> Integer)
-> (Integer -> Maybe EnQuad) -> Prism' Integer EnQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnQuad
EnQuad -> Integer
8192)
(\case
Integer
8192 -> EnQuad -> Maybe EnQuad
forall a. a -> Maybe a
Just EnQuad
EnQuad
Integer
_ -> Maybe EnQuad
forall a. Maybe a
Nothing
)
parseEnQuad ::
CharParsing p =>
p EnQuad
parseEnQuad :: p EnQuad
parseEnQuad =
EnQuad
EnQuad EnQuad -> p Char -> p EnQuad
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8192') p EnQuad -> String -> p EnQuad
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"en quad character"
data EmQuad = EmQuad
deriving (EmQuad -> EmQuad -> Bool
(EmQuad -> EmQuad -> Bool)
-> (EmQuad -> EmQuad -> Bool) -> Eq EmQuad
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmQuad -> EmQuad -> Bool
$c/= :: EmQuad -> EmQuad -> Bool
== :: EmQuad -> EmQuad -> Bool
$c== :: EmQuad -> EmQuad -> Bool
Eq, Eq EmQuad
Eq EmQuad
-> (EmQuad -> EmQuad -> Ordering)
-> (EmQuad -> EmQuad -> Bool)
-> (EmQuad -> EmQuad -> Bool)
-> (EmQuad -> EmQuad -> Bool)
-> (EmQuad -> EmQuad -> Bool)
-> (EmQuad -> EmQuad -> EmQuad)
-> (EmQuad -> EmQuad -> EmQuad)
-> Ord EmQuad
EmQuad -> EmQuad -> Bool
EmQuad -> EmQuad -> Ordering
EmQuad -> EmQuad -> EmQuad
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EmQuad -> EmQuad -> EmQuad
$cmin :: EmQuad -> EmQuad -> EmQuad
max :: EmQuad -> EmQuad -> EmQuad
$cmax :: EmQuad -> EmQuad -> EmQuad
>= :: EmQuad -> EmQuad -> Bool
$c>= :: EmQuad -> EmQuad -> Bool
> :: EmQuad -> EmQuad -> Bool
$c> :: EmQuad -> EmQuad -> Bool
<= :: EmQuad -> EmQuad -> Bool
$c<= :: EmQuad -> EmQuad -> Bool
< :: EmQuad -> EmQuad -> Bool
$c< :: EmQuad -> EmQuad -> Bool
compare :: EmQuad -> EmQuad -> Ordering
$ccompare :: EmQuad -> EmQuad -> Ordering
$cp1Ord :: Eq EmQuad
Ord, Int -> EmQuad -> ShowS
[EmQuad] -> ShowS
EmQuad -> String
(Int -> EmQuad -> ShowS)
-> (EmQuad -> String) -> ([EmQuad] -> ShowS) -> Show EmQuad
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmQuad] -> ShowS
$cshowList :: [EmQuad] -> ShowS
show :: EmQuad -> String
$cshow :: EmQuad -> String
showsPrec :: Int -> EmQuad -> ShowS
$cshowsPrec :: Int -> EmQuad -> ShowS
Show, (forall x. EmQuad -> Rep EmQuad x)
-> (forall x. Rep EmQuad x -> EmQuad) -> Generic EmQuad
forall x. Rep EmQuad x -> EmQuad
forall x. EmQuad -> Rep EmQuad x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EmQuad x -> EmQuad
$cfrom :: forall x. EmQuad -> Rep EmQuad x
Generic)
class HasEmQuad a where
emQuad :: Lens' a EmQuad
instance HasEmQuad EmQuad where
emQuad :: (EmQuad -> f EmQuad) -> EmQuad -> f EmQuad
emQuad = (EmQuad -> f EmQuad) -> EmQuad -> f EmQuad
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasEmQuad () where
emQuad :: (EmQuad -> f EmQuad) -> () -> f ()
emQuad EmQuad -> f EmQuad
f ()
x =
(EmQuad -> ()) -> f EmQuad -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\EmQuad
EmQuad -> ()
x) (EmQuad -> f EmQuad
f EmQuad
EmQuad)
instance Semigroup EmQuad where
EmQuad
EmQuad <> :: EmQuad -> EmQuad -> EmQuad
<> EmQuad
EmQuad = EmQuad
EmQuad
instance Monoid EmQuad where
mempty :: EmQuad
mempty = EmQuad
EmQuad
class AsEmQuad a where
_EmQuad :: Prism' a EmQuad
_EmQuad' :: a
_EmQuad' = Tagged EmQuad (Identity EmQuad) -> Tagged a (Identity a)
forall a. AsEmQuad a => Prism' a EmQuad
_EmQuad (Tagged EmQuad (Identity EmQuad) -> Tagged a (Identity a))
-> EmQuad -> a
forall t b. AReview t b -> b -> t
# EmQuad
EmQuad
instance AsEmQuad EmQuad where
_EmQuad :: p EmQuad (f EmQuad) -> p EmQuad (f EmQuad)
_EmQuad = p EmQuad (f EmQuad) -> p EmQuad (f EmQuad)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsEmQuad () where
_EmQuad :: p EmQuad (f EmQuad) -> p () (f ())
_EmQuad =
(EmQuad -> ()) -> (() -> Maybe EmQuad) -> Prism' () EmQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmQuad
EmQuad -> ())
(\() -> EmQuad -> Maybe EmQuad
forall a. a -> Maybe a
Just EmQuad
EmQuad)
instance AsEmQuad Char where
_EmQuad :: p EmQuad (f EmQuad) -> p Char (f Char)
_EmQuad =
(EmQuad -> Char) -> (Char -> Maybe EmQuad) -> Prism' Char EmQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmQuad
EmQuad -> Char
'\8193')
(\case
Char
'\8193' -> EmQuad -> Maybe EmQuad
forall a. a -> Maybe a
Just EmQuad
EmQuad
Char
_ -> Maybe EmQuad
forall a. Maybe a
Nothing
)
instance AsEmQuad Int where
_EmQuad :: p EmQuad (f EmQuad) -> p Int (f Int)
_EmQuad =
(EmQuad -> Int) -> (Int -> Maybe EmQuad) -> Prism' Int EmQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmQuad
EmQuad -> Int
8193)
(\case
Int
8193 -> EmQuad -> Maybe EmQuad
forall a. a -> Maybe a
Just EmQuad
EmQuad
Int
_ -> Maybe EmQuad
forall a. Maybe a
Nothing
)
instance AsEmQuad Integer where
_EmQuad :: p EmQuad (f EmQuad) -> p Integer (f Integer)
_EmQuad =
(EmQuad -> Integer)
-> (Integer -> Maybe EmQuad) -> Prism' Integer EmQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmQuad
EmQuad -> Integer
8193)
(\case
Integer
8193 -> EmQuad -> Maybe EmQuad
forall a. a -> Maybe a
Just EmQuad
EmQuad
Integer
_ -> Maybe EmQuad
forall a. Maybe a
Nothing
)
parseEmQuad ::
CharParsing p =>
p EmQuad
parseEmQuad :: p EmQuad
parseEmQuad =
EmQuad
EmQuad EmQuad -> p Char -> p EmQuad
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8193') p EmQuad -> String -> p EmQuad
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"em quad character"
data EnSpace = EnSpace
deriving (EnSpace -> EnSpace -> Bool
(EnSpace -> EnSpace -> Bool)
-> (EnSpace -> EnSpace -> Bool) -> Eq EnSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnSpace -> EnSpace -> Bool
$c/= :: EnSpace -> EnSpace -> Bool
== :: EnSpace -> EnSpace -> Bool
$c== :: EnSpace -> EnSpace -> Bool
Eq, Eq EnSpace
Eq EnSpace
-> (EnSpace -> EnSpace -> Ordering)
-> (EnSpace -> EnSpace -> Bool)
-> (EnSpace -> EnSpace -> Bool)
-> (EnSpace -> EnSpace -> Bool)
-> (EnSpace -> EnSpace -> Bool)
-> (EnSpace -> EnSpace -> EnSpace)
-> (EnSpace -> EnSpace -> EnSpace)
-> Ord EnSpace
EnSpace -> EnSpace -> Bool
EnSpace -> EnSpace -> Ordering
EnSpace -> EnSpace -> EnSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnSpace -> EnSpace -> EnSpace
$cmin :: EnSpace -> EnSpace -> EnSpace
max :: EnSpace -> EnSpace -> EnSpace
$cmax :: EnSpace -> EnSpace -> EnSpace
>= :: EnSpace -> EnSpace -> Bool
$c>= :: EnSpace -> EnSpace -> Bool
> :: EnSpace -> EnSpace -> Bool
$c> :: EnSpace -> EnSpace -> Bool
<= :: EnSpace -> EnSpace -> Bool
$c<= :: EnSpace -> EnSpace -> Bool
< :: EnSpace -> EnSpace -> Bool
$c< :: EnSpace -> EnSpace -> Bool
compare :: EnSpace -> EnSpace -> Ordering
$ccompare :: EnSpace -> EnSpace -> Ordering
$cp1Ord :: Eq EnSpace
Ord, Int -> EnSpace -> ShowS
[EnSpace] -> ShowS
EnSpace -> String
(Int -> EnSpace -> ShowS)
-> (EnSpace -> String) -> ([EnSpace] -> ShowS) -> Show EnSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnSpace] -> ShowS
$cshowList :: [EnSpace] -> ShowS
show :: EnSpace -> String
$cshow :: EnSpace -> String
showsPrec :: Int -> EnSpace -> ShowS
$cshowsPrec :: Int -> EnSpace -> ShowS
Show, (forall x. EnSpace -> Rep EnSpace x)
-> (forall x. Rep EnSpace x -> EnSpace) -> Generic EnSpace
forall x. Rep EnSpace x -> EnSpace
forall x. EnSpace -> Rep EnSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnSpace x -> EnSpace
$cfrom :: forall x. EnSpace -> Rep EnSpace x
Generic)
class HasEnSpace a where
enSpace :: Lens' a EnSpace
instance HasEnSpace EnSpace where
enSpace :: (EnSpace -> f EnSpace) -> EnSpace -> f EnSpace
enSpace = (EnSpace -> f EnSpace) -> EnSpace -> f EnSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasEnSpace () where
enSpace :: (EnSpace -> f EnSpace) -> () -> f ()
enSpace EnSpace -> f EnSpace
f ()
x =
(EnSpace -> ()) -> f EnSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\EnSpace
EnSpace -> ()
x) (EnSpace -> f EnSpace
f EnSpace
EnSpace)
instance Semigroup EnSpace where
EnSpace
EnSpace <> :: EnSpace -> EnSpace -> EnSpace
<> EnSpace
EnSpace = EnSpace
EnSpace
instance Monoid EnSpace where
mempty :: EnSpace
mempty = EnSpace
EnSpace
class AsEnSpace a where
_EnSpace :: Prism' a EnSpace
_EnSpace' :: a
_EnSpace' = Tagged EnSpace (Identity EnSpace) -> Tagged a (Identity a)
forall a. AsEnSpace a => Prism' a EnSpace
_EnSpace (Tagged EnSpace (Identity EnSpace) -> Tagged a (Identity a))
-> EnSpace -> a
forall t b. AReview t b -> b -> t
# EnSpace
EnSpace
instance AsEnSpace EnSpace where
_EnSpace :: p EnSpace (f EnSpace) -> p EnSpace (f EnSpace)
_EnSpace = p EnSpace (f EnSpace) -> p EnSpace (f EnSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsEnSpace () where
_EnSpace :: p EnSpace (f EnSpace) -> p () (f ())
_EnSpace =
(EnSpace -> ()) -> (() -> Maybe EnSpace) -> Prism' () EnSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnSpace
EnSpace -> ())
(\() -> EnSpace -> Maybe EnSpace
forall a. a -> Maybe a
Just EnSpace
EnSpace)
instance AsEnSpace Char where
_EnSpace :: p EnSpace (f EnSpace) -> p Char (f Char)
_EnSpace =
(EnSpace -> Char) -> (Char -> Maybe EnSpace) -> Prism' Char EnSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnSpace
EnSpace -> Char
'\8194')
(\case
Char
'\8194' -> EnSpace -> Maybe EnSpace
forall a. a -> Maybe a
Just EnSpace
EnSpace
Char
_ -> Maybe EnSpace
forall a. Maybe a
Nothing
)
instance AsEnSpace Int where
_EnSpace :: p EnSpace (f EnSpace) -> p Int (f Int)
_EnSpace =
(EnSpace -> Int) -> (Int -> Maybe EnSpace) -> Prism' Int EnSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnSpace
EnSpace -> Int
8194)
(\case
Int
8194 -> EnSpace -> Maybe EnSpace
forall a. a -> Maybe a
Just EnSpace
EnSpace
Int
_ -> Maybe EnSpace
forall a. Maybe a
Nothing
)
instance AsEnSpace Integer where
_EnSpace :: p EnSpace (f EnSpace) -> p Integer (f Integer)
_EnSpace =
(EnSpace -> Integer)
-> (Integer -> Maybe EnSpace) -> Prism' Integer EnSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnSpace
EnSpace -> Integer
8194)
(\case
Integer
8194 -> EnSpace -> Maybe EnSpace
forall a. a -> Maybe a
Just EnSpace
EnSpace
Integer
_ -> Maybe EnSpace
forall a. Maybe a
Nothing
)
parseEnSpace ::
CharParsing p =>
p EnSpace
parseEnSpace :: p EnSpace
parseEnSpace =
EnSpace
EnSpace EnSpace -> p Char -> p EnSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8194') p EnSpace -> String -> p EnSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"en space character"
data EmSpace = EmSpace
deriving (EmSpace -> EmSpace -> Bool
(EmSpace -> EmSpace -> Bool)
-> (EmSpace -> EmSpace -> Bool) -> Eq EmSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmSpace -> EmSpace -> Bool
$c/= :: EmSpace -> EmSpace -> Bool
== :: EmSpace -> EmSpace -> Bool
$c== :: EmSpace -> EmSpace -> Bool
Eq, Eq EmSpace
Eq EmSpace
-> (EmSpace -> EmSpace -> Ordering)
-> (EmSpace -> EmSpace -> Bool)
-> (EmSpace -> EmSpace -> Bool)
-> (EmSpace -> EmSpace -> Bool)
-> (EmSpace -> EmSpace -> Bool)
-> (EmSpace -> EmSpace -> EmSpace)
-> (EmSpace -> EmSpace -> EmSpace)
-> Ord EmSpace
EmSpace -> EmSpace -> Bool
EmSpace -> EmSpace -> Ordering
EmSpace -> EmSpace -> EmSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EmSpace -> EmSpace -> EmSpace
$cmin :: EmSpace -> EmSpace -> EmSpace
max :: EmSpace -> EmSpace -> EmSpace
$cmax :: EmSpace -> EmSpace -> EmSpace
>= :: EmSpace -> EmSpace -> Bool
$c>= :: EmSpace -> EmSpace -> Bool
> :: EmSpace -> EmSpace -> Bool
$c> :: EmSpace -> EmSpace -> Bool
<= :: EmSpace -> EmSpace -> Bool
$c<= :: EmSpace -> EmSpace -> Bool
< :: EmSpace -> EmSpace -> Bool
$c< :: EmSpace -> EmSpace -> Bool
compare :: EmSpace -> EmSpace -> Ordering
$ccompare :: EmSpace -> EmSpace -> Ordering
$cp1Ord :: Eq EmSpace
Ord, Int -> EmSpace -> ShowS
[EmSpace] -> ShowS
EmSpace -> String
(Int -> EmSpace -> ShowS)
-> (EmSpace -> String) -> ([EmSpace] -> ShowS) -> Show EmSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmSpace] -> ShowS
$cshowList :: [EmSpace] -> ShowS
show :: EmSpace -> String
$cshow :: EmSpace -> String
showsPrec :: Int -> EmSpace -> ShowS
$cshowsPrec :: Int -> EmSpace -> ShowS
Show, (forall x. EmSpace -> Rep EmSpace x)
-> (forall x. Rep EmSpace x -> EmSpace) -> Generic EmSpace
forall x. Rep EmSpace x -> EmSpace
forall x. EmSpace -> Rep EmSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EmSpace x -> EmSpace
$cfrom :: forall x. EmSpace -> Rep EmSpace x
Generic)
class HasEmSpace a where
emSpace :: Lens' a EmSpace
instance HasEmSpace EmSpace where
emSpace :: (EmSpace -> f EmSpace) -> EmSpace -> f EmSpace
emSpace = (EmSpace -> f EmSpace) -> EmSpace -> f EmSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasEmSpace () where
emSpace :: (EmSpace -> f EmSpace) -> () -> f ()
emSpace EmSpace -> f EmSpace
f ()
x =
(EmSpace -> ()) -> f EmSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\EmSpace
EmSpace -> ()
x) (EmSpace -> f EmSpace
f EmSpace
EmSpace)
instance Semigroup EmSpace where
EmSpace
EmSpace <> :: EmSpace -> EmSpace -> EmSpace
<> EmSpace
EmSpace = EmSpace
EmSpace
instance Monoid EmSpace where
mempty :: EmSpace
mempty = EmSpace
EmSpace
class AsEmSpace a where
_EmSpace :: Prism' a EmSpace
_EmSpace' :: a
_EmSpace' = Tagged EmSpace (Identity EmSpace) -> Tagged a (Identity a)
forall a. AsEmSpace a => Prism' a EmSpace
_EmSpace (Tagged EmSpace (Identity EmSpace) -> Tagged a (Identity a))
-> EmSpace -> a
forall t b. AReview t b -> b -> t
# EmSpace
EmSpace
instance AsEmSpace EmSpace where
_EmSpace :: p EmSpace (f EmSpace) -> p EmSpace (f EmSpace)
_EmSpace = p EmSpace (f EmSpace) -> p EmSpace (f EmSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsEmSpace () where
_EmSpace :: p EmSpace (f EmSpace) -> p () (f ())
_EmSpace =
(EmSpace -> ()) -> (() -> Maybe EmSpace) -> Prism' () EmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmSpace
EmSpace -> ())
(\() -> EmSpace -> Maybe EmSpace
forall a. a -> Maybe a
Just EmSpace
EmSpace)
instance AsEmSpace Char where
_EmSpace :: p EmSpace (f EmSpace) -> p Char (f Char)
_EmSpace =
(EmSpace -> Char) -> (Char -> Maybe EmSpace) -> Prism' Char EmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmSpace
EmSpace -> Char
'\8195')
(\case
Char
'\8195' -> EmSpace -> Maybe EmSpace
forall a. a -> Maybe a
Just EmSpace
EmSpace
Char
_ -> Maybe EmSpace
forall a. Maybe a
Nothing
)
instance AsEmSpace Int where
_EmSpace :: p EmSpace (f EmSpace) -> p Int (f Int)
_EmSpace =
(EmSpace -> Int) -> (Int -> Maybe EmSpace) -> Prism' Int EmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmSpace
EmSpace -> Int
8195)
(\case
Int
8195 -> EmSpace -> Maybe EmSpace
forall a. a -> Maybe a
Just EmSpace
EmSpace
Int
_ -> Maybe EmSpace
forall a. Maybe a
Nothing
)
instance AsEmSpace Integer where
_EmSpace :: p EmSpace (f EmSpace) -> p Integer (f Integer)
_EmSpace =
(EmSpace -> Integer)
-> (Integer -> Maybe EmSpace) -> Prism' Integer EmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmSpace
EmSpace -> Integer
8195)
(\case
Integer
8195 -> EmSpace -> Maybe EmSpace
forall a. a -> Maybe a
Just EmSpace
EmSpace
Integer
_ -> Maybe EmSpace
forall a. Maybe a
Nothing
)
parseEmSpace ::
CharParsing p =>
p EmSpace
parseEmSpace :: p EmSpace
parseEmSpace =
EmSpace
EmSpace EmSpace -> p Char -> p EmSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8195') p EmSpace -> String -> p EmSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"em space character"
data ThreePerEmSpace = ThreePerEmSpace
deriving (ThreePerEmSpace -> ThreePerEmSpace -> Bool
(ThreePerEmSpace -> ThreePerEmSpace -> Bool)
-> (ThreePerEmSpace -> ThreePerEmSpace -> Bool)
-> Eq ThreePerEmSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
$c/= :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
== :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
$c== :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
Eq, Eq ThreePerEmSpace
Eq ThreePerEmSpace
-> (ThreePerEmSpace -> ThreePerEmSpace -> Ordering)
-> (ThreePerEmSpace -> ThreePerEmSpace -> Bool)
-> (ThreePerEmSpace -> ThreePerEmSpace -> Bool)
-> (ThreePerEmSpace -> ThreePerEmSpace -> Bool)
-> (ThreePerEmSpace -> ThreePerEmSpace -> Bool)
-> (ThreePerEmSpace -> ThreePerEmSpace -> ThreePerEmSpace)
-> (ThreePerEmSpace -> ThreePerEmSpace -> ThreePerEmSpace)
-> Ord ThreePerEmSpace
ThreePerEmSpace -> ThreePerEmSpace -> Bool
ThreePerEmSpace -> ThreePerEmSpace -> Ordering
ThreePerEmSpace -> ThreePerEmSpace -> ThreePerEmSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ThreePerEmSpace -> ThreePerEmSpace -> ThreePerEmSpace
$cmin :: ThreePerEmSpace -> ThreePerEmSpace -> ThreePerEmSpace
max :: ThreePerEmSpace -> ThreePerEmSpace -> ThreePerEmSpace
$cmax :: ThreePerEmSpace -> ThreePerEmSpace -> ThreePerEmSpace
>= :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
$c>= :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
> :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
$c> :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
<= :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
$c<= :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
< :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
$c< :: ThreePerEmSpace -> ThreePerEmSpace -> Bool
compare :: ThreePerEmSpace -> ThreePerEmSpace -> Ordering
$ccompare :: ThreePerEmSpace -> ThreePerEmSpace -> Ordering
$cp1Ord :: Eq ThreePerEmSpace
Ord, Int -> ThreePerEmSpace -> ShowS
[ThreePerEmSpace] -> ShowS
ThreePerEmSpace -> String
(Int -> ThreePerEmSpace -> ShowS)
-> (ThreePerEmSpace -> String)
-> ([ThreePerEmSpace] -> ShowS)
-> Show ThreePerEmSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThreePerEmSpace] -> ShowS
$cshowList :: [ThreePerEmSpace] -> ShowS
show :: ThreePerEmSpace -> String
$cshow :: ThreePerEmSpace -> String
showsPrec :: Int -> ThreePerEmSpace -> ShowS
$cshowsPrec :: Int -> ThreePerEmSpace -> ShowS
Show, (forall x. ThreePerEmSpace -> Rep ThreePerEmSpace x)
-> (forall x. Rep ThreePerEmSpace x -> ThreePerEmSpace)
-> Generic ThreePerEmSpace
forall x. Rep ThreePerEmSpace x -> ThreePerEmSpace
forall x. ThreePerEmSpace -> Rep ThreePerEmSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ThreePerEmSpace x -> ThreePerEmSpace
$cfrom :: forall x. ThreePerEmSpace -> Rep ThreePerEmSpace x
Generic)
class HasThreePerEmSpace a where
threePerEmSpace :: Lens' a ThreePerEmSpace
instance HasThreePerEmSpace ThreePerEmSpace where
threePerEmSpace :: (ThreePerEmSpace -> f ThreePerEmSpace)
-> ThreePerEmSpace -> f ThreePerEmSpace
threePerEmSpace = (ThreePerEmSpace -> f ThreePerEmSpace)
-> ThreePerEmSpace -> f ThreePerEmSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasThreePerEmSpace () where
threePerEmSpace :: (ThreePerEmSpace -> f ThreePerEmSpace) -> () -> f ()
threePerEmSpace ThreePerEmSpace -> f ThreePerEmSpace
f ()
x =
(ThreePerEmSpace -> ()) -> f ThreePerEmSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ThreePerEmSpace
ThreePerEmSpace -> ()
x) (ThreePerEmSpace -> f ThreePerEmSpace
f ThreePerEmSpace
ThreePerEmSpace)
instance Semigroup ThreePerEmSpace where
ThreePerEmSpace
ThreePerEmSpace <> :: ThreePerEmSpace -> ThreePerEmSpace -> ThreePerEmSpace
<> ThreePerEmSpace
ThreePerEmSpace = ThreePerEmSpace
ThreePerEmSpace
instance Monoid ThreePerEmSpace where
mempty :: ThreePerEmSpace
mempty = ThreePerEmSpace
ThreePerEmSpace
class AsThreePerEmSpace a where
_ThreePerEmSpace :: Prism' a ThreePerEmSpace
_ThreePerEmSpace' :: a
_ThreePerEmSpace' = Tagged ThreePerEmSpace (Identity ThreePerEmSpace)
-> Tagged a (Identity a)
forall a. AsThreePerEmSpace a => Prism' a ThreePerEmSpace
_ThreePerEmSpace (Tagged ThreePerEmSpace (Identity ThreePerEmSpace)
-> Tagged a (Identity a))
-> ThreePerEmSpace -> a
forall t b. AReview t b -> b -> t
# ThreePerEmSpace
ThreePerEmSpace
instance AsThreePerEmSpace ThreePerEmSpace where
_ThreePerEmSpace :: p ThreePerEmSpace (f ThreePerEmSpace)
-> p ThreePerEmSpace (f ThreePerEmSpace)
_ThreePerEmSpace = p ThreePerEmSpace (f ThreePerEmSpace)
-> p ThreePerEmSpace (f ThreePerEmSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsThreePerEmSpace () where
_ThreePerEmSpace :: p ThreePerEmSpace (f ThreePerEmSpace) -> p () (f ())
_ThreePerEmSpace =
(ThreePerEmSpace -> ())
-> (() -> Maybe ThreePerEmSpace) -> Prism' () ThreePerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThreePerEmSpace
ThreePerEmSpace -> ())
(\() -> ThreePerEmSpace -> Maybe ThreePerEmSpace
forall a. a -> Maybe a
Just ThreePerEmSpace
ThreePerEmSpace)
instance AsThreePerEmSpace Char where
_ThreePerEmSpace :: p ThreePerEmSpace (f ThreePerEmSpace) -> p Char (f Char)
_ThreePerEmSpace =
(ThreePerEmSpace -> Char)
-> (Char -> Maybe ThreePerEmSpace) -> Prism' Char ThreePerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThreePerEmSpace
ThreePerEmSpace -> Char
'\8196')
(\case
Char
'\8196' -> ThreePerEmSpace -> Maybe ThreePerEmSpace
forall a. a -> Maybe a
Just ThreePerEmSpace
ThreePerEmSpace
Char
_ -> Maybe ThreePerEmSpace
forall a. Maybe a
Nothing
)
instance AsThreePerEmSpace Int where
_ThreePerEmSpace :: p ThreePerEmSpace (f ThreePerEmSpace) -> p Int (f Int)
_ThreePerEmSpace =
(ThreePerEmSpace -> Int)
-> (Int -> Maybe ThreePerEmSpace) -> Prism' Int ThreePerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThreePerEmSpace
ThreePerEmSpace -> Int
8196)
(\case
Int
8196 -> ThreePerEmSpace -> Maybe ThreePerEmSpace
forall a. a -> Maybe a
Just ThreePerEmSpace
ThreePerEmSpace
Int
_ -> Maybe ThreePerEmSpace
forall a. Maybe a
Nothing
)
instance AsThreePerEmSpace Integer where
_ThreePerEmSpace :: p ThreePerEmSpace (f ThreePerEmSpace) -> p Integer (f Integer)
_ThreePerEmSpace =
(ThreePerEmSpace -> Integer)
-> (Integer -> Maybe ThreePerEmSpace)
-> Prism' Integer ThreePerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThreePerEmSpace
ThreePerEmSpace -> Integer
8196)
(\case
Integer
8196 -> ThreePerEmSpace -> Maybe ThreePerEmSpace
forall a. a -> Maybe a
Just ThreePerEmSpace
ThreePerEmSpace
Integer
_ -> Maybe ThreePerEmSpace
forall a. Maybe a
Nothing
)
parseThreePerEmSpace ::
CharParsing p =>
p ThreePerEmSpace
parseThreePerEmSpace :: p ThreePerEmSpace
parseThreePerEmSpace =
ThreePerEmSpace
ThreePerEmSpace ThreePerEmSpace -> p Char -> p ThreePerEmSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8196') p ThreePerEmSpace -> String -> p ThreePerEmSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"three per em space character"
data FourPerEmSpace = FourPerEmSpace
deriving (FourPerEmSpace -> FourPerEmSpace -> Bool
(FourPerEmSpace -> FourPerEmSpace -> Bool)
-> (FourPerEmSpace -> FourPerEmSpace -> Bool) -> Eq FourPerEmSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FourPerEmSpace -> FourPerEmSpace -> Bool
$c/= :: FourPerEmSpace -> FourPerEmSpace -> Bool
== :: FourPerEmSpace -> FourPerEmSpace -> Bool
$c== :: FourPerEmSpace -> FourPerEmSpace -> Bool
Eq, Eq FourPerEmSpace
Eq FourPerEmSpace
-> (FourPerEmSpace -> FourPerEmSpace -> Ordering)
-> (FourPerEmSpace -> FourPerEmSpace -> Bool)
-> (FourPerEmSpace -> FourPerEmSpace -> Bool)
-> (FourPerEmSpace -> FourPerEmSpace -> Bool)
-> (FourPerEmSpace -> FourPerEmSpace -> Bool)
-> (FourPerEmSpace -> FourPerEmSpace -> FourPerEmSpace)
-> (FourPerEmSpace -> FourPerEmSpace -> FourPerEmSpace)
-> Ord FourPerEmSpace
FourPerEmSpace -> FourPerEmSpace -> Bool
FourPerEmSpace -> FourPerEmSpace -> Ordering
FourPerEmSpace -> FourPerEmSpace -> FourPerEmSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FourPerEmSpace -> FourPerEmSpace -> FourPerEmSpace
$cmin :: FourPerEmSpace -> FourPerEmSpace -> FourPerEmSpace
max :: FourPerEmSpace -> FourPerEmSpace -> FourPerEmSpace
$cmax :: FourPerEmSpace -> FourPerEmSpace -> FourPerEmSpace
>= :: FourPerEmSpace -> FourPerEmSpace -> Bool
$c>= :: FourPerEmSpace -> FourPerEmSpace -> Bool
> :: FourPerEmSpace -> FourPerEmSpace -> Bool
$c> :: FourPerEmSpace -> FourPerEmSpace -> Bool
<= :: FourPerEmSpace -> FourPerEmSpace -> Bool
$c<= :: FourPerEmSpace -> FourPerEmSpace -> Bool
< :: FourPerEmSpace -> FourPerEmSpace -> Bool
$c< :: FourPerEmSpace -> FourPerEmSpace -> Bool
compare :: FourPerEmSpace -> FourPerEmSpace -> Ordering
$ccompare :: FourPerEmSpace -> FourPerEmSpace -> Ordering
$cp1Ord :: Eq FourPerEmSpace
Ord, Int -> FourPerEmSpace -> ShowS
[FourPerEmSpace] -> ShowS
FourPerEmSpace -> String
(Int -> FourPerEmSpace -> ShowS)
-> (FourPerEmSpace -> String)
-> ([FourPerEmSpace] -> ShowS)
-> Show FourPerEmSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FourPerEmSpace] -> ShowS
$cshowList :: [FourPerEmSpace] -> ShowS
show :: FourPerEmSpace -> String
$cshow :: FourPerEmSpace -> String
showsPrec :: Int -> FourPerEmSpace -> ShowS
$cshowsPrec :: Int -> FourPerEmSpace -> ShowS
Show, (forall x. FourPerEmSpace -> Rep FourPerEmSpace x)
-> (forall x. Rep FourPerEmSpace x -> FourPerEmSpace)
-> Generic FourPerEmSpace
forall x. Rep FourPerEmSpace x -> FourPerEmSpace
forall x. FourPerEmSpace -> Rep FourPerEmSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FourPerEmSpace x -> FourPerEmSpace
$cfrom :: forall x. FourPerEmSpace -> Rep FourPerEmSpace x
Generic)
class HasFourPerEmSpace a where
fourPerEmSpace :: Lens' a FourPerEmSpace
instance HasFourPerEmSpace FourPerEmSpace where
fourPerEmSpace :: (FourPerEmSpace -> f FourPerEmSpace)
-> FourPerEmSpace -> f FourPerEmSpace
fourPerEmSpace = (FourPerEmSpace -> f FourPerEmSpace)
-> FourPerEmSpace -> f FourPerEmSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasFourPerEmSpace () where
fourPerEmSpace :: (FourPerEmSpace -> f FourPerEmSpace) -> () -> f ()
fourPerEmSpace FourPerEmSpace -> f FourPerEmSpace
f ()
x =
(FourPerEmSpace -> ()) -> f FourPerEmSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FourPerEmSpace
FourPerEmSpace -> ()
x) (FourPerEmSpace -> f FourPerEmSpace
f FourPerEmSpace
FourPerEmSpace)
instance Semigroup FourPerEmSpace where
FourPerEmSpace
FourPerEmSpace <> :: FourPerEmSpace -> FourPerEmSpace -> FourPerEmSpace
<> FourPerEmSpace
FourPerEmSpace = FourPerEmSpace
FourPerEmSpace
instance Monoid FourPerEmSpace where
mempty :: FourPerEmSpace
mempty = FourPerEmSpace
FourPerEmSpace
class AsFourPerEmSpace a where
_FourPerEmSpace :: Prism' a FourPerEmSpace
_FourPerEmSpace' :: a
_FourPerEmSpace' = Tagged FourPerEmSpace (Identity FourPerEmSpace)
-> Tagged a (Identity a)
forall a. AsFourPerEmSpace a => Prism' a FourPerEmSpace
_FourPerEmSpace (Tagged FourPerEmSpace (Identity FourPerEmSpace)
-> Tagged a (Identity a))
-> FourPerEmSpace -> a
forall t b. AReview t b -> b -> t
# FourPerEmSpace
FourPerEmSpace
instance AsFourPerEmSpace FourPerEmSpace where
_FourPerEmSpace :: p FourPerEmSpace (f FourPerEmSpace)
-> p FourPerEmSpace (f FourPerEmSpace)
_FourPerEmSpace = p FourPerEmSpace (f FourPerEmSpace)
-> p FourPerEmSpace (f FourPerEmSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsFourPerEmSpace () where
_FourPerEmSpace :: p FourPerEmSpace (f FourPerEmSpace) -> p () (f ())
_FourPerEmSpace =
(FourPerEmSpace -> ())
-> (() -> Maybe FourPerEmSpace) -> Prism' () FourPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FourPerEmSpace
FourPerEmSpace -> ())
(\() -> FourPerEmSpace -> Maybe FourPerEmSpace
forall a. a -> Maybe a
Just FourPerEmSpace
FourPerEmSpace)
instance AsFourPerEmSpace Char where
_FourPerEmSpace :: p FourPerEmSpace (f FourPerEmSpace) -> p Char (f Char)
_FourPerEmSpace =
(FourPerEmSpace -> Char)
-> (Char -> Maybe FourPerEmSpace) -> Prism' Char FourPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FourPerEmSpace
FourPerEmSpace -> Char
'\8197')
(\case
Char
'\8197' -> FourPerEmSpace -> Maybe FourPerEmSpace
forall a. a -> Maybe a
Just FourPerEmSpace
FourPerEmSpace
Char
_ -> Maybe FourPerEmSpace
forall a. Maybe a
Nothing
)
instance AsFourPerEmSpace Int where
_FourPerEmSpace :: p FourPerEmSpace (f FourPerEmSpace) -> p Int (f Int)
_FourPerEmSpace =
(FourPerEmSpace -> Int)
-> (Int -> Maybe FourPerEmSpace) -> Prism' Int FourPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FourPerEmSpace
FourPerEmSpace -> Int
8197)
(\case
Int
8197 -> FourPerEmSpace -> Maybe FourPerEmSpace
forall a. a -> Maybe a
Just FourPerEmSpace
FourPerEmSpace
Int
_ -> Maybe FourPerEmSpace
forall a. Maybe a
Nothing
)
instance AsFourPerEmSpace Integer where
_FourPerEmSpace :: p FourPerEmSpace (f FourPerEmSpace) -> p Integer (f Integer)
_FourPerEmSpace =
(FourPerEmSpace -> Integer)
-> (Integer -> Maybe FourPerEmSpace)
-> Prism' Integer FourPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FourPerEmSpace
FourPerEmSpace -> Integer
8197)
(\case
Integer
8197 -> FourPerEmSpace -> Maybe FourPerEmSpace
forall a. a -> Maybe a
Just FourPerEmSpace
FourPerEmSpace
Integer
_ -> Maybe FourPerEmSpace
forall a. Maybe a
Nothing
)
parseFourPerEmSpace ::
CharParsing p =>
p FourPerEmSpace
parseFourPerEmSpace :: p FourPerEmSpace
parseFourPerEmSpace =
FourPerEmSpace
FourPerEmSpace FourPerEmSpace -> p Char -> p FourPerEmSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8197') p FourPerEmSpace -> String -> p FourPerEmSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"four per em space character"
data SixPerEmSpace = SixPerEmSpace
deriving (SixPerEmSpace -> SixPerEmSpace -> Bool
(SixPerEmSpace -> SixPerEmSpace -> Bool)
-> (SixPerEmSpace -> SixPerEmSpace -> Bool) -> Eq SixPerEmSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SixPerEmSpace -> SixPerEmSpace -> Bool
$c/= :: SixPerEmSpace -> SixPerEmSpace -> Bool
== :: SixPerEmSpace -> SixPerEmSpace -> Bool
$c== :: SixPerEmSpace -> SixPerEmSpace -> Bool
Eq, Eq SixPerEmSpace
Eq SixPerEmSpace
-> (SixPerEmSpace -> SixPerEmSpace -> Ordering)
-> (SixPerEmSpace -> SixPerEmSpace -> Bool)
-> (SixPerEmSpace -> SixPerEmSpace -> Bool)
-> (SixPerEmSpace -> SixPerEmSpace -> Bool)
-> (SixPerEmSpace -> SixPerEmSpace -> Bool)
-> (SixPerEmSpace -> SixPerEmSpace -> SixPerEmSpace)
-> (SixPerEmSpace -> SixPerEmSpace -> SixPerEmSpace)
-> Ord SixPerEmSpace
SixPerEmSpace -> SixPerEmSpace -> Bool
SixPerEmSpace -> SixPerEmSpace -> Ordering
SixPerEmSpace -> SixPerEmSpace -> SixPerEmSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SixPerEmSpace -> SixPerEmSpace -> SixPerEmSpace
$cmin :: SixPerEmSpace -> SixPerEmSpace -> SixPerEmSpace
max :: SixPerEmSpace -> SixPerEmSpace -> SixPerEmSpace
$cmax :: SixPerEmSpace -> SixPerEmSpace -> SixPerEmSpace
>= :: SixPerEmSpace -> SixPerEmSpace -> Bool
$c>= :: SixPerEmSpace -> SixPerEmSpace -> Bool
> :: SixPerEmSpace -> SixPerEmSpace -> Bool
$c> :: SixPerEmSpace -> SixPerEmSpace -> Bool
<= :: SixPerEmSpace -> SixPerEmSpace -> Bool
$c<= :: SixPerEmSpace -> SixPerEmSpace -> Bool
< :: SixPerEmSpace -> SixPerEmSpace -> Bool
$c< :: SixPerEmSpace -> SixPerEmSpace -> Bool
compare :: SixPerEmSpace -> SixPerEmSpace -> Ordering
$ccompare :: SixPerEmSpace -> SixPerEmSpace -> Ordering
$cp1Ord :: Eq SixPerEmSpace
Ord, Int -> SixPerEmSpace -> ShowS
[SixPerEmSpace] -> ShowS
SixPerEmSpace -> String
(Int -> SixPerEmSpace -> ShowS)
-> (SixPerEmSpace -> String)
-> ([SixPerEmSpace] -> ShowS)
-> Show SixPerEmSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SixPerEmSpace] -> ShowS
$cshowList :: [SixPerEmSpace] -> ShowS
show :: SixPerEmSpace -> String
$cshow :: SixPerEmSpace -> String
showsPrec :: Int -> SixPerEmSpace -> ShowS
$cshowsPrec :: Int -> SixPerEmSpace -> ShowS
Show, (forall x. SixPerEmSpace -> Rep SixPerEmSpace x)
-> (forall x. Rep SixPerEmSpace x -> SixPerEmSpace)
-> Generic SixPerEmSpace
forall x. Rep SixPerEmSpace x -> SixPerEmSpace
forall x. SixPerEmSpace -> Rep SixPerEmSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SixPerEmSpace x -> SixPerEmSpace
$cfrom :: forall x. SixPerEmSpace -> Rep SixPerEmSpace x
Generic)
class HasSixPerEmSpace a where
sixPerEmSpace :: Lens' a SixPerEmSpace
instance HasSixPerEmSpace SixPerEmSpace where
sixPerEmSpace :: (SixPerEmSpace -> f SixPerEmSpace)
-> SixPerEmSpace -> f SixPerEmSpace
sixPerEmSpace = (SixPerEmSpace -> f SixPerEmSpace)
-> SixPerEmSpace -> f SixPerEmSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasSixPerEmSpace () where
sixPerEmSpace :: (SixPerEmSpace -> f SixPerEmSpace) -> () -> f ()
sixPerEmSpace SixPerEmSpace -> f SixPerEmSpace
f ()
x =
(SixPerEmSpace -> ()) -> f SixPerEmSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\SixPerEmSpace
SixPerEmSpace -> ()
x) (SixPerEmSpace -> f SixPerEmSpace
f SixPerEmSpace
SixPerEmSpace)
instance Semigroup SixPerEmSpace where
SixPerEmSpace
SixPerEmSpace <> :: SixPerEmSpace -> SixPerEmSpace -> SixPerEmSpace
<> SixPerEmSpace
SixPerEmSpace = SixPerEmSpace
SixPerEmSpace
instance Monoid SixPerEmSpace where
mempty :: SixPerEmSpace
mempty = SixPerEmSpace
SixPerEmSpace
class AsSixPerEmSpace a where
_SixPerEmSpace :: Prism' a SixPerEmSpace
_SixPerEmSpace' :: a
_SixPerEmSpace' = Tagged SixPerEmSpace (Identity SixPerEmSpace)
-> Tagged a (Identity a)
forall a. AsSixPerEmSpace a => Prism' a SixPerEmSpace
_SixPerEmSpace (Tagged SixPerEmSpace (Identity SixPerEmSpace)
-> Tagged a (Identity a))
-> SixPerEmSpace -> a
forall t b. AReview t b -> b -> t
# SixPerEmSpace
SixPerEmSpace
instance AsSixPerEmSpace SixPerEmSpace where
_SixPerEmSpace :: p SixPerEmSpace (f SixPerEmSpace)
-> p SixPerEmSpace (f SixPerEmSpace)
_SixPerEmSpace = p SixPerEmSpace (f SixPerEmSpace)
-> p SixPerEmSpace (f SixPerEmSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsSixPerEmSpace () where
_SixPerEmSpace :: p SixPerEmSpace (f SixPerEmSpace) -> p () (f ())
_SixPerEmSpace =
(SixPerEmSpace -> ())
-> (() -> Maybe SixPerEmSpace) -> Prism' () SixPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\SixPerEmSpace
SixPerEmSpace -> ())
(\() -> SixPerEmSpace -> Maybe SixPerEmSpace
forall a. a -> Maybe a
Just SixPerEmSpace
SixPerEmSpace)
instance AsSixPerEmSpace Char where
_SixPerEmSpace :: p SixPerEmSpace (f SixPerEmSpace) -> p Char (f Char)
_SixPerEmSpace =
(SixPerEmSpace -> Char)
-> (Char -> Maybe SixPerEmSpace) -> Prism' Char SixPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\SixPerEmSpace
SixPerEmSpace -> Char
'\8198')
(\case
Char
'\8198' -> SixPerEmSpace -> Maybe SixPerEmSpace
forall a. a -> Maybe a
Just SixPerEmSpace
SixPerEmSpace
Char
_ -> Maybe SixPerEmSpace
forall a. Maybe a
Nothing
)
instance AsSixPerEmSpace Int where
_SixPerEmSpace :: p SixPerEmSpace (f SixPerEmSpace) -> p Int (f Int)
_SixPerEmSpace =
(SixPerEmSpace -> Int)
-> (Int -> Maybe SixPerEmSpace) -> Prism' Int SixPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\SixPerEmSpace
SixPerEmSpace -> Int
8198)
(\case
Int
8198 -> SixPerEmSpace -> Maybe SixPerEmSpace
forall a. a -> Maybe a
Just SixPerEmSpace
SixPerEmSpace
Int
_ -> Maybe SixPerEmSpace
forall a. Maybe a
Nothing
)
instance AsSixPerEmSpace Integer where
_SixPerEmSpace :: p SixPerEmSpace (f SixPerEmSpace) -> p Integer (f Integer)
_SixPerEmSpace =
(SixPerEmSpace -> Integer)
-> (Integer -> Maybe SixPerEmSpace) -> Prism' Integer SixPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\SixPerEmSpace
SixPerEmSpace -> Integer
8198)
(\case
Integer
8198 -> SixPerEmSpace -> Maybe SixPerEmSpace
forall a. a -> Maybe a
Just SixPerEmSpace
SixPerEmSpace
Integer
_ -> Maybe SixPerEmSpace
forall a. Maybe a
Nothing
)
parseSixPerEmSpace ::
CharParsing p =>
p SixPerEmSpace
parseSixPerEmSpace :: p SixPerEmSpace
parseSixPerEmSpace =
SixPerEmSpace
SixPerEmSpace SixPerEmSpace -> p Char -> p SixPerEmSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8198') p SixPerEmSpace -> String -> p SixPerEmSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"six per em space character"
data FigureSpace = FigureSpace
deriving (FigureSpace -> FigureSpace -> Bool
(FigureSpace -> FigureSpace -> Bool)
-> (FigureSpace -> FigureSpace -> Bool) -> Eq FigureSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FigureSpace -> FigureSpace -> Bool
$c/= :: FigureSpace -> FigureSpace -> Bool
== :: FigureSpace -> FigureSpace -> Bool
$c== :: FigureSpace -> FigureSpace -> Bool
Eq, Eq FigureSpace
Eq FigureSpace
-> (FigureSpace -> FigureSpace -> Ordering)
-> (FigureSpace -> FigureSpace -> Bool)
-> (FigureSpace -> FigureSpace -> Bool)
-> (FigureSpace -> FigureSpace -> Bool)
-> (FigureSpace -> FigureSpace -> Bool)
-> (FigureSpace -> FigureSpace -> FigureSpace)
-> (FigureSpace -> FigureSpace -> FigureSpace)
-> Ord FigureSpace
FigureSpace -> FigureSpace -> Bool
FigureSpace -> FigureSpace -> Ordering
FigureSpace -> FigureSpace -> FigureSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FigureSpace -> FigureSpace -> FigureSpace
$cmin :: FigureSpace -> FigureSpace -> FigureSpace
max :: FigureSpace -> FigureSpace -> FigureSpace
$cmax :: FigureSpace -> FigureSpace -> FigureSpace
>= :: FigureSpace -> FigureSpace -> Bool
$c>= :: FigureSpace -> FigureSpace -> Bool
> :: FigureSpace -> FigureSpace -> Bool
$c> :: FigureSpace -> FigureSpace -> Bool
<= :: FigureSpace -> FigureSpace -> Bool
$c<= :: FigureSpace -> FigureSpace -> Bool
< :: FigureSpace -> FigureSpace -> Bool
$c< :: FigureSpace -> FigureSpace -> Bool
compare :: FigureSpace -> FigureSpace -> Ordering
$ccompare :: FigureSpace -> FigureSpace -> Ordering
$cp1Ord :: Eq FigureSpace
Ord, Int -> FigureSpace -> ShowS
[FigureSpace] -> ShowS
FigureSpace -> String
(Int -> FigureSpace -> ShowS)
-> (FigureSpace -> String)
-> ([FigureSpace] -> ShowS)
-> Show FigureSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FigureSpace] -> ShowS
$cshowList :: [FigureSpace] -> ShowS
show :: FigureSpace -> String
$cshow :: FigureSpace -> String
showsPrec :: Int -> FigureSpace -> ShowS
$cshowsPrec :: Int -> FigureSpace -> ShowS
Show, (forall x. FigureSpace -> Rep FigureSpace x)
-> (forall x. Rep FigureSpace x -> FigureSpace)
-> Generic FigureSpace
forall x. Rep FigureSpace x -> FigureSpace
forall x. FigureSpace -> Rep FigureSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FigureSpace x -> FigureSpace
$cfrom :: forall x. FigureSpace -> Rep FigureSpace x
Generic)
class HasFigureSpace a where
figureSpace :: Lens' a FigureSpace
instance HasFigureSpace FigureSpace where
figureSpace :: (FigureSpace -> f FigureSpace) -> FigureSpace -> f FigureSpace
figureSpace = (FigureSpace -> f FigureSpace) -> FigureSpace -> f FigureSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasFigureSpace () where
figureSpace :: (FigureSpace -> f FigureSpace) -> () -> f ()
figureSpace FigureSpace -> f FigureSpace
f ()
x =
(FigureSpace -> ()) -> f FigureSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FigureSpace
FigureSpace -> ()
x) (FigureSpace -> f FigureSpace
f FigureSpace
FigureSpace)
instance Semigroup FigureSpace where
FigureSpace
FigureSpace <> :: FigureSpace -> FigureSpace -> FigureSpace
<> FigureSpace
FigureSpace = FigureSpace
FigureSpace
instance Monoid FigureSpace where
mempty :: FigureSpace
mempty = FigureSpace
FigureSpace
class AsFigureSpace a where
_FigureSpace :: Prism' a FigureSpace
_FigureSpace' :: a
_FigureSpace' = Tagged FigureSpace (Identity FigureSpace) -> Tagged a (Identity a)
forall a. AsFigureSpace a => Prism' a FigureSpace
_FigureSpace (Tagged FigureSpace (Identity FigureSpace)
-> Tagged a (Identity a))
-> FigureSpace -> a
forall t b. AReview t b -> b -> t
# FigureSpace
FigureSpace
instance AsFigureSpace FigureSpace where
_FigureSpace :: p FigureSpace (f FigureSpace) -> p FigureSpace (f FigureSpace)
_FigureSpace = p FigureSpace (f FigureSpace) -> p FigureSpace (f FigureSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsFigureSpace () where
_FigureSpace :: p FigureSpace (f FigureSpace) -> p () (f ())
_FigureSpace =
(FigureSpace -> ())
-> (() -> Maybe FigureSpace) -> Prism' () FigureSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FigureSpace
FigureSpace -> ())
(\() -> FigureSpace -> Maybe FigureSpace
forall a. a -> Maybe a
Just FigureSpace
FigureSpace)
instance AsFigureSpace Char where
_FigureSpace :: p FigureSpace (f FigureSpace) -> p Char (f Char)
_FigureSpace =
(FigureSpace -> Char)
-> (Char -> Maybe FigureSpace) -> Prism' Char FigureSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FigureSpace
FigureSpace -> Char
'\8199')
(\case
Char
'\8199' -> FigureSpace -> Maybe FigureSpace
forall a. a -> Maybe a
Just FigureSpace
FigureSpace
Char
_ -> Maybe FigureSpace
forall a. Maybe a
Nothing
)
instance AsFigureSpace Int where
_FigureSpace :: p FigureSpace (f FigureSpace) -> p Int (f Int)
_FigureSpace =
(FigureSpace -> Int)
-> (Int -> Maybe FigureSpace) -> Prism' Int FigureSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FigureSpace
FigureSpace -> Int
8199)
(\case
Int
8199 -> FigureSpace -> Maybe FigureSpace
forall a. a -> Maybe a
Just FigureSpace
FigureSpace
Int
_ -> Maybe FigureSpace
forall a. Maybe a
Nothing
)
instance AsFigureSpace Integer where
_FigureSpace :: p FigureSpace (f FigureSpace) -> p Integer (f Integer)
_FigureSpace =
(FigureSpace -> Integer)
-> (Integer -> Maybe FigureSpace) -> Prism' Integer FigureSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FigureSpace
FigureSpace -> Integer
8199)
(\case
Integer
8199 -> FigureSpace -> Maybe FigureSpace
forall a. a -> Maybe a
Just FigureSpace
FigureSpace
Integer
_ -> Maybe FigureSpace
forall a. Maybe a
Nothing
)
parseFigureSpace ::
CharParsing p =>
p FigureSpace
parseFigureSpace :: p FigureSpace
parseFigureSpace =
FigureSpace
FigureSpace FigureSpace -> p Char -> p FigureSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8199') p FigureSpace -> String -> p FigureSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"figure space character"
data PunctuationSpace = PunctuationSpace
deriving (PunctuationSpace -> PunctuationSpace -> Bool
(PunctuationSpace -> PunctuationSpace -> Bool)
-> (PunctuationSpace -> PunctuationSpace -> Bool)
-> Eq PunctuationSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PunctuationSpace -> PunctuationSpace -> Bool
$c/= :: PunctuationSpace -> PunctuationSpace -> Bool
== :: PunctuationSpace -> PunctuationSpace -> Bool
$c== :: PunctuationSpace -> PunctuationSpace -> Bool
Eq, Eq PunctuationSpace
Eq PunctuationSpace
-> (PunctuationSpace -> PunctuationSpace -> Ordering)
-> (PunctuationSpace -> PunctuationSpace -> Bool)
-> (PunctuationSpace -> PunctuationSpace -> Bool)
-> (PunctuationSpace -> PunctuationSpace -> Bool)
-> (PunctuationSpace -> PunctuationSpace -> Bool)
-> (PunctuationSpace -> PunctuationSpace -> PunctuationSpace)
-> (PunctuationSpace -> PunctuationSpace -> PunctuationSpace)
-> Ord PunctuationSpace
PunctuationSpace -> PunctuationSpace -> Bool
PunctuationSpace -> PunctuationSpace -> Ordering
PunctuationSpace -> PunctuationSpace -> PunctuationSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PunctuationSpace -> PunctuationSpace -> PunctuationSpace
$cmin :: PunctuationSpace -> PunctuationSpace -> PunctuationSpace
max :: PunctuationSpace -> PunctuationSpace -> PunctuationSpace
$cmax :: PunctuationSpace -> PunctuationSpace -> PunctuationSpace
>= :: PunctuationSpace -> PunctuationSpace -> Bool
$c>= :: PunctuationSpace -> PunctuationSpace -> Bool
> :: PunctuationSpace -> PunctuationSpace -> Bool
$c> :: PunctuationSpace -> PunctuationSpace -> Bool
<= :: PunctuationSpace -> PunctuationSpace -> Bool
$c<= :: PunctuationSpace -> PunctuationSpace -> Bool
< :: PunctuationSpace -> PunctuationSpace -> Bool
$c< :: PunctuationSpace -> PunctuationSpace -> Bool
compare :: PunctuationSpace -> PunctuationSpace -> Ordering
$ccompare :: PunctuationSpace -> PunctuationSpace -> Ordering
$cp1Ord :: Eq PunctuationSpace
Ord, Int -> PunctuationSpace -> ShowS
[PunctuationSpace] -> ShowS
PunctuationSpace -> String
(Int -> PunctuationSpace -> ShowS)
-> (PunctuationSpace -> String)
-> ([PunctuationSpace] -> ShowS)
-> Show PunctuationSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PunctuationSpace] -> ShowS
$cshowList :: [PunctuationSpace] -> ShowS
show :: PunctuationSpace -> String
$cshow :: PunctuationSpace -> String
showsPrec :: Int -> PunctuationSpace -> ShowS
$cshowsPrec :: Int -> PunctuationSpace -> ShowS
Show, (forall x. PunctuationSpace -> Rep PunctuationSpace x)
-> (forall x. Rep PunctuationSpace x -> PunctuationSpace)
-> Generic PunctuationSpace
forall x. Rep PunctuationSpace x -> PunctuationSpace
forall x. PunctuationSpace -> Rep PunctuationSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PunctuationSpace x -> PunctuationSpace
$cfrom :: forall x. PunctuationSpace -> Rep PunctuationSpace x
Generic)
class HasPunctuationSpace a where
punctuationSpace :: Lens' a PunctuationSpace
instance HasPunctuationSpace PunctuationSpace where
punctuationSpace :: (PunctuationSpace -> f PunctuationSpace)
-> PunctuationSpace -> f PunctuationSpace
punctuationSpace = (PunctuationSpace -> f PunctuationSpace)
-> PunctuationSpace -> f PunctuationSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasPunctuationSpace () where
punctuationSpace :: (PunctuationSpace -> f PunctuationSpace) -> () -> f ()
punctuationSpace PunctuationSpace -> f PunctuationSpace
f ()
x =
(PunctuationSpace -> ()) -> f PunctuationSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\PunctuationSpace
PunctuationSpace -> ()
x) (PunctuationSpace -> f PunctuationSpace
f PunctuationSpace
PunctuationSpace)
instance Semigroup PunctuationSpace where
PunctuationSpace
PunctuationSpace <> :: PunctuationSpace -> PunctuationSpace -> PunctuationSpace
<> PunctuationSpace
PunctuationSpace = PunctuationSpace
PunctuationSpace
instance Monoid PunctuationSpace where
mempty :: PunctuationSpace
mempty = PunctuationSpace
PunctuationSpace
class AsPunctuationSpace a where
_PunctuationSpace :: Prism' a PunctuationSpace
_PunctuationSpace' :: a
_PunctuationSpace' = Tagged PunctuationSpace (Identity PunctuationSpace)
-> Tagged a (Identity a)
forall a. AsPunctuationSpace a => Prism' a PunctuationSpace
_PunctuationSpace (Tagged PunctuationSpace (Identity PunctuationSpace)
-> Tagged a (Identity a))
-> PunctuationSpace -> a
forall t b. AReview t b -> b -> t
# PunctuationSpace
PunctuationSpace
instance AsPunctuationSpace PunctuationSpace where
_PunctuationSpace :: p PunctuationSpace (f PunctuationSpace)
-> p PunctuationSpace (f PunctuationSpace)
_PunctuationSpace = p PunctuationSpace (f PunctuationSpace)
-> p PunctuationSpace (f PunctuationSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsPunctuationSpace () where
_PunctuationSpace :: p PunctuationSpace (f PunctuationSpace) -> p () (f ())
_PunctuationSpace =
(PunctuationSpace -> ())
-> (() -> Maybe PunctuationSpace) -> Prism' () PunctuationSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\PunctuationSpace
PunctuationSpace -> ())
(\() -> PunctuationSpace -> Maybe PunctuationSpace
forall a. a -> Maybe a
Just PunctuationSpace
PunctuationSpace)
instance AsPunctuationSpace Char where
_PunctuationSpace :: p PunctuationSpace (f PunctuationSpace) -> p Char (f Char)
_PunctuationSpace =
(PunctuationSpace -> Char)
-> (Char -> Maybe PunctuationSpace) -> Prism' Char PunctuationSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\PunctuationSpace
PunctuationSpace -> Char
'\8200')
(\case
Char
'\8200' -> PunctuationSpace -> Maybe PunctuationSpace
forall a. a -> Maybe a
Just PunctuationSpace
PunctuationSpace
Char
_ -> Maybe PunctuationSpace
forall a. Maybe a
Nothing
)
instance AsPunctuationSpace Int where
_PunctuationSpace :: p PunctuationSpace (f PunctuationSpace) -> p Int (f Int)
_PunctuationSpace =
(PunctuationSpace -> Int)
-> (Int -> Maybe PunctuationSpace) -> Prism' Int PunctuationSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\PunctuationSpace
PunctuationSpace -> Int
8200)
(\case
Int
8200 -> PunctuationSpace -> Maybe PunctuationSpace
forall a. a -> Maybe a
Just PunctuationSpace
PunctuationSpace
Int
_ -> Maybe PunctuationSpace
forall a. Maybe a
Nothing
)
instance AsPunctuationSpace Integer where
_PunctuationSpace :: p PunctuationSpace (f PunctuationSpace) -> p Integer (f Integer)
_PunctuationSpace =
(PunctuationSpace -> Integer)
-> (Integer -> Maybe PunctuationSpace)
-> Prism' Integer PunctuationSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\PunctuationSpace
PunctuationSpace -> Integer
8200)
(\case
Integer
8200 -> PunctuationSpace -> Maybe PunctuationSpace
forall a. a -> Maybe a
Just PunctuationSpace
PunctuationSpace
Integer
_ -> Maybe PunctuationSpace
forall a. Maybe a
Nothing
)
parsePunctuationSpace ::
CharParsing p =>
p PunctuationSpace
parsePunctuationSpace :: p PunctuationSpace
parsePunctuationSpace =
PunctuationSpace
PunctuationSpace PunctuationSpace -> p Char -> p PunctuationSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8200') p PunctuationSpace -> String -> p PunctuationSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"punctuation space character"
data ThinSpace = ThinSpace
deriving (ThinSpace -> ThinSpace -> Bool
(ThinSpace -> ThinSpace -> Bool)
-> (ThinSpace -> ThinSpace -> Bool) -> Eq ThinSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThinSpace -> ThinSpace -> Bool
$c/= :: ThinSpace -> ThinSpace -> Bool
== :: ThinSpace -> ThinSpace -> Bool
$c== :: ThinSpace -> ThinSpace -> Bool
Eq, Eq ThinSpace
Eq ThinSpace
-> (ThinSpace -> ThinSpace -> Ordering)
-> (ThinSpace -> ThinSpace -> Bool)
-> (ThinSpace -> ThinSpace -> Bool)
-> (ThinSpace -> ThinSpace -> Bool)
-> (ThinSpace -> ThinSpace -> Bool)
-> (ThinSpace -> ThinSpace -> ThinSpace)
-> (ThinSpace -> ThinSpace -> ThinSpace)
-> Ord ThinSpace
ThinSpace -> ThinSpace -> Bool
ThinSpace -> ThinSpace -> Ordering
ThinSpace -> ThinSpace -> ThinSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ThinSpace -> ThinSpace -> ThinSpace
$cmin :: ThinSpace -> ThinSpace -> ThinSpace
max :: ThinSpace -> ThinSpace -> ThinSpace
$cmax :: ThinSpace -> ThinSpace -> ThinSpace
>= :: ThinSpace -> ThinSpace -> Bool
$c>= :: ThinSpace -> ThinSpace -> Bool
> :: ThinSpace -> ThinSpace -> Bool
$c> :: ThinSpace -> ThinSpace -> Bool
<= :: ThinSpace -> ThinSpace -> Bool
$c<= :: ThinSpace -> ThinSpace -> Bool
< :: ThinSpace -> ThinSpace -> Bool
$c< :: ThinSpace -> ThinSpace -> Bool
compare :: ThinSpace -> ThinSpace -> Ordering
$ccompare :: ThinSpace -> ThinSpace -> Ordering
$cp1Ord :: Eq ThinSpace
Ord, Int -> ThinSpace -> ShowS
[ThinSpace] -> ShowS
ThinSpace -> String
(Int -> ThinSpace -> ShowS)
-> (ThinSpace -> String)
-> ([ThinSpace] -> ShowS)
-> Show ThinSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThinSpace] -> ShowS
$cshowList :: [ThinSpace] -> ShowS
show :: ThinSpace -> String
$cshow :: ThinSpace -> String
showsPrec :: Int -> ThinSpace -> ShowS
$cshowsPrec :: Int -> ThinSpace -> ShowS
Show, (forall x. ThinSpace -> Rep ThinSpace x)
-> (forall x. Rep ThinSpace x -> ThinSpace) -> Generic ThinSpace
forall x. Rep ThinSpace x -> ThinSpace
forall x. ThinSpace -> Rep ThinSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ThinSpace x -> ThinSpace
$cfrom :: forall x. ThinSpace -> Rep ThinSpace x
Generic)
class HasThinSpace a where
thinSpace :: Lens' a ThinSpace
instance HasThinSpace ThinSpace where
thinSpace :: (ThinSpace -> f ThinSpace) -> ThinSpace -> f ThinSpace
thinSpace = (ThinSpace -> f ThinSpace) -> ThinSpace -> f ThinSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasThinSpace () where
thinSpace :: (ThinSpace -> f ThinSpace) -> () -> f ()
thinSpace ThinSpace -> f ThinSpace
f ()
x =
(ThinSpace -> ()) -> f ThinSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ThinSpace
ThinSpace -> ()
x) (ThinSpace -> f ThinSpace
f ThinSpace
ThinSpace)
instance Semigroup ThinSpace where
ThinSpace
ThinSpace <> :: ThinSpace -> ThinSpace -> ThinSpace
<> ThinSpace
ThinSpace = ThinSpace
ThinSpace
instance Monoid ThinSpace where
mempty :: ThinSpace
mempty = ThinSpace
ThinSpace
class AsThinSpace a where
_ThinSpace :: Prism' a ThinSpace
_ThinSpace' :: a
_ThinSpace' = Tagged ThinSpace (Identity ThinSpace) -> Tagged a (Identity a)
forall a. AsThinSpace a => Prism' a ThinSpace
_ThinSpace (Tagged ThinSpace (Identity ThinSpace) -> Tagged a (Identity a))
-> ThinSpace -> a
forall t b. AReview t b -> b -> t
# ThinSpace
ThinSpace
instance AsThinSpace ThinSpace where
_ThinSpace :: p ThinSpace (f ThinSpace) -> p ThinSpace (f ThinSpace)
_ThinSpace = p ThinSpace (f ThinSpace) -> p ThinSpace (f ThinSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsThinSpace () where
_ThinSpace :: p ThinSpace (f ThinSpace) -> p () (f ())
_ThinSpace =
(ThinSpace -> ()) -> (() -> Maybe ThinSpace) -> Prism' () ThinSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThinSpace
ThinSpace -> ())
(\() -> ThinSpace -> Maybe ThinSpace
forall a. a -> Maybe a
Just ThinSpace
ThinSpace)
instance AsThinSpace Char where
_ThinSpace :: p ThinSpace (f ThinSpace) -> p Char (f Char)
_ThinSpace =
(ThinSpace -> Char)
-> (Char -> Maybe ThinSpace) -> Prism' Char ThinSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThinSpace
ThinSpace -> Char
'\8201')
(\case
Char
'\8201' -> ThinSpace -> Maybe ThinSpace
forall a. a -> Maybe a
Just ThinSpace
ThinSpace
Char
_ -> Maybe ThinSpace
forall a. Maybe a
Nothing
)
instance AsThinSpace Int where
_ThinSpace :: p ThinSpace (f ThinSpace) -> p Int (f Int)
_ThinSpace =
(ThinSpace -> Int)
-> (Int -> Maybe ThinSpace) -> Prism' Int ThinSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThinSpace
ThinSpace -> Int
8201)
(\case
Int
8201 -> ThinSpace -> Maybe ThinSpace
forall a. a -> Maybe a
Just ThinSpace
ThinSpace
Int
_ -> Maybe ThinSpace
forall a. Maybe a
Nothing
)
instance AsThinSpace Integer where
_ThinSpace :: p ThinSpace (f ThinSpace) -> p Integer (f Integer)
_ThinSpace =
(ThinSpace -> Integer)
-> (Integer -> Maybe ThinSpace) -> Prism' Integer ThinSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThinSpace
ThinSpace -> Integer
8201)
(\case
Integer
8201 -> ThinSpace -> Maybe ThinSpace
forall a. a -> Maybe a
Just ThinSpace
ThinSpace
Integer
_ -> Maybe ThinSpace
forall a. Maybe a
Nothing
)
parseThinSpace ::
CharParsing p =>
p ThinSpace
parseThinSpace :: p ThinSpace
parseThinSpace =
ThinSpace
ThinSpace ThinSpace -> p Char -> p ThinSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8201') p ThinSpace -> String -> p ThinSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"thin space character"
data HairSpace = HairSpace
deriving (HairSpace -> HairSpace -> Bool
(HairSpace -> HairSpace -> Bool)
-> (HairSpace -> HairSpace -> Bool) -> Eq HairSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HairSpace -> HairSpace -> Bool
$c/= :: HairSpace -> HairSpace -> Bool
== :: HairSpace -> HairSpace -> Bool
$c== :: HairSpace -> HairSpace -> Bool
Eq, Eq HairSpace
Eq HairSpace
-> (HairSpace -> HairSpace -> Ordering)
-> (HairSpace -> HairSpace -> Bool)
-> (HairSpace -> HairSpace -> Bool)
-> (HairSpace -> HairSpace -> Bool)
-> (HairSpace -> HairSpace -> Bool)
-> (HairSpace -> HairSpace -> HairSpace)
-> (HairSpace -> HairSpace -> HairSpace)
-> Ord HairSpace
HairSpace -> HairSpace -> Bool
HairSpace -> HairSpace -> Ordering
HairSpace -> HairSpace -> HairSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HairSpace -> HairSpace -> HairSpace
$cmin :: HairSpace -> HairSpace -> HairSpace
max :: HairSpace -> HairSpace -> HairSpace
$cmax :: HairSpace -> HairSpace -> HairSpace
>= :: HairSpace -> HairSpace -> Bool
$c>= :: HairSpace -> HairSpace -> Bool
> :: HairSpace -> HairSpace -> Bool
$c> :: HairSpace -> HairSpace -> Bool
<= :: HairSpace -> HairSpace -> Bool
$c<= :: HairSpace -> HairSpace -> Bool
< :: HairSpace -> HairSpace -> Bool
$c< :: HairSpace -> HairSpace -> Bool
compare :: HairSpace -> HairSpace -> Ordering
$ccompare :: HairSpace -> HairSpace -> Ordering
$cp1Ord :: Eq HairSpace
Ord, Int -> HairSpace -> ShowS
[HairSpace] -> ShowS
HairSpace -> String
(Int -> HairSpace -> ShowS)
-> (HairSpace -> String)
-> ([HairSpace] -> ShowS)
-> Show HairSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HairSpace] -> ShowS
$cshowList :: [HairSpace] -> ShowS
show :: HairSpace -> String
$cshow :: HairSpace -> String
showsPrec :: Int -> HairSpace -> ShowS
$cshowsPrec :: Int -> HairSpace -> ShowS
Show, (forall x. HairSpace -> Rep HairSpace x)
-> (forall x. Rep HairSpace x -> HairSpace) -> Generic HairSpace
forall x. Rep HairSpace x -> HairSpace
forall x. HairSpace -> Rep HairSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HairSpace x -> HairSpace
$cfrom :: forall x. HairSpace -> Rep HairSpace x
Generic)
class HasHairSpace a where
hairSpace :: Lens' a HairSpace
instance HasHairSpace HairSpace where
hairSpace :: (HairSpace -> f HairSpace) -> HairSpace -> f HairSpace
hairSpace = (HairSpace -> f HairSpace) -> HairSpace -> f HairSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasHairSpace () where
hairSpace :: (HairSpace -> f HairSpace) -> () -> f ()
hairSpace HairSpace -> f HairSpace
f ()
x =
(HairSpace -> ()) -> f HairSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\HairSpace
HairSpace -> ()
x) (HairSpace -> f HairSpace
f HairSpace
HairSpace)
instance Semigroup HairSpace where
HairSpace
HairSpace <> :: HairSpace -> HairSpace -> HairSpace
<> HairSpace
HairSpace = HairSpace
HairSpace
instance Monoid HairSpace where
mempty :: HairSpace
mempty = HairSpace
HairSpace
class AsHairSpace a where
_HairSpace :: Prism' a HairSpace
_HairSpace' :: a
_HairSpace' = Tagged HairSpace (Identity HairSpace) -> Tagged a (Identity a)
forall a. AsHairSpace a => Prism' a HairSpace
_HairSpace (Tagged HairSpace (Identity HairSpace) -> Tagged a (Identity a))
-> HairSpace -> a
forall t b. AReview t b -> b -> t
# HairSpace
HairSpace
instance AsHairSpace HairSpace where
_HairSpace :: p HairSpace (f HairSpace) -> p HairSpace (f HairSpace)
_HairSpace = p HairSpace (f HairSpace) -> p HairSpace (f HairSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsHairSpace () where
_HairSpace :: p HairSpace (f HairSpace) -> p () (f ())
_HairSpace =
(HairSpace -> ()) -> (() -> Maybe HairSpace) -> Prism' () HairSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HairSpace
HairSpace -> ())
(\() -> HairSpace -> Maybe HairSpace
forall a. a -> Maybe a
Just HairSpace
HairSpace)
instance AsHairSpace Char where
_HairSpace :: p HairSpace (f HairSpace) -> p Char (f Char)
_HairSpace =
(HairSpace -> Char)
-> (Char -> Maybe HairSpace) -> Prism' Char HairSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HairSpace
HairSpace -> Char
'\8202')
(\case
Char
'\8202' -> HairSpace -> Maybe HairSpace
forall a. a -> Maybe a
Just HairSpace
HairSpace
Char
_ -> Maybe HairSpace
forall a. Maybe a
Nothing
)
instance AsHairSpace Int where
_HairSpace :: p HairSpace (f HairSpace) -> p Int (f Int)
_HairSpace =
(HairSpace -> Int)
-> (Int -> Maybe HairSpace) -> Prism' Int HairSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HairSpace
HairSpace -> Int
8202)
(\case
Int
8202 -> HairSpace -> Maybe HairSpace
forall a. a -> Maybe a
Just HairSpace
HairSpace
Int
_ -> Maybe HairSpace
forall a. Maybe a
Nothing
)
instance AsHairSpace Integer where
_HairSpace :: p HairSpace (f HairSpace) -> p Integer (f Integer)
_HairSpace =
(HairSpace -> Integer)
-> (Integer -> Maybe HairSpace) -> Prism' Integer HairSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HairSpace
HairSpace -> Integer
8202)
(\case
Integer
8202 -> HairSpace -> Maybe HairSpace
forall a. a -> Maybe a
Just HairSpace
HairSpace
Integer
_ -> Maybe HairSpace
forall a. Maybe a
Nothing
)
parseHairSpace ::
CharParsing p =>
p HairSpace
parseHairSpace :: p HairSpace
parseHairSpace =
HairSpace
HairSpace HairSpace -> p Char -> p HairSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8202') p HairSpace -> String -> p HairSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"hair space character"
data NarrowNoBreakSpace = NarrowNoBreakSpace
deriving (NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
(NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool)
-> (NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool)
-> Eq NarrowNoBreakSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
$c/= :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
== :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
$c== :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
Eq, Eq NarrowNoBreakSpace
Eq NarrowNoBreakSpace
-> (NarrowNoBreakSpace -> NarrowNoBreakSpace -> Ordering)
-> (NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool)
-> (NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool)
-> (NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool)
-> (NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool)
-> (NarrowNoBreakSpace -> NarrowNoBreakSpace -> NarrowNoBreakSpace)
-> (NarrowNoBreakSpace -> NarrowNoBreakSpace -> NarrowNoBreakSpace)
-> Ord NarrowNoBreakSpace
NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
NarrowNoBreakSpace -> NarrowNoBreakSpace -> Ordering
NarrowNoBreakSpace -> NarrowNoBreakSpace -> NarrowNoBreakSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> NarrowNoBreakSpace
$cmin :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> NarrowNoBreakSpace
max :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> NarrowNoBreakSpace
$cmax :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> NarrowNoBreakSpace
>= :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
$c>= :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
> :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
$c> :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
<= :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
$c<= :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
< :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
$c< :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Bool
compare :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Ordering
$ccompare :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> Ordering
$cp1Ord :: Eq NarrowNoBreakSpace
Ord, Int -> NarrowNoBreakSpace -> ShowS
[NarrowNoBreakSpace] -> ShowS
NarrowNoBreakSpace -> String
(Int -> NarrowNoBreakSpace -> ShowS)
-> (NarrowNoBreakSpace -> String)
-> ([NarrowNoBreakSpace] -> ShowS)
-> Show NarrowNoBreakSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NarrowNoBreakSpace] -> ShowS
$cshowList :: [NarrowNoBreakSpace] -> ShowS
show :: NarrowNoBreakSpace -> String
$cshow :: NarrowNoBreakSpace -> String
showsPrec :: Int -> NarrowNoBreakSpace -> ShowS
$cshowsPrec :: Int -> NarrowNoBreakSpace -> ShowS
Show, (forall x. NarrowNoBreakSpace -> Rep NarrowNoBreakSpace x)
-> (forall x. Rep NarrowNoBreakSpace x -> NarrowNoBreakSpace)
-> Generic NarrowNoBreakSpace
forall x. Rep NarrowNoBreakSpace x -> NarrowNoBreakSpace
forall x. NarrowNoBreakSpace -> Rep NarrowNoBreakSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NarrowNoBreakSpace x -> NarrowNoBreakSpace
$cfrom :: forall x. NarrowNoBreakSpace -> Rep NarrowNoBreakSpace x
Generic)
class HasNarrowNoBreakSpace a where
narrowNoBreakSpace :: Lens' a NarrowNoBreakSpace
instance HasNarrowNoBreakSpace NarrowNoBreakSpace where
narrowNoBreakSpace :: (NarrowNoBreakSpace -> f NarrowNoBreakSpace)
-> NarrowNoBreakSpace -> f NarrowNoBreakSpace
narrowNoBreakSpace = (NarrowNoBreakSpace -> f NarrowNoBreakSpace)
-> NarrowNoBreakSpace -> f NarrowNoBreakSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasNarrowNoBreakSpace () where
narrowNoBreakSpace :: (NarrowNoBreakSpace -> f NarrowNoBreakSpace) -> () -> f ()
narrowNoBreakSpace NarrowNoBreakSpace -> f NarrowNoBreakSpace
f ()
x =
(NarrowNoBreakSpace -> ()) -> f NarrowNoBreakSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\NarrowNoBreakSpace
NarrowNoBreakSpace -> ()
x) (NarrowNoBreakSpace -> f NarrowNoBreakSpace
f NarrowNoBreakSpace
NarrowNoBreakSpace)
instance Semigroup NarrowNoBreakSpace where
NarrowNoBreakSpace
NarrowNoBreakSpace <> :: NarrowNoBreakSpace -> NarrowNoBreakSpace -> NarrowNoBreakSpace
<> NarrowNoBreakSpace
NarrowNoBreakSpace = NarrowNoBreakSpace
NarrowNoBreakSpace
instance Monoid NarrowNoBreakSpace where
mempty :: NarrowNoBreakSpace
mempty = NarrowNoBreakSpace
NarrowNoBreakSpace
class AsNarrowNoBreakSpace a where
_NarrowNoBreakSpace :: Prism' a NarrowNoBreakSpace
_NarrowNoBreakSpace' :: a
_NarrowNoBreakSpace' = Tagged NarrowNoBreakSpace (Identity NarrowNoBreakSpace)
-> Tagged a (Identity a)
forall a. AsNarrowNoBreakSpace a => Prism' a NarrowNoBreakSpace
_NarrowNoBreakSpace (Tagged NarrowNoBreakSpace (Identity NarrowNoBreakSpace)
-> Tagged a (Identity a))
-> NarrowNoBreakSpace -> a
forall t b. AReview t b -> b -> t
# NarrowNoBreakSpace
NarrowNoBreakSpace
instance AsNarrowNoBreakSpace NarrowNoBreakSpace where
_NarrowNoBreakSpace :: p NarrowNoBreakSpace (f NarrowNoBreakSpace)
-> p NarrowNoBreakSpace (f NarrowNoBreakSpace)
_NarrowNoBreakSpace = p NarrowNoBreakSpace (f NarrowNoBreakSpace)
-> p NarrowNoBreakSpace (f NarrowNoBreakSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsNarrowNoBreakSpace () where
_NarrowNoBreakSpace :: p NarrowNoBreakSpace (f NarrowNoBreakSpace) -> p () (f ())
_NarrowNoBreakSpace =
(NarrowNoBreakSpace -> ())
-> (() -> Maybe NarrowNoBreakSpace) -> Prism' () NarrowNoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NarrowNoBreakSpace
NarrowNoBreakSpace -> ())
(\() -> NarrowNoBreakSpace -> Maybe NarrowNoBreakSpace
forall a. a -> Maybe a
Just NarrowNoBreakSpace
NarrowNoBreakSpace)
instance AsNarrowNoBreakSpace Char where
_NarrowNoBreakSpace :: p NarrowNoBreakSpace (f NarrowNoBreakSpace) -> p Char (f Char)
_NarrowNoBreakSpace =
(NarrowNoBreakSpace -> Char)
-> (Char -> Maybe NarrowNoBreakSpace)
-> Prism' Char NarrowNoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NarrowNoBreakSpace
NarrowNoBreakSpace -> Char
'\8239')
(\case
Char
'\8239' -> NarrowNoBreakSpace -> Maybe NarrowNoBreakSpace
forall a. a -> Maybe a
Just NarrowNoBreakSpace
NarrowNoBreakSpace
Char
_ -> Maybe NarrowNoBreakSpace
forall a. Maybe a
Nothing
)
instance AsNarrowNoBreakSpace Int where
_NarrowNoBreakSpace :: p NarrowNoBreakSpace (f NarrowNoBreakSpace) -> p Int (f Int)
_NarrowNoBreakSpace =
(NarrowNoBreakSpace -> Int)
-> (Int -> Maybe NarrowNoBreakSpace)
-> Prism' Int NarrowNoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NarrowNoBreakSpace
NarrowNoBreakSpace -> Int
8239)
(\case
Int
8239 -> NarrowNoBreakSpace -> Maybe NarrowNoBreakSpace
forall a. a -> Maybe a
Just NarrowNoBreakSpace
NarrowNoBreakSpace
Int
_ -> Maybe NarrowNoBreakSpace
forall a. Maybe a
Nothing
)
instance AsNarrowNoBreakSpace Integer where
_NarrowNoBreakSpace :: p NarrowNoBreakSpace (f NarrowNoBreakSpace)
-> p Integer (f Integer)
_NarrowNoBreakSpace =
(NarrowNoBreakSpace -> Integer)
-> (Integer -> Maybe NarrowNoBreakSpace)
-> Prism' Integer NarrowNoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NarrowNoBreakSpace
NarrowNoBreakSpace -> Integer
8239)
(\case
Integer
8239 -> NarrowNoBreakSpace -> Maybe NarrowNoBreakSpace
forall a. a -> Maybe a
Just NarrowNoBreakSpace
NarrowNoBreakSpace
Integer
_ -> Maybe NarrowNoBreakSpace
forall a. Maybe a
Nothing
)
parseNarrowNoBreakSpace ::
CharParsing p =>
p NarrowNoBreakSpace
parseNarrowNoBreakSpace :: p NarrowNoBreakSpace
parseNarrowNoBreakSpace =
NarrowNoBreakSpace
NarrowNoBreakSpace NarrowNoBreakSpace -> p Char -> p NarrowNoBreakSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8239') p NarrowNoBreakSpace -> String -> p NarrowNoBreakSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"narrow no break space character"
data MediumMathematicalSpace = MediumMathematicalSpace
deriving (MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
(MediumMathematicalSpace -> MediumMathematicalSpace -> Bool)
-> (MediumMathematicalSpace -> MediumMathematicalSpace -> Bool)
-> Eq MediumMathematicalSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
$c/= :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
== :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
$c== :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
Eq, Eq MediumMathematicalSpace
Eq MediumMathematicalSpace
-> (MediumMathematicalSpace -> MediumMathematicalSpace -> Ordering)
-> (MediumMathematicalSpace -> MediumMathematicalSpace -> Bool)
-> (MediumMathematicalSpace -> MediumMathematicalSpace -> Bool)
-> (MediumMathematicalSpace -> MediumMathematicalSpace -> Bool)
-> (MediumMathematicalSpace -> MediumMathematicalSpace -> Bool)
-> (MediumMathematicalSpace
-> MediumMathematicalSpace -> MediumMathematicalSpace)
-> (MediumMathematicalSpace
-> MediumMathematicalSpace -> MediumMathematicalSpace)
-> Ord MediumMathematicalSpace
MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
MediumMathematicalSpace -> MediumMathematicalSpace -> Ordering
MediumMathematicalSpace
-> MediumMathematicalSpace -> MediumMathematicalSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MediumMathematicalSpace
-> MediumMathematicalSpace -> MediumMathematicalSpace
$cmin :: MediumMathematicalSpace
-> MediumMathematicalSpace -> MediumMathematicalSpace
max :: MediumMathematicalSpace
-> MediumMathematicalSpace -> MediumMathematicalSpace
$cmax :: MediumMathematicalSpace
-> MediumMathematicalSpace -> MediumMathematicalSpace
>= :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
$c>= :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
> :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
$c> :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
<= :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
$c<= :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
< :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
$c< :: MediumMathematicalSpace -> MediumMathematicalSpace -> Bool
compare :: MediumMathematicalSpace -> MediumMathematicalSpace -> Ordering
$ccompare :: MediumMathematicalSpace -> MediumMathematicalSpace -> Ordering
$cp1Ord :: Eq MediumMathematicalSpace
Ord, Int -> MediumMathematicalSpace -> ShowS
[MediumMathematicalSpace] -> ShowS
MediumMathematicalSpace -> String
(Int -> MediumMathematicalSpace -> ShowS)
-> (MediumMathematicalSpace -> String)
-> ([MediumMathematicalSpace] -> ShowS)
-> Show MediumMathematicalSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediumMathematicalSpace] -> ShowS
$cshowList :: [MediumMathematicalSpace] -> ShowS
show :: MediumMathematicalSpace -> String
$cshow :: MediumMathematicalSpace -> String
showsPrec :: Int -> MediumMathematicalSpace -> ShowS
$cshowsPrec :: Int -> MediumMathematicalSpace -> ShowS
Show, (forall x.
MediumMathematicalSpace -> Rep MediumMathematicalSpace x)
-> (forall x.
Rep MediumMathematicalSpace x -> MediumMathematicalSpace)
-> Generic MediumMathematicalSpace
forall x. Rep MediumMathematicalSpace x -> MediumMathematicalSpace
forall x. MediumMathematicalSpace -> Rep MediumMathematicalSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MediumMathematicalSpace x -> MediumMathematicalSpace
$cfrom :: forall x. MediumMathematicalSpace -> Rep MediumMathematicalSpace x
Generic)
class HasMediumMathematicalSpace a where
mediumMathematicalSpace :: Lens' a MediumMathematicalSpace
instance HasMediumMathematicalSpace MediumMathematicalSpace where
mediumMathematicalSpace :: (MediumMathematicalSpace -> f MediumMathematicalSpace)
-> MediumMathematicalSpace -> f MediumMathematicalSpace
mediumMathematicalSpace = (MediumMathematicalSpace -> f MediumMathematicalSpace)
-> MediumMathematicalSpace -> f MediumMathematicalSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasMediumMathematicalSpace () where
mediumMathematicalSpace :: (MediumMathematicalSpace -> f MediumMathematicalSpace)
-> () -> f ()
mediumMathematicalSpace MediumMathematicalSpace -> f MediumMathematicalSpace
f ()
x =
(MediumMathematicalSpace -> ())
-> f MediumMathematicalSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\MediumMathematicalSpace
MediumMathematicalSpace -> ()
x) (MediumMathematicalSpace -> f MediumMathematicalSpace
f MediumMathematicalSpace
MediumMathematicalSpace)
instance Semigroup MediumMathematicalSpace where
MediumMathematicalSpace
MediumMathematicalSpace <> :: MediumMathematicalSpace
-> MediumMathematicalSpace -> MediumMathematicalSpace
<> MediumMathematicalSpace
MediumMathematicalSpace = MediumMathematicalSpace
MediumMathematicalSpace
instance Monoid MediumMathematicalSpace where
mempty :: MediumMathematicalSpace
mempty = MediumMathematicalSpace
MediumMathematicalSpace
class AsMediumMathematicalSpace a where
_MediumMathematicalSpace :: Prism' a MediumMathematicalSpace
_MediumMathematicalSpace' :: a
_MediumMathematicalSpace' = Tagged MediumMathematicalSpace (Identity MediumMathematicalSpace)
-> Tagged a (Identity a)
forall a.
AsMediumMathematicalSpace a =>
Prism' a MediumMathematicalSpace
_MediumMathematicalSpace (Tagged MediumMathematicalSpace (Identity MediumMathematicalSpace)
-> Tagged a (Identity a))
-> MediumMathematicalSpace -> a
forall t b. AReview t b -> b -> t
# MediumMathematicalSpace
MediumMathematicalSpace
instance AsMediumMathematicalSpace MediumMathematicalSpace where
_MediumMathematicalSpace :: p MediumMathematicalSpace (f MediumMathematicalSpace)
-> p MediumMathematicalSpace (f MediumMathematicalSpace)
_MediumMathematicalSpace = p MediumMathematicalSpace (f MediumMathematicalSpace)
-> p MediumMathematicalSpace (f MediumMathematicalSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsMediumMathematicalSpace () where
_MediumMathematicalSpace :: p MediumMathematicalSpace (f MediumMathematicalSpace)
-> p () (f ())
_MediumMathematicalSpace =
(MediumMathematicalSpace -> ())
-> (() -> Maybe MediumMathematicalSpace)
-> Prism' () MediumMathematicalSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\MediumMathematicalSpace
MediumMathematicalSpace -> ())
(\() -> MediumMathematicalSpace -> Maybe MediumMathematicalSpace
forall a. a -> Maybe a
Just MediumMathematicalSpace
MediumMathematicalSpace)
instance AsMediumMathematicalSpace Char where
_MediumMathematicalSpace :: p MediumMathematicalSpace (f MediumMathematicalSpace)
-> p Char (f Char)
_MediumMathematicalSpace =
(MediumMathematicalSpace -> Char)
-> (Char -> Maybe MediumMathematicalSpace)
-> Prism' Char MediumMathematicalSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\MediumMathematicalSpace
MediumMathematicalSpace -> Char
'\8287')
(\case
Char
'\8287' -> MediumMathematicalSpace -> Maybe MediumMathematicalSpace
forall a. a -> Maybe a
Just MediumMathematicalSpace
MediumMathematicalSpace
Char
_ -> Maybe MediumMathematicalSpace
forall a. Maybe a
Nothing
)
instance AsMediumMathematicalSpace Int where
_MediumMathematicalSpace :: p MediumMathematicalSpace (f MediumMathematicalSpace)
-> p Int (f Int)
_MediumMathematicalSpace =
(MediumMathematicalSpace -> Int)
-> (Int -> Maybe MediumMathematicalSpace)
-> Prism' Int MediumMathematicalSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\MediumMathematicalSpace
MediumMathematicalSpace -> Int
8287)
(\case
Int
8287 -> MediumMathematicalSpace -> Maybe MediumMathematicalSpace
forall a. a -> Maybe a
Just MediumMathematicalSpace
MediumMathematicalSpace
Int
_ -> Maybe MediumMathematicalSpace
forall a. Maybe a
Nothing
)
instance AsMediumMathematicalSpace Integer where
_MediumMathematicalSpace :: p MediumMathematicalSpace (f MediumMathematicalSpace)
-> p Integer (f Integer)
_MediumMathematicalSpace =
(MediumMathematicalSpace -> Integer)
-> (Integer -> Maybe MediumMathematicalSpace)
-> Prism' Integer MediumMathematicalSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\MediumMathematicalSpace
MediumMathematicalSpace -> Integer
8287)
(\case
Integer
8287 -> MediumMathematicalSpace -> Maybe MediumMathematicalSpace
forall a. a -> Maybe a
Just MediumMathematicalSpace
MediumMathematicalSpace
Integer
_ -> Maybe MediumMathematicalSpace
forall a. Maybe a
Nothing
)
parseMediumMathematicalSpace ::
CharParsing p =>
p MediumMathematicalSpace
parseMediumMathematicalSpace :: p MediumMathematicalSpace
parseMediumMathematicalSpace =
MediumMathematicalSpace
MediumMathematicalSpace MediumMathematicalSpace -> p Char -> p MediumMathematicalSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\8287') p MediumMathematicalSpace -> String -> p MediumMathematicalSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"medium mathematical space character"
data IdeographicSpace = IdeographicSpace
deriving (IdeographicSpace -> IdeographicSpace -> Bool
(IdeographicSpace -> IdeographicSpace -> Bool)
-> (IdeographicSpace -> IdeographicSpace -> Bool)
-> Eq IdeographicSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IdeographicSpace -> IdeographicSpace -> Bool
$c/= :: IdeographicSpace -> IdeographicSpace -> Bool
== :: IdeographicSpace -> IdeographicSpace -> Bool
$c== :: IdeographicSpace -> IdeographicSpace -> Bool
Eq, Eq IdeographicSpace
Eq IdeographicSpace
-> (IdeographicSpace -> IdeographicSpace -> Ordering)
-> (IdeographicSpace -> IdeographicSpace -> Bool)
-> (IdeographicSpace -> IdeographicSpace -> Bool)
-> (IdeographicSpace -> IdeographicSpace -> Bool)
-> (IdeographicSpace -> IdeographicSpace -> Bool)
-> (IdeographicSpace -> IdeographicSpace -> IdeographicSpace)
-> (IdeographicSpace -> IdeographicSpace -> IdeographicSpace)
-> Ord IdeographicSpace
IdeographicSpace -> IdeographicSpace -> Bool
IdeographicSpace -> IdeographicSpace -> Ordering
IdeographicSpace -> IdeographicSpace -> IdeographicSpace
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IdeographicSpace -> IdeographicSpace -> IdeographicSpace
$cmin :: IdeographicSpace -> IdeographicSpace -> IdeographicSpace
max :: IdeographicSpace -> IdeographicSpace -> IdeographicSpace
$cmax :: IdeographicSpace -> IdeographicSpace -> IdeographicSpace
>= :: IdeographicSpace -> IdeographicSpace -> Bool
$c>= :: IdeographicSpace -> IdeographicSpace -> Bool
> :: IdeographicSpace -> IdeographicSpace -> Bool
$c> :: IdeographicSpace -> IdeographicSpace -> Bool
<= :: IdeographicSpace -> IdeographicSpace -> Bool
$c<= :: IdeographicSpace -> IdeographicSpace -> Bool
< :: IdeographicSpace -> IdeographicSpace -> Bool
$c< :: IdeographicSpace -> IdeographicSpace -> Bool
compare :: IdeographicSpace -> IdeographicSpace -> Ordering
$ccompare :: IdeographicSpace -> IdeographicSpace -> Ordering
$cp1Ord :: Eq IdeographicSpace
Ord, Int -> IdeographicSpace -> ShowS
[IdeographicSpace] -> ShowS
IdeographicSpace -> String
(Int -> IdeographicSpace -> ShowS)
-> (IdeographicSpace -> String)
-> ([IdeographicSpace] -> ShowS)
-> Show IdeographicSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IdeographicSpace] -> ShowS
$cshowList :: [IdeographicSpace] -> ShowS
show :: IdeographicSpace -> String
$cshow :: IdeographicSpace -> String
showsPrec :: Int -> IdeographicSpace -> ShowS
$cshowsPrec :: Int -> IdeographicSpace -> ShowS
Show, (forall x. IdeographicSpace -> Rep IdeographicSpace x)
-> (forall x. Rep IdeographicSpace x -> IdeographicSpace)
-> Generic IdeographicSpace
forall x. Rep IdeographicSpace x -> IdeographicSpace
forall x. IdeographicSpace -> Rep IdeographicSpace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IdeographicSpace x -> IdeographicSpace
$cfrom :: forall x. IdeographicSpace -> Rep IdeographicSpace x
Generic)
class HasIdeographicSpace a where
ideographicSpace :: Lens' a IdeographicSpace
instance HasIdeographicSpace IdeographicSpace where
ideographicSpace :: (IdeographicSpace -> f IdeographicSpace)
-> IdeographicSpace -> f IdeographicSpace
ideographicSpace = (IdeographicSpace -> f IdeographicSpace)
-> IdeographicSpace -> f IdeographicSpace
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance HasIdeographicSpace () where
ideographicSpace :: (IdeographicSpace -> f IdeographicSpace) -> () -> f ()
ideographicSpace IdeographicSpace -> f IdeographicSpace
f ()
x =
(IdeographicSpace -> ()) -> f IdeographicSpace -> f ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\IdeographicSpace
IdeographicSpace -> ()
x) (IdeographicSpace -> f IdeographicSpace
f IdeographicSpace
IdeographicSpace)
instance Semigroup IdeographicSpace where
IdeographicSpace
IdeographicSpace <> :: IdeographicSpace -> IdeographicSpace -> IdeographicSpace
<> IdeographicSpace
IdeographicSpace = IdeographicSpace
IdeographicSpace
instance Monoid IdeographicSpace where
mempty :: IdeographicSpace
mempty = IdeographicSpace
IdeographicSpace
class AsIdeographicSpace a where
_IdeographicSpace :: Prism' a IdeographicSpace
_IdeographicSpace' :: a
_IdeographicSpace' = Tagged IdeographicSpace (Identity IdeographicSpace)
-> Tagged a (Identity a)
forall a. AsIdeographicSpace a => Prism' a IdeographicSpace
_IdeographicSpace (Tagged IdeographicSpace (Identity IdeographicSpace)
-> Tagged a (Identity a))
-> IdeographicSpace -> a
forall t b. AReview t b -> b -> t
# IdeographicSpace
IdeographicSpace
instance AsIdeographicSpace IdeographicSpace where
_IdeographicSpace :: p IdeographicSpace (f IdeographicSpace)
-> p IdeographicSpace (f IdeographicSpace)
_IdeographicSpace = p IdeographicSpace (f IdeographicSpace)
-> p IdeographicSpace (f IdeographicSpace)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsIdeographicSpace () where
_IdeographicSpace :: p IdeographicSpace (f IdeographicSpace) -> p () (f ())
_IdeographicSpace =
(IdeographicSpace -> ())
-> (() -> Maybe IdeographicSpace) -> Prism' () IdeographicSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\IdeographicSpace
IdeographicSpace -> ())
(\() -> IdeographicSpace -> Maybe IdeographicSpace
forall a. a -> Maybe a
Just IdeographicSpace
IdeographicSpace)
instance AsIdeographicSpace Char where
_IdeographicSpace :: p IdeographicSpace (f IdeographicSpace) -> p Char (f Char)
_IdeographicSpace =
(IdeographicSpace -> Char)
-> (Char -> Maybe IdeographicSpace) -> Prism' Char IdeographicSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\IdeographicSpace
IdeographicSpace -> Char
'\12288')
(\case
Char
'\12288' -> IdeographicSpace -> Maybe IdeographicSpace
forall a. a -> Maybe a
Just IdeographicSpace
IdeographicSpace
Char
_ -> Maybe IdeographicSpace
forall a. Maybe a
Nothing
)
instance AsIdeographicSpace Int where
_IdeographicSpace :: p IdeographicSpace (f IdeographicSpace) -> p Int (f Int)
_IdeographicSpace =
(IdeographicSpace -> Int)
-> (Int -> Maybe IdeographicSpace) -> Prism' Int IdeographicSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\IdeographicSpace
IdeographicSpace -> Int
12288)
(\case
Int
12288 -> IdeographicSpace -> Maybe IdeographicSpace
forall a. a -> Maybe a
Just IdeographicSpace
IdeographicSpace
Int
_ -> Maybe IdeographicSpace
forall a. Maybe a
Nothing
)
instance AsIdeographicSpace Integer where
_IdeographicSpace :: p IdeographicSpace (f IdeographicSpace) -> p Integer (f Integer)
_IdeographicSpace =
(IdeographicSpace -> Integer)
-> (Integer -> Maybe IdeographicSpace)
-> Prism' Integer IdeographicSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\IdeographicSpace
IdeographicSpace -> Integer
12288)
(\case
Integer
12288 -> IdeographicSpace -> Maybe IdeographicSpace
forall a. a -> Maybe a
Just IdeographicSpace
IdeographicSpace
Integer
_ -> Maybe IdeographicSpace
forall a. Maybe a
Nothing
)
parseIdeographicSpace ::
CharParsing p =>
p IdeographicSpace
parseIdeographicSpace :: p IdeographicSpace
parseIdeographicSpace =
IdeographicSpace
IdeographicSpace IdeographicSpace -> p Char -> p IdeographicSpace
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Char -> Bool) -> p Char
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\12288') p IdeographicSpace -> String -> p IdeographicSpace
forall (m :: * -> *) a. Parsing m => m a -> String -> m a
<?> String
"ideographic space character"
data SpaceChar =
HorizontalTab_
| LineFeed_
| VerticalTab_
| FormFeed_
| CarriageReturn_
| Whitespace_
| NoBreakSpace_
| OghamSpaceMark_
| EnQuad_
| EmQuad_
| EnSpace_
| EmSpace_
| ThreePerEmSpace_
| FourPerEmSpace_
| SixPerEmSpace_
| FigureSpace_
| PunctuationSpace_
| ThinSpace_
| HairSpace_
| NarrowNoBreakSpace_
| MediumMathematicalSpace_
| IdeographicSpace_
deriving (SpaceChar -> SpaceChar -> Bool
(SpaceChar -> SpaceChar -> Bool)
-> (SpaceChar -> SpaceChar -> Bool) -> Eq SpaceChar
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpaceChar -> SpaceChar -> Bool
$c/= :: SpaceChar -> SpaceChar -> Bool
== :: SpaceChar -> SpaceChar -> Bool
$c== :: SpaceChar -> SpaceChar -> Bool
Eq, Eq SpaceChar
Eq SpaceChar
-> (SpaceChar -> SpaceChar -> Ordering)
-> (SpaceChar -> SpaceChar -> Bool)
-> (SpaceChar -> SpaceChar -> Bool)
-> (SpaceChar -> SpaceChar -> Bool)
-> (SpaceChar -> SpaceChar -> Bool)
-> (SpaceChar -> SpaceChar -> SpaceChar)
-> (SpaceChar -> SpaceChar -> SpaceChar)
-> Ord SpaceChar
SpaceChar -> SpaceChar -> Bool
SpaceChar -> SpaceChar -> Ordering
SpaceChar -> SpaceChar -> SpaceChar
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SpaceChar -> SpaceChar -> SpaceChar
$cmin :: SpaceChar -> SpaceChar -> SpaceChar
max :: SpaceChar -> SpaceChar -> SpaceChar
$cmax :: SpaceChar -> SpaceChar -> SpaceChar
>= :: SpaceChar -> SpaceChar -> Bool
$c>= :: SpaceChar -> SpaceChar -> Bool
> :: SpaceChar -> SpaceChar -> Bool
$c> :: SpaceChar -> SpaceChar -> Bool
<= :: SpaceChar -> SpaceChar -> Bool
$c<= :: SpaceChar -> SpaceChar -> Bool
< :: SpaceChar -> SpaceChar -> Bool
$c< :: SpaceChar -> SpaceChar -> Bool
compare :: SpaceChar -> SpaceChar -> Ordering
$ccompare :: SpaceChar -> SpaceChar -> Ordering
$cp1Ord :: Eq SpaceChar
Ord, Int -> SpaceChar -> ShowS
[SpaceChar] -> ShowS
SpaceChar -> String
(Int -> SpaceChar -> ShowS)
-> (SpaceChar -> String)
-> ([SpaceChar] -> ShowS)
-> Show SpaceChar
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpaceChar] -> ShowS
$cshowList :: [SpaceChar] -> ShowS
show :: SpaceChar -> String
$cshow :: SpaceChar -> String
showsPrec :: Int -> SpaceChar -> ShowS
$cshowsPrec :: Int -> SpaceChar -> ShowS
Show, (forall x. SpaceChar -> Rep SpaceChar x)
-> (forall x. Rep SpaceChar x -> SpaceChar) -> Generic SpaceChar
forall x. Rep SpaceChar x -> SpaceChar
forall x. SpaceChar -> Rep SpaceChar x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SpaceChar x -> SpaceChar
$cfrom :: forall x. SpaceChar -> Rep SpaceChar x
Generic)
class HasSpaceChar a where
spaceChar :: Lens' a SpaceChar
instance HasSpaceChar SpaceChar where
spaceChar :: (SpaceChar -> f SpaceChar) -> SpaceChar -> f SpaceChar
spaceChar = (SpaceChar -> f SpaceChar) -> SpaceChar -> f SpaceChar
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
class AsSpaceChar a where
_SpaceChar :: Prism' a SpaceChar
instance AsSpaceChar SpaceChar where
_SpaceChar :: p SpaceChar (f SpaceChar) -> p SpaceChar (f SpaceChar)
_SpaceChar = p SpaceChar (f SpaceChar) -> p SpaceChar (f SpaceChar)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance AsSpaceChar Char where
_SpaceChar :: p SpaceChar (f SpaceChar) -> p Char (f Char)
_SpaceChar =
(SpaceChar -> Char)
-> (Char -> Maybe SpaceChar) -> Prism' Char SpaceChar
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\case
SpaceChar
HorizontalTab_ ->
Char
'\9'
SpaceChar
LineFeed_ ->
Char
'\10'
SpaceChar
VerticalTab_ ->
Char
'\11'
SpaceChar
FormFeed_ ->
Char
'\12'
SpaceChar
CarriageReturn_ ->
Char
'\13'
SpaceChar
Whitespace_ ->
Char
'\32'
SpaceChar
NoBreakSpace_ ->
Char
'\160'
SpaceChar
OghamSpaceMark_ ->
Char
'\5760'
SpaceChar
EnQuad_ ->
Char
'\8192'
SpaceChar
EmQuad_ ->
Char
'\8193'
SpaceChar
EnSpace_ ->
Char
'\8194'
SpaceChar
EmSpace_ ->
Char
'\8195'
SpaceChar
ThreePerEmSpace_ ->
Char
'\8196'
SpaceChar
FourPerEmSpace_ ->
Char
'\8197'
SpaceChar
SixPerEmSpace_ ->
Char
'\8198'
SpaceChar
FigureSpace_ ->
Char
'\8199'
SpaceChar
PunctuationSpace_ ->
Char
'\8200'
SpaceChar
ThinSpace_ ->
Char
'\8201'
SpaceChar
HairSpace_ ->
Char
'\8202'
SpaceChar
NarrowNoBreakSpace_ ->
Char
'\8239'
SpaceChar
MediumMathematicalSpace_ ->
Char
'\8287'
SpaceChar
IdeographicSpace_ ->
Char
'\12288'
)
(\case
Char
'\9' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
HorizontalTab_
Char
'\10' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
LineFeed_
Char
'\11' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
VerticalTab_
Char
'\12' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
FormFeed_
Char
'\13' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
CarriageReturn_
Char
'\32' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
Whitespace_
Char
'\160' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
NoBreakSpace_
Char
'\5760' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
OghamSpaceMark_
Char
'\8192' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
EnQuad_
Char
'\8193' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
EmQuad_
Char
'\8194' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
EnSpace_
Char
'\8195' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
EmSpace_
Char
'\8196' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
ThreePerEmSpace_
Char
'\8197' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
FourPerEmSpace_
Char
'\8198' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
SixPerEmSpace_
Char
'\8199' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
FigureSpace_
Char
'\8200' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
PunctuationSpace_
Char
'\8201' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
ThinSpace_
Char
'\8202' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
HairSpace_
Char
'\8239' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
NarrowNoBreakSpace_
Char
'\8287' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
MediumMathematicalSpace_
Char
'\12288' ->
SpaceChar -> Maybe SpaceChar
forall a. a -> Maybe a
Just SpaceChar
IdeographicSpace_
Char
_ ->
Maybe SpaceChar
forall a. Maybe a
Nothing
)
parseSpaceChar ::
CharParsing p =>
p SpaceChar
parseSpaceChar :: p SpaceChar
parseSpaceChar =
[p SpaceChar] -> p SpaceChar
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [
SpaceChar
HorizontalTab_ SpaceChar -> p HorizontalTab -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p HorizontalTab
forall (p :: * -> *). CharParsing p => p HorizontalTab
parseHorizontalTab
, SpaceChar
LineFeed_ SpaceChar -> p LineFeed -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p LineFeed
forall (p :: * -> *). CharParsing p => p LineFeed
parseLineFeed
, SpaceChar
VerticalTab_ SpaceChar -> p VerticalTab -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p VerticalTab
forall (p :: * -> *). CharParsing p => p VerticalTab
parseVerticalTab
, SpaceChar
FormFeed_ SpaceChar -> p FormFeed -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p FormFeed
forall (p :: * -> *). CharParsing p => p FormFeed
parseFormFeed
, SpaceChar
CarriageReturn_ SpaceChar -> p CarriageReturn -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p CarriageReturn
forall (p :: * -> *). CharParsing p => p CarriageReturn
parseCarriageReturn
, SpaceChar
Whitespace_ SpaceChar -> p Whitespace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p Whitespace
forall (p :: * -> *). CharParsing p => p Whitespace
parseWhitespace
, SpaceChar
NoBreakSpace_ SpaceChar -> p NoBreakSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p NoBreakSpace
forall (p :: * -> *). CharParsing p => p NoBreakSpace
parseNoBreakSpace
, SpaceChar
OghamSpaceMark_ SpaceChar -> p OghamSpaceMark -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p OghamSpaceMark
forall (p :: * -> *). CharParsing p => p OghamSpaceMark
parseOghamSpaceMark
, SpaceChar
EnQuad_ SpaceChar -> p EnQuad -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p EnQuad
forall (p :: * -> *). CharParsing p => p EnQuad
parseEnQuad
, SpaceChar
EmQuad_ SpaceChar -> p EmQuad -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p EmQuad
forall (p :: * -> *). CharParsing p => p EmQuad
parseEmQuad
, SpaceChar
EnSpace_ SpaceChar -> p EnSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p EnSpace
forall (p :: * -> *). CharParsing p => p EnSpace
parseEnSpace
, SpaceChar
EmSpace_ SpaceChar -> p EmSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p EmSpace
forall (p :: * -> *). CharParsing p => p EmSpace
parseEmSpace
, SpaceChar
ThreePerEmSpace_ SpaceChar -> p ThreePerEmSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p ThreePerEmSpace
forall (p :: * -> *). CharParsing p => p ThreePerEmSpace
parseThreePerEmSpace
, SpaceChar
FourPerEmSpace_ SpaceChar -> p FourPerEmSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p FourPerEmSpace
forall (p :: * -> *). CharParsing p => p FourPerEmSpace
parseFourPerEmSpace
, SpaceChar
SixPerEmSpace_ SpaceChar -> p SixPerEmSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p SixPerEmSpace
forall (p :: * -> *). CharParsing p => p SixPerEmSpace
parseSixPerEmSpace
, SpaceChar
FigureSpace_ SpaceChar -> p FigureSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p FigureSpace
forall (p :: * -> *). CharParsing p => p FigureSpace
parseFigureSpace
, SpaceChar
PunctuationSpace_ SpaceChar -> p PunctuationSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p PunctuationSpace
forall (p :: * -> *). CharParsing p => p PunctuationSpace
parsePunctuationSpace
, SpaceChar
ThinSpace_ SpaceChar -> p ThinSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p ThinSpace
forall (p :: * -> *). CharParsing p => p ThinSpace
parseThinSpace
, SpaceChar
HairSpace_ SpaceChar -> p HairSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p HairSpace
forall (p :: * -> *). CharParsing p => p HairSpace
parseHairSpace
, SpaceChar
NarrowNoBreakSpace_ SpaceChar -> p NarrowNoBreakSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p NarrowNoBreakSpace
forall (p :: * -> *). CharParsing p => p NarrowNoBreakSpace
parseNarrowNoBreakSpace
, SpaceChar
MediumMathematicalSpace_ SpaceChar -> p MediumMathematicalSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p MediumMathematicalSpace
forall (p :: * -> *). CharParsing p => p MediumMathematicalSpace
parseMediumMathematicalSpace
, SpaceChar
IdeographicSpace_ SpaceChar -> p IdeographicSpace -> p SpaceChar
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p IdeographicSpace
forall (p :: * -> *). CharParsing p => p IdeographicSpace
parseIdeographicSpace
]
instance AsHorizontalTab SpaceChar where
_HorizontalTab :: p HorizontalTab (f HorizontalTab) -> p SpaceChar (f SpaceChar)
_HorizontalTab =
(HorizontalTab -> SpaceChar)
-> (SpaceChar -> Maybe HorizontalTab)
-> Prism' SpaceChar HorizontalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HorizontalTab
HorizontalTab -> SpaceChar
HorizontalTab_)
(\case
SpaceChar
HorizontalTab_ -> HorizontalTab -> Maybe HorizontalTab
forall a. a -> Maybe a
Just HorizontalTab
HorizontalTab
SpaceChar
_ -> Maybe HorizontalTab
forall a. Maybe a
Nothing
)
instance AsLineFeed SpaceChar where
_LineFeed :: p LineFeed (f LineFeed) -> p SpaceChar (f SpaceChar)
_LineFeed =
(LineFeed -> SpaceChar)
-> (SpaceChar -> Maybe LineFeed) -> Prism' SpaceChar LineFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\LineFeed
LineFeed -> SpaceChar
LineFeed_)
(\case
SpaceChar
LineFeed_ -> LineFeed -> Maybe LineFeed
forall a. a -> Maybe a
Just LineFeed
LineFeed
SpaceChar
_ -> Maybe LineFeed
forall a. Maybe a
Nothing
)
instance AsVerticalTab SpaceChar where
_VerticalTab :: p VerticalTab (f VerticalTab) -> p SpaceChar (f SpaceChar)
_VerticalTab =
(VerticalTab -> SpaceChar)
-> (SpaceChar -> Maybe VerticalTab) -> Prism' SpaceChar VerticalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\VerticalTab
VerticalTab -> SpaceChar
VerticalTab_)
(\case
SpaceChar
VerticalTab_ -> VerticalTab -> Maybe VerticalTab
forall a. a -> Maybe a
Just VerticalTab
VerticalTab
SpaceChar
_ -> Maybe VerticalTab
forall a. Maybe a
Nothing
)
instance AsFormFeed SpaceChar where
_FormFeed :: p FormFeed (f FormFeed) -> p SpaceChar (f SpaceChar)
_FormFeed =
(FormFeed -> SpaceChar)
-> (SpaceChar -> Maybe FormFeed) -> Prism' SpaceChar FormFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FormFeed
FormFeed -> SpaceChar
FormFeed_)
(\case
SpaceChar
FormFeed_ -> FormFeed -> Maybe FormFeed
forall a. a -> Maybe a
Just FormFeed
FormFeed
SpaceChar
_ -> Maybe FormFeed
forall a. Maybe a
Nothing
)
instance AsCarriageReturn SpaceChar where
_CarriageReturn :: p CarriageReturn (f CarriageReturn) -> p SpaceChar (f SpaceChar)
_CarriageReturn =
(CarriageReturn -> SpaceChar)
-> (SpaceChar -> Maybe CarriageReturn)
-> Prism' SpaceChar CarriageReturn
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\CarriageReturn
CarriageReturn -> SpaceChar
CarriageReturn_)
(\case
SpaceChar
CarriageReturn_ -> CarriageReturn -> Maybe CarriageReturn
forall a. a -> Maybe a
Just CarriageReturn
CarriageReturn
SpaceChar
_ -> Maybe CarriageReturn
forall a. Maybe a
Nothing
)
instance AsWhitespace SpaceChar where
_Whitespace :: p Whitespace (f Whitespace) -> p SpaceChar (f SpaceChar)
_Whitespace =
(Whitespace -> SpaceChar)
-> (SpaceChar -> Maybe Whitespace) -> Prism' SpaceChar Whitespace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\Whitespace
Whitespace -> SpaceChar
Whitespace_)
(\case
SpaceChar
Whitespace_ -> Whitespace -> Maybe Whitespace
forall a. a -> Maybe a
Just Whitespace
Whitespace
SpaceChar
_ -> Maybe Whitespace
forall a. Maybe a
Nothing
)
instance AsNoBreakSpace SpaceChar where
_NoBreakSpace :: p NoBreakSpace (f NoBreakSpace) -> p SpaceChar (f SpaceChar)
_NoBreakSpace =
(NoBreakSpace -> SpaceChar)
-> (SpaceChar -> Maybe NoBreakSpace)
-> Prism' SpaceChar NoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NoBreakSpace
NoBreakSpace -> SpaceChar
NoBreakSpace_)
(\case
SpaceChar
NoBreakSpace_ -> NoBreakSpace -> Maybe NoBreakSpace
forall a. a -> Maybe a
Just NoBreakSpace
NoBreakSpace
SpaceChar
_ -> Maybe NoBreakSpace
forall a. Maybe a
Nothing
)
instance AsOghamSpaceMark SpaceChar where
_OghamSpaceMark :: p OghamSpaceMark (f OghamSpaceMark) -> p SpaceChar (f SpaceChar)
_OghamSpaceMark =
(OghamSpaceMark -> SpaceChar)
-> (SpaceChar -> Maybe OghamSpaceMark)
-> Prism' SpaceChar OghamSpaceMark
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\OghamSpaceMark
OghamSpaceMark -> SpaceChar
OghamSpaceMark_)
(\case
SpaceChar
OghamSpaceMark_ -> OghamSpaceMark -> Maybe OghamSpaceMark
forall a. a -> Maybe a
Just OghamSpaceMark
OghamSpaceMark
SpaceChar
_ -> Maybe OghamSpaceMark
forall a. Maybe a
Nothing
)
instance AsEnQuad SpaceChar where
_EnQuad :: p EnQuad (f EnQuad) -> p SpaceChar (f SpaceChar)
_EnQuad =
(EnQuad -> SpaceChar)
-> (SpaceChar -> Maybe EnQuad) -> Prism' SpaceChar EnQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnQuad
EnQuad -> SpaceChar
EnQuad_)
(\case
SpaceChar
EnQuad_ -> EnQuad -> Maybe EnQuad
forall a. a -> Maybe a
Just EnQuad
EnQuad
SpaceChar
_ -> Maybe EnQuad
forall a. Maybe a
Nothing
)
instance AsEmQuad SpaceChar where
_EmQuad :: p EmQuad (f EmQuad) -> p SpaceChar (f SpaceChar)
_EmQuad =
(EmQuad -> SpaceChar)
-> (SpaceChar -> Maybe EmQuad) -> Prism' SpaceChar EmQuad
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmQuad
EmQuad -> SpaceChar
EmQuad_)
(\case
SpaceChar
EmQuad_ -> EmQuad -> Maybe EmQuad
forall a. a -> Maybe a
Just EmQuad
EmQuad
SpaceChar
_ -> Maybe EmQuad
forall a. Maybe a
Nothing
)
instance AsEnSpace SpaceChar where
_EnSpace :: p EnSpace (f EnSpace) -> p SpaceChar (f SpaceChar)
_EnSpace =
(EnSpace -> SpaceChar)
-> (SpaceChar -> Maybe EnSpace) -> Prism' SpaceChar EnSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EnSpace
EnSpace -> SpaceChar
EnSpace_)
(\case
SpaceChar
EnSpace_ -> EnSpace -> Maybe EnSpace
forall a. a -> Maybe a
Just EnSpace
EnSpace
SpaceChar
_ -> Maybe EnSpace
forall a. Maybe a
Nothing
)
instance AsEmSpace SpaceChar where
_EmSpace :: p EmSpace (f EmSpace) -> p SpaceChar (f SpaceChar)
_EmSpace =
(EmSpace -> SpaceChar)
-> (SpaceChar -> Maybe EmSpace) -> Prism' SpaceChar EmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\EmSpace
EmSpace -> SpaceChar
EmSpace_)
(\case
SpaceChar
EmSpace_ -> EmSpace -> Maybe EmSpace
forall a. a -> Maybe a
Just EmSpace
EmSpace
SpaceChar
_ -> Maybe EmSpace
forall a. Maybe a
Nothing
)
instance AsThreePerEmSpace SpaceChar where
_ThreePerEmSpace :: p ThreePerEmSpace (f ThreePerEmSpace) -> p SpaceChar (f SpaceChar)
_ThreePerEmSpace =
(ThreePerEmSpace -> SpaceChar)
-> (SpaceChar -> Maybe ThreePerEmSpace)
-> Prism' SpaceChar ThreePerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThreePerEmSpace
ThreePerEmSpace -> SpaceChar
ThreePerEmSpace_)
(\case
SpaceChar
ThreePerEmSpace_ -> ThreePerEmSpace -> Maybe ThreePerEmSpace
forall a. a -> Maybe a
Just ThreePerEmSpace
ThreePerEmSpace
SpaceChar
_ -> Maybe ThreePerEmSpace
forall a. Maybe a
Nothing
)
instance AsFourPerEmSpace SpaceChar where
_FourPerEmSpace :: p FourPerEmSpace (f FourPerEmSpace) -> p SpaceChar (f SpaceChar)
_FourPerEmSpace =
(FourPerEmSpace -> SpaceChar)
-> (SpaceChar -> Maybe FourPerEmSpace)
-> Prism' SpaceChar FourPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FourPerEmSpace
FourPerEmSpace -> SpaceChar
FourPerEmSpace_)
(\case
SpaceChar
FourPerEmSpace_ -> FourPerEmSpace -> Maybe FourPerEmSpace
forall a. a -> Maybe a
Just FourPerEmSpace
FourPerEmSpace
SpaceChar
_ -> Maybe FourPerEmSpace
forall a. Maybe a
Nothing
)
instance AsSixPerEmSpace SpaceChar where
_SixPerEmSpace :: p SixPerEmSpace (f SixPerEmSpace) -> p SpaceChar (f SpaceChar)
_SixPerEmSpace =
(SixPerEmSpace -> SpaceChar)
-> (SpaceChar -> Maybe SixPerEmSpace)
-> Prism' SpaceChar SixPerEmSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\SixPerEmSpace
SixPerEmSpace -> SpaceChar
SixPerEmSpace_)
(\case
SpaceChar
SixPerEmSpace_ -> SixPerEmSpace -> Maybe SixPerEmSpace
forall a. a -> Maybe a
Just SixPerEmSpace
SixPerEmSpace
SpaceChar
_ -> Maybe SixPerEmSpace
forall a. Maybe a
Nothing
)
instance AsFigureSpace SpaceChar where
_FigureSpace :: p FigureSpace (f FigureSpace) -> p SpaceChar (f SpaceChar)
_FigureSpace =
(FigureSpace -> SpaceChar)
-> (SpaceChar -> Maybe FigureSpace) -> Prism' SpaceChar FigureSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FigureSpace
FigureSpace -> SpaceChar
FigureSpace_)
(\case
SpaceChar
FigureSpace_ -> FigureSpace -> Maybe FigureSpace
forall a. a -> Maybe a
Just FigureSpace
FigureSpace
SpaceChar
_ -> Maybe FigureSpace
forall a. Maybe a
Nothing
)
instance AsPunctuationSpace SpaceChar where
_PunctuationSpace :: p PunctuationSpace (f PunctuationSpace)
-> p SpaceChar (f SpaceChar)
_PunctuationSpace =
(PunctuationSpace -> SpaceChar)
-> (SpaceChar -> Maybe PunctuationSpace)
-> Prism' SpaceChar PunctuationSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\PunctuationSpace
PunctuationSpace -> SpaceChar
PunctuationSpace_)
(\case
SpaceChar
PunctuationSpace_ -> PunctuationSpace -> Maybe PunctuationSpace
forall a. a -> Maybe a
Just PunctuationSpace
PunctuationSpace
SpaceChar
_ -> Maybe PunctuationSpace
forall a. Maybe a
Nothing
)
instance AsThinSpace SpaceChar where
_ThinSpace :: p ThinSpace (f ThinSpace) -> p SpaceChar (f SpaceChar)
_ThinSpace =
(ThinSpace -> SpaceChar)
-> (SpaceChar -> Maybe ThinSpace) -> Prism' SpaceChar ThinSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\ThinSpace
ThinSpace -> SpaceChar
ThinSpace_)
(\case
SpaceChar
ThinSpace_ -> ThinSpace -> Maybe ThinSpace
forall a. a -> Maybe a
Just ThinSpace
ThinSpace
SpaceChar
_ -> Maybe ThinSpace
forall a. Maybe a
Nothing
)
instance AsHairSpace SpaceChar where
_HairSpace :: p HairSpace (f HairSpace) -> p SpaceChar (f SpaceChar)
_HairSpace =
(HairSpace -> SpaceChar)
-> (SpaceChar -> Maybe HairSpace) -> Prism' SpaceChar HairSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HairSpace
HairSpace -> SpaceChar
HairSpace_)
(\case
SpaceChar
HairSpace_ -> HairSpace -> Maybe HairSpace
forall a. a -> Maybe a
Just HairSpace
HairSpace
SpaceChar
_ -> Maybe HairSpace
forall a. Maybe a
Nothing
)
instance AsNarrowNoBreakSpace SpaceChar where
_NarrowNoBreakSpace :: p NarrowNoBreakSpace (f NarrowNoBreakSpace)
-> p SpaceChar (f SpaceChar)
_NarrowNoBreakSpace =
(NarrowNoBreakSpace -> SpaceChar)
-> (SpaceChar -> Maybe NarrowNoBreakSpace)
-> Prism' SpaceChar NarrowNoBreakSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\NarrowNoBreakSpace
NarrowNoBreakSpace -> SpaceChar
NarrowNoBreakSpace_)
(\case
SpaceChar
NarrowNoBreakSpace_ -> NarrowNoBreakSpace -> Maybe NarrowNoBreakSpace
forall a. a -> Maybe a
Just NarrowNoBreakSpace
NarrowNoBreakSpace
SpaceChar
_ -> Maybe NarrowNoBreakSpace
forall a. Maybe a
Nothing
)
instance AsMediumMathematicalSpace SpaceChar where
_MediumMathematicalSpace :: p MediumMathematicalSpace (f MediumMathematicalSpace)
-> p SpaceChar (f SpaceChar)
_MediumMathematicalSpace =
(MediumMathematicalSpace -> SpaceChar)
-> (SpaceChar -> Maybe MediumMathematicalSpace)
-> Prism' SpaceChar MediumMathematicalSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\MediumMathematicalSpace
MediumMathematicalSpace -> SpaceChar
MediumMathematicalSpace_)
(\case
SpaceChar
MediumMathematicalSpace_ -> MediumMathematicalSpace -> Maybe MediumMathematicalSpace
forall a. a -> Maybe a
Just MediumMathematicalSpace
MediumMathematicalSpace
SpaceChar
_ -> Maybe MediumMathematicalSpace
forall a. Maybe a
Nothing
)
instance AsIdeographicSpace SpaceChar where
_IdeographicSpace :: p IdeographicSpace (f IdeographicSpace)
-> p SpaceChar (f SpaceChar)
_IdeographicSpace =
(IdeographicSpace -> SpaceChar)
-> (SpaceChar -> Maybe IdeographicSpace)
-> Prism' SpaceChar IdeographicSpace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\IdeographicSpace
IdeographicSpace -> SpaceChar
IdeographicSpace_)
(\case
SpaceChar
IdeographicSpace_ -> IdeographicSpace -> Maybe IdeographicSpace
forall a. a -> Maybe a
Just IdeographicSpace
IdeographicSpace
SpaceChar
_ -> Maybe IdeographicSpace
forall a. Maybe a
Nothing
)
data IsoLatin1 =
HorizontalTab__
| LineFeed__
| FormFeed__
| CarriageReturn__
| Whitespace__
deriving (IsoLatin1 -> IsoLatin1 -> Bool
(IsoLatin1 -> IsoLatin1 -> Bool)
-> (IsoLatin1 -> IsoLatin1 -> Bool) -> Eq IsoLatin1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsoLatin1 -> IsoLatin1 -> Bool
$c/= :: IsoLatin1 -> IsoLatin1 -> Bool
== :: IsoLatin1 -> IsoLatin1 -> Bool
$c== :: IsoLatin1 -> IsoLatin1 -> Bool
Eq, Eq IsoLatin1
Eq IsoLatin1
-> (IsoLatin1 -> IsoLatin1 -> Ordering)
-> (IsoLatin1 -> IsoLatin1 -> Bool)
-> (IsoLatin1 -> IsoLatin1 -> Bool)
-> (IsoLatin1 -> IsoLatin1 -> Bool)
-> (IsoLatin1 -> IsoLatin1 -> Bool)
-> (IsoLatin1 -> IsoLatin1 -> IsoLatin1)
-> (IsoLatin1 -> IsoLatin1 -> IsoLatin1)
-> Ord IsoLatin1
IsoLatin1 -> IsoLatin1 -> Bool
IsoLatin1 -> IsoLatin1 -> Ordering
IsoLatin1 -> IsoLatin1 -> IsoLatin1
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IsoLatin1 -> IsoLatin1 -> IsoLatin1
$cmin :: IsoLatin1 -> IsoLatin1 -> IsoLatin1
max :: IsoLatin1 -> IsoLatin1 -> IsoLatin1
$cmax :: IsoLatin1 -> IsoLatin1 -> IsoLatin1
>= :: IsoLatin1 -> IsoLatin1 -> Bool
$c>= :: IsoLatin1 -> IsoLatin1 -> Bool
> :: IsoLatin1 -> IsoLatin1 -> Bool
$c> :: IsoLatin1 -> IsoLatin1 -> Bool
<= :: IsoLatin1 -> IsoLatin1 -> Bool
$c<= :: IsoLatin1 -> IsoLatin1 -> Bool
< :: IsoLatin1 -> IsoLatin1 -> Bool
$c< :: IsoLatin1 -> IsoLatin1 -> Bool
compare :: IsoLatin1 -> IsoLatin1 -> Ordering
$ccompare :: IsoLatin1 -> IsoLatin1 -> Ordering
$cp1Ord :: Eq IsoLatin1
Ord, Int -> IsoLatin1 -> ShowS
[IsoLatin1] -> ShowS
IsoLatin1 -> String
(Int -> IsoLatin1 -> ShowS)
-> (IsoLatin1 -> String)
-> ([IsoLatin1] -> ShowS)
-> Show IsoLatin1
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IsoLatin1] -> ShowS
$cshowList :: [IsoLatin1] -> ShowS
show :: IsoLatin1 -> String
$cshow :: IsoLatin1 -> String
showsPrec :: Int -> IsoLatin1 -> ShowS
$cshowsPrec :: Int -> IsoLatin1 -> ShowS
Show, (forall x. IsoLatin1 -> Rep IsoLatin1 x)
-> (forall x. Rep IsoLatin1 x -> IsoLatin1) -> Generic IsoLatin1
forall x. Rep IsoLatin1 x -> IsoLatin1
forall x. IsoLatin1 -> Rep IsoLatin1 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IsoLatin1 x -> IsoLatin1
$cfrom :: forall x. IsoLatin1 -> Rep IsoLatin1 x
Generic)
class HasIsoLatin1 a where
isoLatin1 :: Lens' a IsoLatin1
instance HasIsoLatin1 IsoLatin1 where
isoLatin1 :: (IsoLatin1 -> f IsoLatin1) -> IsoLatin1 -> f IsoLatin1
isoLatin1 = (IsoLatin1 -> f IsoLatin1) -> IsoLatin1 -> f IsoLatin1
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
class AsIsoLatin1 a where
_IsoLatin1 :: Prism' a IsoLatin1
instance AsIsoLatin1 Char where
_IsoLatin1 :: p IsoLatin1 (f IsoLatin1) -> p Char (f Char)
_IsoLatin1 =
(IsoLatin1 -> Char)
-> (Char -> Maybe IsoLatin1) -> Prism' Char IsoLatin1
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\case
IsoLatin1
HorizontalTab__ ->
Char
'\9'
IsoLatin1
LineFeed__ ->
Char
'\10'
IsoLatin1
FormFeed__ ->
Char
'\12'
IsoLatin1
CarriageReturn__ ->
Char
'\13'
IsoLatin1
Whitespace__ ->
Char
'\32'
)
(\case
Char
'\9' ->
IsoLatin1 -> Maybe IsoLatin1
forall a. a -> Maybe a
Just IsoLatin1
HorizontalTab__
Char
'\10' ->
IsoLatin1 -> Maybe IsoLatin1
forall a. a -> Maybe a
Just IsoLatin1
LineFeed__
Char
'\12' ->
IsoLatin1 -> Maybe IsoLatin1
forall a. a -> Maybe a
Just IsoLatin1
FormFeed__
Char
'\13' ->
IsoLatin1 -> Maybe IsoLatin1
forall a. a -> Maybe a
Just IsoLatin1
CarriageReturn__
Char
'\32' ->
IsoLatin1 -> Maybe IsoLatin1
forall a. a -> Maybe a
Just IsoLatin1
Whitespace__
Char
_ ->
Maybe IsoLatin1
forall a. Maybe a
Nothing
)
instance AsIsoLatin1 IsoLatin1 where
_IsoLatin1 :: p IsoLatin1 (f IsoLatin1) -> p IsoLatin1 (f IsoLatin1)
_IsoLatin1 = p IsoLatin1 (f IsoLatin1) -> p IsoLatin1 (f IsoLatin1)
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
parseIsoLatin1 ::
CharParsing p =>
p IsoLatin1
parseIsoLatin1 :: p IsoLatin1
parseIsoLatin1 =
[p IsoLatin1] -> p IsoLatin1
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [
IsoLatin1
HorizontalTab__ IsoLatin1 -> p HorizontalTab -> p IsoLatin1
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p HorizontalTab
forall (p :: * -> *). CharParsing p => p HorizontalTab
parseHorizontalTab
, IsoLatin1
LineFeed__ IsoLatin1 -> p LineFeed -> p IsoLatin1
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p LineFeed
forall (p :: * -> *). CharParsing p => p LineFeed
parseLineFeed
, IsoLatin1
FormFeed__ IsoLatin1 -> p FormFeed -> p IsoLatin1
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p FormFeed
forall (p :: * -> *). CharParsing p => p FormFeed
parseFormFeed
, IsoLatin1
CarriageReturn__ IsoLatin1 -> p CarriageReturn -> p IsoLatin1
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p CarriageReturn
forall (p :: * -> *). CharParsing p => p CarriageReturn
parseCarriageReturn
, IsoLatin1
Whitespace__ IsoLatin1 -> p Whitespace -> p IsoLatin1
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ p Whitespace
forall (p :: * -> *). CharParsing p => p Whitespace
parseWhitespace
]
instance AsHorizontalTab IsoLatin1 where
_HorizontalTab :: p HorizontalTab (f HorizontalTab) -> p IsoLatin1 (f IsoLatin1)
_HorizontalTab =
(HorizontalTab -> IsoLatin1)
-> (IsoLatin1 -> Maybe HorizontalTab)
-> Prism' IsoLatin1 HorizontalTab
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\HorizontalTab
HorizontalTab -> IsoLatin1
HorizontalTab__)
(\case
IsoLatin1
HorizontalTab__ -> HorizontalTab -> Maybe HorizontalTab
forall a. a -> Maybe a
Just HorizontalTab
HorizontalTab
IsoLatin1
_ -> Maybe HorizontalTab
forall a. Maybe a
Nothing
)
instance AsLineFeed IsoLatin1 where
_LineFeed :: p LineFeed (f LineFeed) -> p IsoLatin1 (f IsoLatin1)
_LineFeed =
(LineFeed -> IsoLatin1)
-> (IsoLatin1 -> Maybe LineFeed) -> Prism' IsoLatin1 LineFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\LineFeed
LineFeed -> IsoLatin1
LineFeed__)
(\case
IsoLatin1
LineFeed__ -> LineFeed -> Maybe LineFeed
forall a. a -> Maybe a
Just LineFeed
LineFeed
IsoLatin1
_ -> Maybe LineFeed
forall a. Maybe a
Nothing
)
instance AsFormFeed IsoLatin1 where
_FormFeed :: p FormFeed (f FormFeed) -> p IsoLatin1 (f IsoLatin1)
_FormFeed =
(FormFeed -> IsoLatin1)
-> (IsoLatin1 -> Maybe FormFeed) -> Prism' IsoLatin1 FormFeed
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\FormFeed
FormFeed -> IsoLatin1
FormFeed__)
(\case
IsoLatin1
FormFeed__ -> FormFeed -> Maybe FormFeed
forall a. a -> Maybe a
Just FormFeed
FormFeed
IsoLatin1
_ -> Maybe FormFeed
forall a. Maybe a
Nothing
)
instance AsCarriageReturn IsoLatin1 where
_CarriageReturn :: p CarriageReturn (f CarriageReturn) -> p IsoLatin1 (f IsoLatin1)
_CarriageReturn =
(CarriageReturn -> IsoLatin1)
-> (IsoLatin1 -> Maybe CarriageReturn)
-> Prism' IsoLatin1 CarriageReturn
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\CarriageReturn
CarriageReturn -> IsoLatin1
CarriageReturn__)
(\case
IsoLatin1
CarriageReturn__ -> CarriageReturn -> Maybe CarriageReturn
forall a. a -> Maybe a
Just CarriageReturn
CarriageReturn
IsoLatin1
_ -> Maybe CarriageReturn
forall a. Maybe a
Nothing
)
instance AsWhitespace IsoLatin1 where
_Whitespace :: p Whitespace (f Whitespace) -> p IsoLatin1 (f IsoLatin1)
_Whitespace =
(Whitespace -> IsoLatin1)
-> (IsoLatin1 -> Maybe Whitespace) -> Prism' IsoLatin1 Whitespace
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\Whitespace
Whitespace -> IsoLatin1
Whitespace__)
(\case
IsoLatin1
Whitespace__ -> Whitespace -> Maybe Whitespace
forall a. a -> Maybe a
Just Whitespace
Whitespace
IsoLatin1
_ -> Maybe Whitespace
forall a. Maybe a
Nothing
)