{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
module To
(
ToVector(..),
ToUnboxedVector(..),
ToStorableVector(..),
ToMap(..),
ToHashMap(..),
ToIntMap(..),
ToSet(..),
ToHashSet(..),
ToIntSet(..),
ToString(..),
Utf8ToString(..),
ToText(..),
Utf8ToText(..),
ToLazyText(..),
Utf8ToLazyText(..),
ToTextBuilder(..),
Utf8ToTextBuilder(..),
ToByteString(..),
ToUtf8ByteString(..),
ToLazyByteString(..),
ToUtf8LazyByteString(..),
)
where
import GHC.TypeLits (TypeError, ErrorMessage(..))
import Data.Hashable
import qualified Data.List.NonEmpty as NE
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Generic as VG
import qualified Data.Map.Lazy as ML
import qualified Data.IntMap.Lazy as IML
import qualified Data.Set as S
import qualified Data.IntSet as IS
import qualified Data.HashMap.Lazy as HML
import qualified Data.HashSet as HS
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Encoding.Error as T
import qualified Data.Text.Lazy.Builder as TB
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Lazy.UTF8 as UTF8L
import qualified Data.ByteString.UTF8 as UTF8
class ToVector a e where
toVector :: a -> V.Vector e
instance ToVector [a] a where
toVector = V.fromList
{-# INLINE toVector #-}
instance ToVector (NE.NonEmpty a) a where
toVector = V.fromList . NE.toList
{-# INLINE toVector #-}
instance VU.Unbox a => ToVector (VU.Vector a) a where
toVector = VG.convert
{-# INLINE toVector #-}
instance VS.Storable a => ToVector (VS.Vector a) a where
toVector = VG.convert
{-# INLINE toVector #-}
class ToUnboxedVector a e where
toUnboxedVector :: a -> VU.Vector e
instance VU.Unbox a => ToUnboxedVector [a] a where
toUnboxedVector = VU.fromList
{-# INLINE toUnboxedVector #-}
instance VU.Unbox a => ToUnboxedVector (NE.NonEmpty a) a where
toUnboxedVector = VU.fromList . NE.toList
{-# INLINE toUnboxedVector #-}
instance VU.Unbox a => ToUnboxedVector (V.Vector a) a where
toUnboxedVector = VG.convert
{-# INLINE toUnboxedVector #-}
instance (VU.Unbox a, VS.Storable a) => ToUnboxedVector (VS.Vector a) a where
toUnboxedVector = VG.convert
{-# INLINE toUnboxedVector #-}
class ToStorableVector a e where
toStorableVector :: a -> VS.Vector e
instance VS.Storable a => ToStorableVector [a] a where
toStorableVector = VS.fromList
{-# INLINE toStorableVector #-}
instance VS.Storable a => ToStorableVector (NE.NonEmpty a) a where
toStorableVector = VS.fromList . NE.toList
{-# INLINE toStorableVector #-}
instance VS.Storable a => ToStorableVector (V.Vector a) a where
toStorableVector = VG.convert
{-# INLINE toStorableVector #-}
instance (VU.Unbox a, VS.Storable a) => ToStorableVector (VU.Vector a) a where
toStorableVector = VG.convert
{-# INLINE toStorableVector #-}
class ToMap a k v | a -> k v, a k -> v, a v -> k where
toMap :: a -> ML.Map k v
instance (kv ~ (k, v), Ord k) => ToMap [kv] k v where
toMap = ML.fromList
{-# INLINE toMap #-}
instance (kv ~ (k, v), Ord k) => ToMap (NE.NonEmpty kv) k v where
toMap = ML.fromList . NE.toList
{-# INLINE toMap #-}
instance Ord k => ToMap (HML.HashMap k v) k v where
toMap = HML.foldlWithKey' (\m k v -> ML.insert k v m) mempty
{-# INLINE toMap #-}
instance ToMap (IML.IntMap v) Int v where
toMap = ML.fromDistinctAscList . IML.toAscList
{-# INLINE toMap #-}
class ToSet a k | a -> k where
toSet :: a -> S.Set k
instance Ord k => ToSet [k] k where
toSet = S.fromList
{-# INLINE toSet #-}
instance Ord k => ToSet (NE.NonEmpty k) k where
toSet = S.fromList . NE.toList
{-# INLINE toSet #-}
instance Ord k => ToSet (HS.HashSet k) k where
toSet = HS.foldl' (flip S.insert) mempty
{-# INLINE toSet #-}
instance ToSet IS.IntSet Int where
toSet = S.fromDistinctAscList . IS.toAscList
{-# INLINE toSet #-}
class ToIntMap a v | a -> v where
toIntMap :: a -> IML.IntMap v
instance (kv ~ (Int, v)) => ToIntMap [kv] v where
toIntMap = IML.fromList
{-# INLINE toIntMap #-}
instance (kv ~ (Int, v)) => ToIntMap (NE.NonEmpty kv) v where
toIntMap = IML.fromList . NE.toList
{-# INLINE toIntMap #-}
instance ToIntMap (ML.Map Int v) v where
toIntMap = IML.fromDistinctAscList . ML.toAscList
{-# INLINE toIntMap #-}
instance ToIntMap (HML.HashMap Int v) v where
toIntMap = HML.foldlWithKey' (\m k v -> IML.insert k v m) mempty
{-# INLINE toIntMap #-}
class ToIntSet a where
toIntSet :: a -> IS.IntSet
instance (k ~ Int) => ToIntSet [k] where
toIntSet = IS.fromList
{-# INLINE toIntSet #-}
instance (k ~ Int) => ToIntSet (NE.NonEmpty k) where
toIntSet = IS.fromList . NE.toList
{-# INLINE toIntSet #-}
instance ToIntSet (S.Set Int) where
toIntSet = IS.fromDistinctAscList . S.toAscList
{-# INLINE toIntSet #-}
instance ToIntSet (HS.HashSet Int) where
toIntSet = HS.foldl' (flip IS.insert) mempty
{-# INLINE toIntSet #-}
class ToHashMap a k v | a -> k v, a k -> v, a v -> k where
toHashMap :: a -> HML.HashMap k v
instance (kv ~ (k, v), Eq k, Hashable k) => ToHashMap [kv] k v where
toHashMap = HML.fromList
{-# INLINE toHashMap #-}
instance (kv ~ (k, v), Eq k, Hashable k) => ToHashMap (NE.NonEmpty kv) k v where
toHashMap = HML.fromList . NE.toList
{-# INLINE toHashMap #-}
instance (Eq k, Hashable k) => ToHashMap (ML.Map k v) k v where
toHashMap = ML.foldlWithKey' (\m k v -> HML.insert k v m) mempty
{-# INLINE toHashMap #-}
instance ToHashMap (IML.IntMap v) Int v where
toHashMap = IML.foldlWithKey' (\m k v -> HML.insert k v m) mempty
{-# INLINE toHashMap #-}
class ToHashSet a k | a -> k where
toHashSet :: a -> HS.HashSet k
instance (Eq k, Hashable k) => ToHashSet (NE.NonEmpty k) k where
toHashSet = HS.fromList . NE.toList
{-# INLINE toHashSet #-}
instance (Eq k, Hashable k) => ToHashSet (S.Set k) k where
toHashSet = S.foldl' (flip HS.insert) mempty
{-# INLINE toHashSet #-}
instance ToHashSet IS.IntSet Int where
toHashSet = IS.foldl' (flip HS.insert) mempty
{-# INLINE toHashSet #-}
class ToText a where
toText :: a -> T.Text
instance (a ~ Char) => ToText [a] where
toText = T.pack
{-# INLINE toText #-}
instance ToText TL.Text where
toText = TL.toStrict
{-# INLINE toText #-}
instance ToText TB.Builder where
toText = TL.toStrict . TB.toLazyText
{-# INLINE toText #-}
instance TypeError (SpecifyDecoding BS.ByteString "utf8ToText") =>
ToText BS.ByteString where
toText = error "unreachable"
instance TypeError (SpecifyDecoding BSL.ByteString "utf8ToText") =>
ToText BSL.ByteString where
toText = error "unreachable"
class ToLazyText a where
toLazyText :: a -> TL.Text
instance (a ~ Char) => ToLazyText [a] where
toLazyText = TL.pack
{-# INLINE toLazyText #-}
instance ToLazyText T.Text where
toLazyText = TL.fromStrict
{-# INLINE toLazyText #-}
instance ToLazyText TB.Builder where
toLazyText = TB.toLazyText
{-# INLINE toLazyText #-}
instance TypeError (SpecifyDecoding BS.ByteString "utf8ToLazyText") =>
ToLazyText BS.ByteString where
toLazyText = error "unreachable"
instance TypeError (SpecifyDecoding BSL.ByteString "utf8ToLazyText") =>
ToLazyText BSL.ByteString where
toLazyText = error "unreachable"
class ToTextBuilder a where
toTextBuilder :: a -> TB.Builder
instance (a ~ Char) => ToTextBuilder [a] where
toTextBuilder = TB.fromString
{-# INLINE toTextBuilder #-}
instance ToTextBuilder T.Text where
toTextBuilder = TB.fromText
{-# INLINE toTextBuilder #-}
instance ToTextBuilder TL.Text where
toTextBuilder = TB.fromLazyText
{-# INLINE toTextBuilder #-}
instance TypeError (SpecifyDecoding BS.ByteString "utf8ToTextBuilder") =>
ToTextBuilder BS.ByteString where
toTextBuilder = error "unreachable"
instance TypeError (SpecifyDecoding BSL.ByteString "utf8ToTextBuilder") =>
ToTextBuilder BSL.ByteString where
toTextBuilder = error "unreachable"
class ToString a where
toString :: a -> String
instance ToString T.Text where
toString = T.unpack
{-# INLINE toString #-}
instance ToString TL.Text where
toString = TL.unpack
{-# INLINE toString #-}
instance ToString TB.Builder where
toString = TL.unpack . TB.toLazyText
{-# INLINE toString #-}
instance TypeError (SpecifyDecoding BS.ByteString "utf8ToString") =>
ToString BS.ByteString where
toString = error "unreachable"
instance TypeError (SpecifyDecoding BSL.ByteString "utf8ToString") =>
ToString BSL.ByteString where
toString = error "unreachable"
class ToByteString a where
toByteString :: a -> BS.ByteString
instance TypeError (SpecifyEncoding T.Text "toUtf8ByteString") =>
ToByteString T.Text where
toByteString = error "unreachable"
instance TypeError (SpecifyEncoding TL.Text "toUtf8ByteString") =>
ToByteString TL.Text where
toByteString = error "unreachable"
instance TypeError (SpecifyEncoding TB.Builder "toUtf8ByteString") =>
ToByteString TB.Builder where
toByteString = error "unreachable"
instance (a ~ Char, TypeError (SpecifyEncoding String "toUtf8ByteString")) =>
ToByteString [a] where
toByteString = error "unreachable"
instance ToByteString BSL.ByteString where
toByteString = BSL.toStrict
{-# INLINE toByteString #-}
class ToLazyByteString a where
toLazyByteString :: a -> BSL.ByteString
instance TypeError (SpecifyEncoding T.Text "toUtf8LazyByteString") =>
ToLazyByteString T.Text where
toLazyByteString = error "unreachable"
instance TypeError (SpecifyEncoding TL.Text "toUtf8LazyByteString") =>
ToLazyByteString TL.Text where
toLazyByteString = error "unreachable"
instance TypeError (SpecifyEncoding TB.Builder "toUtf8LazyByteString") =>
ToLazyByteString TB.Builder where
toLazyByteString = error "unreachable"
instance (a ~ Char, TypeError (SpecifyEncoding String "toUtf8LazyByteString")) =>
ToLazyByteString [a] where
toLazyByteString = error "unreachable"
instance ToLazyByteString BS.ByteString where
toLazyByteString = BSL.fromStrict
{-# INLINE toLazyByteString #-}
class Utf8ToString a where
utf8ToString :: a -> String
instance Utf8ToString BS.ByteString where
utf8ToString = UTF8.toString
{-# INLINE utf8ToString #-}
instance Utf8ToString BSL.ByteString where
utf8ToString = UTF8L.toString
{-# INLINE utf8ToString #-}
class Utf8ToText a where
utf8ToText :: a -> T.Text
instance Utf8ToText BS.ByteString where
utf8ToText = T.decodeUtf8With T.lenientDecode
{-# INLINE utf8ToText #-}
instance Utf8ToText BSL.ByteString where
utf8ToText = T.decodeUtf8With T.lenientDecode . BSL.toStrict
{-# INLINE utf8ToText #-}
class Utf8ToLazyText a where
utf8ToLazyText :: a -> TL.Text
instance Utf8ToLazyText BS.ByteString where
utf8ToLazyText = TL.fromStrict . T.decodeUtf8With T.lenientDecode
{-# INLINE utf8ToLazyText #-}
instance Utf8ToLazyText BSL.ByteString where
utf8ToLazyText = TL.decodeUtf8With T.lenientDecode
{-# INLINE utf8ToLazyText #-}
class Utf8ToTextBuilder a where
utf8ToTextBuilder :: a -> TB.Builder
instance Utf8ToTextBuilder BS.ByteString where
utf8ToTextBuilder = TB.fromText . T.decodeUtf8With T.lenientDecode
{-# INLINE utf8ToTextBuilder #-}
instance Utf8ToTextBuilder BSL.ByteString where
utf8ToTextBuilder = TB.fromLazyText . TL.decodeUtf8With T.lenientDecode
{-# INLINE utf8ToTextBuilder #-}
class ToUtf8ByteString a where
toUtf8ByteString :: a -> BS.ByteString
instance ToUtf8ByteString T.Text where
toUtf8ByteString = T.encodeUtf8
{-# INLINE toUtf8ByteString #-}
instance ToUtf8ByteString TL.Text where
toUtf8ByteString = T.encodeUtf8 . TL.toStrict
{-# INLINE toUtf8ByteString #-}
instance ToUtf8ByteString TB.Builder where
toUtf8ByteString = T.encodeUtf8 . TL.toStrict . TB.toLazyText
{-# INLINE toUtf8ByteString #-}
instance (a ~ Char) => ToUtf8ByteString [a] where
toUtf8ByteString = UTF8.fromString
{-# INLINE toUtf8ByteString #-}
class ToUtf8LazyByteString a where
toUtf8LazyByteString :: a -> BSL.ByteString
instance ToUtf8LazyByteString T.Text where
toUtf8LazyByteString = TL.encodeUtf8 . TL.fromStrict
{-# INLINE toUtf8LazyByteString #-}
instance ToUtf8LazyByteString TL.Text where
toUtf8LazyByteString = TL.encodeUtf8
{-# INLINE toUtf8LazyByteString #-}
instance ToUtf8LazyByteString TB.Builder where
toUtf8LazyByteString = TL.encodeUtf8 . TB.toLazyText
{-# INLINE toUtf8LazyByteString #-}
instance (a ~ Char) => ToUtf8LazyByteString [a] where
toUtf8LazyByteString = UTF8L.fromString
{-# INLINE toUtf8LazyByteString #-}
type SpecifyEncoding type_ proposed =
'Text "Can not encode a " :<>: 'ShowType type_ :<>:
'Text " without specifying encoding." :$$:
'Text "Use '" :<>: 'Text proposed :<>:
'Text "' if you want to encode as UTF8."
type SpecifyDecoding type_ proposed =
'Text "Can not decode a " :<>: 'ShowType type_ :<>:
'Text " without specifying encoding." :$$:
'Text "Use '" :<>: 'Text proposed :<>:
'Text "' if you want to decode ASCII or UTF8."