Re: [Haskell-cafe] XCode Dependency for HP on Mac

2011-07-26 Thread Maciej Wos
If you're using Lion you can get Xcode from the App Store (Apple used
to charge something for it, but now it is free).

If you're using Snow Leopard you can download Xcode from
developer.apple.com/xcode. See Looking for Xcode 3? Download Now in
the bottom right corner of the page. You need to register with Apple
but you don't need the paid developer account.

-- Maciej

On Wed, Jul 27, 2011 at 12:55 PM, Tom Murphy amin...@gmail.com wrote:
 This may sound ignorant because, well, it is ignorant: I know very
 little about the underlying mechanics here.

 Installing the Haskell Platform currently requires XCode developer tools.

 To get XCode on my 10.6 machine, I...

 [*** begin ranty details (skippable)

 ... was told I could get a free version by registering as an Apple Developer.
 So I lie on the forms (phone number and address, for example, are
 _required_ fields!), and lie on the  _required_ 2-3 page survey.
 I put in a code that they sent to my email (couldn't lie on that!), and log 
 in.
 The page tells me, in the exact box that told me if I registered I
 could get XCode for free, that I...

 *** end ranty details]

 ...have to either pay to upgrade to their newer OS (10.7: Lion), or
 pay $99/year for a Mac OS Developer Membership.

 Is there a way to install HP without XCode? Could there be in the
 future? I'm tired of dealing with Apple's constant upgrade
 requirements, registration requirements, etc., and it seems like a
 small function that XCode actually performs in the Haskell development
 toolchain.
 Again, I'm ignorant of the details and I'm sorry if this is ranty, but
 I'd love to hear your reactions.

 Thanks!
 Tom

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] For class Monoid; better names than mempty mappend might have been: mid (mident) mbinop

