Re: [Haskell-cafe] One-element tuple

2013-08-19 Thread Chris Wong
 It seems to me that this is Identity given a different name.

Close. But Identity is declared using newtype (just like monad
transformers), whereas OneTuple is declared with data (like the other
tuples).

This may or may not matter, depending on your use case.


 On 20/08/2013 1:17 PM, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
 wrote:

 On 20 August 2013 11:07, AntC anthony_clay...@clear.net.nz wrote:
  Daniel F difrumin at gmail.com writes:
 
  Can you please elaborate why this inconsistency is annoying and what's
  the use of OneTuple?
  Genuine question,
 
  Hi Daniel, the main annoyance is the verbosity (of using a data type and
  constructor), and that it no longer looks like a tuple.
 
  The inconsistency is because a one-element tuple is just as cromulent as
  a
  n-element, or a zero-element. (And that a one-element tuple is a
  distinct
  type from the element on its own/un-tupled.)

 Why is it as cromulent (especially as I'm not so sure we could
 really consider () to be merely a zero-element tuple)?

 I can see what you're trying to do here, but for general usage isn't a
 single element tuple isomorphic to just that element (which is what
 newtypes are for if you need that distinction)?

 
  So if I have instances (as I do) like:
 
  instance C (a, b) ...
  instance C () ...
 
  I can't usefully put either of these next two, because they're equiv to
  the third:
 
  instance C (( a )) ...
  instance C ( a )   ...
  instance C a   ...   -- overlaps every instance
 
  Similarly for patterns and expressions, the so-called superfluous parens
  are just stripped away, so equivalent to the bare term.
 
  The use of OneTuple is that it comes with all Prelude instances pre-
  declared (just like all other tuple constructors). I don't see that it
  has
  an advantage over declaring your own data type(?) I'd also be interested
  to know who is using it, and why.

 As far as I'm aware, it's just a joke package, but two packages
 dealing with tuples seem to use it:
 http://packdeps.haskellers.com/reverse/OneTuple

 
  What I'm doing is building Type-Indexed Tuples [1] mentioned in HList
  [2],
  as an approach to extensible records [3], on the model of Trex [4] --
  all
  of which acknowledge one-element records/rows/tuples. And then I'm using
  the tuples as a platform for relational algebra [5] with natural Join
  (and
  ideas from Tropashko's 'Relational Lattice' [6]).
 
  Is there anybody using OneTuple 'in anger'?
 
  AntC
 
  [1] M. Shields and E.Meijer. Type-indexed rows. In Proceedings
  of the 28th ACM SIGPLAN-SIGACT symposium on Principles
  of Programming Languages, pages 261–275. ACMPress, 2001.
  [2] http://hackage.haskell.org/package/HList
  [3] http://www.haskell.org/haskellwiki/Extensible_record
  [4] http://web.cecs.pdx.edu/~mpj/pubs/polyrec.html
  [5] http://en.wikipedia.org/wiki/Relational_algebra#Natural_join_
  [6] http://vadimtropashko.wordpress.com/relational-lattice/
 
 
 
 
  On Fri, Aug 16, 2013 at 5:35 AM, AntC anthony_clayden at
  clear.net.nz wrote:
  There's an annoying inconsistency:
  (CustId 47, CustName Fred, Gender Male)  -- threeple
  (CustId 47, CustName Fred)-- twople
  --  (CustId 47)-- oneple not!
  () -- nople
 
 
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 http://IvanMiljenovic.wordpress.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




-- 
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] memoization

2013-07-22 Thread Chris Wong
 memoized_fib :: Int - Integer
 memoized_fib = (map fib [0 ..] !!)
where fib 0 = 0
  fib 1 = 1
  fib n = memoized_fib (n-2) + memoized_fib (n-1)


[.. snipped ..]

 Could someone explain the technical details of why this works? Why is map
 fib [0 ..] not recalculated every time I call memoized_fib?

A binding is memoized if, ignoring everything after the equals sign,
it looks like a constant.

In other words, these are memoized:

x = 2

Just x = blah

(x, y) = blah

f = \x - x + 1
-- f = ...

and these are not:

f x = x + 1

f (Just x, y) = x + y

If you remove the right-hand side of memoized_fib, you get:

memoized_fib = ...

This looks like a constant. So the value (map fib [0..] !!) is memoized.

If you change that line to

memoized_fib x = map fib [0..] !! x

GHC no longer memoizes it, and it runs much more slowly.

--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] List Monads and non-determinism

2013-07-19 Thread Chris Wong
 I thought = was left associative?  It seems to be in the examples from
 Learn You A Haskell.

It is. But lambdas are parsed using the maximal munch rule, so they
extend *as far to the right as possible*.

So

\x - x * 2 + 1

would be parsed as

\x - (x * 2 + 1)  -- right

not

(\x - x) * 2 + 1  -- wrong

which is obviously incorrect.

I believe C uses a similar rule for funny expressions like `x+++y`
(using maximal munch: `(x++) + y`).


 I tried to use the associative law to bracket from the right but it didn't
 like that either...

 [1,2] = (\x - (\n - [3,4])) x  = \m - return (n,m))

 Any thoughts?

 Matt

 On 19 Jul 2013, at 23:35, Rogan Creswick cresw...@gmail.com wrote:

 On Fri, Jul 19, 2013 at 3:23 PM, Matt Ford m...@dancingfrog.co.uk wrote:

 I started by putting brackets in

 ([1,2] = \n - [3,4]) = \m - return (n,m)

 This immediately fails when evaluated: I expect it's something to do
 with the n value now not being seen by the final return.


 You're bracketing from the wrong end, which your intuition about n's
 visibility hints at.  Try this as your first set of parens:

  [1,2] = (\n - [3,4] = \m - return (n,m))

 --Rogan



 It seems to me that the return function is doing something more than
 it's definition (return x = [x]).

 If ignore the error introduced by the brackets I have and continue to
 simplify I get.

 [3,4,3,4] = \m - return (n,m)

 Now this obviously won't work as there is no 'n' value.  So what's
 happening here? Return seems to be doing way more work than lifting the
 result to a list, how does Haskell know to do this?  Why's it not in the
 function definition?  Are lists somehow a special case?

 Any pointers appreciated.

 Cheers,

 --
 Matt

 ___
 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




--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] How to write a pure String to String function in Haskell FFI to C++

2013-06-02 Thread Chris Wong
 The C++/C function (e.g. toUppers) is computation-only and as pure as cos
 and tan. The fact that marshaling string incurs an IO monad in current
 examples is kind of unintuitive and like a bug in design. I don't mind
 making redundant copies under the hood from one type to another..

If you can guarantee that the call is pure, then you can execute it
directly using `unsafePerformIO`. Simply call the external function as
usual, then invoke `unsafePerformIO` on the result.

See 
http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/System-IO-Unsafe.html.

