{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Data.SBV.Char (
elem, notElem
, ord, chr
, toLowerL1, toUpperL1
, digitToInt, intToDigit
, isControlL1, isSpaceL1, isLowerL1, isUpperL1, isAlphaL1, isAlphaNumL1, isPrintL1, isDigit, isOctDigit, isHexDigit
, isLetterL1, isMarkL1, isNumberL1, isPunctuationL1, isSymbolL1, isSeparatorL1
, isAscii, isLatin1, isAsciiUpper, isAsciiLower
) where
import Prelude hiding (elem, notElem)
import qualified Prelude as P
import Data.SBV.Core.Data
import Data.SBV.Core.Model
import qualified Data.Char as C
import Data.SBV.String (isInfixOf, singleton)
elem :: SChar -> SString -> SBool
SChar
c elem :: SChar -> SString -> SBool
`elem` SString
s
| Just String
cs <- SString -> Maybe String
forall a. SymVal a => SBV a -> Maybe a
unliteral SString
s, Just Char
cc <- SChar -> Maybe Char
forall a. SymVal a => SBV a -> Maybe a
unliteral SChar
c
= Bool -> SBool
forall a. SymVal a => a -> SBV a
literal (Char
cc Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`P.elem` String
cs)
| Just String
cs <- SString -> Maybe String
forall a. SymVal a => SBV a -> Maybe a
unliteral SString
s
= (SChar -> SBool) -> [SChar] -> SBool
forall a. (a -> SBool) -> [a] -> SBool
sAny (SChar
c SChar -> SChar -> SBool
forall a. EqSymbolic a => a -> a -> SBool
.==) ([SChar] -> SBool) -> [SChar] -> SBool
forall a b. (a -> b) -> a -> b
$ (Char -> SChar) -> String -> [SChar]
forall a b. (a -> b) -> [a] -> [b]
map Char -> SChar
forall a. SymVal a => a -> SBV a
literal String
cs
| Bool
True
= SChar -> SString
singleton SChar
c SString -> SString -> SBool
`isInfixOf` SString
s
notElem :: SChar -> SString -> SBool
SChar
c notElem :: SChar -> SString -> SBool
`notElem` SString
s = SBool -> SBool
sNot (SChar
c SChar -> SString -> SBool
`elem` SString
s)
ord :: SChar -> SInteger
ord :: SChar -> SInteger
ord SChar
c
| Just Char
cc <- SChar -> Maybe Char
forall a. SymVal a => SBV a -> Maybe a
unliteral SChar
c
= Integer -> SInteger
forall a. SymVal a => a -> SBV a
literal (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
C.ord Char
cc))
| Bool
True
= SVal -> SInteger
forall a. SVal -> SBV a
SBV (SVal -> SInteger) -> SVal -> SInteger
forall a b. (a -> b) -> a -> b
$ Kind -> Either CV (Cached SV) -> SVal
SVal Kind
KUnbounded (Either CV (Cached SV) -> SVal) -> Either CV (Cached SV) -> SVal
forall a b. (a -> b) -> a -> b
$ Cached SV -> Either CV (Cached SV)
forall a b. b -> Either a b
Right (Cached SV -> Either CV (Cached SV))
-> Cached SV -> Either CV (Cached SV)
forall a b. (a -> b) -> a -> b
$ (State -> IO SV) -> Cached SV
forall a. (State -> IO a) -> Cached a
cache State -> IO SV
r
where r :: State -> IO SV
r State
st = do SV
csv <- State -> SChar -> IO SV
forall a. State -> SBV a -> IO SV
sbvToSV State
st SChar
c
State -> Kind -> SBVExpr -> IO SV
newExpr State
st Kind
KUnbounded (Op -> [SV] -> SBVExpr
SBVApp (StrOp -> Op
StrOp StrOp
StrToCode) [SV
csv])
chr :: SInteger -> SChar
chr :: SInteger -> SChar
chr SInteger
w
| Just Integer
cw <- SInteger -> Maybe Integer
forall a. SymVal a => SBV a -> Maybe a
unliteral SInteger
w
= Char -> SChar
forall a. SymVal a => a -> SBV a
literal (Int -> Char
C.chr (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
cw))
| Bool
True
= SVal -> SChar
forall a. SVal -> SBV a
SBV (SVal -> SChar) -> SVal -> SChar
forall a b. (a -> b) -> a -> b
$ Kind -> Either CV (Cached SV) -> SVal
SVal Kind
KChar (Either CV (Cached SV) -> SVal) -> Either CV (Cached SV) -> SVal
forall a b. (a -> b) -> a -> b
$ Cached SV -> Either CV (Cached SV)
forall a b. b -> Either a b
Right (Cached SV -> Either CV (Cached SV))
-> Cached SV -> Either CV (Cached SV)
forall a b. (a -> b) -> a -> b
$ (State -> IO SV) -> Cached SV
forall a. (State -> IO a) -> Cached a
cache State -> IO SV
r
where r :: State -> IO SV
r State
st = do SV
wsv <- State -> SInteger -> IO SV
forall a. State -> SBV a -> IO SV
sbvToSV State
st SInteger
w
State -> Kind -> SBVExpr -> IO SV
newExpr State
st Kind
KChar (Op -> [SV] -> SBVExpr
SBVApp (StrOp -> Op
StrOp StrOp
StrFromCode) [SV
wsv])
liftFunL1 :: (Char -> Char) -> SChar -> SChar
liftFunL1 :: (Char -> Char) -> SChar -> SChar
liftFunL1 Char -> Char
f SChar
c = String -> SChar
walk String
kernel
where kernel :: String
kernel = [Char
g | Char
g <- (Int -> Char) -> [Int] -> String
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
C.chr [Int
0 .. Int
255], Char
g Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char -> Char
f Char
g]
walk :: String -> SChar
walk [] = SChar
c
walk (Char
d:String
ds) = SBool -> SChar -> SChar -> SChar
forall a. Mergeable a => SBool -> a -> a -> a
ite (Char -> SChar
forall a. SymVal a => a -> SBV a
literal Char
d SChar -> SChar -> SBool
forall a. EqSymbolic a => a -> a -> SBool
.== SChar
c) (Char -> SChar
forall a. SymVal a => a -> SBV a
literal (Char -> Char
f Char
d)) (String -> SChar
walk String
ds)
liftPredL1 :: (Char -> Bool) -> SChar -> SBool
liftPredL1 :: (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
predicate SChar
c = SChar
c SChar -> [SChar] -> SBool
forall a. EqSymbolic a => a -> [a] -> SBool
`sElem` [Char -> SChar
forall a. SymVal a => a -> SBV a
literal Char
g | Char
g <- (Int -> Char) -> [Int] -> String
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
C.chr [Int
0 .. Int
255], Char -> Bool
predicate Char
g]
toLowerL1 :: SChar -> SChar
toLowerL1 :: SChar -> SChar
toLowerL1 = (Char -> Char) -> SChar -> SChar
liftFunL1 Char -> Char
C.toLower
toUpperL1 :: SChar -> SChar
toUpperL1 :: SChar -> SChar
toUpperL1 = (Char -> Char) -> SChar -> SChar
liftFunL1 Char -> Char
C.toUpper
digitToInt :: SChar -> SInteger
digitToInt :: SChar -> SInteger
digitToInt SChar
c = SBool -> SInteger -> SInteger -> SInteger
forall a. Mergeable a => SBool -> a -> a -> a
ite (SChar
uc SChar -> SString -> SBool
`elem` SString
"0123456789") (SInteger -> SInteger
forall a b.
(Integral a, HasKind a, Num a, SymVal a, HasKind b, Num b,
SymVal b) =>
SBV a -> SBV b
sFromIntegral (SInteger
o SInteger -> SInteger -> SInteger
forall a. Num a => a -> a -> a
- SChar -> SInteger
ord (Char -> SChar
forall a. SymVal a => a -> SBV a
literal Char
'0')))
(SInteger -> SInteger) -> SInteger -> SInteger
forall a b. (a -> b) -> a -> b
$ SBool -> SInteger -> SInteger -> SInteger
forall a. Mergeable a => SBool -> a -> a -> a
ite (SChar
uc SChar -> SString -> SBool
`elem` SString
"ABCDEF") (SInteger -> SInteger
forall a b.
(Integral a, HasKind a, Num a, SymVal a, HasKind b, Num b,
SymVal b) =>
SBV a -> SBV b
sFromIntegral (SInteger
o SInteger -> SInteger -> SInteger
forall a. Num a => a -> a -> a
- SChar -> SInteger
ord (Char -> SChar
forall a. SymVal a => a -> SBV a
literal Char
'A') SInteger -> SInteger -> SInteger
forall a. Num a => a -> a -> a
+ SInteger
10))
(SInteger -> SInteger) -> SInteger -> SInteger
forall a b. (a -> b) -> a -> b
$ -SInteger
1
where uc :: SChar
uc = SChar -> SChar
toUpperL1 SChar
c
o :: SInteger
o = SChar -> SInteger
ord SChar
uc
intToDigit :: SInteger -> SChar
intToDigit :: SInteger -> SChar
intToDigit SInteger
i = SBool -> SChar -> SChar -> SChar
forall a. Mergeable a => SBool -> a -> a -> a
ite (SInteger
i SInteger -> SInteger -> SBool
forall a. OrdSymbolic a => a -> a -> SBool
.>= SInteger
0 SBool -> SBool -> SBool
.&& SInteger
i SInteger -> SInteger -> SBool
forall a. OrdSymbolic a => a -> a -> SBool
.<= SInteger
9) (SInteger -> SChar
chr (SInteger -> SInteger
forall a b.
(Integral a, HasKind a, Num a, SymVal a, HasKind b, Num b,
SymVal b) =>
SBV a -> SBV b
sFromIntegral SInteger
i SInteger -> SInteger -> SInteger
forall a. Num a => a -> a -> a
+ SChar -> SInteger
ord (Char -> SChar
forall a. SymVal a => a -> SBV a
literal Char
'0')))
(SChar -> SChar) -> SChar -> SChar
forall a b. (a -> b) -> a -> b
$ SBool -> SChar -> SChar -> SChar
forall a. Mergeable a => SBool -> a -> a -> a
ite (SInteger
i SInteger -> SInteger -> SBool
forall a. OrdSymbolic a => a -> a -> SBool
.>= SInteger
10 SBool -> SBool -> SBool
.&& SInteger
i SInteger -> SInteger -> SBool
forall a. OrdSymbolic a => a -> a -> SBool
.<= SInteger
15) (SInteger -> SChar
chr (SInteger -> SInteger
forall a b.
(Integral a, HasKind a, Num a, SymVal a, HasKind b, Num b,
SymVal b) =>
SBV a -> SBV b
sFromIntegral SInteger
i SInteger -> SInteger -> SInteger
forall a. Num a => a -> a -> a
+ SChar -> SInteger
ord (Char -> SChar
forall a. SymVal a => a -> SBV a
literal Char
'a') SInteger -> SInteger -> SInteger
forall a. Num a => a -> a -> a
- SInteger
10))
(SChar -> SChar) -> SChar -> SChar
forall a b. (a -> b) -> a -> b
$ Char -> SChar
forall a. SymVal a => a -> SBV a
literal Char
' '
isControlL1 :: SChar -> SBool
isControlL1 :: SChar -> SBool
isControlL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isControl
isSpaceL1 :: SChar -> SBool
isSpaceL1 :: SChar -> SBool
isSpaceL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isSpace
isLowerL1 :: SChar -> SBool
isLowerL1 :: SChar -> SBool
isLowerL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isLower
isUpperL1 :: SChar -> SBool
isUpperL1 :: SChar -> SBool
isUpperL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isUpper
isAlphaL1 :: SChar -> SBool
isAlphaL1 :: SChar -> SBool
isAlphaL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isAlpha
isAlphaNumL1 :: SChar -> SBool
isAlphaNumL1 :: SChar -> SBool
isAlphaNumL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isAlphaNum
isPrintL1 :: SChar -> SBool
isPrintL1 :: SChar -> SBool
isPrintL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isPrint
isDigit :: SChar -> SBool
isDigit :: SChar -> SBool
isDigit = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isDigit
isOctDigit :: SChar -> SBool
isOctDigit :: SChar -> SBool
isOctDigit = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isOctDigit
isHexDigit :: SChar -> SBool
isHexDigit :: SChar -> SBool
isHexDigit = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isHexDigit
isLetterL1 :: SChar -> SBool
isLetterL1 :: SChar -> SBool
isLetterL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isLetter
isMarkL1 :: SChar -> SBool
isMarkL1 :: SChar -> SBool
isMarkL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isMark
isNumberL1 :: SChar -> SBool
isNumberL1 :: SChar -> SBool
isNumberL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isNumber
isPunctuationL1 :: SChar -> SBool
isPunctuationL1 :: SChar -> SBool
isPunctuationL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isPunctuation
isSymbolL1 :: SChar -> SBool
isSymbolL1 :: SChar -> SBool
isSymbolL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isSymbol
isSeparatorL1 :: SChar -> SBool
isSeparatorL1 :: SChar -> SBool
isSeparatorL1 = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isSeparator
isAscii :: SChar -> SBool
isAscii :: SChar -> SBool
isAscii SChar
c = SChar -> SInteger
ord SChar
c SInteger -> SInteger -> SBool
forall a. OrdSymbolic a => a -> a -> SBool
.< SInteger
128
isLatin1 :: SChar -> SBool
isLatin1 :: SChar -> SBool
isLatin1 SChar
c = SChar -> SInteger
ord SChar
c SInteger -> SInteger -> SBool
forall a. OrdSymbolic a => a -> a -> SBool
.< SInteger
256
isAsciiUpper :: SChar -> SBool
isAsciiUpper :: SChar -> SBool
isAsciiUpper = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isAsciiUpper
isAsciiLower :: SChar -> SBool
isAsciiLower :: SChar -> SBool
isAsciiLower = (Char -> Bool) -> SChar -> SBool
liftPredL1 Char -> Bool
C.isAsciiLower