{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
#endif
module Data.BEncode
( BValue (..)
, BEncode (..)
, encode
, decode
, Assoc
, (.=!)
, (.=?)
, (.:)
, endDict
, toDict
, Get
, Result
, decodingError
, fromDict
, lookAhead
, next
, req
, opt
, field
, match
, (<$>!)
, (<$>?)
, (<*>!)
, (<*>?)
) where
import Control.Applicative
import Control.Monad
import Control.Monad.State
#if MIN_VERSION_mtl(2, 2, 0)
import Control.Monad.Except
#else
import Control.Monad.Error
#endif
import Data.Int
import Data.List as L
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup ((<>))
#endif
import Data.Word (Word8, Word16, Word32, Word64)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString.Lazy as Lazy
import Data.Text (Text)
import qualified Data.Text.Encoding as T
import Data.Typeable
import Data.Version
import qualified Text.ParserCombinators.ReadP as ReadP
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (Monoid (mempty))
import Data.Word (Word)
#endif
#if __GLASGOW_HASKELL__ >= 702
import GHC.Generics
#endif
import Data.BEncode.BDict as BD
import Data.BEncode.Internal
import Data.BEncode.Types
type Result = Either String
class BEncode a where
toBEncode :: a -> BValue
#if __GLASGOW_HASKELL__ >= 702
default toBEncode
:: Generic a
=> GBEncodable (Rep a) BValue
=> a -> BValue
toBEncode = forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a x. Generic a => a -> Rep a x
from
#endif
fromBEncode :: BValue -> Result a
#if __GLASGOW_HASKELL__ >= 702
default fromBEncode
:: Generic a
=> GBEncodable (Rep a) BValue
=> BValue -> Result a
fromBEncode BValue
x = forall a x. Generic a => Rep a x -> a
to forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom BValue
x
#endif
decodingError :: String -> Result a
decodingError :: forall a. String -> Result a
decodingError String
s = forall a b. a -> Either a b
Left (String
"fromBEncode: unable to decode " forall a. [a] -> [a] -> [a]
++ String
s)
{-# INLINE decodingError #-}
#if __GLASGOW_HASKELL__ >= 702
class GBEncodable f e where
gto :: f a -> e
gfrom :: e -> Result (f a)
instance BEncode f
=> GBEncodable (K1 R f) BValue where
{-# INLINE gto #-}
gto :: forall a. K1 R f a -> BValue
gto = forall a. BEncode a => a -> BValue
toBEncode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i c (p :: k). K1 i c p -> c
unK1
{-# INLINE gfrom #-}
gfrom :: forall a. BValue -> Result (K1 R f a)
gfrom BValue
x = forall k i c (p :: k). c -> K1 i c p
K1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
x
instance (Eq e, Monoid e)
=> GBEncodable U1 e where
{-# INLINE gto #-}
gto :: forall a. U1 a -> e
gto U1 a
U1 = forall a. Monoid a => a
mempty
{-# INLINE gfrom #-}
gfrom :: forall a. e -> Result (U1 a)
gfrom e
x
| e
x forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall k (p :: k). U1 p
U1
| Bool
otherwise = forall a. String -> Result a
decodingError String
"U1"
instance (GBEncodable a BList, GBEncodable b BList)
=> GBEncodable (a :*: b) BList where
{-# INLINE gto #-}
gto :: forall a. (:*:) a b a -> BList
gto (a a
a :*: b a
b) = forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto a a
a forall a. [a] -> [a] -> [a]
++ forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto b a
b
{-# INLINE gfrom #-}
gfrom :: forall a. BList -> Result ((:*:) a b a)
gfrom (BValue
x : BList
xs) = forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom [BValue
x] forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom BList
xs
gfrom [] = forall a. String -> Result a
decodingError String
"generic: not enough fields"
instance (GBEncodable a BDict, GBEncodable b BDict)
=> GBEncodable (a :*: b) BDict where
{-# INLINE gto #-}
gto :: forall a. (:*:) a b a -> BDict
gto (a a
a :*: b a
b) = forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto a a
a forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto b a
b
{-# INLINE gfrom #-}
gfrom :: forall a. BDict -> Result ((:*:) a b a)
gfrom BDict
dict = forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom BDict
dict forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom BDict
dict
instance (GBEncodable a e, GBEncodable b e)
=> GBEncodable (a :+: b) e where
{-# INLINE gto #-}
gto :: forall a. (:+:) a b a -> e
gto (L1 a a
x) = forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto a a
x
gto (R1 b a
x) = forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto b a
x
{-# INLINE gfrom #-}
gfrom :: forall a. e -> Result ((:+:) a b a)
gfrom e
x = case forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom e
x of
Right a a
lv -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 a a
lv)
Left String
le -> do
case forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom e
x of
Right b a
rv -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 b a
rv)
Left String
re -> forall a. String -> Result a
decodingError forall a b. (a -> b) -> a -> b
$ String
"generic: both" forall a. [a] -> [a] -> [a]
++ String
le forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ String
re
selRename :: String -> String
selRename :: String -> String
selRename = forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char
'_'forall a. Eq a => a -> a -> Bool
==)
gfromM1S :: forall c f i p. Selector c
=> GBEncodable f BValue
=> BDict -> Result (M1 i c f p)
gfromM1S :: forall (c :: Meta) (f :: * -> *) i p.
(Selector c, GBEncodable f BValue) =>
BDict -> Result (M1 i c f p)
gfromM1S BDict
dict
| Just BValue
va <- forall a. BKey -> BDictMap a -> Maybe a
BD.lookup (String -> BKey
BC.pack (String -> String
selRename String
name)) BDict
dict = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom BValue
va
| Bool
otherwise = forall a. String -> Result a
decodingError forall a b. (a -> b) -> a -> b
$ String
"generic: Selector not found " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show String
name
where
name :: String
name = forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName (forall a. HasCallStack => String -> a
error String
"gfromM1S: impossible" :: M1 i c f p)
instance (Selector s, GBEncodable f BValue)
=> GBEncodable (M1 S s f) BDict where
{-# INLINE gto #-}
gto :: forall a. M1 S s f a -> BDict
gto s :: M1 S s f a
s@(M1 f a
x) = String -> BKey
BC.pack (String -> String
selRename (forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName M1 S s f a
s)) forall a. BKey -> a -> BDictMap a
`BD.singleton` forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto f a
x
{-# INLINE gfrom #-}
gfrom :: forall a. BDict -> Result (M1 S s f a)
gfrom = forall (c :: Meta) (f :: * -> *) i p.
(Selector c, GBEncodable f BValue) =>
BDict -> Result (M1 i c f p)
gfromM1S
instance GBEncodable f BValue
=> GBEncodable (M1 S s f) BList where
{-# INLINE gto #-}
gto :: forall a. M1 S s f a -> BList
gto (M1 f a
x) = [forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto f a
x]
gfrom :: forall a. BList -> Result (M1 S s f a)
gfrom [BValue
x] = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom BValue
x
gfrom BList
_ = forall a. String -> Result a
decodingError String
"generic: empty selector"
{-# INLINE gfrom #-}
instance (Constructor c, GBEncodable f BDict, GBEncodable f BList)
=> GBEncodable (M1 C c f) BValue where
{-# INLINE gto #-}
gto :: forall a. M1 C c f a -> BValue
gto con :: M1 C c f a
con@(M1 f a
x)
| forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> Bool
conIsRecord M1 C c f a
con = BDict -> BValue
BDict (forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto f a
x)
| Bool
otherwise = BList -> BValue
BList (forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto f a
x)
{-# INLINE gfrom #-}
gfrom :: forall a. BValue -> Result (M1 C c f a)
gfrom (BDict BDict
a) = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom BDict
a
gfrom (BList BList
a) = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom BList
a
gfrom BValue
_ = forall a. String -> Result a
decodingError String
"generic: Constr"
instance GBEncodable f e
=> GBEncodable (M1 D d f) e where
{-# INLINE gto #-}
gto :: forall a. M1 D d f a -> e
gto (M1 f a
x) = forall (f :: * -> *) e a. GBEncodable f e => f a -> e
gto f a
x
{-# INLINE gfrom #-}
gfrom :: forall a. e -> Result (M1 D d f a)
gfrom e
x = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) e a. GBEncodable f e => e -> Result (f a)
gfrom e
x
#endif
instance BEncode BValue where
toBEncode :: BValue -> BValue
toBEncode = forall a. a -> a
id
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result BValue
fromBEncode = forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE fromBEncode #-}
instance BEncode BInteger where
toBEncode :: BInteger -> BValue
toBEncode = BInteger -> BValue
BInteger
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result BInteger
fromBEncode (BInteger BInteger
i) = forall (f :: * -> *) a. Applicative f => a -> f a
pure BInteger
i
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"BInteger"
{-# INLINE fromBEncode #-}
instance BEncode BString where
toBEncode :: BKey -> BValue
toBEncode = BKey -> BValue
BString
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result BKey
fromBEncode (BString BKey
s) = forall (f :: * -> *) a. Applicative f => a -> f a
pure BKey
s
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"BString"
{-# INLINE fromBEncode #-}
instance BEncode BDict where
toBEncode :: BDict -> BValue
toBEncode = BDict -> BValue
BDict
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result BDict
fromBEncode (BDict BDict
d) = forall (f :: * -> *) a. Applicative f => a -> f a
pure BDict
d
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"BDict"
{-# INLINE fromBEncode #-}
toBEncodeIntegral :: Integral a => a -> BValue
toBEncodeIntegral :: forall a. Integral a => a -> BValue
toBEncodeIntegral = BInteger -> BValue
BInteger forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE toBEncodeIntegral #-}
fromBEncodeIntegral :: forall a. Typeable a => Integral a => BValue -> Result a
fromBEncodeIntegral :: forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral (BInteger BInteger
i) = forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. (Integral a, Num b) => a -> b
fromIntegral BInteger
i)
fromBEncodeIntegral BValue
_
= forall a. String -> Result a
decodingError forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall a. Typeable a => a -> TypeRep
typeOf (forall a. HasCallStack => String -> a
error String
"fromBEncodeIntegral: imposible" :: a)
{-# INLINE fromBEncodeIntegral #-}
instance BEncode Word8 where
toBEncode :: Word8 -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Word8
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Word16 where
toBEncode :: Word16 -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Word16
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Word32 where
toBEncode :: Word32 -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Word32
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Word64 where
toBEncode :: Word64 -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Word64
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Word where
toBEncode :: Word -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Word
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Int8 where
toBEncode :: Int8 -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Int8
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Int16 where
toBEncode :: Int16 -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Int16
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Int32 where
toBEncode :: Int32 -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Int32
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Int64 where
toBEncode :: Int64 -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Int64
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Int where
toBEncode :: Int -> BValue
toBEncode = forall a. Integral a => a -> BValue
toBEncodeIntegral
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Int
fromBEncode = forall a. (Typeable a, Integral a) => BValue -> Result a
fromBEncodeIntegral
{-# INLINE fromBEncode #-}
instance BEncode Bool where
toBEncode :: Bool -> BValue
toBEncode = forall a. BEncode a => a -> BValue
toBEncode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Bool
fromBEncode BValue
b = do
Int
i <- forall a. BEncode a => BValue -> Result a
fromBEncode BValue
b
case Int
i :: Int of
Int
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Int
1 -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Int
_ -> forall a. String -> Result a
decodingError String
"Bool"
{-# INLINE fromBEncode #-}
instance BEncode Text where
toBEncode :: Text -> BValue
toBEncode = forall a. BEncode a => a -> BValue
toBEncode forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> BKey
T.encodeUtf8
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Text
fromBEncode BValue
b = BKey -> Text
T.decodeUtf8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
b
{-# INLINE fromBEncode #-}
instance BEncode a => BEncode [a] where
{-# SPECIALIZE instance BEncode BList #-}
toBEncode :: [a] -> BValue
toBEncode = BList -> BValue
BList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
L.map forall a. BEncode a => a -> BValue
toBEncode
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result [a]
fromBEncode (BList BList
xs) = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall a. BEncode a => BValue -> Result a
fromBEncode BList
xs
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"list"
{-# INLINE fromBEncode #-}
instance BEncode Version where
toBEncode :: Version -> BValue
toBEncode = forall a. BEncode a => a -> BValue
toBEncode forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> BKey
BC.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
showVersion
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result Version
fromBEncode (BString BKey
bs)
| [(Version
v, String
_)] <- forall a. ReadP a -> ReadS a
ReadP.readP_to_S ReadP Version
parseVersion (BKey -> String
BC.unpack BKey
bs)
= forall (m :: * -> *) a. Monad m => a -> m a
return Version
v
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"Data.Version"
{-# INLINE fromBEncode #-}
instance BEncode () where
toBEncode :: () -> BValue
toBEncode () = BList -> BValue
BList []
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result ()
fromBEncode (BList []) = forall a b. b -> Either a b
Right ()
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"Unable to decode unit value"
{-# INLINE fromBEncode #-}
instance (BEncode a, BEncode b) => BEncode (a, b) where
{-# SPECIALIZE instance (BEncode b) => BEncode (BValue, b) #-}
{-# SPECIALIZE instance (BEncode a) => BEncode (a, BValue) #-}
{-# SPECIALIZE instance BEncode (BValue, BValue) #-}
toBEncode :: (a, b) -> BValue
toBEncode (a
a, b
b) = BList -> BValue
BList [forall a. BEncode a => a -> BValue
toBEncode a
a, forall a. BEncode a => a -> BValue
toBEncode b
b]
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result (a, b)
fromBEncode (BList [BValue
a, BValue
b]) = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
b
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"Unable to decode a pair."
{-# INLINE fromBEncode #-}
instance (BEncode a, BEncode b, BEncode c) => BEncode (a, b, c) where
toBEncode :: (a, b, c) -> BValue
toBEncode (a
a, b
b, c
c) = BList -> BValue
BList [forall a. BEncode a => a -> BValue
toBEncode a
a, forall a. BEncode a => a -> BValue
toBEncode b
b, forall a. BEncode a => a -> BValue
toBEncode c
c]
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result (a, b, c)
fromBEncode (BList [BValue
a, BValue
b, BValue
c]) =
(,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
c
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"Unable to decode a triple"
{-# INLINE fromBEncode #-}
instance (BEncode a, BEncode b, BEncode c, BEncode d)
=> BEncode (a, b, c, d) where
toBEncode :: (a, b, c, d) -> BValue
toBEncode (a
a, b
b, c
c, d
d) = BList -> BValue
BList [ forall a. BEncode a => a -> BValue
toBEncode a
a, forall a. BEncode a => a -> BValue
toBEncode b
b
, forall a. BEncode a => a -> BValue
toBEncode c
c, forall a. BEncode a => a -> BValue
toBEncode d
d
]
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result (a, b, c, d)
fromBEncode (BList [BValue
a, BValue
b, BValue
c, BValue
d]) =
(,,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
c forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
d
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"Unable to decode a tuple4"
{-# INLINE fromBEncode #-}
instance (BEncode a, BEncode b, BEncode c, BEncode d, BEncode e)
=> BEncode (a, b, c, d, e) where
toBEncode :: (a, b, c, d, e) -> BValue
toBEncode (a
a, b
b, c
c, d
d, e
e) = BList -> BValue
BList [ forall a. BEncode a => a -> BValue
toBEncode a
a, forall a. BEncode a => a -> BValue
toBEncode b
b
, forall a. BEncode a => a -> BValue
toBEncode c
c, forall a. BEncode a => a -> BValue
toBEncode d
d
, forall a. BEncode a => a -> BValue
toBEncode e
e
]
{-# INLINE toBEncode #-}
fromBEncode :: BValue -> Result (a, b, c, d, e)
fromBEncode (BList [BValue
a, BValue
b, BValue
c, BValue
d, BValue
e]) =
(,,,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
c forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
d forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => BValue -> Result a
fromBEncode BValue
e
fromBEncode BValue
_ = forall a. String -> Result a
decodingError String
"Unable to decode a tuple5"
{-# INLINE fromBEncode #-}
data Assoc = Some !BKey BValue
| None
(.=!) :: BEncode a => BKey -> a -> Assoc
(!BKey
k) .=! :: forall a. BEncode a => BKey -> a -> Assoc
.=! a
v = BKey -> BValue -> Assoc
Some BKey
k (forall a. BEncode a => a -> BValue
toBEncode a
v)
{-# INLINE (.=!) #-}
infix 6 .=!
(.=?) :: BEncode a => BKey -> Maybe a -> Assoc
BKey
_ .=? :: forall a. BEncode a => BKey -> Maybe a -> Assoc
.=? Maybe a
Nothing = Assoc
None
BKey
k .=? Just a
v = BKey -> BValue -> Assoc
Some BKey
k (forall a. BEncode a => a -> BValue
toBEncode a
v)
{-# INLINE (.=?) #-}
infix 6 .=?
(.:) :: Assoc -> BDict -> BDict
Assoc
None .: :: Assoc -> BDict -> BDict
.: BDict
d = BDict
d
Some BKey
k BValue
v .: BDict
d = forall a. BKey -> a -> BDictMap a -> BDictMap a
Cons BKey
k BValue
v BDict
d
{-# INLINE (.:) #-}
infixr 5 .:
toDict :: BDict -> BValue
toDict :: BDict -> BValue
toDict = BDict -> BValue
BDict
{-# INLINE toDict #-}
endDict :: BDict
endDict :: BDict
endDict = forall a. BDictMap a
Nil
{-# INLINE endDict #-}
newtype Get a = Get { forall a. Get a -> StateT BDict Result a
runGet :: StateT BDict Result a }
deriving (forall a b. a -> Get b -> Get a
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Get b -> Get a
$c<$ :: forall a b. a -> Get b -> Get a
fmap :: forall a b. (a -> b) -> Get a -> Get b
$cfmap :: forall a b. (a -> b) -> Get a -> Get b
Functor, Functor Get
forall a. a -> Get a
forall a b. Get a -> Get b -> Get a
forall a b. Get a -> Get b -> Get b
forall a b. Get (a -> b) -> Get a -> Get b
forall a b c. (a -> b -> c) -> Get a -> Get b -> Get c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. Get a -> Get b -> Get a
$c<* :: forall a b. Get a -> Get b -> Get a
*> :: forall a b. Get a -> Get b -> Get b
$c*> :: forall a b. Get a -> Get b -> Get b
liftA2 :: forall a b c. (a -> b -> c) -> Get a -> Get b -> Get c
$cliftA2 :: forall a b c. (a -> b -> c) -> Get a -> Get b -> Get c
<*> :: forall a b. Get (a -> b) -> Get a -> Get b
$c<*> :: forall a b. Get (a -> b) -> Get a -> Get b
pure :: forall a. a -> Get a
$cpure :: forall a. a -> Get a
Applicative)
instance Monad Get where
Get StateT BDict Result a
m >>= :: forall a b. Get a -> (a -> Get b) -> Get b
>>= a -> Get b
f = forall a. StateT BDict Result a -> Get a
Get (StateT BDict Result a
m forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. Get a -> StateT BDict Result a
runGet forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Get b
f)
{-# INLINE (>>=) #-}
#if __GLASGOW_HASKELL__ < 808
fail msg = Get (lift (Left msg))
{-# INLINE fail #-}
#else
instance MonadFail Get where
fail :: forall a. String -> Get a
fail String
msg = forall a. StateT BDict Result a -> Get a
Get (forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall a b. a -> Either a b
Left String
msg))
{-# INLINE fail #-}
#endif
instance Alternative Get where
empty :: forall a. Get a
empty = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
""
Get (StateT BDict -> Result (a, BDict)
m) <|> :: forall a. Get a -> Get a -> Get a
<|> Get (StateT BDict -> Result (a, BDict)
n) = forall a. StateT BDict Result a -> Get a
Get forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT forall a b. (a -> b) -> a -> b
$ \BDict
s -> BDict -> Result (a, BDict)
m BDict
s forall a. Semigroup a => a -> a -> a
<> BDict -> Result (a, BDict)
n BDict
s
lookAhead :: Get a -> Get a
lookAhead :: forall a. Get a -> Get a
lookAhead (Get StateT BDict Result a
m) = forall a. StateT BDict Result a -> Get a
Get forall a b. (a -> b) -> a -> b
$ do
BDict
s <- forall s (m :: * -> *). MonadState s m => m s
get
a
r <- StateT BDict Result a
m
forall s (m :: * -> *). MonadState s m => s -> m ()
put BDict
s
forall (m :: * -> *) a. Monad m => a -> m a
return a
r
next :: Get BValue
next :: Get BValue
next = forall a. StateT BDict Result a -> Get a
Get (forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT forall {m :: * -> *} {a}.
MonadError String m =>
BDictMap a -> m (a, BDictMap a)
go)
where
go :: BDictMap a -> m (a, BDictMap a)
go BDictMap a
Nil = forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError String
"no next"
go (Cons BKey
_ a
v BDictMap a
xs) = forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
v, BDictMap a
xs)
req :: BKey -> Get BValue
req :: BKey -> Get BValue
req !BKey
key = forall a. StateT BDict Result a -> Get a
Get (forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT forall {a}. BDictMap a -> Either String (a, BDictMap a)
search)
where
search :: BDictMap a -> Either String (a, BDictMap a)
search BDictMap a
Nil = forall a b. a -> Either a b
Left String
msg
search (Cons BKey
k a
v BDictMap a
xs) =
case forall a. Ord a => a -> a -> Ordering
compare BKey
k BKey
key of
Ordering
EQ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
v, BDictMap a
xs)
Ordering
LT -> BDictMap a -> Either String (a, BDictMap a)
search BDictMap a
xs
Ordering
GT -> forall a b. a -> Either a b
Left String
msg
msg :: String
msg = String
"required field `" forall a. [a] -> [a] -> [a]
++ BKey -> String
BC.unpack BKey
key forall a. [a] -> [a] -> [a]
++ String
"' not found"
{-# INLINE req #-}
opt :: BKey -> Get (Maybe BValue)
opt :: BKey -> Get (Maybe BValue)
opt = forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall b c a. (b -> c) -> (a -> b) -> a -> c
. BKey -> Get BValue
req
{-# INLINE opt #-}
field :: BEncode a => Get BValue -> Get a
{-# SPECIALIZE field :: Get BValue -> Get BValue #-}
field :: forall a. BEncode a => Get BValue -> Get a
field Get BValue
m = forall a. StateT BDict Result a -> Get a
Get forall a b. (a -> b) -> a -> b
$ do
BValue
v <- forall a. Get a -> StateT BDict Result a
runGet Get BValue
m
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. BEncode a => BValue -> Result a
fromBEncode BValue
v
match :: BKey -> BValue -> Get ()
match :: BKey -> BValue -> Get ()
match BKey
key BValue
expected = do
BValue
actual <- BKey -> Get BValue
req BKey
key
if BValue
actual forall a. Eq a => a -> a -> Bool
== BValue
expected
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"key match failure(" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show BKey
key forall a. [a] -> [a] -> [a]
++ String
"): " forall a. [a] -> [a] -> [a]
++
String
"expected = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show BValue
expected forall a. [a] -> [a] -> [a]
++
String
"actual = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show BValue
actual
(<$>!) :: BEncode a => (a -> b) -> BKey -> Get b
a -> b
f <$>! :: forall a b. BEncode a => (a -> b) -> BKey -> Get b
<$>! BKey
k = a -> b
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. BEncode a => Get BValue -> Get a
field (BKey -> Get BValue
req BKey
k)
{-# INLINE (<$>!) #-}
infixl 4 <$>!
(<$>?) :: BEncode a => (Maybe a -> b) -> BKey -> Get b
Maybe a -> b
f <$>? :: forall a b. BEncode a => (Maybe a -> b) -> BKey -> Get b
<$>? BKey
k = Maybe a -> b
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (forall a. BEncode a => Get BValue -> Get a
field (BKey -> Get BValue
req BKey
k))
{-# INLINE (<$>?) #-}
infixl 4 <$>?
(<*>!) :: BEncode a => Get (a -> b) -> BKey -> Get b
Get (a -> b)
f <*>! :: forall a b. BEncode a => Get (a -> b) -> BKey -> Get b
<*>! BKey
k = Get (a -> b)
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. BEncode a => Get BValue -> Get a
field (BKey -> Get BValue
req BKey
k)
{-# INLINE (<*>!) #-}
infixl 4 <*>!
(<*>?) :: BEncode a => Get (Maybe a -> b) -> BKey -> Get b
Get (Maybe a -> b)
f <*>? :: forall a b. BEncode a => Get (Maybe a -> b) -> BKey -> Get b
<*>? BKey
k = Get (Maybe a -> b)
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (forall a. BEncode a => Get BValue -> Get a
field (BKey -> Get BValue
req BKey
k))
{-# INLINE (<*>?) #-}
infixl 4 <*>?
fromDict :: forall a. Typeable a => Get a -> BValue -> Result a
fromDict :: forall a. Typeable a => Get a -> BValue -> Result a
fromDict Get a
m (BDict BDict
d) = forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (forall a. Get a -> StateT BDict Result a
runGet Get a
m) BDict
d
fromDict Get a
_ BValue
_ = forall a. String -> Result a
decodingError (forall a. Show a => a -> String
show (forall a. Typeable a => a -> TypeRep
typeOf a
inst))
where
inst :: a
inst = forall a. HasCallStack => String -> a
error String
"fromDict: impossible" :: a
decode :: BEncode a => ByteString -> Result a
decode :: forall a. BEncode a => BKey -> Result a
decode = BKey -> Result BValue
parse forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. BEncode a => BValue -> Result a
fromBEncode
encode :: BEncode a => a -> Lazy.ByteString
encode :: forall a. BEncode a => a -> ByteString
encode = BValue -> ByteString
build forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. BEncode a => a -> BValue
toBEncode