On another note, if you really care about performance, you should use
the `bytestring` and `text` packages instead of String. They are
implemented in terms of byte arrays, instead of linked lists, hence
are both faster and more FFI-friendly.




 On Sun, Jun 2, 2013 at 8:08 PM, Brandon Allbery allber...@gmail.com wrote:

 On Sun, Jun 2, 2013 at 8:01 PM, Thomas Davie tom.da...@gmail.com wrote:

 On 2 Jun 2013, at 16:48, Brandon Allbery allber...@gmail.com wrote:

 (String is a linked list of Char, which is also not a C char; it is a
 constructor and a machine word large enough to hold a Unicode codepoint. And
 because Haskell is non-strict, any part of that linked list can be an
 unevaluated thunk which requires forcing the evaluation of arbitrary Haskell
 code elsewhere to reify the value; this obviously cannot be done in the
 middle of random C code, so it must be done during marshalling.)


 I'm not convinced that that's obvious – though it certainly requires
 functions (that go through the FFI) to grab each character at a time.


 I think you underestimate the complexity of the Haskell runtime and the
 interactions between it and the FFI. Admittedly it is probably not obvious
 in the sense of anyone can tell without knowing anything about it that it
 can't possibly work, but it should be at least somewhat obvious to someone
 who sees why there needs to be an FFI in the first place that the situation
 is not trivial, and that they probably should not blindly assume that the
 only reason one can't just pass Haskell values directly to C is that some
 GHC developer was feeling lazy at the time.

 --
 brandon s allbery kf8nh   sine nomine
 associates
 allber...@gmail.com
 ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net



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




--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] question about GADT and deriving automatically a Show instance

2013-05-17 Thread Chris Wong
On Sat, May 18, 2013 at 9:11 AM, TP paratribulati...@free.fr wrote:

 So the following version does not work:
 
 [..]
 data Person :: Gender - * where
 Dead :: Person Gender  -- WHAT DO I PUT HERE
 Alive :: { name :: String
   , weight :: Float
   , father :: Person Gender } - Person Gender

Here's the problem. In the line:

Dead :: Person Gender

you are referring to the Gender *type*, not the Gender kind.

To refer to the kind instead, change this to:

Dead :: forall (a :: Gender). Person a

This means for all types A which have the kind Gender, I can give you
a Person with that type. The Alive declaration and deriving clause
can be fixed in a similar way.

Also, to enable the forall syntax, you need to add

{-# LANGUAGE ExplicitForAll #-}

at the top of the file.

Chris


--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] ANN: Robot - Simulate keyboard and mouse events under X11

2013-05-13 Thread Chris Wong
Oh, I see now. I originally made the runRobot functions reset the
input state when the Robot finished running. That worked well for my
use case (testing GUIs), but as you have noticed, it causes
unintuitive behavior when runRobot is called at a high frequency.

In hindsight, that was a design flaw on my part: that resetting
behavior should be specified explicitly, not attached unconditionally
to every call to runRobot.

I've removed the offending code, and released it as version 1.1.
Hopefully I've ironed out the issues now :)


On Mon, May 13, 2013 at 12:49 PM, Niklas Hambüchen m...@nh2.me wrote:
 Can you show me the code that triggers that behavior?

 It is basically

 Just connection - connect
 forever $ do
   (x,y) - getGyroMovement
   runRobotWithConnection (moveBy x y) connection



--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] ANN: Robot - Simulate keyboard and mouse events under X11

2013-05-13 Thread Chris Wong
I removed the functionality because I didn't really see a use for it
anymore. The `hold` and `tap` functions are already exception safe
(thanks to `bracket`), and anyone who uses the unguarded `press`
function probably wants to keep it held down anyway.

Chris


On Tue, May 14, 2013 at 12:46 PM, Niklas Hambüchen m...@nh2.me wrote:
 Awesome, that works very well, and it even made my program run faster /
 with less CPU.

 The reset functionality is useful, but I think optional is better. Did
 you remove it entirely or is it still available?

 On Tue 14 May 2013 08:25:04 SGT, Chris Wong wrote:
 Oh, I see now. I originally made the runRobot functions reset the
 input state when the Robot finished running. That worked well for my
 use case (testing GUIs), but as you have noticed, it causes
 unintuitive behavior when runRobot is called at a high frequency.

 In hindsight, that was a design flaw on my part: that resetting
 behavior should be specified explicitly, not attached unconditionally
 to every call to runRobot.

 I've removed the offending code, and released it as version 1.1.
 Hopefully I've ironed out the issues now :)


 On Mon, May 13, 2013 at 12:49 PM, Niklas Hambüchen m...@nh2.me wrote:
 Can you show me the code that triggers that behavior?

 It is basically

 Just connection - connect
 forever $ do
   (x,y) - getGyroMovement
   runRobotWithConnection (moveBy x y) connection



 --
 Chris Wong, fixpoint conjurer
   e: lambda.fa...@gmail.com
   w: http://lfairy.github.io/



--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] ANN: Robot - Simulate keyboard and mouse events under X11

2013-05-12 Thread Chris Wong
On Thu, May 9, 2013 at 1:36 PM, Chris Wong
chrisyco+haskell-c...@gmail.com wrote:
 On Thu, May 9, 2013 at 4:47 AM, Niklas Hambüchen m...@nh2.me wrote:
 Hi,

 I just started using your library to move my cursor.

 Is it possible that it ignores negative values in moveBy?

 In other words, I can only move the cursor into one direction.

 I did some research, and traced this to a bug in an old (1.6) version
 of xcb-proto [1]. The coordinates were declared incorrectly as Word16,
 instead of Int16 as they should have been. It's been fixed in
 xcb-proto since 1.7.

Okay, I've released a new version of Robot (1.0.1.1), that should fix
this bug. Niklas: can you try it out please?

Also, it turns out taking a screenshot is much easier than I thought.
A single call to getImage returns a list of bytes, which happens to
match exactly the internal structure used by JuicyPixels. I'll look
deeper into this when I get the time.

Chris

--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] ANN: Robot - Simulate keyboard and mouse events under X11

2013-05-12 Thread Chris Wong
On Sun, May 12, 2013 at 8:46 PM, Niklas Hambüchen m...@nh2.me wrote:
 Yes, that works now.

Excellent!

 I have another problem though: I move the cursor at high resolution
 (128 Hz) and it seems that when robot issues a command to X, it
 disables (keyboard) state so far. This means that it's impossible for
 me to Ctrl-C my program: Only c is sent all the time, me pressing
 Ctrl seems to be reset with the next robot event.

Can you show me the code that triggers that behavior?

--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] ANN: Robot - Simulate keyboard and mouse events under X11

2013-05-08 Thread Chris Wong
On Thu, May 9, 2013 at 4:47 AM, Niklas Hambüchen m...@nh2.me wrote:
 Hi,

 I just started using your library to move my cursor.

 Is it possible that it ignores negative values in moveBy?

 In other words, I can only move the cursor into one direction.

I did some research, and traced this to a bug in an old (1.6) version
of xcb-proto [1]. The coordinates were declared incorrectly as Word16,
instead of Int16 as they should have been. It's been fixed in
xcb-proto since 1.7.

I've cc'd Antoine Latter, the maintainer of XHB, about this bug. Once
he uploads a new version of XHB, I'll be happy to fix it on my end.

[1] 
http://cgit.freedesktop.org/~keithp/xcb-proto/commit/src/xtest.xml?id=f3ae971edce37ad96ef0b8a6059c1f853e88fcf3

On Tue, May 7, 2013 at 5:18 AM, Jeanne-Kamikaze
jeannekamik...@gmail.com wrote:
 Looks like an interesting library. Will it be able to read pixels from a
 window at some point?

Not sure -- I have no idea how screen capturing works in X11. Calling
gnome-screenshot should probably cover most use cases.

Chris

--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


[Haskell-cafe] ANN: Robot - Simulate keyboard and mouse events under X11

2013-04-22 Thread Chris Wong
I'm pleased to announce the initial release of Robot!

Robot lets you send fake keyboard and mouse events, just like its
namesake in Java.

