module Data.Char.Alpha(
AlphaUpper
, HasAlphaUpper(alphaUpper)
, AsAlphaUpper(_AlphaUpper)
, parseAlphaUpper
, AlphaLower
, HasAlphaLower(alphaLower)
, AsAlphaLower(_AlphaLower)
, parseAlphaLower
, Alpha(UpperAlpha, LowerAlpha)
, HasAlpha(alpha)
, AsAlpha(_Alpha, _UpperAlpha, _LowerAlpha)
, parseAlpha
, upperlower
, lowerupper
) where
import Control.Applicative((<$>), (<|>), empty)
import Control.Category((.), id)
import Control.Lens(makeClassy, makeClassyPrisms, from, iso, prism', (^?), Iso', Prism')
import Control.Monad(Monad((>>=), return))
import Data.Char(Char, toLower, toUpper)
import Data.Eq(Eq)
import Data.Foldable(elem)
import Data.Maybe(Maybe(Just, Nothing), maybe)
import Data.Ord(Ord)
import Prelude(Show)
import Text.Parser.Char(CharParsing, anyChar)
import Text.Parser.Combinators((<?>), try)
newtype AlphaUpper =
AlphaUpper Char
deriving (Eq, Ord, Show)
makeClassy ''AlphaUpper
class AsAlphaUpper a where
_AlphaUpper ::
Prism'
a
AlphaUpper
instance AsAlphaUpper AlphaUpper where
_AlphaUpper =
id
instance AsAlphaUpper Char where
_AlphaUpper =
prism'
(\(AlphaUpper c) -> c)
(\c -> if c `elem` ['A'..'Z']
then
Just (AlphaUpper c)
else
Nothing)
parseAlphaUpper ::
(Monad f, CharParsing f) =>
f AlphaUpper
parseAlphaUpper =
try (anyChar >>= \c -> maybe empty return (c ^? _AlphaUpper)) <?> "AlphaUpper"
newtype AlphaLower =
AlphaLower Char
deriving (Eq, Ord, Show)
makeClassy ''AlphaLower
class AsAlphaLower a where
_AlphaLower ::
Prism'
a
AlphaLower
instance AsAlphaLower AlphaLower where
_AlphaLower =
id
instance AsAlphaLower Char where
_AlphaLower =
prism'
(\(AlphaLower c) -> c)
(\c -> if c `elem` ['a'..'z']
then
Just (AlphaLower c)
else
Nothing)
parseAlphaLower ::
(Monad f, CharParsing f) =>
f AlphaLower
parseAlphaLower =
try (anyChar >>= \c -> maybe empty return (c ^? _AlphaLower)) <?> "AlphaLower"
data Alpha =
UpperAlpha AlphaUpper
| LowerAlpha AlphaLower
deriving (Eq, Ord, Show)
makeClassyPrisms ''Alpha
makeClassy ''Alpha
parseAlpha ::
(Monad f, CharParsing f) =>
f Alpha
parseAlpha =
UpperAlpha <$> parseAlphaUpper <|> LowerAlpha <$> parseAlphaLower
instance AsAlphaLower Alpha where
_AlphaLower =
_LowerAlpha . _AlphaLower
instance AsAlphaUpper Alpha where
_AlphaUpper =
_UpperAlpha . _AlphaUpper
upperlower ::
Iso'
AlphaUpper
AlphaLower
upperlower =
iso
(\(AlphaUpper c) -> AlphaLower (toLower c))
(\(AlphaLower c) -> AlphaUpper (toUpper c))
lowerupper ::
Iso'
AlphaLower
AlphaUpper
lowerupper =
from upperlower