{-# LANGUAGE CPP                #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
module Distribution.Utils.ShortText
    ( 
      ShortText
    , toShortText
    , fromShortText
    , unsafeFromUTF8BS
      
    , null
    , length
      
    , decodeStringUtf8
    , encodeStringUtf8
    ) where
import Distribution.Compat.Prelude hiding (length, null)
import Prelude ()
import Distribution.Utils.String     (decodeStringUtf8, encodeStringUtf8)
import Distribution.Utils.Structured (Structured (..), nominalStructure)
#if defined(MIN_VERSION_bytestring)
# if MIN_VERSION_bytestring(0,10,4)
# define HAVE_SHORTBYTESTRING 1
# endif
#endif
#ifndef MIN_VERSION_binary
#define MIN_VERSION_binary(x, y, z) 0
#endif
import qualified Data.ByteString as BS
import qualified Data.List       as List
#if HAVE_SHORTBYTESTRING
import qualified Data.ByteString.Short as BS.Short
#else
import Distribution.Utils.Generic (fromUTF8BS)
#endif
toShortText :: String -> ShortText
fromShortText :: ShortText -> String
unsafeFromUTF8BS :: BS.ByteString -> ShortText
null :: ShortText -> Bool
#if HAVE_SHORTBYTESTRING
newtype ShortText = ST { ShortText -> ShortByteString
unST :: BS.Short.ShortByteString }
                  deriving (ShortText -> ShortText -> Bool
(ShortText -> ShortText -> Bool)
-> (ShortText -> ShortText -> Bool) -> Eq ShortText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShortText -> ShortText -> Bool
$c/= :: ShortText -> ShortText -> Bool
== :: ShortText -> ShortText -> Bool
$c== :: ShortText -> ShortText -> Bool
Eq,Eq ShortText
Eq ShortText
-> (ShortText -> ShortText -> Ordering)
-> (ShortText -> ShortText -> Bool)
-> (ShortText -> ShortText -> Bool)
-> (ShortText -> ShortText -> Bool)
-> (ShortText -> ShortText -> Bool)
-> (ShortText -> ShortText -> ShortText)
-> (ShortText -> ShortText -> ShortText)
-> Ord ShortText
ShortText -> ShortText -> Bool
ShortText -> ShortText -> Ordering
ShortText -> ShortText -> ShortText
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 :: ShortText -> ShortText -> ShortText
$cmin :: ShortText -> ShortText -> ShortText
max :: ShortText -> ShortText -> ShortText
$cmax :: ShortText -> ShortText -> ShortText
>= :: ShortText -> ShortText -> Bool
$c>= :: ShortText -> ShortText -> Bool
> :: ShortText -> ShortText -> Bool
$c> :: ShortText -> ShortText -> Bool
<= :: ShortText -> ShortText -> Bool
$c<= :: ShortText -> ShortText -> Bool
< :: ShortText -> ShortText -> Bool
$c< :: ShortText -> ShortText -> Bool
compare :: ShortText -> ShortText -> Ordering
$ccompare :: ShortText -> ShortText -> Ordering
$cp1Ord :: Eq ShortText
Ord,(forall x. ShortText -> Rep ShortText x)
-> (forall x. Rep ShortText x -> ShortText) -> Generic ShortText
forall x. Rep ShortText x -> ShortText
forall x. ShortText -> Rep ShortText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ShortText x -> ShortText
$cfrom :: forall x. ShortText -> Rep ShortText x
Generic,Typeable ShortText
DataType
Constr
Typeable ShortText
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> ShortText -> c ShortText)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ShortText)
-> (ShortText -> Constr)
-> (ShortText -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ShortText))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortText))
-> ((forall b. Data b => b -> b) -> ShortText -> ShortText)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ShortText -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ShortText -> r)
-> (forall u. (forall d. Data d => d -> u) -> ShortText -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ShortText -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ShortText -> m ShortText)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ShortText -> m ShortText)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ShortText -> m ShortText)
-> Data ShortText
ShortText -> DataType
ShortText -> Constr
(forall b. Data b => b -> b) -> ShortText -> ShortText
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortText -> c ShortText
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortText
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ShortText -> u
forall u. (forall d. Data d => d -> u) -> ShortText -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortText -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortText -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ShortText -> m ShortText
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortText -> m ShortText
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortText
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortText -> c ShortText
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortText)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortText)
$cST :: Constr
$tShortText :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ShortText -> m ShortText
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortText -> m ShortText
gmapMp :: (forall d. Data d => d -> m d) -> ShortText -> m ShortText
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortText -> m ShortText
gmapM :: (forall d. Data d => d -> m d) -> ShortText -> m ShortText
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ShortText -> m ShortText
gmapQi :: Int -> (forall d. Data d => d -> u) -> ShortText -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ShortText -> u
gmapQ :: (forall d. Data d => d -> u) -> ShortText -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ShortText -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortText -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortText -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortText -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortText -> r
gmapT :: (forall b. Data b => b -> b) -> ShortText -> ShortText
$cgmapT :: (forall b. Data b => b -> b) -> ShortText -> ShortText
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortText)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortText)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ShortText)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortText)
dataTypeOf :: ShortText -> DataType
$cdataTypeOf :: ShortText -> DataType
toConstr :: ShortText -> Constr
$ctoConstr :: ShortText -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortText
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortText
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortText -> c ShortText
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortText -> c ShortText
$cp1Data :: Typeable ShortText
Data,Typeable)
# if MIN_VERSION_binary(0,8,1)
instance Binary ShortText where
    put :: ShortText -> Put