Only X11 systems are supported right now (via XTest), but Windows and
Mac can be added later if anyone cares.


## Features

+ Simple API (only 9 functions and 3 types)

+ Few dependencies

+ Exception safe -- unlike with other libraries, all keys and buttons
are released automatically when the robot terminates. `bracket` and
`finally` are used where appropriate.


## Links

Hackage: http://hackage.haskell.org/package/robot-1.0

Examples: https://github.com/lfairy/robot/tree/master/examples


Happy hacking!
Chris

--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] Fwd: [Haskell-beginners] Monad instances and type synonyms

2013-04-14 Thread Chris Wong
On Sun, Apr 14, 2013 at 5:10 PM, Christopher Howard
christopher.how...@frigidcode.com wrote:
 type Adjustment a = SaleVariables - a

 [...]

 instance Monad Adjustment where

   (=) = ...
   return = ...

Essentially, you can't partially apply type synonyms. I don't recall
the exact reasoning, but if this sort of thing was allowed it would
probably poke funny holes in the type system.

Also, Control.Monad.Instances already supplies a Monad instance for
functions (r - a). So even if that did pass, you'd bump into
overlapping instances anyway.

Chris

 
 If I try this, I get

 code:
 
 Type synonym `Adjustment' should have 1 argument, but has been given none
 In the instance declaration for `Monad Adjustment'
 

 But if I give an argument, then it doesn't compile either (it becomes a
 * kind). And I didn't want to make the type with a regular data
 declaration either, because then I have to give it a constructor, which
 doesn't fit with what I want the type to do.

 --
 frigidcode.com

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


--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-28 Thread Chris Wong
On Thu, Feb 28, 2013 at 1:26 PM, Brandon Allbery allber...@gmail.com wrote:
 On Wed, Feb 27, 2013 at 8:37 AM, Corentin Dupont corentin.dup...@gmail.com
 wrote:
 Hi Chris,
 Thanks!
 That's true for the user number. What should I do? Encrypt it?

 It's not that you have a user number, or even that it's accessible: it's
 that it's the entirety of access control, meaning that if the user changes
 it they can masquerade as another user. The correct solution is that a user
 should authenticate, which creates a session hash that you stash away and
 also send back to the user as a cookie so the browser will present it on
 accesses. Then you check that the presented hash is there and matches the
 session hash. These should expire periodically, requiring the user to log
 back in again.

Brandon pretty much pulled the words out of my mouth, but I have one
last thing to add: no matter how well you encrypt the information, as
long as it's in the URL it's insecure.

Hypothetical situation #1: if there's someone looking over your
shoulder, they can just note down the address -- it is in plain view,
after all.

Even more likely: your friend wants to watch the game, so you send her
the link. Unfortunately, you forget to delete your session information
from the URL. Now your friend (conveniently named Eve) has hijacked
your account and is voting on your behalf.

The Ruby on Rails website has an excellent explanation of common
security holes [1]. The article is Rails-centric, but most of it
applies to Haskell as well.

[1] http://guides.rubyonrails.org/security.html

As for libraries, Happstack has happstack-authenticate [2]. I haven't
used it myself, but it looks good.

[2] http://hackage.haskell.org/package/happstack-authenticate

Chris

 --
 brandon s allbery kf8nh   sine nomine associates
 allber...@gmail.com  ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net

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


Re: [Haskell-cafe] ANN: Nomyx 0.1 beta, the game where you can change the rules

2013-02-26 Thread Chris Wong
 Hello everybody!
 I am very happy to announce the beta release [1] of Nomyx, the only game
 where You can change the rules.

I just gave it a go -- it looks fun :)

However, I've spotted a security hole. The current user number is
stored in the URL -- if I change that number, I can masquerade as
someone else! Is this behavior intended?

 This is an implementation of a Nomic [2] game in Haskell (I believe the
 first complete implementation). In a Nomyx game you can change the rules of
 the game itself while playing it. The players can submit new rules or modify
 existing ones, thus completely changing the behaviour of the game through
 time. The rules are managed and interpreted by the computer. They must be
 written in the Nomyx language, which is a subset of Haskell.
 At the beginning, the initial rules are describing:
 - how to add new rules and change existing ones. For example a unanimity
 vote is necessary to have a new rule accepted.
 - how to win the game. For example you win the game if you have 5 rules
 accepted.
 But of course even that can be changed!

 Here is a video introduction and first tutorial of the game:
 http://vimeo.com/58265498
 The game is running here: www.nomyx.net:8000/Nomyx
 I have set up a forum where players can learn about Nomyx and discuss the
 rules they intend to propose: www.nomyx.net/forum

 As this is the first beta release of the game, I'm looking for beta testers
 :) Although I tested it quite a lot, I'm sure a lot of bugs remains,
 especially in multiplayer.
 So if you are interested in testing Nomyx, please go to this forum thread
 and we'll set up a small team to start a match!
 http://www.nomyx.net/forum/viewtopic.php?p=5

 Comments/contributions are very highly welcome! There is still a lot to do.
 As for now, the game is not completely securised. It is easy to break it by
 submitting rules containing malicious code. I'm working on it. If you'd like
 to do security testing, please do it locally on your own machine and send me
 a bug report :).

 Cheers,
 Corentin

 [1] http://hackage.haskell.org/package/Nomyx
 [2] www.nomic.net

 ___
 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] catamorphisms and attribute grammars

2013-01-26 Thread Chris Wong
Hi Petr,

Congratulations -- you've just implemented a Moore machine! [1]

I posted something very much like this just last year [2]. It's a very
common pattern in Haskell, forming the basis of coroutines and
iteratees and many other things.

Edward Kmett includes it in his machines package [3]. His variation,
like mine, hides the state inside a closure, removing the need for
existentials. pipes 2.0 contains one implemented as a free monad [4].

[1] http://en.wikipedia.org/wiki/Moore_machine
[2] 
http://hackage.haskell.org/packages/archive/machines/0.2.3/doc/html/Data-Machine-Moore.html
[3] http://www.haskell.org/pipermail/haskell-cafe/2012-May/101460.html
[4] 
http://hackage.haskell.org/packages/archive/pipes/2.0.0/doc/html/Control-Pipe-Common.html

Chris

On Sun, Jan 27, 2013 at 11:03 AM, Petr P petr@gmail.com wrote:
   Dear Haskellers,

 I read some stuff about attribute grammars recently [1] and how UUAGC [2]
 can be used for code generation. I felt like this should be possible inside
 Haskell too so I did some experiments and I realized that indeed
 catamorphisms can be represented in such a way that they can be combined
 together and all run in a single pass over a data structure. In fact, they
 form an applicative functor.

 [1] http://www.haskell.org/haskellwiki/Attribute_grammar
 [2] Utrecht University Attribute Grammar Compiler

 To give an example, let's say we want to compute the average value of a
 binary tree. If we compute a sum first and then count the elements, the
 whole tree is retained in memory (and moreover, deforestation won't happen).
 So it's desirable to compute both values at once during a single pass:

 -- Count nodes in a tree.
 count' :: (Num i) = CataBase (BinTree a) i
 count' = ...

 -- Sums all nodes in a tree.
 sum' :: (Num n) = CataBase (BinTree n) n
 sum' = ...

 -- Computes the average value of a tree.
 avg' :: (Fractional b) = CataBase (BinTree b) b
 avg' = (/) $ sum' * count'

 Then we can compute the average in a single pass like

 runHylo avg' treeAnamorphism seed

 My experiments together with the example are available at
 https://github.com/ppetr/recursion-attributes

 I wonder, is there an existing library that expresses this idea?

   Best regards,
   Petr Pudlak


 ___
 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] mtl: Why there is Monoid w constraint in the definition of class MonadWriter?

