summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-09-30 05:20:54 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-09-30 05:20:54 +0400
commitd9047c6597d6d99858d15514392096b997cf9b9d (patch)
treeb3d06d7e9d4de26e14b9cb3c302a86ceb6a908f0
parente4151710e4749814337c0a22cefa417aa4735264 (diff)
Remove old dictionary builder
-rw-r--r--src/Data/BEncode.hs38
1 files changed, 11 insertions, 27 deletions
diff --git a/src/Data/BEncode.hs b/src/Data/BEncode.hs
index 427d401..f12d116 100644
--- a/src/Data/BEncode.hs
+++ b/src/Data/BEncode.hs
@@ -622,7 +622,7 @@ fromDict _ _ = decodingError (show (typeOf inst))
622{-------------------------------------------------------------------- 622{--------------------------------------------------------------------
623 Building dictionaries 623 Building dictionaries
624--------------------------------------------------------------------} 624--------------------------------------------------------------------}
625{- 625
626-- | /Assoc/ used to easily build dictionaries with required and 626-- | /Assoc/ used to easily build dictionaries with required and
627-- optional keys. Suppose we have we following datatype we want to 627-- optional keys. Suppose we have we following datatype we want to
628-- serialize: 628-- serialize:
@@ -648,42 +648,21 @@ fromDict _ _ = decodingError (show (typeOf inst))
648-- > ] 648-- > ]
649-- > ... 649-- > ...
650-- 650--
651newtype Assoc = Assoc { unAssoc :: Maybe (ByteString, BValue) } 651type Assoc = Maybe BPair
652
653-- | Make required key value pair.
654(-->) :: BEncode a => BKey -> a -> Assoc
655key --> val = Assoc $ Just $ (key, toBEncode val)
656{-# INLINE (-->) #-}
657
658-- | Like (-->) but if the value is not present then the key do not
659-- appear in resulting bencoded dictionary.
660--
661(-->?) :: BEncode a => BKey -> Maybe a -> Assoc
662key -->? mval = Assoc $ ((,) key . toBEncode) <$> mval
663{-# INLINE (-->?) #-}
664
665-- | Build BEncode dictionary using key -> value description.
666fromAssocs :: [Assoc] -> BValue
667fromAssocs = undefined -- BDict . M.fromList . mapMaybe unAssoc
668{-# INLINE fromAssocs #-}
669
670-- | A faster version of 'fromAssocs'. Should be used only when keys
671-- in builder list are sorted by ascending.
672fromAscAssocs :: [Assoc] -> BValue
673fromAscAssocs = BDict . BD.fromAscList . mapMaybe unAssoc
674{-# INLINE fromAscAssocs #-}
675-}
676 652
677type BPair = (BKey, BValue) 653type BPair = (BKey, BValue)
678type Assoc = Maybe BPair
679 654
680-- TODO better name 655-- TODO better name
656-- | Make required key value pair.
681(.=!) :: BEncode a => BKey -> a -> Assoc 657(.=!) :: BEncode a => BKey -> a -> Assoc
682k .=! v = Just (k, toBEncode v) 658k .=! v = Just (k, toBEncode v)
683{-# INLINE (.=!) #-} 659{-# INLINE (.=!) #-}
684 660
685infix 6 .=! 661infix 6 .=!
686 662
663-- | Like (.=!) but if the value is not present then the key do not
664-- appear in resulting bencoded dictionary.
665--
687(.=?) :: BEncode a => BKey -> Maybe a -> Assoc 666(.=?) :: BEncode a => BKey -> Maybe a -> Assoc
688_ .=? Nothing = Nothing 667_ .=? Nothing = Nothing
689k .=? Just v = Just (k, toBEncode v) 668k .=? Just v = Just (k, toBEncode v)
@@ -698,6 +677,11 @@ Just (k, v) .: d = Cons k v d
698 677
699infixr 5 .: 678infixr 5 .:
700 679
680-- | Build BEncode dictionary using key -> value description.
681
682-- | A faster version of 'fromAssocs'. Should be used only when keys
683-- in builder list are sorted by ascending.
684--
701toDict :: BDict -> BValue 685toDict :: BDict -> BValue
702toDict = BDict 686toDict = BDict
703{-# INLINE toDict #-} 687{-# INLINE toDict #-}