{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE LambdaCase #-} module Data.Char.Space( -- * Individual space characters HasHorizontalTab(..) , AsHorizontalTab(..) , parseHorizontalTab , HasLineFeed(..) , AsLineFeed(..) , parseLineFeed , HasVerticalTab(..) , AsVerticalTab(..) , parseVerticalTab , HasFormFeed(..) , AsFormFeed(..) , parseFormFeed , HasCarriageReturn(..) , AsCarriageReturn(..) , parseCarriageReturn , HasWhitespace(..) , AsWhitespace(..) , parseWhitespace , HasNoBreakSpace(..) , AsNoBreakSpace(..) , parseNoBreakSpace , HasOghamSpaceMark(..) , AsOghamSpaceMark(..) , parseOghamSpaceMark , HasEnQuad(..) , AsEnQuad(..) , parseEnQuad , HasEmQuad(..) , AsEmQuad(..) , parseEmQuad , HasEnSpace(..) , AsEnSpace(..) , parseEnSpace , HasEmSpace(..) , AsEmSpace(..) , parseEmSpace , HasThreePerEmSpace(..) , AsThreePerEmSpace(..) , parseThreePerEmSpace , HasFourPerEmSpace(..) , AsFourPerEmSpace(..) , parseFourPerEmSpace , HasSixPerEmSpace(..) , AsSixPerEmSpace(..) , parseSixPerEmSpace , HasFigureSpace(..) , AsFigureSpace(..) , parseFigureSpace , HasPunctuationSpace(..) , AsPunctuationSpace(..) , parsePunctuationSpace , HasThinSpace(..) , AsThinSpace(..) , parseThinSpace , HasHairSpace(..) , AsHairSpace(..) , parseHairSpace , HasNarrowNoBreakSpace(..) , AsNarrowNoBreakSpace(..) , parseNarrowNoBreakSpace , HasMediumMathematicalSpace(..) , AsMediumMathematicalSpace(..) , parseMediumMathematicalSpace , HasIdeographicSpace(..) , AsIdeographicSpace(..) , parseIdeographicSpace -- * All space characters , SpaceChar(..) , HasSpaceChar(..) , AsSpaceChar(..) , parseSpaceChar -- * ISO Latin-1 space characters /(horizontal tab, line feed, form feed, carriage return, whitespace)/ , IsoLatin1(..) , HasIsoLatin1(..) , AsIsoLatin1(..) , parseIsoLatin1 ) where import Control.Category ( Category(id) ) import Control.Lens ( Prism', prism', (#), Lens' ) import Data.Bool ( Bool ) import Data.Char ( Char ) import Data.Eq ( Eq((==)) ) import Data.Int ( Int ) import Data.Foldable ( asum ) import Data.Functor ( Functor((<$)) ) import Data.Maybe ( Maybe(Nothing, Just) ) import Data.Ord ( Ord ) import GHC.Generics ( Generic ) import GHC.Show ( Show ) import Prelude(Integer) import Text.Parser.Char ( CharParsing(satisfy) ) import Text.Parser.Combinators ( Parsing(()) ) class HasHorizontalTab a where horizontalTab :: Lens' a () instance HasHorizontalTab () where horizontalTab = id class AsHorizontalTab a where _HorizontalTab :: Prism' a () _HorizontalTab' :: a _HorizontalTab' = _HorizontalTab # () instance AsHorizontalTab () where _HorizontalTab = id instance AsHorizontalTab Char where _HorizontalTab = prism' (\() -> '\9') (\case '\9' -> Just () _ -> Nothing ) instance AsHorizontalTab Int where _HorizontalTab = prism' (\() -> 9) (\case 9 -> Just () _ -> Nothing ) instance AsHorizontalTab Integer where _HorizontalTab = prism' (\() -> 9) (\case 9 -> Just () _ -> Nothing ) parseHorizontalTab :: CharParsing p => p () parseHorizontalTab = satisfy' (== '\9') "horizontal tab character" class HasLineFeed a where lineFeed :: Lens' a () instance HasLineFeed () where lineFeed = id class AsLineFeed a where _LineFeed :: Prism' a () _LineFeed' :: a _LineFeed' = _LineFeed # () instance AsLineFeed () where _LineFeed = id instance AsLineFeed Char where _LineFeed = prism' (\() -> '\10') (\case '\10' -> Just () _ -> Nothing ) instance AsLineFeed Int where _LineFeed = prism' (\() -> 10) (\case 10 -> Just () _ -> Nothing ) instance AsLineFeed Integer where _LineFeed = prism' (\() -> 10) (\case 10 -> Just () _ -> Nothing ) parseLineFeed :: CharParsing p => p () parseLineFeed = satisfy' (== '\10') "line feed character" class HasVerticalTab a where verticalTab :: Lens' a () instance HasVerticalTab () where verticalTab = id class AsVerticalTab a where _VerticalTab :: Prism' a () _VerticalTab' :: a _VerticalTab' = _VerticalTab # () instance AsVerticalTab () where _VerticalTab = id instance AsVerticalTab Char where _VerticalTab = prism' (\() -> '\11') (\case '\11' -> Just () _ -> Nothing ) instance AsVerticalTab Int where _VerticalTab = prism' (\() -> 11) (\case 11 -> Just () _ -> Nothing ) instance AsVerticalTab Integer where _VerticalTab = prism' (\() -> 11) (\case 11 -> Just () _ -> Nothing ) parseVerticalTab :: CharParsing p => p () parseVerticalTab = satisfy' (== '\11') "vertical tab character" class HasFormFeed a where formFeed :: Lens' a () instance HasFormFeed () where formFeed = id class AsFormFeed a where _FormFeed :: Prism' a () _FormFeed' :: a _FormFeed' = _FormFeed # () instance AsFormFeed () where _FormFeed = id instance AsFormFeed Char where _FormFeed = prism' (\() -> '\12') (\case '\12' -> Just () _ -> Nothing ) instance AsFormFeed Int where _FormFeed = prism' (\() -> 12) (\case 12 -> Just () _ -> Nothing ) instance AsFormFeed Integer where _FormFeed = prism' (\() -> 12) (\case 12 -> Just () _ -> Nothing ) parseFormFeed :: CharParsing p => p () parseFormFeed = satisfy' (== '\12') "form feed character" class HasCarriageReturn a where carriageReturn :: Lens' a () instance HasCarriageReturn () where carriageReturn = id class AsCarriageReturn a where _CarriageReturn :: Prism' a () _CarriageReturn' :: a _CarriageReturn' = _CarriageReturn # () instance AsCarriageReturn () where _CarriageReturn = id instance AsCarriageReturn Char where _CarriageReturn = prism' (\() -> '\13') (\case '\13' -> Just () _ -> Nothing ) instance AsCarriageReturn Int where _CarriageReturn = prism' (\() -> 13) (\case 13 -> Just () _ -> Nothing ) instance AsCarriageReturn Integer where _CarriageReturn = prism' (\() -> 13) (\case 13 -> Just () _ -> Nothing ) parseCarriageReturn :: CharParsing p => p () parseCarriageReturn = satisfy' (== '\13') "carriage return character" class HasWhitespace a where whitespace :: Lens' a () instance HasWhitespace () where whitespace = id class AsWhitespace a where _Whitespace :: Prism' a () _Whitespace' :: a _Whitespace' = _Whitespace # () instance AsWhitespace () where _Whitespace = id instance AsWhitespace Char where _Whitespace = prism' (\() -> '\32') (\case '\32' -> Just () _ -> Nothing ) instance AsWhitespace Int where _Whitespace = prism' (\() -> 32) (\case 32 -> Just () _ -> Nothing ) instance AsWhitespace Integer where _Whitespace = prism' (\() -> 32) (\case 32 -> Just () _ -> Nothing ) parseWhitespace :: CharParsing p => p () parseWhitespace = satisfy' (== '\32') "whitespace character" class HasNoBreakSpace a where noBreakSpace :: Lens' a () instance HasNoBreakSpace () where noBreakSpace = id class AsNoBreakSpace a where _NoBreakSpace :: Prism' a () _NoBreakSpace' :: a _NoBreakSpace' = _NoBreakSpace # () instance AsNoBreakSpace () where _NoBreakSpace = id instance AsNoBreakSpace Char where _NoBreakSpace = prism' (\() -> '\160') (\case '\160' -> Just () _ -> Nothing ) instance AsNoBreakSpace Int where _NoBreakSpace = prism' (\() -> 160) (\case 160 -> Just () _ -> Nothing ) instance AsNoBreakSpace Integer where _NoBreakSpace = prism' (\() -> 160) (\case 160 -> Just () _ -> Nothing ) parseNoBreakSpace :: CharParsing p => p () parseNoBreakSpace = satisfy' (== '\160') "no break space character" class HasOghamSpaceMark a where oghamSpaceMark :: Lens' a () instance HasOghamSpaceMark () where oghamSpaceMark = id class AsOghamSpaceMark a where _OghamSpaceMark :: Prism' a () _OghamSpaceMark' :: a _OghamSpaceMark' = _OghamSpaceMark # () instance AsOghamSpaceMark () where _OghamSpaceMark = id instance AsOghamSpaceMark Char where _OghamSpaceMark = prism' (\() -> '\5760') (\case '\5760' -> Just () _ -> Nothing ) instance AsOghamSpaceMark Int where _OghamSpaceMark = prism' (\() -> 5760) (\case 5760 -> Just () _ -> Nothing ) instance AsOghamSpaceMark Integer where _OghamSpaceMark = prism' (\() -> 5760) (\case 5760 -> Just () _ -> Nothing ) parseOghamSpaceMark :: CharParsing p => p () parseOghamSpaceMark = satisfy' (== '\5760') "ogham space mark character" class HasEnQuad a where enQuad :: Lens' a () instance HasEnQuad () where enQuad = id class AsEnQuad a where _EnQuad :: Prism' a () _EnQuad' :: a _EnQuad' = _EnQuad # () instance AsEnQuad () where _EnQuad = id instance AsEnQuad Char where _EnQuad = prism' (\() -> '\8192') (\case '\8192' -> Just () _ -> Nothing ) instance AsEnQuad Int where _EnQuad = prism' (\() -> 8192) (\case 8192 -> Just () _ -> Nothing ) instance AsEnQuad Integer where _EnQuad = prism' (\() -> 8192) (\case 8192 -> Just () _ -> Nothing ) parseEnQuad :: CharParsing p => p () parseEnQuad = satisfy' (== '\8192') "en quad character" class HasEmQuad a where emQuad :: Lens' a () instance HasEmQuad () where emQuad = id class AsEmQuad a where _EmQuad :: Prism' a () _EmQuad' :: a _EmQuad' = _EmQuad # () instance AsEmQuad () where _EmQuad = id instance AsEmQuad Char where _EmQuad = prism' (\() -> '\8193') (\case '\8193' -> Just () _ -> Nothing ) instance AsEmQuad Int where _EmQuad = prism' (\() -> 8193) (\case 8193 -> Just () _ -> Nothing ) instance AsEmQuad Integer where _EmQuad = prism' (\() -> 8193) (\case 8193 -> Just () _ -> Nothing ) parseEmQuad :: CharParsing p => p () parseEmQuad = satisfy' (== '\8193') "em quad character" class HasEnSpace a where enSpace :: Lens' a () instance HasEnSpace () where enSpace = id class AsEnSpace a where _EnSpace :: Prism' a () _EnSpace' :: a _EnSpace' = _EnSpace # () instance AsEnSpace () where _EnSpace = id instance AsEnSpace Char where _EnSpace = prism' (\() -> '\8194') (\case '\8194' -> Just () _ -> Nothing ) instance AsEnSpace Int where _EnSpace = prism' (\() -> 8194) (\case 8194 -> Just () _ -> Nothing ) instance AsEnSpace Integer where _EnSpace = prism' (\() -> 8194) (\case 8194 -> Just () _ -> Nothing ) parseEnSpace :: CharParsing p => p () parseEnSpace = satisfy' (== '\8194') "en space character" class HasEmSpace a where emSpace :: Lens' a () instance HasEmSpace () where emSpace = id class AsEmSpace a where _EmSpace :: Prism' a () _EmSpace' :: a _EmSpace' = _EmSpace # () instance AsEmSpace () where _EmSpace = id instance AsEmSpace Char where _EmSpace = prism' (\() -> '\8195') (\case '\8195' -> Just () _ -> Nothing ) instance AsEmSpace Int where _EmSpace = prism' (\() -> 8195) (\case 8195 -> Just () _ -> Nothing ) instance AsEmSpace Integer where _EmSpace = prism' (\() -> 8195) (\case 8195 -> Just () _ -> Nothing ) parseEmSpace :: CharParsing p => p () parseEmSpace = satisfy' (== '\8195') "em space character" class HasThreePerEmSpace a where threePerEmSpace :: Lens' a () instance HasThreePerEmSpace () where threePerEmSpace = id class AsThreePerEmSpace a where _ThreePerEmSpace :: Prism' a () _ThreePerEmSpace' :: a _ThreePerEmSpace' = _ThreePerEmSpace # () instance AsThreePerEmSpace () where _ThreePerEmSpace = id instance AsThreePerEmSpace Char where _ThreePerEmSpace = prism' (\() -> '\8196') (\case '\8196' -> Just () _ -> Nothing ) instance AsThreePerEmSpace Int where _ThreePerEmSpace = prism' (\() -> 8196) (\case 8196 -> Just () _ -> Nothing ) instance AsThreePerEmSpace Integer where _ThreePerEmSpace = prism' (\() -> 8196) (\case 8196 -> Just () _ -> Nothing ) parseThreePerEmSpace :: CharParsing p => p () parseThreePerEmSpace = satisfy' (== '\8196') "three per em space character" class HasFourPerEmSpace a where fourPerEmSpace :: Lens' a () instance HasFourPerEmSpace () where fourPerEmSpace = id class AsFourPerEmSpace a where _FourPerEmSpace :: Prism' a () _FourPerEmSpace' :: a _FourPerEmSpace' = _FourPerEmSpace # () instance AsFourPerEmSpace () where _FourPerEmSpace = id instance AsFourPerEmSpace Char where _FourPerEmSpace = prism' (\() -> '\8197') (\case '\8197' -> Just () _ -> Nothing ) instance AsFourPerEmSpace Int where _FourPerEmSpace = prism' (\() -> 8197) (\case 8197 -> Just () _ -> Nothing ) instance AsFourPerEmSpace Integer where _FourPerEmSpace = prism' (\() -> 8197) (\case 8197 -> Just () _ -> Nothing ) parseFourPerEmSpace :: CharParsing p => p () parseFourPerEmSpace = satisfy' (== '\8197') "four per em space character" class HasSixPerEmSpace a where sixPerEmSpace :: Lens' a () instance HasSixPerEmSpace () where sixPerEmSpace = id class AsSixPerEmSpace a where _SixPerEmSpace :: Prism' a () _SixPerEmSpace' :: a _SixPerEmSpace' = _SixPerEmSpace # () instance AsSixPerEmSpace () where _SixPerEmSpace = id instance AsSixPerEmSpace Char where _SixPerEmSpace = prism' (\() -> '\8198') (\case '\8198' -> Just () _ -> Nothing ) instance AsSixPerEmSpace Int where _SixPerEmSpace = prism' (\() -> 8198) (\case 8198 -> Just () _ -> Nothing ) instance AsSixPerEmSpace Integer where _SixPerEmSpace = prism' (\() -> 8198) (\case 8198 -> Just () _ -> Nothing ) parseSixPerEmSpace :: CharParsing p => p () parseSixPerEmSpace = satisfy' (== '\8198') "six per em space character" class HasFigureSpace a where figureSpace :: Lens' a () instance HasFigureSpace () where figureSpace = id class AsFigureSpace a where _FigureSpace :: Prism' a () _FigureSpace' :: a _FigureSpace' = _FigureSpace # () instance AsFigureSpace () where _FigureSpace = id instance AsFigureSpace Char where _FigureSpace = prism' (\() -> '\8199') (\case '\8199' -> Just () _ -> Nothing ) instance AsFigureSpace Int where _FigureSpace = prism' (\() -> 8199) (\case 8199 -> Just () _ -> Nothing ) instance AsFigureSpace Integer where _FigureSpace = prism' (\() -> 8199) (\case 8199 -> Just () _ -> Nothing ) parseFigureSpace :: CharParsing p => p () parseFigureSpace = satisfy' (== '\8199') "figure space character" class HasPunctuationSpace a where punctuationSpace :: Lens' a () instance HasPunctuationSpace () where punctuationSpace = id class AsPunctuationSpace a where _PunctuationSpace :: Prism' a () _PunctuationSpace' :: a _PunctuationSpace' = _PunctuationSpace # () instance AsPunctuationSpace () where _PunctuationSpace = id instance AsPunctuationSpace Char where _PunctuationSpace = prism' (\() -> '\8200') (\case '\8200' -> Just () _ -> Nothing ) instance AsPunctuationSpace Int where _PunctuationSpace = prism' (\() -> 8200) (\case 8200 -> Just () _ -> Nothing ) instance AsPunctuationSpace Integer where _PunctuationSpace = prism' (\() -> 8200) (\case 8200 -> Just () _ -> Nothing ) parsePunctuationSpace :: CharParsing p => p () parsePunctuationSpace = satisfy' (== '\8200') "punctuation space character" class HasThinSpace a where thinSpace :: Lens' a () instance HasThinSpace () where thinSpace = id class AsThinSpace a where _ThinSpace :: Prism' a () _ThinSpace' :: a _ThinSpace' = _ThinSpace # () instance AsThinSpace () where _ThinSpace = id instance AsThinSpace Char where _ThinSpace = prism' (\() -> '\8201') (\case '\8201' -> Just () _ -> Nothing ) instance AsThinSpace Int where _ThinSpace = prism' (\() -> 8201) (\case 8201 -> Just () _ -> Nothing ) instance AsThinSpace Integer where _ThinSpace = prism' (\() -> 8201) (\case 8201 -> Just () _ -> Nothing ) parseThinSpace :: CharParsing p => p () parseThinSpace = satisfy' (== '\8201') "thin space character" class HasHairSpace a where hairSpace :: Lens' a () instance HasHairSpace () where hairSpace = id class AsHairSpace a where _HairSpace :: Prism' a () _HairSpace' :: a _HairSpace' = _HairSpace # () instance AsHairSpace () where _HairSpace = id instance AsHairSpace Char where _HairSpace = prism' (\() -> '\8202') (\case '\8202' -> Just () _ -> Nothing ) instance AsHairSpace Int where _HairSpace = prism' (\() -> 8202) (\case 8202 -> Just () _ -> Nothing ) instance AsHairSpace Integer where _HairSpace = prism' (\() -> 8202) (\case 8202 -> Just () _ -> Nothing ) parseHairSpace :: CharParsing p => p () parseHairSpace = satisfy' (== '\8202') "hair space character" class HasNarrowNoBreakSpace a where narrowNoBreakSpace :: Lens' a () instance HasNarrowNoBreakSpace () where narrowNoBreakSpace = id class AsNarrowNoBreakSpace a where _NarrowNoBreakSpace :: Prism' a () _NarrowNoBreakSpace' :: a _NarrowNoBreakSpace' = _NarrowNoBreakSpace # () instance AsNarrowNoBreakSpace () where _NarrowNoBreakSpace = id instance AsNarrowNoBreakSpace Char where _NarrowNoBreakSpace = prism' (\() -> '\8239') (\case '\8239' -> Just () _ -> Nothing ) instance AsNarrowNoBreakSpace Int where _NarrowNoBreakSpace = prism' (\() -> 8239) (\case 8239 -> Just () _ -> Nothing ) instance AsNarrowNoBreakSpace Integer where _NarrowNoBreakSpace = prism' (\() -> 8239) (\case 8239 -> Just () _ -> Nothing ) parseNarrowNoBreakSpace :: CharParsing p => p () parseNarrowNoBreakSpace = satisfy' (== '\8239') "narrow no break space character" class HasMediumMathematicalSpace a where mediumMathematicalSpace :: Lens' a () instance HasMediumMathematicalSpace () where mediumMathematicalSpace = id class AsMediumMathematicalSpace a where _MediumMathematicalSpace :: Prism' a () _MediumMathematicalSpace' :: a _MediumMathematicalSpace' = _MediumMathematicalSpace # () instance AsMediumMathematicalSpace () where _MediumMathematicalSpace = id instance AsMediumMathematicalSpace Char where _MediumMathematicalSpace = prism' (\() -> '\8287') (\case '\8287' -> Just () _ -> Nothing ) instance AsMediumMathematicalSpace Int where _MediumMathematicalSpace = prism' (\() -> 8287) (\case 8287 -> Just () _ -> Nothing ) instance AsMediumMathematicalSpace Integer where _MediumMathematicalSpace = prism' (\() -> 8287) (\case 8287 -> Just () _ -> Nothing ) parseMediumMathematicalSpace :: CharParsing p => p () parseMediumMathematicalSpace = satisfy' (== '\8287') "medium mathematical space character" class HasIdeographicSpace a where ideographicSpace :: Lens' a () instance HasIdeographicSpace () where ideographicSpace = id class AsIdeographicSpace a where _IdeographicSpace :: Prism' a () _IdeographicSpace' :: a _IdeographicSpace' = _IdeographicSpace # () instance AsIdeographicSpace () where _IdeographicSpace = id instance AsIdeographicSpace Char where _IdeographicSpace = prism' (\() -> '\12288') (\case '\12288' -> Just () _ -> Nothing ) instance AsIdeographicSpace Int where _IdeographicSpace = prism' (\() -> 12288) (\case 12288 -> Just () _ -> Nothing ) instance AsIdeographicSpace Integer where _IdeographicSpace = prism' (\() -> 12288) (\case 12288 -> Just () _ -> Nothing ) parseIdeographicSpace :: CharParsing p => p () parseIdeographicSpace = satisfy' (== '\12288') "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 (Eq, Ord, Show, Generic) class HasSpaceChar a where spaceChar :: Lens' a SpaceChar instance HasSpaceChar SpaceChar where spaceChar = id class AsSpaceChar a where _SpaceChar :: Prism' a SpaceChar instance AsSpaceChar SpaceChar where _SpaceChar = id instance AsSpaceChar Char where _SpaceChar = prism' (\case HorizontalTab -> '\9' LineFeed -> '\10' VerticalTab -> '\11' FormFeed -> '\12' CarriageReturn -> '\13' Whitespace -> '\32' NoBreakSpace -> '\160' OghamSpaceMark -> '\5760' EnQuad -> '\8192' EmQuad -> '\8193' EnSpace -> '\8194' EmSpace -> '\8195' ThreePerEmSpace -> '\8196' FourPerEmSpace -> '\8197' SixPerEmSpace -> '\8198' FigureSpace -> '\8199' PunctuationSpace -> '\8200' ThinSpace -> '\8201' HairSpace -> '\8202' NarrowNoBreakSpace -> '\8239' MediumMathematicalSpace -> '\8287' IdeographicSpace -> '\12288' ) (\case '\9' -> Just HorizontalTab '\10' -> Just LineFeed '\11' -> Just VerticalTab '\12' -> Just FormFeed '\13' -> Just CarriageReturn '\32' -> Just Whitespace '\160' -> Just NoBreakSpace '\5760' -> Just OghamSpaceMark '\8192' -> Just EnQuad '\8193' -> Just EmQuad '\8194' -> Just EnSpace '\8195' -> Just EmSpace '\8196' -> Just ThreePerEmSpace '\8197' -> Just FourPerEmSpace '\8198' -> Just SixPerEmSpace '\8199' -> Just FigureSpace '\8200' -> Just PunctuationSpace '\8201' -> Just ThinSpace '\8202' -> Just HairSpace '\8239' -> Just NarrowNoBreakSpace '\8287' -> Just MediumMathematicalSpace '\12288' -> Just IdeographicSpace _ -> Nothing ) parseSpaceChar :: CharParsing p => p SpaceChar parseSpaceChar = asum [ HorizontalTab <$ parseHorizontalTab , LineFeed <$ parseLineFeed , VerticalTab <$ parseVerticalTab , FormFeed <$ parseFormFeed , CarriageReturn <$ parseCarriageReturn , Whitespace <$ parseWhitespace , NoBreakSpace <$ parseNoBreakSpace , OghamSpaceMark <$ parseOghamSpaceMark , EnQuad <$ parseEnQuad , EmQuad <$ parseEmQuad , EnSpace <$ parseEnSpace , EmSpace <$ parseEmSpace , ThreePerEmSpace <$ parseThreePerEmSpace , FourPerEmSpace <$ parseFourPerEmSpace , SixPerEmSpace <$ parseSixPerEmSpace , FigureSpace <$ parseFigureSpace , PunctuationSpace <$ parsePunctuationSpace , ThinSpace <$ parseThinSpace , HairSpace <$ parseHairSpace , NarrowNoBreakSpace <$ parseNarrowNoBreakSpace , MediumMathematicalSpace <$ parseMediumMathematicalSpace , IdeographicSpace <$ parseIdeographicSpace ] instance AsHorizontalTab SpaceChar where _HorizontalTab = prism' (\() -> HorizontalTab) (\case HorizontalTab -> Just () _ -> Nothing ) instance AsLineFeed SpaceChar where _LineFeed = prism' (\() -> LineFeed) (\case LineFeed -> Just () _ -> Nothing ) instance AsVerticalTab SpaceChar where _VerticalTab = prism' (\() -> VerticalTab) (\case VerticalTab -> Just () _ -> Nothing ) instance AsFormFeed SpaceChar where _FormFeed = prism' (\() -> FormFeed) (\case FormFeed -> Just () _ -> Nothing ) instance AsCarriageReturn SpaceChar where _CarriageReturn = prism' (\() -> CarriageReturn) (\case CarriageReturn -> Just () _ -> Nothing ) instance AsWhitespace SpaceChar where _Whitespace = prism' (\() -> Whitespace) (\case Whitespace -> Just () _ -> Nothing ) instance AsNoBreakSpace SpaceChar where _NoBreakSpace = prism' (\() -> NoBreakSpace) (\case NoBreakSpace -> Just () _ -> Nothing ) instance AsOghamSpaceMark SpaceChar where _OghamSpaceMark = prism' (\() -> OghamSpaceMark) (\case OghamSpaceMark -> Just () _ -> Nothing ) instance AsEnQuad SpaceChar where _EnQuad = prism' (\() -> EnQuad) (\case EnQuad -> Just () _ -> Nothing ) instance AsEmQuad SpaceChar where _EmQuad = prism' (\() -> EmQuad) (\case EmQuad -> Just () _ -> Nothing ) instance AsEnSpace SpaceChar where _EnSpace = prism' (\() -> EnSpace) (\case EnSpace -> Just () _ -> Nothing ) instance AsEmSpace SpaceChar where _EmSpace = prism' (\() -> EmSpace) (\case EmSpace -> Just () _ -> Nothing ) instance AsThreePerEmSpace SpaceChar where _ThreePerEmSpace = prism' (\() -> ThreePerEmSpace) (\case ThreePerEmSpace -> Just () _ -> Nothing ) instance AsFourPerEmSpace SpaceChar where _FourPerEmSpace = prism' (\() -> FourPerEmSpace) (\case FourPerEmSpace -> Just () _ -> Nothing ) instance AsSixPerEmSpace SpaceChar where _SixPerEmSpace = prism' (\() -> SixPerEmSpace) (\case SixPerEmSpace -> Just () _ -> Nothing ) instance AsFigureSpace SpaceChar where _FigureSpace = prism' (\() -> FigureSpace) (\case FigureSpace -> Just () _ -> Nothing ) instance AsPunctuationSpace SpaceChar where _PunctuationSpace = prism' (\() -> PunctuationSpace) (\case PunctuationSpace -> Just () _ -> Nothing ) instance AsThinSpace SpaceChar where _ThinSpace = prism' (\() -> ThinSpace) (\case ThinSpace -> Just () _ -> Nothing ) instance AsHairSpace SpaceChar where _HairSpace = prism' (\() -> HairSpace) (\case HairSpace -> Just () _ -> Nothing ) instance AsNarrowNoBreakSpace SpaceChar where _NarrowNoBreakSpace = prism' (\() -> NarrowNoBreakSpace) (\case NarrowNoBreakSpace -> Just () _ -> Nothing ) instance AsMediumMathematicalSpace SpaceChar where _MediumMathematicalSpace = prism' (\() -> MediumMathematicalSpace) (\case MediumMathematicalSpace -> Just () _ -> Nothing ) instance AsIdeographicSpace SpaceChar where _IdeographicSpace = prism' (\() -> IdeographicSpace) (\case IdeographicSpace -> Just () _ -> Nothing ) data IsoLatin1 = HorizontalTab_ | LineFeed_ | FormFeed_ | CarriageReturn_ | Whitespace_ deriving (Eq, Ord, Show, Generic) class HasIsoLatin1 a where isoLatin1 :: Lens' a IsoLatin1 instance HasIsoLatin1 IsoLatin1 where isoLatin1 = id class AsIsoLatin1 a where _IsoLatin1 :: Prism' a IsoLatin1 instance AsIsoLatin1 Char where _IsoLatin1 = prism' (\case HorizontalTab_ -> '\9' LineFeed_ -> '\10' FormFeed_ -> '\12' CarriageReturn_ -> '\13' Whitespace_ -> '\32' ) (\case '\9' -> Just HorizontalTab_ '\10' -> Just LineFeed_ '\12' -> Just FormFeed_ '\13' -> Just CarriageReturn_ '\32' -> Just Whitespace_ _ -> Nothing ) instance AsIsoLatin1 IsoLatin1 where _IsoLatin1 = id parseIsoLatin1 :: CharParsing p => p IsoLatin1 parseIsoLatin1 = asum [ HorizontalTab_ <$ parseHorizontalTab , LineFeed_ <$ parseLineFeed , FormFeed_ <$ parseFormFeed , CarriageReturn_ <$ parseCarriageReturn , Whitespace_ <$ parseWhitespace ] instance AsHorizontalTab IsoLatin1 where _HorizontalTab = prism' (\() -> HorizontalTab_) (\case HorizontalTab_ -> Just () _ -> Nothing ) instance AsLineFeed IsoLatin1 where _LineFeed = prism' (\() -> LineFeed_) (\case LineFeed_ -> Just () _ -> Nothing ) instance AsFormFeed IsoLatin1 where _FormFeed = prism' (\() -> FormFeed_) (\case FormFeed_ -> Just () _ -> Nothing ) instance AsCarriageReturn IsoLatin1 where _CarriageReturn = prism' (\() -> CarriageReturn_) (\case CarriageReturn_ -> Just () _ -> Nothing ) instance AsWhitespace IsoLatin1 where _Whitespace = prism' (\() -> Whitespace_) (\case Whitespace_ -> Just () _ -> Nothing ) -- not exported satisfy' :: CharParsing f => (Char -> Bool) -> f () satisfy' p = () <$ satisfy p