2012-12-10 Thread Chris Wong
Hi Petr,

On Sun, Dec 9, 2012 at 7:59 AM, Petr P petr@gmail.com wrote:

 The class is defined as

  class (Monoid w, Monad m) = MonadWriter w m | m - w where
...

 What is the reason for the Monoid constrait? It seems superfluous to me. I
 recompiled the whole package without it, with no problems.

How I see it, the MTL classes are there to lift operations
automatically through layers of transformers. They're just a hack to
avoid having to call `lift` all the time, and aren't really designed
to be used on monads other than the original WriterT.

With this interpretation, the constraint makes sense -- it is simply
reflecting the constraints already on the concrete monad.

Chris

 Of course, the Monoid constraint is necessary for most _instances_, like
 in

  instance (Monoid w, Monad m) = MonadWriter w (Lazy.WriterT w m) where
  ...

 but this is a different thing - it depends on how the particular instance
 is implemented.

 I encountered the problem when I needed to define an instance where the
 monoidal structure is fixed (Last) and I didn't want to expose it to the
 user. I wanted to spare the user of of having to write Last/getLast
 everywhere. (I have an instance of MonadWriter independent of WriterT, its
 'tell' saves values to a MVar. Functions 'listen' and 'pass' create a new
 temporary MVar. I can post the detail, if anybody is interested.)

 Would anything break by removing the constraint? I think the type class
 would get a bit more general this way.

   Thanks for help,
   Petr Pudlak

 ___
 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] Parsing different types, same typeclass

2012-11-17 Thread Chris Wong
Hello José,

 So, I have a typeclass Action which defines method run:

 class Action a where
 run :: a - Int

 (snipped)

 Now, I want to parse either A or B from a String.
 I was thinking about something like this...

 parseAction :: (Action a, Read a) = String - a
 parseAction str
 | (A  `isPrefixOf` str = (read :: String - A) str
 | (B  `isPrefixOf` str = (read :: String - B) str

 The problem is that when calling parseAction I get ambiguous type
 constraints. How to implement a parse function for two distinct
 types that share the same typeclass Action. Because after calling
 parseAction I don't whether A or B was returned: I only care
 that they are Action instances so I can call run.

The problem with your current type:

(Action a, Read a) = String - a

is that it actually means:

For any type that implements Action and Read, I can convert a
string to that type.

This is wrong because if a user of your module added another type C,
your function wouldn't be able to handle it -- it only knows about A
and B. That is what GHC is trying to tell you.

How you can solve this problem depends on what you're trying to do. If
there is a finite number of actions, you can merge them into a single
type and remove the type class altogether:

data Action = A Int | B Int
deriving (Read, Show)

run :: Action - Int
run (A x) = x
run (B x) = x

parse :: String - Action
parse = read

If you have a possibly unlimited number of possible actions, there are
many approaches to this -- including, as Stephen said, existential
types. However, it's hard to decide on a proper solution without
knowing what you're actually trying to do.

Chris

 Best regards,
 José

 ___
 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] generalizing the writer monad

2012-10-17 Thread Chris Wong
Hello!

On Thu, Oct 18, 2012 at 6:59 AM, Petr P petr@gmail.com wrote:
 Hi,

 (this is a literate Haskell post.)

 lately I was playing with the Writer monad and it seems to me that it
 is too tightly coupled with monoids. Currently, MonadWriter makes the
 following assumptions:

 (1) The written value can be read again later.
 (2) For that to be possible it has to be monoid so that multiple (or
 zero) values can be combined.

 I fell say that this is a bit restricting. Sometimes, the written
 value can be lost - either used to compute something else or for
 example sent out using some IO action to a file, network etc. For
 example, I'd like to create an IO-based writer monad whose `tell` logs
 its argument somewhere - prints it, stores to a file etc.

Try the Coroutine monad transformer:

http://hackage.haskell.org/package/monad-coroutine

Instead of writing the log inside the monad, you can yield the message
instead. The calling code is then free to choose what to do with the
messages.

 So what I'm suggesting is to have another type class between Monad and
 MonadWriter, let's say MonadTell, which only allows to write values,
 not to retrieve them later:

 {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, 
 FunctionalDependencies #-}
 import Control.Monad
 import Control.Monad.Trans
 import qualified Control.Monad.Writer as W
 import qualified Control.Monad.Reader as R
 import Data.Monoid

 class Monad m = MonadTell w m where
 tell :: w - m ()
 tell w = writer ((), w)
 writer :: (a, w) - m a
 writer ~(a, w) = tell w  return a

 (We don't need fun.deps. here, they're needed in MonadWriter because
 of `listen`. IDK if it'd be still better to add fun.dep. just to
 eliminate typing problems?)

 And MonadWriter would be defined by inheriting from MonadTell:

 class (MonadTell w m, Monoid w) = MonadWriter' w m | m - w where
 listen :: m a - m (a, w)
 pass :: m (a, w - w) - m a

 Now we could use MonadWriter as before, but we could also make more
 generic writers like:

 newtype Log = Log String deriving Show
 -- Prints logs to stdout.
 instance MonadTell Log IO where
 tell (Log s) = putStrLn s

 -- Collects the length of written logs.
 instance Monad m = MonadTell Log (W.WriterT (Sum Int) m) where
 tell (Log s) = W.tell (Sum $ length s)


 main = do
 let l = Log Hello world
 tell l
 print . getSum . W.execWriter $ (tell l :: W.Writer (Sum Int) ())

 The same applies to MonadReader. We could make another type class
 between Monad and MonadReader just with `ask`:

 class Monad m = MonadAsk r m | m - r where
 ask :: m r

 This would allow us to write instances like

 instance MonadAsk Log IO where
 ask = liftM Log getLine

 Does it make sense?

 Best regards,
 Petr Pudlak

 ___
 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] ANNOUNCE: Sylvia, a lambda calculus visualizer

2012-10-01 Thread Chris Wong
On Tue, Oct 2, 2012 at 3:23 PM, Conrad Parker con...@metadecks.org wrote:
 Nice, it builds and runs fine for me. Perhaps you could include a few
 more example commandlines to get started?  Running without arguments
 (as the README.mkd suggests) just prints the help text.

Thanks for pointing that out! I've added an examples page at

https://github.com/lfairy/sylvia/wiki/Examples

 This is still in very early alpha, but it renders a fair number of
 combinators correctly. I plan to add animated reduction (once I figure
 out how to do it), and eventually develop this into a sandbox game of
 some sort. I'm hoping to get some comments and ideas on how I can take
 it from here.

 I'd love to see a game which incrementally teaches reduction and
 expansion steps in the way that DragonBox [http://dragonboxapp.com/]
 teaches algebra. That would be a learning mode like Angry Birds, where
 new combinator birds are introduced every few levels and a small
 selection of useful birds are provided to help solve each level.

Interesting! I'll have a closer look at it when I have the time.

 (Lambda calculus really should be a kids' game, grown-ups always make
 it seem more complex than it is).

That's exactly the point I'm trying to make :)

Heck, lambda calculus is just as simple as natural numbers (if not
simpler), yet people learn the former at university and the latter a
few months after they're born.

I think the difference is in the way they are taught. Want to teach
someone about numbers? Here's one orange. Here's two oranges. And look
-- put them together, and you get three.

Want to teach someone lambda calculus? Give 'em a textbook, and an
hour-long lecture about programming language theory.

The result doesn't surprise me one bit.

 Conrad.

On Tue, Oct 2, 2012 at 4:16 PM, Alistair Bayley alist...@abayley.org wrote:
 Not sure if it's what you're after, but I was reminded of this (models
 untyped lambda calculus):
   http://worrydream.com/AlligatorEggs/

Thanks -- I've tried that before, and unfortunately it suffers the
same problem I've had with many other visualizations. Because it uses
colors to refer to variables, we end up with two problems:

1. Color blind people can't play it.

2. More subtly: colors - absolute variable names - lots of alpha
conversion. Alligators eating each other is fun. Swapping alligators
frantically to stop accidental capture is not.

Chris

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


[Haskell-cafe] ANNOUNCE: Sylvia, a lambda calculus visualizer

2012-09-27 Thread Chris Wong
Hello all

Some of you in the audience may have read Dave Keenan's paper, [To
Dissect a Mockingbird][]. A subset of that may have wondered if it was
possible to generate those pretty pictures programmatically. For that
subset, I can answer to you -- yes, yes you can.

