module Data.AttoBencode.Types
( BValue(..)
, Dict
, FromBencode(..)
, ToBencode(..)
, (.:)
, dict
, (.=)
) where
import qualified Data.Map as M
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B
import Data.Traversable (traverse)
data BValue = BString !ByteString
| BInt !Integer
| BList ![BValue]
| BDict !Dict
deriving (Show, Eq)
type Dict = M.Map ByteString BValue
class ToBencode a where
toBencode :: a -> BValue
class FromBencode a where
fromBencode :: BValue -> Maybe a
instance ToBencode ByteString where
toBencode = BString
instance ToBencode String where
toBencode = BString . B.pack
instance ToBencode Integer where
toBencode = BInt
instance ToBencode Int where
toBencode = BInt . fromIntegral
instance ToBencode a => ToBencode [a] where
toBencode = BList . map toBencode
instance ToBencode a => ToBencode (M.Map ByteString a) where
toBencode = BDict . M.map toBencode
instance ToBencode a => ToBencode [(ByteString, a)] where
toBencode = BDict . M.fromList . map (\(k, v) -> (k, toBencode v))
instance ToBencode BValue where
toBencode = id
instance FromBencode ByteString where
fromBencode (BString bs) = Just bs
fromBencode _ = Nothing
instance FromBencode Integer where
fromBencode (BInt n) = Just n
fromBencode _ = Nothing
instance FromBencode BValue where
fromBencode = Just
instance (FromBencode a) => FromBencode (M.Map ByteString a) where
fromBencode (BDict d) = traverse fromBencode d
fromBencode _ = Nothing
instance (FromBencode a) => FromBencode [a] where
fromBencode (BList l) = mapM fromBencode l
fromBencode _ = Nothing
(.:) :: FromBencode a => Dict -> ByteString -> Maybe a
d .: s = M.lookup s d >>= fromBencode
dict :: [(ByteString, BValue)] -> BValue
dict = BDict . M.fromList
(.=) :: ToBencode a => ByteString -> a -> (ByteString, BValue)
key .= value = (key, toBencode value)