put = ShortByteString -> Put
forall t. Binary t => t -> Put
put (ShortByteString -> Put)
-> (ShortText -> ShortByteString) -> ShortText -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
unST
    get :: Get ShortText
get = (ShortByteString -> ShortText)
-> Get ShortByteString -> Get ShortText
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShortByteString -> ShortText
ST Get ShortByteString
forall t. Binary t => Get t
get
# else
instance Binary ShortText where
    put = put . BS.Short.fromShort . unST
    get = fmap (ST . BS.Short.toShort) get
# endif
toShortText :: String -> ShortText
toShortText = ShortByteString -> ShortText
ST (ShortByteString -> ShortText)
-> (String -> ShortByteString) -> String -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ShortByteString
BS.Short.pack ([Word8] -> ShortByteString)
-> (String -> [Word8]) -> String -> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [Word8]
encodeStringUtf8
fromShortText :: ShortText -> String
fromShortText = [Word8] -> String
decodeStringUtf8 ([Word8] -> String)
-> (ShortText -> [Word8]) -> ShortText -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
BS.Short.unpack (ShortByteString -> [Word8])
-> (ShortText -> ShortByteString) -> ShortText -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
unST
unsafeFromUTF8BS :: ByteString -> ShortText
unsafeFromUTF8BS = ShortByteString -> ShortText
ST (ShortByteString -> ShortText)
-> (ByteString -> ShortByteString) -> ByteString -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortByteString
BS.Short.toShort
null :: ShortText -> Bool
null = ShortByteString -> Bool
BS.Short.null (ShortByteString -> Bool)
-> (ShortText -> ShortByteString) -> ShortText -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
unST
#else
newtype ShortText = ST { unST :: String }
                  deriving (Eq,Ord,Generic,Data,Typeable)
instance Binary ShortText where
    put = put . encodeStringUtf8 . unST
    get = fmap (ST . decodeStringUtf8) get
toShortText = ST
fromShortText = unST
unsafeFromUTF8BS = ST . fromUTF8BS
null = List.null . unST
#endif
instance Structured ShortText where structure :: Proxy ShortText -> Structure
structure = Proxy ShortText -> Structure
forall k (a :: k). Typeable a => Proxy a -> Structure
nominalStructure
instance NFData ShortText where
    rnf :: ShortText -> ()
rnf = ShortByteString -> ()
forall a. NFData a => a -> ()
rnf (ShortByteString -> ())
-> (ShortText -> ShortByteString) -> ShortText -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
unST
instance Show ShortText where
    show :: ShortText -> String
show = ShowS
forall a. Show a => a -> String
show ShowS -> (ShortText -> String) -> ShortText -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> String
fromShortText
instance Read ShortText where
    readsPrec :: Int -> ReadS ShortText
readsPrec Int
p = ((String, String) -> (ShortText, String))
-> [(String, String)] -> [(ShortText, String)]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> ShortText) -> (String, String) -> (ShortText, String)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first String -> ShortText
toShortText) ([(String, String)] -> [(ShortText, String)])
-> (String -> [(String, String)]) -> ReadS ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> [(String, String)]
forall a. Read a => Int -> ReadS a
readsPrec Int
p
instance Semigroup ShortText where
    ST ShortByteString
a <> :: ShortText -> ShortText -> ShortText
<> ST ShortByteString
b = ShortByteString -> ShortText
ST (ShortByteString -> ShortByteString -> ShortByteString
forall a. Monoid a => a -> a -> a
mappend ShortByteString
a ShortByteString
b)
instance Monoid ShortText where
    mempty :: ShortText
mempty = ShortByteString -> ShortText
ST ShortByteString
forall a. Monoid a => a
mempty
    mappend :: ShortText -> ShortText -> ShortText
mappend = ShortText -> ShortText -> ShortText
forall a. Semigroup a => a -> a -> a
(<>)
instance IsString ShortText where
    fromString :: String -> ShortText
fromString = String -> ShortText
toShortText
length :: ShortText -> Int
length :: ShortText -> Int
length = String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
List.length (String -> Int) -> (ShortText -> String) -> ShortText -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> String
fromShortText