You're welcome!

On 9/15/15 1:14 PM, Dylan Tisdall wrote:
Great, thanks again!

On Tuesday, September 15, 2015 at 4:10:54 PM UTC-4, Gabriel Gonzalez wrote:

    There are two solutions to this.

    The first solution is to enable the `{-# LANGUAGE RankNTypes #-}`
    extension like the compiler suggests.

    The reason why is that the `Parser` type synonym is:

        type Parser a m r = forall x . StateT (Producer a m x) m r

    ... which means that this type:

        Monad m => Int -> Parser ByteString m ()

    ... expands out to this type:

        Monad m => Int -> (forall x . StateT (Producer a m x) m r)

    ... which is a higher-rank type (because of the `forall` after the
    `(->)`).  This is normal in the case of `pipes-parse` and is used
    to simplify type signatures.

    There's a second solution, which is to just use the type inferred
    by the compiler, which will be a little bit more verbose:

        Monad m => Int -> StateT (Producer a m x) m r

    ... which is almost the same as the previous type, except now that
    the `forall` has been implicitly been pulled out of the type like
    this:

        forall x . Monad m => Int -> StateT (Producer a m x) m r

    This type doesn't require the `RankNTypes` language extension, but
    you can no longer simplify the type using the `Parser` type synonym.

    It's up to you which solution you prefer.

    On 9/15/15 1:03 PM, Dylan Tisdall wrote:
    Hi Gabriel,

    Thanks for the quick reply. I had to modify the snippet a little
    bit so ghci find definitions for all the symbols (just changed
    the import lines a bit), but now I'm getting an error about
    illegal types. Below is the code, and the output from ghci. Any
    suggestions what I've done wrong?

    --- code ---
    import Prelude hiding (splitAt)
    import Control.Lens (zoom)
    import Pipes                          -- from the `pipes` package
    import Pipes.ByteString (ByteString, splitAt)     -- from the
    `pipes-bytestring` package
    import Pipes.Parse (Parser, skipAll)  -- from the `pipes-parse`
    package

    skipNBytes :: Monad m => Int -> Parser ByteString m ()
    skipNBytes n = zoom (splitAt n) skipAll

    --- ghci 7.10.2 output --
    Illegal polymorphic or qualified type: Parser ByteString m ()
    Perhaps you intended to use RankNTypes or Rank2Types
    In the type signature for ‘skipNBytes’:
      skipNBytes :: Monad m => Int -> Parser ByteString m ()


    Thanks,
    Dylan



    On Tuesday, September 15, 2015 at 3:24:31 PM UTC-4, Gabriel
    Gonzalez wrote:

        Here's how you can skip N bytes in the context of a
        `Parser`.  I can add this to `Pipes.ByteString` in some form
        as a useful utility in the "Parsers" section if it solves
        your issue:

            import Lens.Micro (zoom)-- from the `microlens` package
            import Pipes-- from the `pipes` package
            import Pipes.ByteString (splitAt)-- from the
        `pipes-bytestring` package
            import Pipes.Parse (Parser, skipAll)  -- from the
        `pipes-parse` package

            skipNBytes :: Monad m => Int -> Parser ByteString m ()
            skipNBytes n = zoom (splitAt n) skipAll

        On 9/15/15 12:17 PM, Dylan Tisdall wrote:
        Hi,

        I'm new to pipes (and pretty new to Haskell), and so have a
        question that's probably quite simple, but has managed to
        stump me for the last day. Basically, I'm trying to parse a
        file that consists of the two "sub-files" (call them first
        and second), with the length of first prefixed. My goal is
        to write a parser that reads just the length of first, then
        skips over first without read it all into memory, and then
        reads in and prints out the contents of the second file. So
        far I can read the length, but I'm stumped at how to do the
        skip, and handle the error case where even reading the
        length failed. Basically, I'm looking for what should go
        into "parseRest" in the following code, or any suggestions
        for how to refactor this to make it more consistent with the
        design of pipes.

        import           Prelude hiding (length, concat, splitAt)
        import Data.ByteString.Lazy.Char8 (pack)
        import Data.ByteString.Lazy (ByteString, length, copy, concat)
        import Data.Binary (Word32)
        import           Data.Int (Int32)
        import Data.Binary.Put (runPut, putWord32le)
        import Data.Binary.Get (getWord32le)
        import           Pipes
        import Pipes.ByteString (fromLazy, stdout, splitAt)
        import qualified Pipes.ByteString as P (ByteString)
        import Pipes.Parse (runStateT, evalStateT, drawAll, Parser)
        import Pipes.Binary (decodeGet, DecodingError, decoded, decode)
        import Control.Lens (view, zoom)

        first :: ByteString
        first = pack "foo"

        second :: ByteString
        second = pack "bar"

        merge :: ByteString -> ByteString -> ByteString
        merge a b = concat [lengthBS a, a, b]
          where
            lengthBS = runPut . putWord32le . fromIntegral . length

        split :: Monad m => Producer P.ByteString m r ->
              m (Either DecodingError
                 (Producer P.ByteString m (Producer P.ByteString m r)))
        split p = do
            (headerLen, p') <- runStateT (decodeGet getWord32le) p
            return $ case headerLen of
                Left err -> Left err
                Right headerLen' -> Right $
                    view (splitAt  $ fromIntegral $ (headerLen' ::
        Word32)) p'

        decoder :: Parser P.ByteString IO ()
        decoder = do
            headerLen <- decode
            lift $ print (headerLen :: Either DecodingError Word32)
            case headerLen of
                Left err -> lift $ print err
                Right hLen -> parseRest

        main :: IO ()
        main = do
            evalStateT decoder $ fromLazy (merge first second)


        Thanks,
        Dylan
-- You received this message because you are subscribed to the
        Google Groups "Haskell Pipes" group.
        To unsubscribe from this group and stop receiving emails
        from it, send an email to haskell-pipe...@googlegroups.com.
        To post to this group, send email to haskel...@googlegroups.com.

-- You received this message because you are subscribed to the
    Google Groups "Haskell Pipes" group.
    To unsubscribe from this group and stop receiving emails from it,
    send an email to haskell-pipe...@googlegroups.com <javascript:>.
    To post to this group, send email to haskel...@googlegroups.com
    <javascript:>.

--
You received this message because you are subscribed to the Google Groups "Haskell Pipes" group. To unsubscribe from this group and stop receiving emails from it, send an email to haskell-pipes+unsubscr...@googlegroups.com <mailto:haskell-pipes+unsubscr...@googlegroups.com>. To post to this group, send email to haskell-pipes@googlegroups.com <mailto:haskell-pipes@googlegroups.com>.

--
You received this message because you are subscribed to the Google Groups "Haskell 
Pipes" group.
To unsubscribe from this group and stop receiving emails from it, send an email 
to haskell-pipes+unsubscr...@googlegroups.com.
To post to this group, send email to haskell-pipes@googlegroups.com.

Reply via email to