[To Dissect a Mockingbird]: http://dkeenan.com/Lambda/

Sylvia is a lambda calculus visualizer. It takes in an expression in
the untyped lambda calculus and spits out a pretty picture.

This is still in very early alpha, but it renders a fair number of
combinators correctly. I plan to add animated reduction (once I figure
out how to do it), and eventually develop this into a sandbox game of
some sort. I'm hoping to get some comments and ideas on how I can take
it from here.


Obligatory links


Hackage: http://hackage.haskell.org/package/sylvia

Source: https://github.com/lfairy/sylvia

Documentation: https://github.com/lfairy/sylvia/wiki



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


Re: [Haskell-cafe] hellno - a somewhat different approach to tackling cabal hell

2012-09-02 Thread Chris Wong
On Mon, Sep 3, 2012 at 3:15 PM, Richard Wallace
rwall...@thewallacepack.net wrote:
 I like the approach so far.  But hellno itself seems to have several
 dependencies itself.  So installing with cabal pulls these in as
 fixed libraries (text, mtl, transformers, and parsec).  Any
 plans to make these not have to be fixed? Or is there a trick I'm
 missing?

All of those libraries are included in the Haskell Platform anyway.
The majority of users shouldn't need to install extra packages to get
it to work.

 On Sun, Sep 2, 2012 at 11:25 AM, Danny B danny.b@gmail.com wrote:
 Like many of us, I've suffered from cabal dependency hell and sought relief.

 I wasn't exactly happy with sandboxes - because using per-project ones
 meant package duplication and shared sandboxes suffer from the same
 issues as the GHC package database itself, i.e. reinstalls can break
 other projects, etc. So I wrote hellno, which is so named because that's
 the expression one makes when seeing cabal hell suddenly manifest itself
 and that's also the expression one makes upon encountering yet ANOTHER
 cabal wrapper.

 To quote the README:
 Generally, with hellno you'll get the same result as for blowing away your 
 user
 package database and doing a nice clean install but without having to 
 recompile
 everything and with ability to easily revert back and change between 
 projects.

 Hellno works by keeping all the compiled packages to itself in a
 database, so that when you ask it to bring in the dependencies of a
 project, it will use the precompiled packages if available or install
 the deps and save them for later reuse.

 Hellno puts symlinks in the user package database pointing to packages
 in its storage to make them visible. Mutating the user db is hardly
 elegant, although shouldn't result in much trouble.

 It's been working fine for me, so I figured it may be useful to others.
 You can get hellno from GitHub:
 https://github.com/db81/hellno

 I don't mean to say that sandboxing is inherently bad or should not be
 used, but I guess it's better to consider more than one way.

 ___
 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] How to implement instance of MonadBaseControl IO

2012-08-22 Thread Chris Wong
On Wed, Aug 22, 2012 at 7:16 PM, yi huang yi.codepla...@gmail.com wrote:
 I have a `newtype Yun a = Yun { unYun :: ReaderT YunEnv (ResourceT IO) a }`
 , and i need to define an instance of `MonadBaseControl IO` for it.
 Newtype instance deriving don't work here. I guess the answer is simple, i
 just can't figure it out, hope anybody can lightening me.

I had the same problem some time ago. In my case it's StateT instead
of ReaderT, but it's the same idea. The tough part is getting around
the crazy CPS -- it's supposed to help with performance, but at the
cost of usability.

Anyway, here's my implementation:
https://github.com/lfairy/haskol/blob/master/Web/KoL/Core.hs#L58

Michael Snoyman has written a tutorial as well:
http://www.yesodweb.com/book/monad-control
I'd recommend printing it out and going over it slowly -- it can get
pretty dense at times.

Chris

 Best regards.
 Yihuang.

 ___
 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] Announce: Haskell Platform 2012.2.0.0

2012-06-03 Thread Chris Wong
On Mon, Jun 4, 2012 at 1:16 PM, Jens Petersen
j...@community.haskell.org wrote:
 Congratulations on the release!
 Equally surprising to me is that the number of slashes
 also seems to affect the CSS presentation of the website
 in Chrome.

 // seems to give the Summer theme,
 whereas / gives the Winter one!

 Kind of weird.  Anyway I agree it would be better to avoid
 the superfluous slashes if possible.

Your browser might be caching the file. Try pressing Ctrl-F5 on the winter page.

 I am going build HP 2012.2 for Fedora 18 soon but
 the first proper build may be after ghc-7.4.2 is released.

 Jens

 ___
 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] Announce: Haskell Platform 2012.2.0.0

2012-06-03 Thread Chris Wong
On Mon, Jun 4, 2012 at 1:16 PM, Jens Petersen
j...@community.haskell.org wrote:
 Congratulations on the release!
 Equally surprising to me is that the number of slashes
 also seems to affect the CSS presentation of the website
 in Chrome.

 // seems to give the Summer theme,
 whereas / gives the Winter one!

 Kind of weird.  Anyway I agree it would be better to avoid
 the superfluous slashes if possible.

Your browser might be caching the file. Try pressing Ctrl-F5 on the
winter page to force a reload.

 I am going build HP 2012.2 for Fedora 18 soon but
 the first proper build may be after ghc-7.4.2 is released.

 Jens

 ___
 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] Need inputs for a Haskell awareness presentation

2012-05-31 Thread Chris Wong
On Fri, Jun 1, 2012 at 6:23 AM, C K Kashyap ckkash...@gmail.com wrote:
 Hi folks,

 I have the opportunity to make a presentation to folks (developers and
 managers) in my organization about Haskell - and why it's important - and
 why it's the only way forward. I request you to share your
 experiences/suggestions for the following -
 1. Any thoughts around the outline of the presentation - target audience
 being seasoned imperative programmers who love and live at the pinnacle of
  object oriented bliss.

Rustom nailed it. Take something imperative languages are really,
really bad at and *show* how it's done in Haskell.

*   Parsing

Haskell parser combinators make yacc look old school. By
leveraging Haskell's DSL features, parsers often end up looking like
the grammar they're implementing. Different parser combinator
libraries let you do incremental input  (Attoparsec), show clang-style
diagnostics (Trifecta), or perform crazy optimizations automatically
(uu-parsinglib).

*   Iteratee I/O

encodeFile from to = mapOutput encode (sourceFile from) $$ sinkFile to

