7

私はこのコードを使用してリストを怠惰にエンコードしています(このSOの質問から取得):

import Data.Binary

newtype Stream a = Stream { unstream :: [a] }

instance Binary a => Binary (Stream a) where

    put (Stream [])     = putWord8 0
    put (Stream (x:xs)) = putWord8 1 >> put x >> put (Stream xs)

問題は、デコードの実装が怠惰ではないことです。

    get = do
        t <- getWord8
        case t of
            0 -> return (Stream [])
            1 -> do x         <- get
                    Stream xs <- get
                    return (Stream (x:xs))

これは怠惰なはずのように私には見えますが、このテストコードを実行すると:

head $ unstream (decode $ encode $ Stream [1..10000000::Integer] :: Stream Integer)

メモリ使用量が爆発します。何らかの理由で、最初の要素を確認する前に、リスト全体をデコードしたいと考えています。

なぜこれは怠惰ではないのですか、そしてどうすればそれを怠惰にすることができますか?

4

1 に答える 1

7

Getモナドは厳密な状態のモナドであるため、怠惰ではありません( binary-0.5.0.2から0.5.1.1 ;以前は怠惰な状態のモナドでしたが、binary-0.6。*では継続モナドになりました。その変更の厳密さの影響を分析しました):

-- | The parse state
data S = S {-# UNPACK #-} !B.ByteString  -- current chunk
           L.ByteString                  -- the rest of the input
           {-# UNPACK #-} !Int64         -- bytes read

-- | The Get monad is just a State monad carrying around the input ByteString
-- We treat it as a strict state monad. 
newtype Get a = Get { unGet :: S -> (# a, S #) }

-- Definition directly from Control.Monad.State.Strict
instance Monad Get where
    return a  = Get $ \s -> (# a, s #)
    {-# INLINE return #-}

    m >>= k   = Get $ \s -> case unGet m s of
                             (# a, s' #) -> unGet (k a) s'
    {-# INLINE (>>=) #-}

したがって、最終的な再帰

get >>= \x ->
get >>= \(Stream xs) ->
return (Stream (x:xs))

返される前に全体Streamを強制的に読み取らせます。

モナドでaを怠惰にデコードすることは不可能だと思います(したがって、インスタンスではないフォルティStreamオリ)。ただし、次を使用して遅延デコード関数を記述できます。GetBinaryrunGetState

-- | Run the Get monad applies a 'get'-based parser on the input
-- ByteString. Additional to the result of get it returns the number of
-- consumed bytes and the rest of the input.
runGetState :: Get a -> L.ByteString -> Int64 -> (a, L.ByteString, Int64)
runGetState m str off =
    case unGet m (mkState str off) of
      (# a, ~(S s ss newOff) #) -> (a, s `join` ss, newOff)

最初に、Getを返すパーサーを記述しますMaybe a

getMaybe :: Binary a => Get (Maybe a)
getMaybe = do
    t <- getWord8
    case t of
      0 -> return Nothing
      _ -> fmap Just get

次に、それを使用して次のタイプの関数を作成します(ByteString,Int64) -> Maybe (a,(ByteString,Int64))

step :: Binary a => (ByteString,Int64) -> Maybe (a,(ByteString,Int64))
step (xs,offset) = case runGetState getMaybe xs offset of
                     (Just v, ys, newOffset) -> Just (v,(ys,newOffset))
                     _                       -> Nothing

Data.List.unfoldr次に、リストを遅延デコードするために使用できます。

lazyDecodeList :: Binary a => ByteString -> [a]
lazyDecodeList xs = unfoldr step (xs,0)

そしてそれをStream

lazyDecodeStream :: Binary a => ByteString -> Stream a
lazyDecodeStream = Stream . lazyDecodeList
于 2012-07-27T23:26:12.437 に答える