2011-07-24 Thread Maciej Wos
Personally, I have nothing against mempty (although I agree that mid makes
more sense), but I don't like mappend at all. I wonder what happened to the
idea of using  instead of mappend (that's what I always do). I think

a  b  c

looks so much better than

a `mappend` b `mappend` c

and it solves the name problem altogether.

-- Maciej
On Jul 24, 2011 3:42 AM, KC kc1...@gmail.com wrote:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IterIO: How to write use my inumReverse

2011-07-11 Thread Maciej Wos
Sorry, my previous message got truncated.

I was trying to say that many iteratees like iterReverse can be
defined nicely using combinators from Control.Applicative. You end up
with much cleaner code.

Also, iterLines doesn't work as the name would suggest. It only
consumes one line from the input stream and returns it inside a
singleton list.

Instead, iterLines can be defined like this:

iterLines :: (Monad m) = Iter L.ByteString m [L.ByteString]
iterLines = do
el - tryBI lineI
case el of
-- no more full lines left, return the remaining data
Left (e :: SomeException) - (:[]) $ dataI
-- read one line; add it to the list and read more
Right line - (line:) $ iterLines

enumPure line1\nline2\nline3 |$ iterLines
[Chunk line1 Empty,Chunk line2 Empty,Chunk line3 Empty]

However, the above returns the resulting list only after consuming the
whole stream, which is something to avoid.

In case of iterReverse it is better to read and accumulate characters
until \n is found and then return the reversed string. One way to do
this is to read one character at a time:

reverseLineSlow :: Iter L.ByteString IO L.ByteString
reverseLineSlow = iter 
where
iter acc = do
c - headI
case c of
10 - return $ L.reverse acc
_  - iter (acc `mappend` L.singleton c)

But this will be really slow. Instead, the data should be read one
chunk at a time:

reverseLine :: Iter L.ByteString IO L.ByteString
reverseLine = iter 
where
iter acc = do
-- read the data from the stream one chunk at a time
Chunk c eof - chunkI
-- check if there is any \n, i.e. if we read a whole line
let (a,b) = L.break (==10) c
if b == 
-- haven't found any \n yet; append all data to the accumulator
then iter (acc `mappend` a)
-- have found \n
else do
-- put the data after \n back (while removing \n itself)
ungetI $ L.tail b
-- return reversed accumulator plus the data up to \n
return $ L.reverse $ acc `mappend` a

Hope this helps!

-- Maciej

On Tue, Jul 12, 2011 at 12:47 AM, Maciej Wos maciej@gmail.com wrote:
 Don't forget Applicative instance!
 iterReverse = L.reverse $ lineI

 On Monday, 4 July 2011 at 22:54, dm-list-haskell-c...@scs.stanford.edu
 wrote:

 At Mon, 4 Jul 2011 20:36:33 +1000,
 John Ky wrote:

 Hi Haskell Cafe,

       enum |$ inumLines .| inumReverse .| inumUnlines .| iter
 ...

 iterLines :: (Monad m) = Iter L.ByteString m [L.ByteString]
 iterLines = do
   line - lineI
   return [[line]

 iterUnlines :: (Monad m) = Iter [L.ByteString] m L.ByteString
 iterUnlines = (L.concat . (++ [C.pack \n])) `liftM` dataI

 iterReverse :: (Monad m) = Iter [L.ByteString] m [L.ByteString]
 iterReverse = do
   lines - dataI
   return (map L.reverse lines)

 inumLines = mkInum iterLines
 inumUnlines = mkInum iterUnlines
 inumReverse = mkInum iterReverse

 It all works fine.

 My question is: Is it possible to rewrite inumReverse to be this:

 iterReverse :: (Monad m) = Iter L.ByteString m L.ByteString
 iterReverse = do
   line - dataI
   return (L.reverse line)

 inumReverse = mkInum iterReverse

 And still be able to use it in the line:

 enum |$ inumLines .| {-- inumReverse goes in here somehow --} .|
 inumUnlines .| iter

 The reason I ask is that the Haskell function reverse has the type [a] -
 [a],
 not  [[a]] - [[a]].

 I thought perhaps the alternative inumReverse is cleaner than the original
 as
 it behaves more similarly to Haskell's own reverse function.

 I'm not sure what you are trying to achieve. If you want an iter that
 works on L.ByteStrings, then you can say:

 iterReverse :: (Monad m) = Iter L.ByteString m L.ByteString
 iterReverse = do
 line - lineI
 return (L.reverse line)

 In that case you don't need inumLines and inumUnlines. If, however,
 you want the type to be [L.ByteString], and you would rather do this
 one line at a time, instead of calling map, then you could do
 something like the following:

 iterReverse :: (Monad m) = Iter [L.ByteString] m [L.ByteString]
 iterReverse = do
 line - headI
 return [L.reverse line]

 But the code you have above should also work, so it all depends on
 what you are trying to achieve.

 David

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sub-optimal

2011-02-13 Thread Maciej Wos
I was battling a similar (the same?) issue recently. The problem might
indeed be caused by excessive sharing. There's a good example in GHC's
trac [1]. Try compiling your code with -O2 and -fno-full-laziness.

There is also an issue with full-laziness and recursive overloaded
functions [2]. Again, compiling with -fno-full-laziness should help.
Alternatively, if you're using ghc-7.0.1, try switching to HEAD.

-- Maciej

[1] http://hackage.haskell.org/trac/ghc/ticket/917
[2] 
http://www.haskell.org/pipermail/glasgow-haskell-users/2011-February/019997.html

On Sat, Feb 12, 2011 at 7:30 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 I have a small program that fills a file with random numbers. If I compile
 it without optimisation, it runs in constant space. And yet, if I supply -O2
 (or even just -O1), for large output files the program gobbles large amounts
 of RAM.

 Is this a known bug? (GHC 6.10.x)

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with iteratees

2011-02-02 Thread Maciej Wos
I think the problem is that the iteratee you give to I.convStream
always returns Just [something] while you should return Nothing on
EOF.

Suppose you want to have an enumeratee that adds 1 to each integer in
the stream and then use stream2list to get an iteratee that consumes
the result stream and returns it as a list:

 let iter = joinI $ (convStream (head = return . Just . (:[]) . (+1))) 
 stream2list :: IterateeG [] Int IO [Int]
 run iter
*** Exception: control message: Just (Err EOF)

Note that run simply passes EOF to iter and extracts the result.
Instead of throwing an error the code above should produce an [] (i.e.
no stream to consume, no elements in the list). This can be fixed by
checking whether the stream is empty:

 let iter = joinI $ (convStream (isFinished = maybe (head = return . Just 
 . (:[]) . (+1)) (\_ - return Nothing))) stream2list :: IterateeG [] Int IO 
 [Int]
 run iter
[]

I think you should do the same in your code:

runGetEnumeratee get =
I.convStream $ isFinished = maybe convIter (\_ - return Nothing)
where
convIter = (Just . return) `liftM` (runGetIteratee get)

When the stream is not empty, it runs (runGetIteratee get) and returns
its result wrapped in Just . (:[]). When the stream is empty, it
returns Nothing so convStream knows it is done.

-- Maciej

On Thu, Feb 3, 2011 at 10:06 AM, wren ng thornton w...@freegeek.org wrote:
 I'm working on a project that's using John Lato's old implementation of
 iteratees (iteratee = 0.3.5   0.4; I'm hoping to migrate to 0.7 soon,
 but that's a ways off yet) and I'm running into some issues I haven't been
 able to untangle. Maybe a new set of eyes can help...

 The overarching program brings three things together for doing some
 interprocess communication: the medium is Posix FIFOs, the messages
 themselves are encoded with Google's Protocol Buffers[1], and the control
 flow for getting and processing the messages is handled by iteratees. The
 error message indicates iteratees are at fault, though it could be an error
 elsewhere instead.

 First, some boilerplate.

    -- For messageWithLengthEnumeratee only
    {-# LANGUAGE ScopedTypeVariables #-}

    import qualified Text.ProtocolBuffers.Reflections as R
    import qualified Text.ProtocolBuffers.WireMessage as W
    import qualified Text.ProtocolBuffers.Get         as G
    import qualified Data.ByteString                  as S
    import qualified Data.ByteString.Lazy             as L
    import qualified Data.Iteratee                    as I
    import           Data.Iteratee.WrappedByteString
    import           Data.Word                        (Word8)
    import           Control.Monad                    (liftM)


    -- | Return a final value, and the remainder of the stream.
    idone :: a - c el - I.IterGV c el m a
    idone a xs = I.Done a (I.Chunk xs)
    {-# INLINE idone #-}


    -- | Convert a continuation into 'I.IterGV'.
    icontinue
        :: (I.StreamG c el - m (I.IterGV c el m a))
        - I.IterGV c el m a
    icontinue k = I.Cont (I.IterateeG k) Nothing
    {-# INLINE icontinue #-}


    -- | Throw an error message.
    ifail :: (Monad m) = String - I.IterGV c el m a
    ifail msg = ierror (I.Err msg)
    {-# INLINE ifail #-}


    -- | An 'I.IterGV' variant of 'I.throwErr'.
    ierror :: (Monad m) = I.ErrMsg - I.IterGV c el m a
    ierror err = I.Cont (I.throwErr err) (Just err)
    {-# INLINE ierror #-}


    toLazyBS :: S.ByteString - L.ByteString
    toLazyBS = L.fromChunks . (:[])
    {-# INLINE toLazyBS #-}


    toStrictBS :: L.ByteString - S.ByteString
    toStrictBS = S.concat . L.toChunks
    {-# INLINE toStrictBS #-}

 Now we have the code for converting the Get monad used by protocol buffers
 into an iteratee. This should be correct, and it's pretty straightforward.

    -- | Convert a 'G.Result' iteratee state into a 'I.IterGV'
    -- iteratee state.
    result2iterv
        :: (Monad m)
        = G.Result a
        - I.IterGV WrappedByteString Word8 m a
    result2iterv (G.Finished rest _ a) = idone a (WrapBS $ toStrictBS rest)
    result2iterv (G.Failed _ msg)      = ifail msg
    result2iterv (G.Partial k)         = I.Cont (iterify k) Nothing


    -- | Convert a protobuf-style continuation into an
    -- iteratee-style continuation.
    iterify
        :: (Monad m)
        = (Maybe L.ByteString - G.Result a)
        - I.IterateeG WrappedByteString Word8 m a
    iterify k =
        I.IterateeG $ \s - return $!
            case s of
            I.Chunk (WrapBS xs) - result2iterv $ k (Just $ toLazyBS xs)
            I.EOF Nothing       - result2iterv $ k Nothing
            I.EOF (Just err)    - ierror err


    -- | A variant of 'G.runGet' as an iteratee.
    runGetIteratee
        :: (Monad m, R.ReflectDescriptor a, W.Wire a)
        = G.Get a
        - I.IterateeG WrappedByteString Word8 m a
    runGetIteratee g =
        I.IterateeG $ \s - return $!
            case s of
            I.Chunk (WrapBS xs) - result2iterv $ G.runGet 

[Haskell-cafe] sequence and sequence_ for iteratees

2011-01-17 Thread Maciej Wos
Hello Cafe!

I have written some iteratee functions that I found to be very very
useful and I hope they will soon make it to the iteratee library.
However, I'd like to get some feedback first, particularly about the
error handling.

I'm sending this here rather than to iteratee mailing list at
projects.haskell.org because the latter is (and has been for a while!)
down...

Anyway, enumSequence and enumSequence_ are inspired by Prelude's
sequence and sequence_. They are useful when one has to deal with
several iteratees consuming the same data. For instance, one could use
enumSequence as follows:

 run $ joinIM $ enumPureNChunk [1..100] 3 $
enumSequence [I.head, I.head = \x - I.head = \y - return
(x+y), I.last]

which produces:

[1,3,100]

Each iteratee in the list is given the same input stream. Also,
enumSequence consumes as much of the stream as the iteratee in the
list that consumes the most. In the above example there is no stream
left after enumSequence finishes because I.last consumes everything.

As an another example, enumSequence below consumes only the first two
elements of the stream and the remainder is passed to stream2list:

 run $ joinIM $ enumPureNChunk [1..10] 3 $
(enumSequence [I.head, I.head  I.head]  stream2list)

[3,4,5,6,7,8,9,10]

The code for enumSequence is enclosed below (enumSequence_ is almost
identical!) To make it complete though I should add some sort of error
handling. I'm not quite sure however what would be the best thing to
do. For instance, what should happen if the stream is finished, but
one of the iteratees is not done yet? Should the whole enumSequence
fail? Similarly, should the whole enumSequence fail if one of the
iteratees throws an error?

I guess throwing some sort of recoverable error could work. But I
still need to figure out how to do that!

-- Maciej

## code ##

enumSequence :: forall m s a el . (Monad m, LL.ListLike s el, Nullable s)
 = [Iteratee s m a]
 - Iteratee s m [a]
enumSequence is = liftI step
where
step :: Stream s - Iteratee s m [a]
step s@(Chunk xs) | LL.null xs = liftI step
  | otherwise  = do
  let is'  = map (joinIM . enumPure1Chunk xs) is
  allDone - lift (checkIfDone is')
  if allDone then uncurry idone = lift (collectResults is')
 else enumSequence (updateChunk s is')
-- TODO: should return an error if not all iteratees are done
step (EOF _) = uncurry idone = lift (collectResults . map
(joinIM . enumEof) $ is)

-- returns true if *all* iteratees are done; otherwise returns false
checkIfDone :: [Iteratee s m a] - m Bool
checkIfDone = liftM and . mapM (\i - runIter i onDone onCont)
where
onDone _ _ = return True
onCont _ _ = return False

-- returns a list of result values and the unconsumed part of the stream
collectResults :: [Iteratee s m a] - m ([a], Stream s)
collectResults = liftM (id *** foldl1 shortest)
 . mapAndUnzipM (\i - runIter i onDone onCont)
where
onDone a s = return (a,s)
onCont _ _ = error enumSequence: collectResults
failed; all iteratees should be done

shortest :: Stream s - Stream s - Stream s
shortest (Chunk xs) (Chunk ys)
| LL.length xs  LL.length ys = Chunk ys
| otherwise   = Chunk xs
shortest s@(EOF _) _ = s
shortest _ s@(EOF _) = s


-- iteratee in *done* state holds the unconsumed part of the chunk it
-- was given; this chunk needs to be discarded when we move further in
-- the stream
updateChunk :: Stream s - [Iteratee s m a] - [Iteratee s m a]
updateChunk s = map (\i - joinIM $ runIter i (\a _ - return
$ idone a s) icontM)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe