module Refined.Extras.Predicates.Text
(
SymEqualTo,
Space,
Lower,
Upper,
Alpha,
AlphaNum,
Letter,
Mark,
Number,
Punctuation,
Symbol,
Separator,
Control,
Digit,
OctDigit,
HexDigit,
Ascii,
Latin1,
AsciiUpper,
AsciiLower,
AsciiAlpha,
AsciiAlphaNum,
)
where
import Data.ByteString.Internal qualified as BS
import Data.Char qualified as C
import Data.Kind (Type)
import Data.Proxy (Proxy (Proxy))
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.Lazy qualified as LT
import Data.Typeable qualified as Ty
import Data.Word (Word8)
import GHC.Generics (Generic)
import GHC.TypeLits (KnownSymbol)
import GHC.TypeLits qualified as TL
import Refined (Predicate (validate), RefineException (RefineOtherException))
type SymEqualTo :: TL.Symbol -> Type
data SymEqualTo c
deriving stock
(
(forall x. SymEqualTo c -> Rep (SymEqualTo c) x)
-> (forall x. Rep (SymEqualTo c) x -> SymEqualTo c)
-> Generic (SymEqualTo c)
forall x. Rep (SymEqualTo c) x -> SymEqualTo c
forall x. SymEqualTo c -> Rep (SymEqualTo c) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (c :: Symbol) x. Rep (SymEqualTo c) x -> SymEqualTo c
forall (c :: Symbol) x. SymEqualTo c -> Rep (SymEqualTo c) x
$cfrom :: forall (c :: Symbol) x. SymEqualTo c -> Rep (SymEqualTo c) x
from :: forall x. SymEqualTo c -> Rep (SymEqualTo c) x
$cto :: forall (c :: Symbol) x. Rep (SymEqualTo c) x -> SymEqualTo c
to :: forall x. Rep (SymEqualTo c) x -> SymEqualTo c
Generic
)
instance (KnownSymbol c) => Predicate (SymEqualTo c) Char where
validate :: Proxy (SymEqualTo c) -> Char -> Maybe RefineException
validate Proxy (SymEqualTo c)
proxy Char
x = case String
sym of
[Char
y] ->
if Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
y
then Maybe RefineException
forall a. Maybe a
Nothing
else RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy (SymEqualTo c) -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy (SymEqualTo c)
proxy) Text
eqErr
String
_ -> RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy (SymEqualTo c) -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy (SymEqualTo c)
proxy) Text
nonCharErr
where
sym :: String
sym = forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
TL.symbolVal @c Proxy c
forall {k} (t :: k). Proxy t
Proxy
eqErr :: Text
eqErr = Char -> Text
T.singleton Char
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" does not equal the predicate"
nonCharErr :: Text
nonCharErr = Char -> Text
T.singleton Char
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a single Char"
instance (KnownSymbol c) => Predicate (SymEqualTo c) String where
validate :: Proxy (SymEqualTo c) -> String -> Maybe RefineException
validate Proxy (SymEqualTo c)
proxy String
txt
| String
txt String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
sym = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy (SymEqualTo c) -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy (SymEqualTo c)
proxy) Text
err
where
sym :: String
sym = forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
TL.symbolVal @c Proxy c
forall {k} (t :: k). Proxy t
Proxy
err :: Text
err = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
txt String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" does not equal the predicate"
instance (KnownSymbol c) => Predicate (SymEqualTo c) Text where
validate :: Proxy (SymEqualTo c) -> Text -> Maybe RefineException
validate Proxy (SymEqualTo c)
proxy Text
txt
| Text
txt Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
sym = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy (SymEqualTo c) -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy (SymEqualTo c)
proxy) Text
err
where
sym :: Text
sym = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
TL.symbolVal @c Proxy c
forall {k} (t :: k). Proxy t
Proxy
err :: Text
err = Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" does not equal the predicate"
instance (KnownSymbol c) => Predicate (SymEqualTo c) LT.Text where
validate :: Proxy (SymEqualTo c) -> Text -> Maybe RefineException
validate Proxy (SymEqualTo c)
proxy Text
txt
| Text
txt' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
sym = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy (SymEqualTo c) -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy (SymEqualTo c)
proxy) Text
err
where
txt' :: Text
txt' = Text -> Text
LT.toStrict Text
txt
sym :: Text
sym = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
TL.symbolVal @c Proxy c
forall {k} (t :: k). Proxy t
Proxy
err :: Text
err = Text
txt' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" does not equal the predicate"
type Space :: Type
data Space
deriving stock
(
(forall x. Space -> Rep Space x)
-> (forall x. Rep Space x -> Space) -> Generic Space
forall x. Rep Space x -> Space
forall x. Space -> Rep Space x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Space -> Rep Space x
from :: forall x. Space -> Rep Space x
$cto :: forall x. Rep Space x -> Space
to :: forall x. Rep Space x -> Space
Generic
)
instance Predicate Space Char where
validate :: Proxy Space -> Char -> Maybe RefineException
validate Proxy Space
proxy Char
c
| Char -> Bool
C.isSpace Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Space -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Space
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a space character"
type Lower :: Type
data Lower
deriving stock
(
(forall x. Lower -> Rep Lower x)
-> (forall x. Rep Lower x -> Lower) -> Generic Lower
forall x. Rep Lower x -> Lower
forall x. Lower -> Rep Lower x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Lower -> Rep Lower x
from :: forall x. Lower -> Rep Lower x
$cto :: forall x. Rep Lower x -> Lower
to :: forall x. Rep Lower x -> Lower
Generic
)
instance Predicate Lower Char where
validate :: Proxy Lower -> Char -> Maybe RefineException
validate Proxy Lower
proxy Char
c
| Char -> Bool
C.isLower Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Lower -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Lower
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not lowercase"
type Upper :: Type
data Upper
deriving stock
(
(forall x. Upper -> Rep Upper x)
-> (forall x. Rep Upper x -> Upper) -> Generic Upper
forall x. Rep Upper x -> Upper
forall x. Upper -> Rep Upper x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Upper -> Rep Upper x
from :: forall x. Upper -> Rep Upper x
$cto :: forall x. Rep Upper x -> Upper
to :: forall x. Rep Upper x -> Upper
Generic
)
instance Predicate Upper Char where
validate :: Proxy Upper -> Char -> Maybe RefineException
validate Proxy Upper
proxy Char
c
| Char -> Bool
C.isUpper Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Upper -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Upper
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not uppercase"
type Alpha :: Type
data Alpha
deriving stock
(
(forall x. Alpha -> Rep Alpha x)
-> (forall x. Rep Alpha x -> Alpha) -> Generic Alpha
forall x. Rep Alpha x -> Alpha
forall x. Alpha -> Rep Alpha x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Alpha -> Rep Alpha x
from :: forall x. Alpha -> Rep Alpha x
$cto :: forall x. Rep Alpha x -> Alpha
to :: forall x. Rep Alpha x -> Alpha
Generic
)
instance Predicate Alpha Char where
validate :: Proxy Alpha -> Char -> Maybe RefineException
validate Proxy Alpha
proxy Char
c
| Char -> Bool
C.isAlpha Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Alpha -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Alpha
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not an alphabetic character"
type AlphaNum :: Type
data AlphaNum
deriving stock
(
(forall x. AlphaNum -> Rep AlphaNum x)
-> (forall x. Rep AlphaNum x -> AlphaNum) -> Generic AlphaNum
forall x. Rep AlphaNum x -> AlphaNum
forall x. AlphaNum -> Rep AlphaNum x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AlphaNum -> Rep AlphaNum x
from :: forall x. AlphaNum -> Rep AlphaNum x
$cto :: forall x. Rep AlphaNum x -> AlphaNum
to :: forall x. Rep AlphaNum x -> AlphaNum
Generic
)
instance Predicate AlphaNum Char where
validate :: Proxy AlphaNum -> Char -> Maybe RefineException
validate Proxy AlphaNum
proxy Char
c
| Char -> Bool
C.isAlphaNum Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AlphaNum -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AlphaNum
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not an alpha-numeric character"
type Print :: Type
data Print
deriving stock
(
(forall x. Print -> Rep Print x)
-> (forall x. Rep Print x -> Print) -> Generic Print
forall x. Rep Print x -> Print
forall x. Print -> Rep Print x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Print -> Rep Print x
from :: forall x. Print -> Rep Print x
$cto :: forall x. Rep Print x -> Print
to :: forall x. Rep Print x -> Print
Generic
)
instance Predicate Print Char where
validate :: Proxy Print -> Char -> Maybe RefineException
validate Proxy Print
proxy Char
c
| Char -> Bool
C.isPrint Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Print -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Print
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a printable character"
type Letter :: Type
data Letter
deriving stock
(
(forall x. Letter -> Rep Letter x)
-> (forall x. Rep Letter x -> Letter) -> Generic Letter
forall x. Rep Letter x -> Letter
forall x. Letter -> Rep Letter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Letter -> Rep Letter x
from :: forall x. Letter -> Rep Letter x
$cto :: forall x. Rep Letter x -> Letter
to :: forall x. Rep Letter x -> Letter
Generic
)
instance Predicate Letter Char where
validate :: Proxy Letter -> Char -> Maybe RefineException
validate Proxy Letter
proxy Char
c
| Char -> Bool
C.isLetter Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Letter -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Letter
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a letter"
type Mark :: Type
data Mark
deriving stock
(
(forall x. Mark -> Rep Mark x)
-> (forall x. Rep Mark x -> Mark) -> Generic Mark
forall x. Rep Mark x -> Mark
forall x. Mark -> Rep Mark x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Mark -> Rep Mark x
from :: forall x. Mark -> Rep Mark x
$cto :: forall x. Rep Mark x -> Mark
to :: forall x. Rep Mark x -> Mark
Generic
)
instance Predicate Mark Char where
validate :: Proxy Mark -> Char -> Maybe RefineException
validate Proxy Mark
proxy Char
c
| Char -> Bool
C.isMark Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Mark -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Mark
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a mark"
type Number :: Type
data Number
deriving stock
(
(forall x. Number -> Rep Number x)
-> (forall x. Rep Number x -> Number) -> Generic Number
forall x. Rep Number x -> Number
forall x. Number -> Rep Number x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Number -> Rep Number x
from :: forall x. Number -> Rep Number x
$cto :: forall x. Rep Number x -> Number
to :: forall x. Rep Number x -> Number
Generic
)
instance Predicate Number Char where
validate :: Proxy Number -> Char -> Maybe RefineException
validate Proxy Number
proxy Char
c
| Char -> Bool
C.isNumber Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Number -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Number
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a number"
type Punctuation :: Type
data Punctuation
deriving stock
(
(forall x. Punctuation -> Rep Punctuation x)
-> (forall x. Rep Punctuation x -> Punctuation)
-> Generic Punctuation
forall x. Rep Punctuation x -> Punctuation
forall x. Punctuation -> Rep Punctuation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Punctuation -> Rep Punctuation x
from :: forall x. Punctuation -> Rep Punctuation x
$cto :: forall x. Rep Punctuation x -> Punctuation
to :: forall x. Rep Punctuation x -> Punctuation
Generic
)
instance Predicate Punctuation Char where
validate :: Proxy Punctuation -> Char -> Maybe RefineException
validate Proxy Punctuation
proxy Char
c
| Char -> Bool
C.isPunctuation Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Punctuation -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Punctuation
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not punctuation"
type Symbol :: Type
data Symbol
deriving stock
(
(forall x. Symbol -> Rep Symbol x)
-> (forall x. Rep Symbol x -> Symbol) -> Generic Symbol
forall x. Rep Symbol x -> Symbol
forall x. Symbol -> Rep Symbol x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Symbol -> Rep Symbol x
from :: forall x. Symbol -> Rep Symbol x
$cto :: forall x. Rep Symbol x -> Symbol
to :: forall x. Rep Symbol x -> Symbol
Generic
)
instance Predicate Symbol Char where
validate :: Proxy Symbol -> Char -> Maybe RefineException
validate Proxy Symbol
proxy Char
c
| Char -> Bool
C.isSymbol Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Symbol -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Symbol
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a symbol"
type Separator :: Type
data Separator
deriving stock
(
(forall x. Separator -> Rep Separator x)
-> (forall x. Rep Separator x -> Separator) -> Generic Separator
forall x. Rep Separator x -> Separator
forall x. Separator -> Rep Separator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Separator -> Rep Separator x
from :: forall x. Separator -> Rep Separator x
$cto :: forall x. Rep Separator x -> Separator
to :: forall x. Rep Separator x -> Separator
Generic
)
instance Predicate Separator Char where
validate :: Proxy Separator -> Char -> Maybe RefineException
validate Proxy Separator
proxy Char
c
| Char -> Bool
C.isSeparator Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Separator -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Separator
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a separator"
type Control :: Type
data Control
deriving stock
(
(forall x. Control -> Rep Control x)
-> (forall x. Rep Control x -> Control) -> Generic Control
forall x. Rep Control x -> Control
forall x. Control -> Rep Control x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Control -> Rep Control x
from :: forall x. Control -> Rep Control x
$cto :: forall x. Rep Control x -> Control
to :: forall x. Rep Control x -> Control
Generic
)
instance Predicate Control Char where
validate :: Proxy Control -> Char -> Maybe RefineException
validate Proxy Control
proxy Char
c
| Char -> Bool
C.isControl Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Control -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Control
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a control character"
instance Predicate Control Word8 where
validate :: Proxy Control -> Word8 -> Maybe RefineException
validate Proxy Control
proxy Word8
w
| Char -> Bool
C.isControl Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Control -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Control
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a control character"
type Digit :: Type
data Digit
deriving stock
(
(forall x. Digit -> Rep Digit x)
-> (forall x. Rep Digit x -> Digit) -> Generic Digit
forall x. Rep Digit x -> Digit
forall x. Digit -> Rep Digit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Digit -> Rep Digit x
from :: forall x. Digit -> Rep Digit x
$cto :: forall x. Rep Digit x -> Digit
to :: forall x. Rep Digit x -> Digit
Generic
)
instance Predicate Digit Char where
validate :: Proxy Digit -> Char -> Maybe RefineException
validate Proxy Digit
proxy Char
c
| Char -> Bool
C.isDigit Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Digit -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Digit
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a digit"
instance Predicate Digit Word8 where
validate :: Proxy Digit -> Word8 -> Maybe RefineException
validate Proxy Digit
proxy Word8
w
| Char -> Bool
C.isDigit Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Digit -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Digit
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a digit"
type OctDigit :: Type
data OctDigit
deriving stock
(
(forall x. OctDigit -> Rep OctDigit x)
-> (forall x. Rep OctDigit x -> OctDigit) -> Generic OctDigit
forall x. Rep OctDigit x -> OctDigit
forall x. OctDigit -> Rep OctDigit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OctDigit -> Rep OctDigit x
from :: forall x. OctDigit -> Rep OctDigit x
$cto :: forall x. Rep OctDigit x -> OctDigit
to :: forall x. Rep OctDigit x -> OctDigit
Generic
)
instance Predicate OctDigit Char where
validate :: Proxy OctDigit -> Char -> Maybe RefineException
validate Proxy OctDigit
proxy Char
c
| Char -> Bool
C.isOctDigit Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy OctDigit -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy OctDigit
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not an octal digit"
instance Predicate OctDigit Word8 where
validate :: Proxy OctDigit -> Word8 -> Maybe RefineException
validate Proxy OctDigit
proxy Word8
w
| Char -> Bool
C.isOctDigit Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy OctDigit -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy OctDigit
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not an octal digit"
type HexDigit :: Type
data HexDigit
deriving stock
(
(forall x. HexDigit -> Rep HexDigit x)
-> (forall x. Rep HexDigit x -> HexDigit) -> Generic HexDigit
forall x. Rep HexDigit x -> HexDigit
forall x. HexDigit -> Rep HexDigit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HexDigit -> Rep HexDigit x
from :: forall x. HexDigit -> Rep HexDigit x
$cto :: forall x. Rep HexDigit x -> HexDigit
to :: forall x. Rep HexDigit x -> HexDigit
Generic
)
instance Predicate HexDigit Char where
validate :: Proxy HexDigit -> Char -> Maybe RefineException
validate Proxy HexDigit
proxy Char
c
| Char -> Bool
C.isHexDigit Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy HexDigit -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy HexDigit
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a hexadecimal digit"
instance Predicate HexDigit Word8 where
validate :: Proxy HexDigit -> Word8 -> Maybe RefineException
validate Proxy HexDigit
proxy Word8
w
| Char -> Bool
C.isHexDigit Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy HexDigit -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy HexDigit
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not a hexadecimal digit"
type Ascii :: Type
data Ascii
deriving stock
(
(forall x. Ascii -> Rep Ascii x)
-> (forall x. Rep Ascii x -> Ascii) -> Generic Ascii
forall x. Rep Ascii x -> Ascii
forall x. Ascii -> Rep Ascii x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Ascii -> Rep Ascii x
from :: forall x. Ascii -> Rep Ascii x
$cto :: forall x. Rep Ascii x -> Ascii
to :: forall x. Rep Ascii x -> Ascii
Generic
)
instance Predicate Ascii Char where
validate :: Proxy Ascii -> Char -> Maybe RefineException
validate Proxy Ascii
proxy Char
c
| Char -> Bool
C.isAscii Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Ascii -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Ascii
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not ascii"
instance Predicate Ascii Word8 where
validate :: Proxy Ascii -> Word8 -> Maybe RefineException
validate Proxy Ascii
proxy Word8
w
| Char -> Bool
C.isAscii Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Ascii -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Ascii
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not ascii"
type Latin1 :: Type
data Latin1
deriving stock
(
(forall x. Latin1 -> Rep Latin1 x)
-> (forall x. Rep Latin1 x -> Latin1) -> Generic Latin1
forall x. Rep Latin1 x -> Latin1
forall x. Latin1 -> Rep Latin1 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Latin1 -> Rep Latin1 x
from :: forall x. Latin1 -> Rep Latin1 x
$cto :: forall x. Rep Latin1 x -> Latin1
to :: forall x. Rep Latin1 x -> Latin1
Generic
)
instance Predicate Latin1 Char where
validate :: Proxy Latin1 -> Char -> Maybe RefineException
validate Proxy Latin1
proxy Char
c
| Char -> Bool
C.isLatin1 Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Latin1 -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Latin1
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not latin1"
instance Predicate Latin1 Word8 where
validate :: Proxy Latin1 -> Word8 -> Maybe RefineException
validate Proxy Latin1
proxy Word8
w
| Char -> Bool
C.isLatin1 Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy Latin1 -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy Latin1
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not latin1"
type AsciiUpper :: Type
data AsciiUpper
deriving stock
(
(forall x. AsciiUpper -> Rep AsciiUpper x)
-> (forall x. Rep AsciiUpper x -> AsciiUpper) -> Generic AsciiUpper
forall x. Rep AsciiUpper x -> AsciiUpper
forall x. AsciiUpper -> Rep AsciiUpper x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AsciiUpper -> Rep AsciiUpper x
from :: forall x. AsciiUpper -> Rep AsciiUpper x
$cto :: forall x. Rep AsciiUpper x -> AsciiUpper
to :: forall x. Rep AsciiUpper x -> AsciiUpper
Generic
)
instance Predicate AsciiUpper Char where
validate :: Proxy AsciiUpper -> Char -> Maybe RefineException
validate Proxy AsciiUpper
proxy Char
c
| Char -> Bool
C.isAsciiUpper Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AsciiUpper -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AsciiUpper
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not uppercase ascii"
instance Predicate AsciiUpper Word8 where
validate :: Proxy AsciiUpper -> Word8 -> Maybe RefineException
validate Proxy AsciiUpper
proxy Word8
w
| Char -> Bool
C.isAsciiUpper Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AsciiUpper -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AsciiUpper
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not uppercase ascii"
type AsciiLower :: Type
data AsciiLower
deriving stock
(
(forall x. AsciiLower -> Rep AsciiLower x)
-> (forall x. Rep AsciiLower x -> AsciiLower) -> Generic AsciiLower
forall x. Rep AsciiLower x -> AsciiLower
forall x. AsciiLower -> Rep AsciiLower x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AsciiLower -> Rep AsciiLower x
from :: forall x. AsciiLower -> Rep AsciiLower x
$cto :: forall x. Rep AsciiLower x -> AsciiLower
to :: forall x. Rep AsciiLower x -> AsciiLower
Generic
)
instance Predicate AsciiLower Char where
validate :: Proxy AsciiLower -> Char -> Maybe RefineException
validate Proxy AsciiLower
proxy Char
c
| Char -> Bool
C.isAsciiLower Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AsciiLower -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AsciiLower
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not lowercase ascii"
instance Predicate AsciiLower Word8 where
validate :: Proxy AsciiLower -> Word8 -> Maybe RefineException
validate Proxy AsciiLower
proxy Word8
w
| Char -> Bool
C.isAsciiLower Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AsciiLower -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AsciiLower
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not lowercase ascii"
type AsciiAlpha :: Type
data AsciiAlpha
deriving stock
(
(forall x. AsciiAlpha -> Rep AsciiAlpha x)
-> (forall x. Rep AsciiAlpha x -> AsciiAlpha) -> Generic AsciiAlpha
forall x. Rep AsciiAlpha x -> AsciiAlpha
forall x. AsciiAlpha -> Rep AsciiAlpha x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AsciiAlpha -> Rep AsciiAlpha x
from :: forall x. AsciiAlpha -> Rep AsciiAlpha x
$cto :: forall x. Rep AsciiAlpha x -> AsciiAlpha
to :: forall x. Rep AsciiAlpha x -> AsciiAlpha
Generic
)
instance Predicate AsciiAlpha Char where
validate :: Proxy AsciiAlpha -> Char -> Maybe RefineException
validate Proxy AsciiAlpha
proxy Char
c
| Char -> Bool
C.isAscii Char
c Bool -> Bool -> Bool
&& Char -> Bool
C.isAlpha Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AsciiAlpha -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AsciiAlpha
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not alpha ascii"
instance Predicate AsciiAlpha Word8 where
validate :: Proxy AsciiAlpha -> Word8 -> Maybe RefineException
validate Proxy AsciiAlpha
proxy Word8
w
| Char -> Bool
C.isAscii Char
c Bool -> Bool -> Bool
&& Char -> Bool
C.isAlpha Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AsciiAlpha -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AsciiAlpha
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not alpha ascii"
type AsciiAlphaNum :: Type
data AsciiAlphaNum
deriving stock
(
(forall x. AsciiAlphaNum -> Rep AsciiAlphaNum x)
-> (forall x. Rep AsciiAlphaNum x -> AsciiAlphaNum)
-> Generic AsciiAlphaNum
forall x. Rep AsciiAlphaNum x -> AsciiAlphaNum
forall x. AsciiAlphaNum -> Rep AsciiAlphaNum x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AsciiAlphaNum -> Rep AsciiAlphaNum x
from :: forall x. AsciiAlphaNum -> Rep AsciiAlphaNum x
$cto :: forall x. Rep AsciiAlphaNum x -> AsciiAlphaNum
to :: forall x. Rep AsciiAlphaNum x -> AsciiAlphaNum
Generic
)
instance Predicate AsciiAlphaNum Char where
validate :: Proxy AsciiAlphaNum -> Char -> Maybe RefineException
validate Proxy AsciiAlphaNum
proxy Char
c
| Char -> Bool
C.isAscii Char
c Bool -> Bool -> Bool
&& Char -> Bool
C.isAlphaNum Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AsciiAlphaNum -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AsciiAlphaNum
proxy) Text
err
where
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not alpha-numeric ascii"
instance Predicate AsciiAlphaNum Word8 where
validate :: Proxy AsciiAlphaNum -> Word8 -> Maybe RefineException
validate Proxy AsciiAlphaNum
proxy Word8
w
| Char -> Bool
C.isAscii Char
c Bool -> Bool -> Bool
&& Char -> Bool
C.isAlphaNum Char
c = Maybe RefineException
forall a. Maybe a
Nothing
| Bool
otherwise = RefineException -> Maybe RefineException
forall a. a -> Maybe a
Just (RefineException -> Maybe RefineException)
-> RefineException -> Maybe RefineException
forall a b. (a -> b) -> a -> b
$ TypeRep -> Text -> RefineException
RefineOtherException (Proxy AsciiAlphaNum -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Ty.typeRep Proxy AsciiAlphaNum
proxy) Text
err
where
c :: Char
c = Word8 -> Char
BS.w2c Word8
w
err :: Text
err = Char -> Text
T.singleton Char
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is not alpha-numeric ascii"