summaryrefslogtreecommitdiff
path: root/src/Data/BEncode.hs
diff options
context:
space:
mode:
authorSam T <pxqr.sta@gmail.com>2013-08-26 06:21:54 +0400
committerSam T <pxqr.sta@gmail.com>2013-08-26 06:21:54 +0400
commit007e669a651ef6b024432279fbd9ab3e4dd1d1c2 (patch)
tree37af0ff1db0d3f8b476bfcad6b5d361bcb3bdfc9 /src/Data/BEncode.hs
parent243285da661f710ac1864d9ddd1c05e4a7b1190f (diff)
+ Documentation to the dictionary extraction section
Diffstat (limited to 'src/Data/BEncode.hs')
-rw-r--r--src/Data/BEncode.hs25
1 files changed, 23 insertions, 2 deletions
diff --git a/src/Data/BEncode.hs b/src/Data/BEncode.hs
index 4d76fb4..9896114 100644
--- a/src/Data/BEncode.hs
+++ b/src/Data/BEncode.hs
@@ -483,6 +483,7 @@ instance BEncodable Version where
483-- > , "path" --> filePath 483-- > , "path" --> filePath
484-- > , "tags" -->? fileTags 484-- > , "tags" -->? fileTags
485-- > ] 485-- > ]
486-- > ...
486-- 487--
487newtype Assoc = Assoc { unAssoc :: Maybe (ByteString, BEncode) } 488newtype Assoc = Assoc { unAssoc :: Maybe (ByteString, BEncode) }
488 489
@@ -510,9 +511,25 @@ fromAscAssocs = BDict . M.fromAscList . mapMaybe unAssoc
510{-# INLINE fromAscAssocs #-} 511{-# INLINE fromAscAssocs #-}
511 512
512{-------------------------------------------------------------------- 513{--------------------------------------------------------------------
513 Extraction 514 Dictionary extraction
514--------------------------------------------------------------------} 515--------------------------------------------------------------------}
515 516
517-- | Dictionary extractor are similar to dictionary builders, but play
518-- the opposite role: they are used to define 'fromBEncode' method in
519-- declarative style. Using the same /FileInfo/ datatype 'fromBEncode'
520-- looks like:
521--
522-- > instance BEncodable FileInfo where
523-- > ...
524-- > fromBEncode (BDict d) =
525-- > FileInfo <$> d >-- "length"
526-- > <*> d >--? "md5sum"
527-- > <*> d >-- "path"
528-- > <*> d >--? "tags"
529-- > fromBEncode _ = decodingError "FileInfo"
530--
531-- The /reqKey/ is used to extract required key — if lookup is failed
532-- then whole destructuring fail.
516reqKey :: BEncodable a => Dict -> ByteString -> Result a 533reqKey :: BEncodable a => Dict -> ByteString -> Result a
517reqKey d key 534reqKey d key
518 | Just b <- M.lookup key d = fromBEncode b 535 | Just b <- M.lookup key d = fromBEncode b
@@ -520,16 +537,20 @@ reqKey d key
520 where 537 where
521 msg = "required field `" ++ BC.unpack key ++ "' not found" 538 msg = "required field `" ++ BC.unpack key ++ "' not found"
522 539
540-- | Used to extract optional key — if lookup is failed returns
541-- 'Nothing'.
523optKey :: BEncodable a => Dict -> ByteString -> Result (Maybe a) 542optKey :: BEncodable a => Dict -> ByteString -> Result (Maybe a)
524optKey d key 543optKey d key
525 | Just b <- M.lookup key d 544 | Just b <- M.lookup key d
526 , Right r <- fromBEncode b = return (Just r) 545 , Right r <- fromBEncode b = return (Just r)
527 | otherwise = return Nothing 546 | otherwise = return Nothing
528 547
548-- | Infix version of the 'reqKey'.
529(>--) :: BEncodable a => Dict -> ByteString -> Result a 549(>--) :: BEncodable a => Dict -> ByteString -> Result a
530(>--) = reqKey 550(>--) = reqKey
531{-# INLINE (>--) #-} 551{-# INLINE (>--) #-}
532 552
553-- | Infix version of the 'optKey'.
533(>--?) :: BEncodable a => Dict -> ByteString -> Result (Maybe a) 554(>--?) :: BEncodable a => Dict -> ByteString -> Result (Maybe a)
534(>--?) = optKey 555(>--?) = optKey
535{-# INLINE (>--?) #-} 556{-# INLINE (>--?) #-}
@@ -603,7 +624,7 @@ builder = go
603 B.byteString s 624 B.byteString s
604 {-# INLINE buildString #-} 625 {-# INLINE buildString #-}
605 626
606-- | TODO try to replace peekChar with something else 627-- TODO try to replace peekChar with something else
607parser :: Parser BEncode 628parser :: Parser BEncode
608parser = valueP 629parser = valueP
609 where 630 where