Re: [Haskell-cafe] How to write Source for TChan working with LC.take?

2012-05-29 Thread Michael Snoyman
OK, after thinking on this for the past week, I've come up with a
proposal to make this kind of code easier to write (and more of an
explanation on why the behavior was unintuitive in the first place).

http://www.yesodweb.com/blog/2012/05/next-conduit-changes

Do you think the modified yield/await would be a good solution to the problem?

Michael

On Mon, May 21, 2012 at 6:07 AM, Michael Snoyman mich...@snoyman.com wrote:
 I agree that this behavior is non-intuitive, but still believe it's
 the necessary approach. The short answer to why it's happening is that
 there's no exit path in the yield version of the function. To
 understand why, let's expand the code a little bit. Realizing that

    liftIO = lift . liftIO

 and

    lift mr = PipeM (Done Nothing `liftM` mr) (Finalize mr)

 we can expand the yield version into:

 sourceTChanYield2 ch = forever $ do
  let action = liftIO . atomically $ readTChan ch
  ans - PipeM (Done Nothing `liftM` action) (FinalizeM action)
  yield ans

 So the first hint that something is wrong is that the finalize
 function is calling the action. If you try to change that finalize
 action into a no-op, e.g.:

 sourceTChanYield3 :: MonadIO m = TChan a - Source m a
 sourceTChanYield3 ch = forever $ do
  let action = liftIO . atomically $ readTChan ch
  ans - PipeM (Done Nothing `liftM` action) (return ())
  yield ans

 then you get an error message:

 test.hs:36:53:
    Could not deduce (a ~ ())

 The problem is that, as the monadic binding is set up here, the code
 says after running the PipeM, I want you to continue by yielding, and
 then start over again. If you want to expand it further, you can
 change `forever` into a recursive call, expand `yield`, and then
 expand all the monadic binding. Every finalization call is forcing
 things to keep running.

 And remember: all of this is the desired behavior of conduit, since we
 want to guarantee finalizers are always called. Imagine that, instead
 of reading data from a TChan, you were reading from a Handle. In the
 code above, there was no way to call out to the finalizers.

 Not sure if all of that rambling was coherent, but here's my
 recommended solution. What we need is a helper function that allows
 you to branch based on whether or not it's time to clean up. `lift`,
 `liftIO`, and monadic bind all perform the same actions regardless of
 whether or not finalization is being called. The following code,
 however, works correctly:

 liftFinal :: Monad m = m a - Finalize m () - (a - Source m a) - Source m 
 a
 liftFinal action final f = PipeM (liftM f action) final

 sourceTChanYield :: Show a = MonadIO m = TChan a - Source m a
 sourceTChanYield ch = liftFinal
    (liftIO . atomically $ readTChan ch)
    (return ())
    $ \ans - do
        yield ans
        sourceTChanYield ch

 Michael

 On Sun, May 20, 2012 at 4:22 PM, Hiromi ISHII konn.ji...@gmail.com wrote:
 Oops, sorry.
 The last case's behaviour was not as I expected... A correct log is below:

 
 ghci sourceTChanRaw ch $$ LC.isolate 10 =$= LC.mapM_ print
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ghci sourceTChanState ch $$ LC.isolate 10 =$= LC.mapM_ print
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ghci sourceTChanYield ch $$ LC.isolate 10 =$= LC.mapM_ print
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 ()
 *blocks*
 

 So again, sourceTChanYield blocks here even if it is already supplied with 
 enough values!

 -- Hiromi ISHII
 konn.ji...@gmail.com




 ___
 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] What is the difference between runhaskell and compile?

2012-05-29 Thread Chris Dornan
On 29 May 2012 02:21, Magicloud Magiclouds
magicloud.magiclo...@gmail.com wrote:
 Interesting. I have this code tested in Debian unstable/stable, CentOS
 6.1, all 64 bit, with two different version of libldap2.
 At first, Debian-s were installed with 7.4.1, CentOS with 7.2.2. Only
 in CentOS the code connected after compiled.
 Then I removed 7.4.1 from Debian stable and installed 7.2.2. The code worked.
 At last, I installed 7.4.1 in CentOS. The code did not work.

 Could you send the .hi/.o to me, so maybe I could find out the
 different? Also the exact original source.
 Thank you.

Interesting indeed! I am guessing that you are using the GHC-7.4.1
bindist from haskell.org.

I will try and find some time to marshal the source code and
intermediate files (am on the road --
will need to collect it from base, make it generic etc.).