It may not look like it, but the above function (using the
conduit package) sets up a I/O pipeline that uses constant memory.
There are HTTP, FTP, text encoding and parser libraries that can hook
into the pipeline the same way. All the resources (sockets, file
handles) tied up in the pipeline are finalized automatically when it
finishes or when an exception is thrown.

*   Epic concurrency

GHC comes with preemptive scheduling, STM and async I/O built in.
Maybe you could demonstrate these with a ping-pong-style application.

 2. Handling questions/comments like these in witty/interesting ways -
     a) It looks good and mathematical but practically, what can we do with
 it, all our stuff is in C++

Anything you can do in another Turing-complete language ;)

Quite a few folks have helped push Haskell into the practical world,
with useful things like web frameworks, ByteStrings, GUI bindings...
It's suitable for practical applications already.

     b) Wow, what do you mean you cannot reason about its space complexity?

That's not a bug, it's a feature!

C++ gives you lots of control over how your program runs.
Unfortunately, most people don't need that or don't know how to use it
effectively. So most of the time, these low-level features just add a
bunch of cruft with no real benefit to the programmer.

Haskell goes the opposite way. The Haskell standard goes out of its
way *not* to say how programs actually run -- only what the result
should be. This lets the compiler optimize much more than in other
languages.

This philosophy is reflected in a common technique called stream
fusion. I can't be bothered writing an example for this, but Google
it and you'll find a few.

     c) Where's my inheritance?

Right behind you ;)

     d) Debugging looks like a nightmare - we cannot even put a print in the
 function?

Traditional debugging -- stepping through the program line by line --
fails miserably in Haskell, mostly due to (b).

Haskell programmers tend to use more mathematical techniques:
* Property-based testing, e.g. reverse (reverse xs) == xs. Used
extensively in Xmonad.
* Algebraic proofs (this works especially well for framework stuff
like the MTL).
* Sexy types: encoding invariants in the type so the compiler checks
it for you. The fb (Facebook API) package does this with the NoAuth
and Auth phantom types.

For I/O-centric code, there's the traditional HUnit and HSpec.

And as Clark said, there's always Debug.Trace.

     e) Static types - in this day and age - come on - productivity in X is
 so much more - and that's because they got rid of type mess.

The designers of Haskell went out of their way to make sure 99% of
types can be inferred by the compiler. It's good practice to put type
annotations on things, but you don't have to.

     f)  Is there anything serious/large written in it? [GHC will not
 qualify as a good answer I feel]

* Yesod and Snap and Happstack -- all mature, well documented web
frameworks. Yesod is the check-everything-at-compile-time one, Snap is
the mix-and-match one and Happstack is the use-lots-of-combinators
one.
* Warp, a simple yet full-featured web server, trashes the competition
in terms of performance -- yet consists of less than 1k lines of code.
It uses all three of the techniques I mentioned above.
* Xmonad is a window manager. I've used quite a few tiling window
managers before, and Xmonad is the only one that hasn't crashed.
* Geordi (http://www.eelis.net/geordi/), an IRC bot that compiles and
runs C++ code, is written in Haskell.

     g) Oh FP, as in Lisp, oh, that's AI stuff right ... we don't really do
 AI.
     h) Any other questions/comments that you may have heard.
 3. Ideas about interesting problems that can be used so that it appeals to
 people. I mean, while fibonacci etc look good but showing those examples
 tend to send the signal that it's good for those kind of problems.
 

Re: [Haskell-cafe] Finding the average in constant space

2012-05-30 Thread Chris Wong
Sorry for the delayed response -- I've had exams the past few days.

On Sun, May 27, 2012 at 8:21 PM, Eugene Kirpichov ekirpic...@gmail.com wrote:
 A lot of people have done this :) eg from me: google up a fairly recent 
 thread from me about processing streams and perhaps the keyword timeplot 
 (writing from a dying phone, can't do myself)

If you mean this:
http://www.haskell.org/pipermail/haskell-cafe/2011-December/097908.html
and this: 
https://github.com/jkff/timeplot/blob/master/Tools/TimePlot/Incremental.hs
then you're right -- the types match up exactly!

The funny thing is, I remember seeing that message half a year ago and
having absolutely no idea what any of it meant. Now I've actually
tried it myself, reifying the case expression actually makes perfect
sense.

On Sun, May 27, 2012 at 11:43 PM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 There are a few blog posts by Conal Elliott and Max Rabkin (I think)
 reifying folds as a data type to get more composition and thus fold
 different functions at the same time. Search for beautiful folding
 with the above authors names.

 Personally I didn't find the examples significantly more beautiful
 that using regular composition in a normal fold - only that that the
 helper functions to manage pairs aren't in the standard library.

This was already bookmarked, funnily enough:
http://squing.blogspot.co.nz/2008/11/beautiful-folding.html

I don't think that solution was particularly beautiful either. It
seems a bit over-the-top, hiding the state in an existential type when
a simple closure would do. However, I don't understand what you mean
by regular composition in a normal fold. Wait, what's an irregular
composition? Abnormal fold? ;)

On Mon, May 28, 2012 at 7:33 AM, Steffen Schuldenzucker
sschuldenzuc...@uni-bonn.de wrote:
 This is (a special case of) the main point in the design of iteratees. See
 e.g. the definition of the 'Iteratee' type in the enumeratee library. -
 Looks pretty much like your 'Fold' type with an additional state (done or
 not yet done).

 Also, the pipe package seems to provide something similar.

I haven't looked too much into iteratees until now, but in hindsight
it seems obvious why they're implemented that way -- they have to
iterate over a stream chunk by chunk, keeping state as they go along,
just like the Fold type. Thanks for pointing that out!

Chris

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


[Haskell-cafe] Finding the average in constant space

2012-05-27 Thread Chris Wong
Hello all

I just came up with a way of executing multiple folds in a single
pass. In short, we can write code like this:

   average = foldLeft $ (/) $ sumF * lengthF

and it will only traverse the input list once.

The code is at: https://gist.github.com/2802644

My question is: has anyone done this already? If not, I might release
this on Hackage -- it seems quite useful.

Chris

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


Re: [Haskell-cafe] Correspondence between libraries and modules

2012-05-25 Thread Chris Wong
Rustom:

 O well... If the noob trap is one error playing it safe is probably another
 so here goes with me saying things that I (probably) know nothing about:
 1. cabal was a beautiful system 10 years ago.  Now its being forcibly scaled
 up 2 (3?) orders of magnitude and is creaking at the seams

The problem is, Cabal is not a package management system. The name
gives it away: it is the Common Architecture for *Building*
Applications and Libraries. Cabal is to Haskell how GNU autotools +
make is to C: a thin wrapper that checks for dependencies and invokes
the compiler. All that boring
not-making-your-package-break-everything-else stuff belongs to the
distribution maintainer, not Hackage and Cabal.

 2. There's too much conflicting suggestions out there on the web for a noob
     - use system install (eg apt-get) or use cabal

Use apt-get. Your distribution packages are usually new enough, have
been tested thoroughly, and most importantly, do not conflict with
each other.

     - cabal in user area or system area etc

Installing with --user is usually the best, since they won't clobber
system packages and if^H^Hwhen they do go wrong, you can simply rm -r
~/.ghc. For actual coding, it's better to use a sandboxing tool such
as [cabal-dev][] instead.

[cabal-dev]: http://hackage.haskell.org/package/cabal-dev

     - the problem is exponentiated by the absence of cabal uninstall

See above.

