Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Restrictions "r-ban:"
cover commonly used fixed (short) size strings with restricted
characters such as GUID, credit card numbers, etc.
Alphanumeric chars are ordered: 0-9
followed by A-Z
,
followed by a-z
. Annotation specifies upper character bound.
Any non alpha numeric characters are considered fixed delimiters
and need to be present exactly as specified.
For example "r-ban:999-99-9999"
could be used to describe SSN numbers,
@"r-ban:FFFF" would describe strings consisting of 4 hex digits.
This is a simple implementation that converts to String
, should be used
only with short length data.
This module does not create instances of EncodeF
typeclass to avoid duplicate instance issues.
Decoding function decFR
is located in
Data.TypedEncoding.Combinators.Restriction.Common
Use recWithEncR
to create manual recovery step that can be combined with recreateFPart
.
Since: 0.2.1.0
Synopsis
- type family IsBan (s :: Symbol) :: Bool where ...
- encFBan :: forall f s t xs c str. (IsStringR str, KnownSymbol s, IsBan s ~ True, f ~ Either EncodeEx) => Enc xs c str -> f (Enc (s ': xs) c str)
- verifyBoundedAlphaNum :: forall s a str. (KnownSymbol s, IsStringR str) => Proxy s -> str -> Either String str
Documentation
>>>
:set -XOverloadedStrings -XMultiParamTypeClasses -XDataKinds -XTypeApplications
>>>
import qualified Data.Text as T
>>>
import Data.TypedEncoding.Combinators.Restriction.Common
encFBan :: forall f s t xs c str. (IsStringR str, KnownSymbol s, IsBan s ~ True, f ~ Either EncodeEx) => Enc xs c str -> f (Enc (s ': xs) c str) Source #
>>>
encFBan . toEncoding () $ "C59F9FB7-4621-44D9-9020-CE37BF6E2BD1" :: Either EncodeEx (Enc '["r-ban:FFFFFFFF-FFFF-FFFF-FFFF-FFFFFFFFFFFF"] () T.Text)
Right (MkEnc Proxy () "C59F9FB7-4621-44D9-9020-CE37BF6E2BD1")
>>>
recWithEncR encFBan . toEncoding () $ "211-22-9934" :: Either RecreateEx (Enc '["r-ban:999-99-9999"] () T.Text)
Right (MkEnc Proxy () "211-22-9934")
verifyBoundedAlphaNum :: forall s a str. (KnownSymbol s, IsStringR str) => Proxy s -> str -> Either String str Source #
>>>
verifyBoundedAlphaNum (Proxy :: Proxy "r-ban:FF-FF") (T.pack "12-3E")
Right "12-3E">>>
verifyBoundedAlphaNum (Proxy :: Proxy "r-ban:FF-FF") (T.pack "1G-3E")
Left "'G' not boulded by 'F'">>>
verifyBoundedAlphaNum (Proxy :: Proxy "r-ban:FF-FF") (T.pack "13G3E")
Left "'G' not matching '-'">>>
verifyBoundedAlphaNum (Proxy :: Proxy "r-ban:FF-FF") (T.pack "13-234")
Left "Input list has wrong size expecting 5 but length \"13-234\" == 6"