You might also like to try the http://justhub.org ghc-7.4.1-hub on
your CentOS-6.1 node. It is a
separate build from the haskell.org bindist and comes with it's own
in-board gcc (4.6.1) and binutils (2.21)
used for the build. It should work for you.

(You could also try ghc-7.4.2-RC1-hub.)

Chris

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


Re: [Haskell-cafe] What is the difference between runhaskell and compile?

2012-05-29 Thread Chris Dornan
I will send the header and object files off list.

Here is the test program I am using:

import LDAP

main :: IO ()
main =
 do putStrLn domain
domain - getLine
putStrLn bindDN
bindDN - getLine
putStrLn bindPW
bindPW - getLine
putStrLn conecting...
ldap - ldapInit domain ldapPort
ldapSimpleBind ldap bindDN bindPW
putStrLn done

Chris

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


[Haskell-cafe] ANN: hledger 0.18

2012-05-29 Thread Simon Michael
I'm pleased to announce version 0.18 of hledger!

hledger (http://hledger.org) is a haskell library, command-line tool and
web application for working with financial data (or anything that can be
tracked numerically in an accounting journal). It is inspired by and
compatible with John Wiegley's Ledger. hledger reads a plain text file
describing transactions and lets you query account balances or transaction
details by various criteria.  It can also help you record new
transactions, or convert CSV data from your bank.

Release notes (http://hledger.org/NEWS.html):

* web: hledger-web is now based on yesod 1.0

* web: fix js error breaking second use of add form (#72)

* web: make `yesod devel` work

* the command-line now supports a more powerful query language, 
  consistent with the web UI

* hledger now fully supports tags (aka metadata) on both transactions
  and postings, and querying by tag or tag value

* new commands `incomestatement`, `balancesheet`, and `cashflow`
  provide basic financial statements under certain conditions

* format conversion is now done on demand, and the convert command
  has been dropped. So instead of `hledger convert FILE.csv` just do
  `hledger -f FILE.csv print` or any other command. You can also pipe
  any supported format into `hledger -f- CMD` and hledger will try to
  do the right thing.

* support for GHC 6.12 has been dropped; this release has been tested
  with GHC 7.0.4, 7.2.2, and 7.4.1

* unicode is now handled properly on all supported GHC versions

* extensive API, test and internal cleanups

Stats:

- Release contributors: Simon Michael, xiaoruoruo

- 87 days, 155 commits, 6 end-user features and 3 end-user bug fixes
  since last major release

- 216 unit  functional tests (hledger-lib  hledger)

- 7836 lines of code (hledger-lib, hledger  hledger-web)

Install it:

  cabal update; cabal install hledger [hledger-web]

If you have trouble, see http://hledger.org/MANUAL.html#installing .
You can fund a ready-to-run binary for your platform with a donation at
http://hledger.org/DOWNLOAD.html .

Prosperity and clarity,
-Simon

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


Re: [Haskell-cafe] vector operations

2012-05-29 Thread Evan Laforge
Good question.. I copied both to a file and tried ghc-core, but it
inlines big chunks of Data.Vector and I can't read it very well, but
it looks like the answer is no, it still builds the the list of sums.
I guess the next step is to benchmark and see how busy the gc is on
each version.

But my impression was that stream fusion can't handle early aborts,
which was why I was wondering why Vector lacks a foldAbort type
function.

On Wed, May 23, 2012 at 5:13 AM, Jake McArthur jake.mcart...@gmail.com wrote:
 Have you already verified that stream fusion won't just do this for you?

 On May 23, 2012 12:35 AM, Evan Laforge qdun...@gmail.com wrote:

 So I wanted to find the first index in a vector whose running sum is
 greater than a given number.

 The straightforward way is to create the running sum and then search:

 Vector.findIndex (=target) (Vector.scanl' (+) 0 vector)

 But vectors are strict so it could do extra work, and what if I don't
 want to generate garbage?  I could do it with a fold, but it would
 have to have the ability to abort early.  Of course I could write such
 a fold myself using indexing:

 import qualified Data.Vector.Generic as Vector

 fold_abort :: (Vector.Vector v a) = (accum - a - Maybe accum) - accum
    - v a - accum
 fold_abort f accum vec = go 0 accum
    where go i accum = maybe accum (go (i+1)) $ f accum = vec Vector.!? i

 find_before :: (Vector.Vector v a, Num a, Ord a) = a - v a - Int
 find_before n = fst . fold_abort go (0, 0)
    where
    go (i, total) a
        | total + a = n = Nothing
        | otherwise = Just (i+1, total+a)

 So it's bigger and clunkier, but I would think it would be much more
 efficient (provided using Data.Vector.Generic won't inhibit inlining
 and unboxing).  But I'm a bit surprised there isn't already something
 like fold_abort... or is there?

 ___
 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] vector operations

2012-05-29 Thread Roman Leshchinskiy
On 29/05/2012, at 19:49, Evan Laforge wrote:

 Good question.. I copied both to a file and tried ghc-core, but it
 inlines big chunks of Data.Vector and I can't read it very well, but
 it looks like the answer is no, it still builds the the list of sums.
 I guess the next step is to benchmark and see how busy the gc is on
 each version.

Vector should definitely fuse this, if it doesn't it's a bug. Please report if 
it doesn't for you. To verify, just count the number of letrecs in the 
optimised Core. You'll see one letrec if it has been fused and two if it hasn't.

 But my impression was that stream fusion can't handle early aborts,
 which was why I was wondering why Vector lacks a foldAbort type
 function.

Stream fusion easily handles early aborts. There isn't anything like foldAbort 
precisely because it can be built out of existing operations at no extra cost.

Roman

 On Wed, May 23, 2012 at 5:13 AM, Jake McArthur jake.mcart...@gmail.com 
 wrote:
 Have you already verified that stream fusion won't just do this for you?
 
 On May 23, 2012 12:35 AM, Evan Laforge qdun...@gmail.com wrote:
 
 So I wanted to find the first index in a vector whose running sum is
 greater than a given number.
 
 The straightforward way is to create the running sum and then search:
 
 Vector.findIndex (=target) (Vector.scanl' (+) 0 vector)
 
 But vectors are strict so it could do extra work, and what if I don't
 want to generate garbage?  I could do it with a fold, but it would
 have to have the ability to abort early.  Of course I could write such
 a fold myself using indexing:
 
 import qualified Data.Vector.Generic as Vector
 
 fold_abort :: (Vector.Vector v a) = (accum - a - Maybe accum) - accum
- v a - accum
 fold_abort f accum vec = go 0 accum
where go i accum = maybe accum (go (i+1)) $ f accum = vec Vector.!? i
 
 find_before :: (Vector.Vector v a, Num a, Ord a) = a - v a - Int
 find_before n = fst . fold_abort go (0, 0)
where
go (i, total) a
| total + a = n = Nothing
| otherwise = Just (i+1, total+a)
 
 So it's bigger and clunkier, but I would think it would be much more
 efficient (provided using Data.Vector.Generic won't inhibit inlining
 and unboxing).  But I'm a bit surprised there isn't already something
 like fold_abort... or is there?
 
 ___
 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


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


Re: [Haskell-cafe] vector operations

2012-05-29 Thread Duncan Coutts
On 29 May 2012 11:49, Evan Laforge qdun...@gmail.com wrote:
 Good question.. I copied both to a file and tried ghc-core, but it
 inlines big chunks of Data.Vector and I can't read it very well, but
 it looks like the answer is no, it still builds the the list of sums.
 I guess the next step is to benchmark and see how busy the gc is on
 each version.

 But my impression was that stream fusion can't handle early aborts,
 which was why I was wondering why Vector lacks a foldAbort type
 function.

Note that foldr allows early abort so that's fine. Also, there's no
fundamental restriction due to stream fusion. Stream fusion can be
used for lazy lists afterall and can implement Data.List.foldr just
fine.

Duncan

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


Re: [Haskell-cafe] A functional programming solution for Mr and Mrs Hollingberry

2012-05-29 Thread Eric Rasmussen
I added a Scala solution since Haskell is already well represented.

Regarding exercises that are easier in OO, I don't think you'll find one
that a good Haskell programmer can't match in a functional style. But if
you make simulation the goal of the exercise (rather than writing a program
that takes input and produces the correct output however it likes), you'll
get a nice compare/contrast of OO and non-OO approaches.

One idea (contrived and silly though it is) is modeling a Courier that
delivers message to Persons. There is a standard default reply for all
Persons, some individuals have their own default reply, and there are
conditional replies based on the sender. Each reply has the ability to
alter a Person's mood. The goal of the exercise would be to read in a CSV
file in the form of To, From, Message, and then output the interactions
based on rules. A sample run might look like:

Courier delivers let's have lunch from Susan to Joe
Joe replies Thanks for the message!
Courier delivers how's your day? from Joe's Best Friend to Joe
Joe replies Hey Best Friend, thanks for the message!
Joe's mood changes from normal to happy

This would be a trivial exercise for any OO programmer, and I suspect
solutions in different OO languages would look pretty much the same. But in
pure functional programming there are more choices to make (particularly
the choice of data structures and types), so you might see a wider range of
creative approaches.


On Sun, May 27, 2012 at 8:21 PM, Alexander Solla alex.so...@gmail.comwrote:



 On Sun, May 27, 2012 at 7:07 PM, Richard O'Keefe o...@cs.otago.ac.nzwrote:


 On 26/05/2012, at 4:16 AM, David Turner wrote:
 
  I don't. I think the trouble is that classes don't add value in
 exercises of this size.

 This was the key point, I think.
 In this example, there wasn't any significant behaviour that could be
 moved
 to superclasses.  For that matter, whether a supplier is plain, preferred,
 or problematic is, one hopes, not a *permanent* property of a supplier.

 Sometimes higher-order functions can substitute for classes.


 Functors can always substitute for OO classes.  A class system is a
 functor from the set of objects to a set of methods, mediated by
 inheritance, or things like message-passing, duck typing, prototyping, etc.

 Functions with the type Foo - Foo can be easily used to implement a
 prototype based dispatch mechanism.  Indeed, this is a common Haskell
 pattern.  Define:

 -- Library code:
 defaultFoo :: Foo
 defaultFoo = Foo { bar =  ..., baz = ... }

 -- Client code
 myFoo = defaultFoo { bar = myBar }

 Things can get as complicated as you would like, up to and including
 inheritance, by using functors other than ((-) a)

 The defining characteristic of OO is that objects are stateful, but
 self-contained entities.  How methods are defined and dispatched vary
 wildly across OO languages.

 ___
 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] A functional programming solution for Mr and Mrs Hollingberry

2012-05-29 Thread Richard O'Keefe

On 30/05/2012, at 10:16 AM, Eric Rasmussen wrote:
 One idea (contrived and silly though it is) is modeling a Courier that 
 delivers message to Persons. There is a standard default reply for all 
 Persons, some individuals have their own default reply, and there are 
 conditional replies based on the sender. Each reply has the ability to alter 
 a Person's mood. The goal of the exercise would be to read in a CSV file in 
 the form of To, From, Message, and then output the interactions based on 
 rules.

Simulation is of course what Simula 67, the first well known object oriented 
language,
was devised for.  Simula 67 was also one of the first three languages I know of 
to
include concurrency as a standard feature, the others being PL/I and Algol 68.  
And
to an Erlang programmer, the obvious way to model a simulation is with one 
process
per entity.  It's also not accidental that Smalltalk has had concurrency since 
it
first appeared, and the simulation example in the Blue Book (and the simulation
library derived form it) makes essential use of concurrency.

In ML I would use the Concurrent ML facilities (supported in SML/NJ and MLton).
Using Haskell I would definitely consider simulation using concurrency.

And objects per se might not be all that useful.  In F# I would expect to use
threads but not classes.




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


Re: [Haskell-cafe] What is the difference between runhaskell and compile?

2012-05-29 Thread Magicloud Magiclouds
A little information.
I did not notice the gcc/binutils versions. But in CentOS, the ghc
7.2.2/7.4.1 were all compiled myself with all default configurations.

On Tue, May 29, 2012 at 10:54 PM, Chris Dornan ch...@chrisdornan.com wrote:
 On 29 May 2012 02:21, Magicloud Magiclouds
 magicloud.magiclo...@gmail.com wrote:
 Interesting. I have this code tested in Debian unstable/stable, CentOS
 6.1, all 64 bit, with two different version of libldap2.
 At first, Debian-s were installed with 7.4.1, CentOS with 7.2.2. Only
 in CentOS the code connected after compiled.
 Then I removed 7.4.1 from Debian stable and installed 7.2.2. The code worked.
 At last, I installed 7.4.1 in CentOS. The code did not work.

 Could you send the .hi/.o to me, so maybe I could find out the
 different? Also the exact original source.
 Thank you.

 Interesting indeed! I am guessing that you are using the GHC-7.4.1
 bindist from haskell.org.

 I will try and find some time to marshal the source code and
 intermediate files (am on the road --
 will need to collect it from base, make it generic etc.).

 You might also like to try the http://justhub.org ghc-7.4.1-hub on
 your CentOS-6.1 node. It is a
 separate build from the haskell.org bindist and comes with it's own
 in-board gcc (4.6.1) and binutils (2.21)
 used for the build. It should work for you.

 (You could also try ghc-7.4.2-RC1-hub.)

 Chris



-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.

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