By the way, someone else a whole article about it:
https://ivanmiljenovic.wordpress.com/2010/03/15/repeat-after-me-cabal-is-not-a-package-manager/

Hope that clears it up for you.

Chris

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


Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-11 Thread Chris Wong
On Sat, May 12, 2012 at 12:41 AM, Gregg Lebovitz glebov...@gmail.com wrote:
 I would find it useful to pull all this information together into a single
 document that discusses all the performance issues in one place and shares
 the real life experience is dealing with each issue. I see this as a best
 practice paper rather than a research document.

 Does such a document exist? If not, I am willing try and start one.

http://www.haskell.org/haskellwiki/Performance

;)

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


Re: [Haskell-cafe] Installing REPA

2012-04-06 Thread Chris Wong
On Sat, Apr 7, 2012 at 2:02 AM, Dominic Steinitz
idontgetoutm...@googlemail.com wrote:
 Hi,

 I'm trying to install REPA but getting the following. Do I just install
 base? Or is it more complicated than that?

 Thanks, Dominic.

I think the easiest solution is to just use an older version of Repa.
According to Hackage, the latest one that works with base 4.3 is Repa
2.1.1.3:

$ cabal install repa==2.1.1.3

Chris

 ___
 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] Is there a generic way to detect mzero?

2012-03-26 Thread Chris Wong
On Tue, Mar 27, 2012 at 11:03 AM, Antoine Latter aslat...@gmail.com wrote:
 On Mon, Mar 26, 2012 at 4:25 PM, Ting Lei tin...@hotmail.com wrote:
 Hi Antoine and Tobias (and everyone else),

 Thanks a lot for your answers. They are really helpful

 Can you please show me how to use the (Eq m) constraint to do this?

 Also, my general question (probably novice-level) is that in monadic
 programming, you can convert not necessarily monadic codes into monadic
 ones.
 I know for many cases, it is impossible to do the reverse conversion, e.g.
 you can't make a function involving real IO operations into a pure code.
 In other cases, for example, I may need to using things like Nothing as the
 null value as in other programming languages, just to represent a special
 missing value outside the regular type.
 Is mzero a reasonable replacement for this or is there any reasonable
 (abstract) approximation in Haskell for doing this? (Like null, I need the
 ability to detect it.)

 I think using 'Maybe' (with Nothing) is perfect for this - this
 function should come in handy:

 http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Maybe.html#v:isNothing

Ting,

It's often not good style to check Nothing explicitly, rather, it's
better to use monads to thread it through automatically.

If you have many functions that return a Maybe, then you can chain
them together using do syntax:

frobnicate = do
foo - function1
bar - function2 foo
return (bar + 1)

If any of the functions in the chain return Nothing, then the monad
will short circuit and the whole expression will result in Nothing.
The - acts like an automatic null check.

Chris

 Antoine

 ___
 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] Empty Input list

2012-03-12 Thread Chris Wong
On Tue, Mar 13, 2012 at 12:24 PM, Chris Smith cdsm...@gmail.com wrote:
 On Mon, Mar 12, 2012 at 3:14 PM, Kevin Clees k.cl...@web.de wrote:
 Now my function looks like this:

 tmp:: [(Int, Int)] - Int - (Int, Int)
 tmp [] y = (0,0)
 tmp xs y = xs !! (y-1)

 Just a warning that this will still crash if the list is non-empty by
 the index exceeds the length.  That's because your function is no
 longer recursive, so you only catch the case where the top-level list
 is empty.  The drop function doesn't crash when dropping too many
 elements though, so you can do this and get a non-recursive function
 that's still total:

 tmp :: [(Int,Int)] - Int - (Int, Int)
 tmp xs y = case drop (y-1) xs of
    []         - (0,0)
    Just (x:_) - x

That last line should be

(x:_) - x

without the Just. Hopefully that'll save a bit of confusion.

Chris

 --
 Chris Smith

 ___
 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] Need Help.

2012-02-21 Thread Chris Wong
Hello

On Tue, Feb 21, 2012 at 8:32 PM, Manoj Chaudhari manoj...@gmail.com wrote:
 Hi,

 We are looking for senior technical resources with skills in
 Haskell/Functional programming.
 Experience : 6 to 20 years,

 Job Location : Pune (India).

Out of curiosity, what will the job involve?

Also, it is bad netiquette to use bcc when you don't need to -- next
time, try entering Haskell Cafe in the to field instead.

Chris

 Regards!
 Manoj

 ___
 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] network-2.3.0.10 compiled for ghc 7.4.1 windows

2012-02-21 Thread Chris Wong
Hello Matias

On Wed, Feb 22, 2012 at 4:02 PM, Matias Hernandez mhern...@gmail.com wrote:
 Hi Alberto.

 Do we need cygwin to install your compiled package?

I don't believe you do. If memory doesn't fail me, the Haskell
Platform includes a compiler (MinGW), but not a shell (MSYS).

This page explains all: http://trac.haskell.org/haskell-platform/ticket/165

Chris

 I thought not (I'm not very versed on this) but when I tried cabal install 
 network after
 extracting it I got:

 Configuring network-2.3.0.11...
 cabal: The package has a './configure' script. This requires a Unix
 compatibility toolchain such as MinGW+MSYS or Cygwin.
 cabal: Error: some packages failed to install:
 network-2.3.0.11 failed during the configure step. The exception was:
 ExitFailure 1

 Best regards, and thanks for any help!
 - Matias

 ___
 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] Fwd: Contributing to http-conduit

2012-02-02 Thread Chris Wong
Sorry, accidentally clicked Reply rather than Reply to all. Here's
the message I sent:


-- Forwarded message --
From: Chris Wong chrisyco+haskell-c...@gmail.com
Date: Fri, Feb 3, 2012 at 7:44 PM
Subject: Re: [Haskell-cafe] Contributing to http-conduit
To: Myles C. Maxfield myles.maxfi...@gmail.com


On Fri, Feb 3, 2012 at 5:32 PM, Myles C. Maxfield
myles.maxfi...@gmail.com wrote:
 I propose making an entirely unrelated package, public-suffix-list, with a
 module Network.PublicSuffixList, which will expose this function, as well as
 functions about parsing the list itself. Thoughts?

I'll volunteer to write this module, but I'm not sure whether to read
it in at run time, or generate the module containing the data in
advance. The latter seems less error-prone -- no messing around with
file paths or IO.

Chris

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


Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-29 Thread Chris Wong
On Mon, Jan 30, 2012 at 10:13 AM, Marc Weber marco-owe...@gmx.de wrote:
 A lot of work has been gone into GHC and its libraries.
 However for some use cases C is still preferred, for obvious speed
 reasons - because optimizing an Haskell application can take much time.

As much as any other high-level language, I guess. Don't compare
apples to oranges and complain oranges aren't crunchy enough ;)

 Is there any document describing why there is no ghc --strict flag
 making all code strict by default?

Yes -- it's called the Haskell Report :)

GHC does a lot of optimization already. If making something strict
won't change how it behaves, it will, using a process called
strictness analysis.

The reason why there is no --strict flag is that strictness isn't just
something you turn on and off willy-nilly: it changes how the whole
language works. Structures such as infinite lists and Don Stewart's
lazy bytestrings *depend* on laziness for their performance.

 Wouldn't this make it easier to apply Haskell to some additional fields
 such as video processing etc?

 Wouldn't such a '--strict' flag turn Haskell/GHC into a better C/gcc
 compiler?

See above.

 Projects like this: https://github.com/thoughtpolice/strict-ghc-plugin
 show that the idea is not new.

