{-# LANGUAGE CPP #-}
module Flat.Instances.Text(
UTF8Text(..)
#if! defined(ghcjs_HOST_OS) && ! defined (ETA_VERSION) && ! defined (ETA)
,UTF16Text(..)
#endif
) where
import Flat.Instances.Util
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
instance Flat T.Text where
size :: Text -> NumBits -> NumBits
size = Text -> NumBits -> NumBits
sUTF8Max
encode :: Text -> Encoding
encode = Text -> Encoding
eUTF8
decode :: Get Text
decode = Get Text
dUTF8
instance Flat TL.Text where
size :: Text -> NumBits -> NumBits
size = Text -> NumBits -> NumBits
sUTF8Max (Text -> NumBits -> NumBits)
-> (Text -> Text) -> Text -> NumBits -> NumBits
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.toStrict
encode :: Text -> Encoding
encode = Text -> Encoding
eUTF8 (Text -> Encoding) -> (Text -> Text) -> Text -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.toStrict
decode :: Get Text
decode = Text -> Text
TL.fromStrict (Text -> Text) -> Get Text -> Get Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
dUTF8
newtype UTF8Text = UTF8Text {UTF8Text -> Text
unUTF8::T.Text} deriving (UTF8Text -> UTF8Text -> Bool
(UTF8Text -> UTF8Text -> Bool)
-> (UTF8Text -> UTF8Text -> Bool) -> Eq UTF8Text
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UTF8Text -> UTF8Text -> Bool
$c/= :: UTF8Text -> UTF8Text -> Bool
== :: UTF8Text -> UTF8Text -> Bool
$c== :: UTF8Text -> UTF8Text -> Bool
Eq,Eq UTF8Text
Eq UTF8Text
-> (UTF8Text -> UTF8Text -> Ordering)
-> (UTF8Text -> UTF8Text -> Bool)
-> (UTF8Text -> UTF8Text -> Bool)
-> (UTF8Text -> UTF8Text -> Bool)
-> (UTF8Text -> UTF8Text -> Bool)
-> (UTF8Text -> UTF8Text -> UTF8Text)
-> (UTF8Text -> UTF8Text -> UTF8Text)
-> Ord UTF8Text
UTF8Text -> UTF8Text -> Bool
UTF8Text -> UTF8Text -> Ordering
UTF8Text -> UTF8Text -> UTF8Text
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UTF8Text -> UTF8Text -> UTF8Text
$cmin :: UTF8Text -> UTF8Text -> UTF8Text
max :: UTF8Text -> UTF8Text -> UTF8Text
$cmax :: UTF8Text -> UTF8Text -> UTF8Text
>= :: UTF8Text -> UTF8Text -> Bool
$c>= :: UTF8Text -> UTF8Text -> Bool
> :: UTF8Text -> UTF8Text -> Bool
$c> :: UTF8Text -> UTF8Text -> Bool
<= :: UTF8Text -> UTF8Text -> Bool
$c<= :: UTF8Text -> UTF8Text -> Bool
< :: UTF8Text -> UTF8Text -> Bool
$c< :: UTF8Text -> UTF8Text -> Bool
compare :: UTF8Text -> UTF8Text -> Ordering
$ccompare :: UTF8Text -> UTF8Text -> Ordering
$cp1Ord :: Eq UTF8Text
Ord,NumBits -> UTF8Text -> ShowS
[UTF8Text] -> ShowS
UTF8Text -> String
(NumBits -> UTF8Text -> ShowS)
-> (UTF8Text -> String) -> ([UTF8Text] -> ShowS) -> Show UTF8Text
forall a.
(NumBits -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UTF8Text] -> ShowS
$cshowList :: [UTF8Text] -> ShowS
show :: UTF8Text -> String
$cshow :: UTF8Text -> String
showsPrec :: NumBits -> UTF8Text -> ShowS
$cshowsPrec :: NumBits -> UTF8Text -> ShowS
Show)
instance Flat UTF8Text where
size :: UTF8Text -> NumBits -> NumBits
size (UTF8Text Text
t) = Text -> NumBits -> NumBits
sUTF8Max Text
t
encode :: UTF8Text -> Encoding
encode (UTF8Text Text
t) = Text -> Encoding
eUTF8 Text
t
decode :: Get UTF8Text
decode = Text -> UTF8Text
UTF8Text (Text -> UTF8Text) -> Get Text -> Get UTF8Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
dUTF8
#if ! defined(ghcjs_HOST_OS) && ! defined (ETA_VERSION) && ! defined (ETA)
newtype UTF16Text = UTF16Text {UTF16Text -> Text
unUTF16::T.Text} deriving (UTF16Text -> UTF16Text -> Bool
(UTF16Text -> UTF16Text -> Bool)
-> (UTF16Text -> UTF16Text -> Bool) -> Eq UTF16Text
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UTF16Text -> UTF16Text -> Bool
$c/= :: UTF16Text -> UTF16Text -> Bool
== :: UTF16Text -> UTF16Text -> Bool
$c== :: UTF16Text -> UTF16Text -> Bool
Eq,Eq UTF16Text
Eq UTF16Text
-> (UTF16Text -> UTF16Text -> Ordering)
-> (UTF16Text -> UTF16Text -> Bool)
-> (UTF16Text -> UTF16Text -> Bool)
-> (UTF16Text -> UTF16Text -> Bool)
-> (UTF16Text -> UTF16Text -> Bool)
-> (UTF16Text -> UTF16Text -> UTF16Text)
-> (UTF16Text -> UTF16Text -> UTF16Text)
-> Ord UTF16Text
UTF16Text -> UTF16Text -> Bool
UTF16Text -> UTF16Text -> Ordering
UTF16Text -> UTF16Text -> UTF16Text
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UTF16Text -> UTF16Text -> UTF16Text
$cmin :: UTF16Text -> UTF16Text -> UTF16Text
max :: UTF16Text -> UTF16Text -> UTF16Text
$cmax :: UTF16Text -> UTF16Text -> UTF16Text
>= :: UTF16Text -> UTF16Text -> Bool
$c>= :: UTF16Text -> UTF16Text -> Bool
> :: UTF16Text -> UTF16Text -> Bool
$c> :: UTF16Text -> UTF16Text -> Bool
<= :: UTF16Text -> UTF16Text -> Bool
$c<= :: UTF16Text -> UTF16Text -> Bool
< :: UTF16Text -> UTF16Text -> Bool
$c< :: UTF16Text -> UTF16Text -> Bool
compare :: UTF16Text -> UTF16Text -> Ordering
$ccompare :: UTF16Text -> UTF16Text -> Ordering
$cp1Ord :: Eq UTF16Text
Ord,NumBits -> UTF16Text -> ShowS
[UTF16Text] -> ShowS
UTF16Text -> String
(NumBits -> UTF16Text -> ShowS)
-> (UTF16Text -> String)
-> ([UTF16Text] -> ShowS)
-> Show UTF16Text
forall a.
(NumBits -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UTF16Text] -> ShowS
$cshowList :: [UTF16Text] -> ShowS
show :: UTF16Text -> String
$cshow :: UTF16Text -> String
showsPrec :: NumBits -> UTF16Text -> ShowS
$cshowsPrec :: NumBits -> UTF16Text -> ShowS
Show)
instance Flat UTF16Text where
size :: UTF16Text -> NumBits -> NumBits
size (UTF16Text Text
t) = Text -> NumBits -> NumBits
sUTF16 Text
t
encode :: UTF16Text -> Encoding
encode (UTF16Text Text
t) = Text -> Encoding
eUTF16 Text
t
decode :: Get UTF16Text
decode = Text -> UTF16Text
UTF16Text (Text -> UTF16Text) -> Get Text -> Get UTF16Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Text
dUTF16
#endif