-- |
-- Module: Data.AttoBencode.Types
-- Copyright: Florian Hartwig
-- License: BSD3
-- Maintainer: Florian Hartwig <florian.j.hartwig@gmail.com>
-- Stability: experimental
-- Portability: GHC

{-# LANGUAGE FlexibleInstances #-}

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)

-- | The Haskell data type for Bencode values
data BValue = BString !ByteString
            | BInt !Integer
            | BList ![BValue]
            | BDict !Dict
    deriving (Show, Eq)

-- | A Bencode dictionary. Dictionaries have 'ByteString' keys and 'BValue'
--   values.
type Dict = M.Map ByteString BValue

-- TODO: example
-- | A type that can be converted to a 'BValue'.
class ToBencode a where
    toBencode :: a -> BValue

-- TODO: example
-- | A type that can be converted from a 'BValue'. The conversion can fail.
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
-- TODO: make sure these are inlined


instance FromBencode ByteString where
    fromBencode (BString bs) = Just bs
    fromBencode _            = Nothing

instance FromBencode Integer where
    fromBencode (BInt n) = Just n
    fromBencode _        = Nothing

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

-- | Look up the value corresponding to a (ByteString) key from a dictionary.
--   Returns 'Nothing' if the key is not in the dictionary or if the 'BValue'
--   cannot be converted to the expected type.
(.:) :: FromBencode a => Dict -> ByteString -> Maybe a
d .: s = M.lookup s d >>= fromBencode

-- | Make a BDict from a list of (key, value) tuples.
dict :: [(ByteString, BValue)] -> BValue
dict = BDict . M.fromList

-- | Create a (key, value) tuple from a ByteString key and some bencode-able
--   value. Can be used with the 'dict' function as a convenient way to create
--   'BDict's.
(.=) :: ToBencode a => ByteString -> a -> (ByteString, BValue)
key .= value = (key, toBencode value)