Not sure what that does, but I'll have a look at it.

 Eg some time ago I had to do some logfile analysis. I ended doing it in
 PHP because optimizing the Haskell code took too much time.

That probably because you're using linked lists for strings. For
intensive text processing, it's better to use the text package instead
[1]

Chris

[1] http://hackage.haskell.org/package/text

 Marc Weber

 ___
 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] where to put general-purpose utility functions

2012-01-24 Thread Chris Wong
 I like  let (hd, _ : tl) = break prd lst in...

 Oh, wait.  That won't always work. :(


second (drop 1) . break prd list?

:)

 ___
 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] Level of Win32 GUI support in the Haskell platform

2011-12-29 Thread Chris Wong
On Fri, Dec 30, 2011 at 2:53 PM, Steve Horne
sh006d3...@blueyonder.co.uk wrote:
 I've been for functions like GetMessage, TranslateMessage and
 DispatchMessage in the Haskell Platform Win32 library - the usual message
 loop stuff - and not finding them. Hoogle says no results found.

 Is this level of Win32 GUI coding supported? (other than by dealing with the
 FFI myself)

I'd recommend using Gtk2hs (http://haskell.org/gtk2hs). It's well
supported and your program will work on Mac  Linux  BSD to boot.

Trying to grapple with Win32 APIs isn't exactly my idea of fun. :)

 ___
 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] IO typeclasses

2011-12-29 Thread Chris Wong
On Fri, Dec 30, 2011 at 4:47 PM, David Thomas davidleotho...@gmail.com wrote:
 Is there any particular reason IO functions in the standard libraries aren't
 grouped into type-classes?

I'm guessing it's to stop the report from getting too complicated. If
you want an IO abstraction, you can try HVIO:


http://hackage.haskell.org/packages/archive/MissingH/latest/doc/html/System-IO-HVIO.html

 ___
 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] Text.Regex.Base throws exceptions with makeRegexOptsM

2011-12-29 Thread Chris Wong
On Fri, Dec 30, 2011 at 1:24 PM, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 On Thursday 29 December 2011, 23:52:46, Omari Norman wrote:
 [...]

 'fail' doesn't properly belong in the Monad class, it was added for the
 purpose of dealing with pattern-match failures, but most monads can't do
 anything better than abort with an error in such cases.
 'fail' is widely considered a wart.

I thought I'd add my own reason why I don't like fail.

Take these two functions, for example:

test :: Maybe Int
test = do
(Right v) - Just (Left 1)
return v

test' :: Maybe Int
test' = do
let (Right v) = Left 1
return v

The first returns Nothing. The second crashes with a pattern match failure.

Why should a pattern failure cause a crash everywhere *except* a do
binding? It makes no sense. It violates the principle of least
surprise by behaving differently to every other occurrence of pattern
matching in the whole language.

As for custom failures, I'd recommend either Michael Snoyman's Failure
class or MonadPlus, which were both designed for this sort of thing.
But I'd stay away from using fail, since as Omari Norman said, it's a
wart.

 ___
 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] Windows: openFile gives permission denied when file in use

2011-12-28 Thread Chris Wong
On Thu, Dec 29, 2011 at 2:45 PM, Antoine Latter aslat...@gmail.com wrote:
 [...]

 When GHC opens files for reading, it asks windows to disallow write
 access to the file. I'm guessing that Framemaker has the file open for
 writing, so GHC can't get that permission.

In fact, this is required behavior according to the Haskell Report:

 Implementations should enforce as far as possible, at least locally to the 
 Haskell process, multiple-reader single-writer locking on files. That is, 
 there may either be many handles on the same file which manage input, or just 
 one handle on the file which manages output.

I guess on Windows, as far as possible means locking it across the
whole system.

(See 
http://www.haskell.org/onlinereport/haskell2010/haskellch41.html#x49-32800041.3.4
for the gory details)

-- Chris

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


Re: [Haskell-cafe] If you'd design a Haskell-like language, what would you do different?

2011-12-20 Thread Chris Wong
 One thing that concerns me is the use of capital letters to distinguish type
 and class names and constructors from values.  If I was doing it over I
 would use a typographical distinction like italics for types, bold for
 classes.  That way we could have a constructor named ∅, a function named ∈,
 a class named ℝ.

It's Algol all over again! Will we have to typeset our keywords in bold too?

 ___
 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] If you'd design a Haskell-like language, what would you do different?

2011-12-20 Thread Chris Wong
On Wed, Dec 21, 2011 at 10:53 AM, Matthew Farkas-Dyck
strake...@gmail.com wrote:
 With GHC 7.0.3:

 $ cat test.hs
 class ℝ a where {
  test :: a;
 };

 (∈) :: Eq a = a - [a] - Bool;
 x ∈ (y:ys) = x == y || x ∈ ys;

 main = putStrLn Two of three ain't bad (^_~);
 $ runhaskell test.hs
 Two of three ain't bad (^_~)
 $

Why not expand it even further?

class Monoid m where
(•) :: m - m - m
(∅) :: m

(∈) :: (Foldable t, Eq a) = a - t a - Bool

(∘) :: (b - c) - (a - b) - (a - c)

(∧) :: Bool - Bool - Bool

etc.

We can write a whole Haskell library full of these aliases --
syntactic-heroin perhaps? ;)

(http://www.haskell.org/haskellwiki/Syntactic_sugar/Cons#Syntactic_heroin)

 ___
 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] I've just heard of a neat security measure that when you compile the code it generates different object code...

2011-12-16 Thread Chris Wong
On Sat, Dec 17, 2011 at 12:27 PM, KC kc1...@gmail.com wrote:
 ... with the same functionality.

 Thus, your program would be a moving target to hackers.

 Would this be challenging with ghc?

Although it's possible, I doubt this would do anything. Most exploits
are just programmer mistakes; changing the object code doesn't change
the fact that there's a gaping security hole in your program. Plus, it
would be harder to debug the compiler, since the mangling code would
be non-deterministic by definition. So I doubt anyone would try to
implement that.

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


Re: [Haskell-cafe] [Alternative] summary of my understanding so far

2011-12-15 Thread Chris Wong
On Thu, Dec 15, 2011 at 9:13 PM, Gregory Crosswhite
gcrosswh...@gmail.com wrote:
 First of all, it sounds like we all agree that the documentation for
 Alternative needs to be improved;  that alone would clear a lot of the
 confusion up.

I wonder if fully documenting the Haskell base library is a valid
SoC project :)

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


Re: [Haskell-cafe] [Alternative] some/many narrative

2011-12-14 Thread Chris Wong
 Okay, so how about the following as a user narrative for some and many?

 ...

I was in the middle of writing my own version of Applicative when I
stumbled on this intense debate. Here's what I wrote for the
documentation:

class (Applicative f, Monoid f) = Alternative f where
-- | Keep repeating the action (consuming its values) until it
fails, and then return the values consumed.
--
-- [Warning]: This is only defined for actions that eventually fail
-- after being performed repeatedly, such as parsing. For pure values such
-- as 'Maybe', this will cause an infinite loop.
some :: f a - f [a]
some v = ...

-- | Similar to 'many', but if no values are consumed it returns
'empty' instead of @f []@.
--
-- [Warning]: This is only defined for actions that eventually fail
-- after being performed repeatedly, such as parsing. For pure values such
-- as 'Maybe', this will cause an infinite loop.
many :: f a - f [a]
many v = ...

Warnings are repeated for emphasis :)

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