module Agda.Utils.Char where
import Data.Char
replacementChar :: Char
replacementChar :: Char
replacementChar = Char
'\xFFFD'
isSurrogateCodePoint :: Char -> Bool
isSurrogateCodePoint :: Char -> Bool
isSurrogateCodePoint Char
c = Char -> GeneralCategory
generalCategory Char
c forall a. Eq a => a -> a -> Bool
== GeneralCategory
Surrogate
replaceSurrogateCodePoint :: Char -> Char
replaceSurrogateCodePoint :: Char -> Char
replaceSurrogateCodePoint Char
c
| Char -> Bool
isSurrogateCodePoint Char
c = Char
replacementChar
| Bool
otherwise = Char
c
integerToChar :: Integer -> Char
integerToChar :: Integer -> Char
integerToChar = Char -> Char
replaceSurrogateCodePoint forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Integral a => a -> a -> a
`mod` Integer
0x110000)