Re: [Haskell-cafe] How to compare PortNumbers or Bug in Network.Socket?

2009-03-12 Thread Bryan O'Sullivan
On Thu, Mar 12, 2009 at 8:45 PM, Antoine Latter  wrote:

> So the Ord instance is wrong for the PortNumber type?  Well, maybe not
> wrong.


It's out and out wrong. You get different results on machines of different
endianness. Now, this begs the question of why not just simply use an
unwrapped Word16 instead :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using a monad to decompose a function into functions

2009-03-12 Thread minh thu
2009/3/13 Marcin Kosiba :
> On Thursday 12 March 2009, you wrote:
>> 2009/3/12 Marcin Kosiba :
>> > Hi,
>> >        I'm doing a bit of research into mobility models and I'm currently
>> > exploring implementation language choices for the simulator
>> > (*snip*)
>> > The simulation algorithm requires expressing
>> > the node's mobility so that it is "stateless". The mobility model
>> > algorithm's type should be something like:
>> > mobility_model :: WorldState -> NodeState -> OtherInput -> (Action,
>> > NodeState)
>> >
>> > where Action can alter WorldState and the second NodeState is an altered
>> > input NodeState. I perform a form of speculative execution on
>> > mobility_model so sometimes I need to backtrack to a previous world and
>> > node state. This is all fairly simple stuff, and was just an
>> > introduction. What I do now is store an enum in NodeState and implement
>> > mobility_model as one big case statement. Yes, this is very imperative of
>> > me, I know. What I'd like to do is to express mobility_model, so that the
>> > code would look like:
>> >
>> > mobility_model world node input = do
>> >    do_calculus
>> >    emit_action
>> >    if something
>> >      then emit_action
>> >      else emit_action
>> >    do_calculus
>> >    emit_action
>> >    mobility_model world node input
>>
>> Hi,
>>
>> It seems you can use
>> http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Mon
>>ad-State-Lazy.html Just have a look at the exemple :
>>
>>  tick :: State Int Int
>>  tick = do n <- get
>>            put (n+1)
>>            return n
>>
>> your code would become something like
>> mobility_model :: OtherInput -> State (WorldState,NodeState) ()
>> mobility_model input = do
>>   world <- gets fst
>>   node <- gets snd
>>   
>>   let (world',node') = ...
>>   put (world',node')
>
> ok, that solves part of the problem. what this doesn't solve is that somewhere
> between these lines (which corespond to emit_action in my example)
>>   let (world',node') = ...
>>   put (world',node')
> I need to return a value and an Action and NodeState to the simulation
> algorithm. and then, after the simulation algorithm calculates a new
> WorldState it will want the mobility_model to where it left off, but with a
> new WorldState.
>
> I hope I'm clear about what I wish to achieve: each emit_action should return
> a value (Action, NodeState) and maybe a function mobility_model_cont which I
> then could call with the new WorldState to continue from where emit_action
> returned.

I'm not entirely sure ... but I think it doesn't matter that much :)
Here is why.

This was just an exemple :
 mobility_model :: OtherInput -> State (WorldState,NodeState) ()

You could also have
 mobility_model :: OtherInput -> NodeState -> State WorldState
(NodeState,Action)
or whatever.

In fact, the State monad makes it easy to thread (in this context, it
means 'pass around') an argument to many functions, providing a nice
syntax reminiscent of imperative language. But it lets you completely
free of what is passed around. It depends on what you want to be
explicitely passed by argument, and what you want to pass in the state
of the monad (that is, what you want to appear, inside the monad only,
as some global variable).

So in your code, if you often need to pass a WorldState to a function
which should return a modified WorldState, it makes sense to put
WorldState inside the state monad. But, maybe, if there is just a few
functions which act on NodeState, it has not to be part of the state
carried by the state monad.

I'm not entirely sure of what is a problem to you : is it the use of
the State monad, or something else ?
If it can help you to formulate your question you can post some code
(or past it to http://hpaste.org/)...

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


[Haskell-cafe] Typing Dynamic Typing [Was: Dynamically typing TH.Exp at runtime]

2009-03-12 Thread oleg

Martin Hofmann asked:
> Is there a Haskell implementation of the paper "Typing Dynamic Typing"
> by Baars and Swierstra

There is a different implementation but in the same spirit

http://okmij.org/ftp/tagless-final/IncopeTypecheck.hs
http://okmij.org/ftp/Computation/tagless-typed.html#tc-final


The first difference between IncopeTypecheck and Baars and Swierstra's
one is in the type representation and safe coercions. IncopeTypecheck
uses Typeable, and so it needs to define reflection from a type rep to
a value of that type. The projection function of Typeable requires a
value of a specific type rather than a typerep.

The main difference is treating environments and
weakening. Baars and Swierstra treat an Identifier, at compile time,
as a projection function \env->t. Here env is the run-time env
represented as a nested tuple. `Closing the Stage' paper relies on the
same idea. To be able to collect those projection functions into a
regular list, they wrap them into a Dynamic. IncopeTypecheck, in
contrast, represents compile-time variables as functions \x->x, which
are weakened as they are embedded into a reacher environment. The
functions are wrapped into Dynamic, as this is the result of
typechecking. The type environment Gamma in IncopeTypecheck contains
only TypeRep but no Dynamics!

Here a few examples to illustrate the difference between Baars and
Swierstra and IncopeTypecheck:

Source expression: Add (Int 2) (Int 3)

Baars and Swierstra: \env -> (\_ -> 2) env + (_ -> 3) env
IncopeTypecheck: add (int 1) (int 2)

Source expression: (Lam "x" Int (x + (Int 1)))

Baars and Swierstra: 
\env -> \x -> (\env -> (\(x,_) ->x) env  + (\_ -> 1) env) (x,env)
IncopeTypecheck:
\x -> (\x -> x) x `add` (\_ -> int 1) x

(of course, in IncopeTypecheck, instead of (\x -> ...) there should be
lam (\x -> ...) and instead of meta-language application there should
be app. I drop them for clarity).

For deeply nested functions, IncopeTypecheck probably has to do more
redices as it repeatedly applies coercions. Since the environment is
known, I could have built the weakening in one step rather than as a
sequence of weakening into a progressively richer environment. Each
step into this sequence includes an administrative redex. The
sequential weakening was easier to implement though.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: Vintage BASIC 1.0

2009-03-12 Thread Joe Fredette

Well, there goes any productivity I might have had on my spring break...

Hurrah for old BASIC games!

Lyle Kopnicky wrote:
I am pleased to announce the initial release of Vintage BASIC, an 
interpreter for microcomputer-era BASIC. Fully unit-tested, it 
faithfully implements the common elements of the language. On the web 
site, you can find 102 games from the classic book BASIC Computer 
Games, all of which run flawlessly. Have fun!


This is a standalone interpreter, operating on text files. Although 
not an embedding, like Lennart Augustsson's clever implementation, it 
does use a custom BASIC monad in order to execute the code. A unique 
feature of this implementation is that control structures such as FOR 
are implemented using resumable exceptions: FOR is a handler and NEXT 
throws an exception. A Developer's Guide is included with the source.


This is my first public release of open source software. I have been 
working on this project since 2003.


Home page: http://www.vintage-basic.net

Also available on Hackage 
 
and patch-tag.com .


Please e-mail me at l...@vintage-basic.net 
 with any questions/comments.


- Lyle


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
  
begin:vcard
fn:Joseph Fredette
n:Fredette;Joseph
adr:Apartment #3;;6 Dean Street;Worcester;Massachusetts;01609;United States of America
email;internet:jfred...@gmail.com
tel;home:1-508-966-9889
tel;cell:1-508-254-9901
x-mozilla-html:FALSE
url:lowlymath.net, humbuggery.net
version:2.1
end:vcard

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


Re: [Haskell-cafe] Distributing Linux binaries

2009-03-12 Thread Lyle Kopnicky
Thanks, folks. I have decided for now just to release a tarball with an
executable and some docs, that can be expanded where the user deems
appropriate. I'll try a static link if people are having problems with it.
- Lyle
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Does anybody dislike implicit params as much as I do?

2009-03-12 Thread Miguel Mitrofanov

There is an old joke in Russia:

- I don't like cats.
- You just don't know how to cook them.

Well, maybe, you don't know how to cook implicit parameters?

Anyway, what about type classes - aren't they a sort of implicit  
parameters?


On 12 Mar 2009, at 23:36, Thomas Hartman wrote:


http://blog.patch-tag.com/2009/03/09/implicitparams-are-evil-thoughts-on-adapting-gitit/

I understand there are arguments for using IPs, but after this
experience, the ImplicitParams extension is a "code smell" for me.
___
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] ANNOUNCE: Vintage BASIC 1.0

2009-03-12 Thread Lyle Kopnicky
I am pleased to announce the initial release of Vintage BASIC, an
interpreter for microcomputer-era BASIC. Fully unit-tested, it faithfully
implements the common elements of the language. On the web site, you can
find 102 games from the classic book BASIC Computer Games, all of which run
flawlessly. Have fun!
This is a standalone interpreter, operating on text files. Although not an
embedding, like Lennart Augustsson's clever implementation, it does use a
custom BASIC monad in order to execute the code. A unique feature of this
implementation is that control structures such as FOR are implemented using
resumable exceptions: FOR is a handler and NEXT throws an exception. A
Developer's Guide is included with the source.

This is my first public release of open source software. I have been working
on this project since 2003.

Home page: http://www.vintage-basic.net

Also available on
Hackageand
patch-tag.com .

Please e-mail me at l...@vintage-basic.net with any questions/comments.

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


Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-12 Thread Denis Bueno
2009/3/12 Peter Verswyvelen :
> I think. Or is it defined in some other package?

Note that you can get an Applicative instance for "free" by using
"WrapMonad" in Control.Applicative.  For example, just today I was
writing a quickcheck Arbitrary instance, and the Gen monad doesn't
have an Applicative instance.  No problem:

>instance Gen MyDataType where
>   arbitrary = MyDataConstructor <$> arbitrary <*> arbitrary

becomes

>instance Gen MyDataType where
>   arbitrary = unWrapMonad (MyDataConstructor <$> WrapMonad arbitrary <*> 
> WrapMonad arbitrary)

This works because every monad induces an Applicative instance in a
way I've ingested just enough wine to forget. =]


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


Re: [Haskell-cafe] Natural Numbers: Best implementation?

2009-03-12 Thread Brandon S. Allbery KF8NH

On 2009 Mar 12, at 22:54, Mark Spezzano wrote:
I was wondering what the best way to implement Natural number would  
be. Is there a package which already does this?


type-level on Hackage.


2.  Use the type
data Natural = Zero | Succ !Natural


One of the reasons people use type-level naturals is to get laziness;  
you've made this strict.  Is there a reason?


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to compare PortNumbers or Bug in Network.Socket?

2009-03-12 Thread Antoine Latter
On Thu, Mar 12, 2009 at 5:32 PM, Stefan Schmidt
 wrote:
> Philippa Cowderoy wrote:
>>
>> On Thu, 2009-03-12 at 14:56 -0700, Bryan O'Sullivan wrote:
>>>
>>> However, it's also arguably the case that you shouldn't care about port
>>> number ordering. That smells dodgy to me.
>>
>> Port ranges aren't that uncommon.
>
> That's exactly were I need the comparison. I'm writing a program which takes
> a range of port numbers and tries to open a socket with the first available
> port number. The whole thing is part of a distributed system and I cannot
> specify just a single port number because I could already been taken.
>
> Stefan

So the Ord instance is wrong for the PortNumber type?  Well, maybe not
wrong.  But not as useful as it could be.

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


[Haskell-cafe] Re: Against cuteness

2009-03-12 Thread Benjamin L . Russell
On Fri, 13 Mar 2009 03:22:41 +0100, Deniz Dogan
 wrote:

>2009/3/13 Benjamin L. Russell :
>> On Thu, 12 Mar 2009 09:11:15 -0500, Gregg Reynolds 
>> wrote:
>
>[snip]
>
>Why even bother discussing whether a potential mascot should be cute
>or not?  You guys should come up with new ideas instead of simply
>stating what you *don't* want. :)

Good point.

Okay, here's a suggestion:

Consider the following logo:

Silver red monad.png
http://commons.wikimedia.org/wiki/File:Silver_red_monad.png

This logo "[s]ignifies balance between consumption and production,"
and is the "Official Symbol of Technocracy -
http://www.technocracy.org/.";

The above-mentioned logo is essentially a silver-red variation of the
Yin-Yang symbol without the dots on both ends.

Then consider the background of the following Yin-Yang symbol:

Yin-Yang Symbol (on a swirling orange-gold background)
http://thumbs.dreamstime.com/thumb_236/1202779093o0VB6w.jpg

Given that the representation of the Pythagorean monad can already be
considered as a portion of the Yin-Yang symbol (see
http://en.wikipedia.org/wiki/Monad_(Greek_philosophy)), why not take
the background for the above-mentioned Yin-Yang symbol, superimpose
the silver-red monad, and then simply superimpose representations of
the Pythagorean monad as gradiated halos where there are dots in a
traditional Yin-Yang symbol?

We would then have a silver-red monad that closely resembles a
Yin-Yang symbol, except that the dots would each be surrounded by a
gradiated halo representing a monad, on a wavy orange-gold background:
essentially, a pair of Pythagorean monads in a silver-red monad on a
distinctive background.

This symbol would represent the three-way balance between purity
(symbolized by the red), laziness (symbolized by the silver), and
monads (symbolized by the dots surrounded by halos).

I don't have time to craft the image right now, but I may be able to
come up with something after lunch.

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 

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


Re: [Haskell-cafe] Re: Haskell-Wiki Account registration

2009-03-12 Thread Joe Fredette
As long as one is implementing a CAPTCHA, the "reCAPTCHA" [1] is my 
humble suggestion, I have no idea how the haskellwiki is implemented or 
how easy this is to implement, but I imagine it couldn't be _that_ hard.


/Joe

[1] http://recaptcha.net/

Benjamin L.Russell wrote:

On Thu, 12 Mar 2009 17:31:49 +0100 (CET), Henning Thielemann
 wrote:

  
How long will the Wiki account registration be disabled? Would it be 
possible to ask a question, that real Haskellers could easily answer, but 
a spambot cannot? E.g. "What's Haskell's surname?"



Indeed.  Disabling Wiki account registration indefinitely, and not
replacing it by at least some form of automatic registration, risks
allowing outsiders to think that the HaskellWiki is somehow run by
some "clique," which I'm sure is not the case.  Automating the process
removes most of the risk of this misimpression.

Why not ask new users to identify letters in a random bitmapped image
of a string, as is commonly done?  Then any new user who still
registers and starts submitting spam can be tracked and moderated.

-- Benjamin L. Russell
  
begin:vcard
fn:Joseph Fredette
n:Fredette;Joseph
adr:Apartment #3;;6 Dean Street;Worcester;Massachusetts;01609;United States of America
email;internet:jfred...@gmail.com
tel;home:1-508-966-9889
tel;cell:1-508-254-9901
x-mozilla-html:FALSE
url:lowlymath.net, humbuggery.net
version:2.1
end:vcard

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


Re: [Haskell-cafe] Natural Numbers: Best implementation?

2009-03-12 Thread Alexander Dunlap
2009/3/12 Mark Spezzano :
> Hi,
>
>
>
> I was wondering what the best way to implement Natural number would be. Is
> there a package which already does this?
>
>
>
> Here are some options:
>
>
>
> 1.  Don’t bother. Just use Integer.
>
> 2.  Use the type
>
> data Natural = Zero | Succ !Natural
>
> 3.  Use the following definition taken from the Gentle Introduction to
> Haskell 98
>
> newtype Natural = MakeNatural Integer
>
> toNatural ::Integer-> Integer
>
> toNatural x | x < 0 = error “Can’t create negative naturals!”
>
>      | otherwise = MakeNatural x
>
> fromNatural :: Natural -> Integer
>
> fromNatural (MakeNatural i) = i
>
>
>
> and then...
>
>
>
> instance Num Natural where
>
>   fromInteger = toNAtural
>
>   x + y   = toNatural (fromNatural x + fromNatural y)
>
>   x – y   = etc..
>
>   x * y   = etc...
>
>
>
> Which method is best? So far, I’ve been picking option #1 – just leaving
> things as they are and using Integer to keep things simple.
>
>
>
> I’ve got that feeling that [2] would be fast and [3] would be slow. Comment
> appreciated on the merits of each.
>
>
>
> Cheers,
>
>
>
> Mark Spezzano
>

I would tend to use option (1) unless there's a compelling reason not
to. Since naturals aren't closed under subtraction, you would in
practice probably have just as many non-total functions as you would
with the regular Int{,eger} type. Also, a lot of functions just take
Integers so it would be more of a pain to use.

In terms of speed, I think that [3] would be reasonably fast (unless
you do a ton of subtraction with bounds-checking) and [2] would
probably be quite slow, because you don't get the speed-boost from
doing computations right on the processor.

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


[Haskell-cafe] Natural Numbers: Best implementation?

2009-03-12 Thread Mark Spezzano
Hi,

 

I was wondering what the best way to implement Natural number would be. Is
there a package which already does this?

 

Here are some options:

 

1.  Don’t bother. Just use Integer.

2.  Use the type 

data Natural = Zero | Succ !Natural

3.  Use the following definition taken from the Gentle Introduction to
Haskell 98

newtype Natural = MakeNatural Integer

toNatural ::Integer-> Integer

toNatural x | x < 0 = error “Can’t create negative naturals!”

 | otherwise = MakeNatural x

fromNatural :: Natural -> Integer

fromNatural (MakeNatural i) = i

 

and then...

 

instance Num Natural where

  fromInteger = toNAtural

  x + y   = toNatural (fromNatural x + fromNatural y)

  x – y   = etc..

  x * y   = etc...

 

Which method is best? So far, I’ve been picking option #1 – just leaving
things as they are and using Integer to keep things simple.

 

I’ve got that feeling that [2] would be fast and [3] would be slow. Comment
appreciated on the merits of each.

 

Cheers,

 

Mark Spezzano

 


No virus found in this outgoing message.
Checked by AVG. 
Version: 7.5.557 / Virus Database: 270.11.12/1998 - Release Date: 12/03/2009
6:23 PM
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haskell-Wiki Account registration

2009-03-12 Thread Benjamin L . Russell
On Thu, 12 Mar 2009 17:31:49 +0100 (CET), Henning Thielemann
 wrote:

>
>How long will the Wiki account registration be disabled? Would it be 
>possible to ask a question, that real Haskellers could easily answer, but 
>a spambot cannot? E.g. "What's Haskell's surname?"

Indeed.  Disabling Wiki account registration indefinitely, and not
replacing it by at least some form of automatic registration, risks
allowing outsiders to think that the HaskellWiki is somehow run by
some "clique," which I'm sure is not the case.  Automating the process
removes most of the risk of this misimpression.

Why not ask new users to identify letters in a random bitmapped image
of a string, as is commonly done?  Then any new user who still
registers and starts submitting spam can be tracked and moderated.

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 

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


Re: [Haskell-cafe] Re: Against cuteness

2009-03-12 Thread Deniz Dogan
2009/3/13 Benjamin L. Russell :
> On Thu, 12 Mar 2009 09:11:15 -0500, Gregg Reynolds 
> wrote:

[snip]

Why even bother discussing whether a potential mascot should be cute
or not?  You guys should come up with new ideas instead of simply
stating what you *don't* want. :)

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


[Haskell-cafe] Re: Against cuteness

2009-03-12 Thread Benjamin L . Russell
On Thu, 12 Mar 2009 09:11:15 -0500, Gregg Reynolds 
wrote:

>I don't think so.  Bad design will lose them (and many others), but
>good design and cuteness are two different things.

It's also possible for a good design to be cute, too.

>> You can still distinguish yourself from O'Reilly without losing the
>> cuteness factor with a logo like one of the following:
>>
>
>We must have vastly different ideas of cute.  I don't consider those
>examples cute.  How about this as a criterion:  if it makes 13-year
>old Japanese girls squeal "kawa!" then it's too cute.  Also if it
>involves the color pink.

What's wrong with the color pink (not that I prefer it personally, but
just wondering)?

You're also assuming that all 13-year old Japanese girls "squeal
'kawa!'" in response to the same stimuli.  I know for a fact that
this isn't true (I recently saw a study asking Japanese girls to rate
different mascots for cuteness, and the poll fell roughly 50-50, as a
matter of fact).  Which 13-year old Japanese girls are you referring
to?

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 

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


Re: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Richard O'Keefe


On 12 Mar 2009, at 11:08 pm, Satnam Singh wrote:

I agree that looking for a mascot that is inspired by "laziness" is  
a bad idea from a P.R. perspective (I am tired of people walking out  
the room when I give Haskell talks to general audiences and explain  
lazy evaluation).


Perhaps we should call it "Just-In-Time evaluation.

As for mascots, let's take a photo of Simon Peyton Jones,
shrink him to hobbit size, give him furry feet, and announce
that "here is one of the warm fuzzy things we have in mind
when we use monads".  (:-)

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


[Haskell-cafe] Re: Has anybody replicated =~ s/../../ or even something more basic for doing replacements with pcre haskell regexen?

2009-03-12 Thread ChrisK

Thomas Hartman wrote:

Is there something like subRegex... something like =~ s/.../.../ in
perl... for haskell pcre Regexen?

I mean, subRegex from Text.Regex of course:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/regex-compat

Thanks for any advice,

thomas.


Short answer: No.

This is a FAQ.  The usual answer to your follow up "Why not?" is that the design 
space is rather huge.  Rather than justify this statement, I will point at the 
complicated module:


http://hackage.haskell.org/packages/archive/split/0.1.1/doc/html/Data-List-Split.html

The above module is "a wide range of strategies for splitting lists", which is a 
much simpler problem than your subRegex request, and only works on lists.  A 
subRegex library should also work on bytestrings (and Seq).


At the cost of writing your own routine you get exactly what you want in a 
screen or less of code, see

http://hackage.haskell.org/packages/archive/regex-compat/0.92/doc/html/src/Text-Regex.html#subRegex
for "subRegex" which is 30 lines of code.

Cheers,
  Chris

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


[Haskell-cafe] Combining haddock documentation from multiple packages

2009-03-12 Thread Heikki Aitakangas

Is it possible to generate a "unified" documentation tree similar to
http://www.haskell.org/ghc/docs/latest/html/libraries/index.html from
packages installed via cabal from hackage? And if so, how does one go
about doing it?


 -- Heikki Aitakangas

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


[Haskell-cafe] Has anybody replicated =~ s/../../ or even something more basic for doing replacements with pcre haskell regexen?

2009-03-12 Thread Thomas Hartman
Is there something like subRegex... something like =~ s/.../.../ in
perl... for haskell pcre Regexen?

I mean, subRegex from Text.Regex of course:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/regex-compat

Thanks for any advice,

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


Re: [Haskell-cafe] Using a monad to decompose a function into functions

2009-03-12 Thread Marcin Kosiba
On Thursday 12 March 2009, you wrote:
> 2009/3/12 Marcin Kosiba :
> > Hi,
> >        I'm doing a bit of research into mobility models and I'm currently
> > exploring implementation language choices for the simulator 
> > (*snip*) 
> > The simulation algorithm requires expressing 
> > the node's mobility so that it is "stateless". The mobility model
> > algorithm's type should be something like:
> > mobility_model :: WorldState -> NodeState -> OtherInput -> (Action,
> > NodeState)
> >
> > where Action can alter WorldState and the second NodeState is an altered
> > input NodeState. I perform a form of speculative execution on
> > mobility_model so sometimes I need to backtrack to a previous world and
> > node state. This is all fairly simple stuff, and was just an
> > introduction. What I do now is store an enum in NodeState and implement
> > mobility_model as one big case statement. Yes, this is very imperative of
> > me, I know. What I'd like to do is to express mobility_model, so that the
> > code would look like:
> >
> > mobility_model world node input = do
> >    do_calculus
> >    emit_action
> >    if something
> >      then emit_action
> >      else emit_action
> >    do_calculus
> >    emit_action
> >    mobility_model world node input
>
> Hi,
>
> It seems you can use
> http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Mon
>ad-State-Lazy.html Just have a look at the exemple :
>
>  tick :: State Int Int
>  tick = do n <- get
>put (n+1)
>return n
>
> your code would become something like
> mobility_model :: OtherInput -> State (WorldState,NodeState) ()
> mobility_model input = do
>   world <- gets fst
>   node <- gets snd
>   
>   let (world',node') = ...
>   put (world',node')

ok, that solves part of the problem. what this doesn't solve is that somewhere 
between these lines (which corespond to emit_action in my example)
>   let (world',node') = ...
>   put (world',node')
I need to return a value and an Action and NodeState to the simulation 
algorithm. and then, after the simulation algorithm calculates a new 
WorldState it will want the mobility_model to where it left off, but with a 
new WorldState.

I hope I'm clear about what I wish to achieve: each emit_action should return 
a value (Action, NodeState) and maybe a function mobility_model_cont which I 
then could call with the new WorldState to continue from where emit_action 
returned.

Thanks,
Marcin Kosiba


signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to compare PortNumbers or Bug in Network.Socket?

2009-03-12 Thread Stefan Schmidt

Philippa Cowderoy wrote:

On Thu, 2009-03-12 at 14:56 -0700, Bryan O'Sullivan wrote:

However, it's also arguably the case that you shouldn't care about port number 
ordering. That smells dodgy to me.

Port ranges aren't that uncommon.


That's exactly were I need the comparison. I'm writing a program which 
takes a range of port numbers and tries to open a socket with the first 
available port number. The whole thing is part of a distributed system 
and I cannot specify just a single port number because I could already 
been taken.


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


Re: [Haskell-cafe] How to compare PortNumbers or Bug in Network.Socket?

2009-03-12 Thread Philippa Cowderoy
On Thu, 2009-03-12 at 14:56 -0700, Bryan O'Sullivan wrote:

> However, it's also arguably the case that you shouldn't care about port 
> number ordering. That smells dodgy to me.
> 

Port ranges aren't that uncommon.

-- 
Philippa Cowderoy 

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


Re: [Haskell-cafe] Using a monad to decompose a function into functions

2009-03-12 Thread minh thu
2009/3/12 Marcin Kosiba :
> Hi,
>        I'm doing a bit of research into mobility models and I'm currently 
> exploring
> implementation language choices for the simulator (yes, sadly it needs to be
> a custom one).
>        I've been using Haskell here and there for some small tasks, and 
> thought I
> should consider it as an implementation language for the simulator.
>        While I already have an working implementation in Haskell, there is 
> one thing
> that I would like to express in a more elegant way, but just can't figure
> out. The simulation algorithm requires expressing the node's mobility so that
> it is "stateless". The mobility model algorithm's type should be something
> like:
> mobility_model :: WorldState -> NodeState -> OtherInput -> (Action, NodeState)
>
> where Action can alter WorldState and the second NodeState is an altered input
> NodeState. I perform a form of speculative execution on mobility_model so
> sometimes I need to backtrack to a previous world and node state.
>        This is all fairly simple stuff, and was just an introduction. What I 
> do now
> is store an enum in NodeState and implement mobility_model as one big case
> statement. Yes, this is very imperative of me, I know. What I'd like to do is
> to express mobility_model, so that the code would look like:
>
> mobility_model world node input = do
>    do_calculus
>    emit_action
>    if something
>      then emit_action
>      else emit_action
>    do_calculus
>    emit_action
>    mobility_model world node input

Hi,

It seems you can use
http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-State-Lazy.html
Just have a look at the exemple :

 tick :: State Int Int
 tick = do n <- get
   put (n+1)
   return n

your code would become something like
mobility_model :: OtherInput -> State (WorldState,NodeState) ()
mobility_model input = do
  world <- gets fst
  node <- gets snd
  
  let (world',node') = ...
  put (world',node')

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


[Haskell-cafe] Using a monad to decompose a function into functions

2009-03-12 Thread Marcin Kosiba
Hi,
I'm doing a bit of research into mobility models and I'm currently 
exploring 
implementation language choices for the simulator (yes, sadly it needs to be 
a custom one).
I've been using Haskell here and there for some small tasks, and 
thought I 
should consider it as an implementation language for the simulator.
While I already have an working implementation in Haskell, there is one 
thing 
that I would like to express in a more elegant way, but just can't figure 
out. The simulation algorithm requires expressing the node's mobility so that 
it is "stateless". The mobility model algorithm's type should be something 
like:
mobility_model :: WorldState -> NodeState -> OtherInput -> (Action, NodeState)

where Action can alter WorldState and the second NodeState is an altered input 
NodeState. I perform a form of speculative execution on mobility_model so 
sometimes I need to backtrack to a previous world and node state. 
This is all fairly simple stuff, and was just an introduction. What I 
do now 
is store an enum in NodeState and implement mobility_model as one big case 
statement. Yes, this is very imperative of me, I know. What I'd like to do is 
to express mobility_model, so that the code would look like:

mobility_model world node input = do
do_calculus
emit_action
if something
  then emit_action
  else emit_action
do_calculus
emit_action
mobility_model world node input

but I'd like to be able to alter world and node state before continuing from 
emit_action. 

I've tried to get this working by using the idea from 
http://www.haskell.org/pipermail/haskell/2005-April/015684.html but couldn't 
get the state-altering behavior I was looking for. I've also taken a look at 
http://monadicheadaches.blogspot.com/2008/01/python-25s-iterators-in-haskell-sort-of.html,
 
the unified concurrency model and Control.Coroutine, but couldn't get the 
behavior I was going for.

Thanks!
Marcin Kosiba


signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to compare PortNumbers or Bug in Network.Socket?

2009-03-12 Thread Bryan O'Sullivan
On Thu, Mar 12, 2009 at 2:44 PM, Stefan Schmidt <
stefanschmid...@googlemail.com> wrote:

> As a work around, I could convert two PortNumbers back to Int-Values before
> comparing them, but I think the ordering functions for the PortNumber-Type
> do not work as expected. Or am I wrong?
>

You're right. Arguably the port numbers shouldn't have their endianness
switched until the need actually arises (passed into bind or the like).

However, it's also arguably the case that you shouldn't care about port
number ordering. That smells dodgy to me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to compare PortNumbers or Bug in Network.Socket?

2009-03-12 Thread Stefan Schmidt

Hello,

I want to compare two PortNumber-Values from the Network.Socket module 
and I think I've experienced some unexpected behavior of the derived 
ordering methods. I'm using the ghc-6.10.1 and the network library 
2.2.0.1 on a x86 32-Bit machine.


The following program creates two pairs of PortNumber values and 
compares them with each other.



module Main(main) where

import Network.Socket

-- Block A
p1 :: PortNumber
p1 = fromIntegral 9000
p2 :: PortNumber
p2 = fromIntegral 1

-- Block B
pp1 :: PortNumber
pp1 = PortNum 9000
pp2 :: PortNumber
pp2 = PortNum 1

main :: IO ()
main
  = do
putStrLn $ "A - " ++ (show $ p1  > p2)
putStrLn $ "B - " ++ (show $ pp1 > pp2)


On my machine, I get the result:

A - True
A - False


At the first glance, it seemed to me, that there is a bug in the 
fromIntegral Implementation. But after I looked into the code, I saw 
that fromIntegral calls the system function "htons" to change the byte 
order from my machine to the network byte order, which on my machine is 
different. Because of this the values 9000 and 1 are transferred, so 
that their ordering changes.


Block B preservers this ordering, because the Constructor PortNum does 
not call htons, but since the byte order is wrong, I cannot use pp1 and 
pp2 to address port 9000 and 1.


As a work around, I could convert two PortNumbers back to Int-Values 
before comparing them, but I think the ordering functions for the 
PortNumber-Type do not work as expected. Or am I wrong?


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


Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-12 Thread Bas van Dijk
2009/3/12 Peter Verswyvelen :
> I think. Or is it defined in some other package?

There's an existing ticket about this:

http://hackage.haskell.org/trac/ghc/ticket/2316

Note that the ticket links to some old threads on
librar...@haskell.org about the issue.

regards,

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


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-12 Thread Adam Vogt
This seems to be in ghc for those reasons:
http://www.haskell.org/haskellwiki/Quasiquotation

* On Monday, March 02 2009, Andrew Hunter wrote:

>Several times now I've had to define an EDSL for working with
>(vaguely) numeric expressions.  For stuff like 2*X+Y, this is easy,
>looking pretty much like:
>
>> data Expr = Const Integer | Plus Expr Expr | Times Expr Expr
>>
>> instance Num Expr where
>> fromInterger = Const
>> (+) = Plus
>> (*) = Times
>
>&c.  This lets me get a perfectly nice AST, which is what I want.
>When I want to be able to express and work with inequalities and
>equalities, this breaks.  Suppose I want to write 2*X + Y < 3.  I
>either have to:
>
>a) Hide Prelude.(<) and define a simple < that builds the AST term I want.
>b) Come up with a new symbol for it that doesn't look totally awful.
>
>Neither of these work decently well.  Hiding Eq and Ord operators,
>which is what I effectively have to do for a), is pretty much a
>nonstarter--we'll have to use them too much for that to be practical.
>
>On the other hand, b) works...but is about as ugly as it gets.  We
>have lots and lots of symbols that are already taken for important
>purposes that are syntactically "near" <,<=,==, and the like: << and
>>> and >>= for monads, >>> for arrows, etc.  There...are not good
>choices that I know of for the symbols that don't defeat the purpose
>of making a nice clean EDSL for expressions; I might as well use 3*X +
>Y `lessthan` 3, which is just not cool.
>
>Does anyone know of a good solution, here?  Are there good
>substitutions for all the six operators that are important
>(<,>,>=,<=,==,/=), that are close enough to be pretty-looking but not
>used for other important modules?
>
>Better yet, though a little harder, is there a nice type trick I'm not
>thinking of?  This works for Num methods but not for Ord methods
>because:
>
>(+) :: (Num a) => a -> a -> a
>(<) :: (Ord a) => a -> a -> Bool
>
>i.e. the return type of comparisons is totally fixed.  I don't suppose
>there's a good way to...well, I don't know what the *right* answer is,
>but maybe define a new typeclass with a more flexible type for < that
>lets both standard types return Bool and my expressions return Expr?
>Any good solution would be appreciated.  
>
>Thanks,
>AHH
>___
>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] Does anybody dislike implicit params as much as I do?

2009-03-12 Thread Dan Doel
On Thursday 12 March 2009 4:36:28 pm Thomas Hartman wrote:
> http://blog.patch-tag.com/2009/03/09/implicitparams-are-evil-thoughts-on-ad
>apting-gitit/
>
> I understand there are arguments for using IPs, but after this
> experience, the ImplicitParams extension is a "code smell" for me.

Implicit parameters are a (sort of) impure version of the reader monad. Of 
course, the 'effects' are still indicated in the type to a degree, but it's 
similar in a way to other languages which have impure IO (for example), except 
that reader is a lot less evil. :)

The main thing they buy you, of course, is programming in a nice, normal, 
applicative style, instead of having to fool with monadic style (of course, 
they also give you multiple such variables, with names no less, that can be 
combined in a more dynamic fashion than Reader. To mimic all that (without 
passing around ST-like references), would probably require, off the top of my 
head, both indexed monads and extensible records. But I digress :)). Perhaps 
with applicative functor combinators, that gap can be lessened a bit. 
Incidentally, your example looks as follows with Reader:

  type ParamsHandler = Reader Params Handler

  withMessages :: [String] -> ParamsHandler -> ParamsHandler
  withMessages msgs val =
local (\params -> params { pMessages = msgs ++ pMessages params }) val

It'd be even nicer with lenses for updating the params. :)

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


Re: [Haskell-cafe] Hand calculation of Bird's definition of zip using foldr

2009-03-12 Thread Ryan Ingram
2009/3/12 R J :
> Part of my problem is that "e" is defined as a function that takes
> one argument, I don't see how that fits in with the usual scheme for foldr,
> which, as I understand it, is:
>
> foldr f e [x1, x2, ...] = f x1 (f x2 (f x3 ...(f xn e)))...

It's pretty easy, actually.  Lets rewrite the type signatures a bit:

> foldr :: (a -> b -> b) -> b -> ([a] -> b)
> zip :: [x] -> [y] -> [(x,y)]
> zip = foldr f e where
>   e _ = []
>   f _ _ [] = []
>   f x g (y:ys) = (x,y) : g ys

So, from the signature for foldr, we can derive:

> f :: (a -> b -> b)
> e :: b
> zip :: [a] -> b

And from the two type signatures for zip, we derive:

> b ~ [y] -> [(x,y)]
> a ~ x

(~ is type equality)

This gives

> e :: [y] -> [(x,y)]
> f :: x -> ([y] -> [(x,y)]) -> ([y] -> [(x,y)])

or, removing the extra parenthesis

> f :: x -> ([y] -> [(x,y)]) -> [y] -> [(x,y)]

that is, f takes *three* arguments, the second of which is a function
of type [y] ->[(x,y)]

What happens is that the *partially applied* f is getting chained
through the fold; so you get

zip [1,2,3] ['a','b','c']
= foldr f e [1,2,3] ['a','b','c']
= f 1 (f 2 (f 3 e)) ['a', 'b', 'c']

Then, in the first application of f, "g" is (f 2 (f 3 e)):

= (1, 'a') : (f 2 (f 3 e)) ['b','c']

Now, there are two termination conditions; if the first list ends, we
reach "e", which eats the remainder of the second list, returning [].
In fact, e is the only total function of its type (forall x y. [y] ->
[(x,y)]).

If the second list ends, then f sees that and doesn't call g; that is,
the rest of the foldr is unevaluated and unused!

foldr f e [1,2,3] []
=> f 1 (foldr f e [2,3]) []
=> []

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


Re: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Martijn van Steenbergen

Deniz Dogan wrote:

Then of course,
there's the downside that there's no connection to the language itself
in any way.


I usually go for names that don't have to do anything with the
application itself: GroteTrap (translates to GreatBustard), Yogurt, 
Custard... saves me from having to think of "appropriate" names. :-P


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


Re: [Haskell-cafe] Does anybody dislike implicit params as much as I do?

2009-03-12 Thread minh thu
2009/3/12 Thomas Hartman :
> http://blog.patch-tag.com/2009/03/09/implicitparams-are-evil-thoughts-on-adapting-gitit/
>
> I understand there are arguments for using IPs, but after this
> experience, the ImplicitParams extension is a "code smell" for me.

I think you state the obvious for many haskellers, so no, you're not alone :)

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


[Haskell-cafe] Does anybody dislike implicit params as much as I do?

2009-03-12 Thread Thomas Hartman
http://blog.patch-tag.com/2009/03/09/implicitparams-are-evil-thoughts-on-adapting-gitit/

I understand there are arguments for using IPs, but after this
experience, the ImplicitParams extension is a "code smell" for me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State monad is missing Applicative instance

2009-03-12 Thread Matt Hellige
Looks like it may be defined in the package applicative-extras:
  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/applicative-extras

But I'm not positive about that, and the docs are... sparse.

Matt

2009/3/12 Peter Verswyvelen :
> I think. Or is it defined in some other package?
>
> ___
> 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] ThreadScope: Request for features for the performance tuning of parallel and concurrent Haskell programs

2009-03-12 Thread Don Stewart
karel.gardas:
> Don Stewart wrote:
> > marlowsd:
> >> Ben Lippmeier wrote:
> >>
> >>> On 12/03/2009, at 12:24 AM, Satnam Singh wrote:
>  Before making the release I thought it would be an idea to ask people 
>  what other features people would find useful or performance tuning. 
>  So if you have any suggestions please do let us know!
> 
> >>> Is it available in a branch somewhere to try out?
> >> There are three parts to it:
> >>
> >>  - some patches to GHC to generate the log files.  The patches are
> >>not yet in, but I hope to get them in in the next couple of weeks.
> > 
> > Just as a meta-point, it makes a *lot* of sense for the runtime to
> > support proper logging -- it's practically a microkernel after all, so
> > logging makes as much sense for GHC's rts as it does for regular
> > kernels.
> > 
> > Now we just need a /proc for the rts, so I can peek at GC stats live.
> 
> Seeing this thread and discussion direction I cannot resist to
> temptation to ask: is anybody going to write rts DTrace[1] provider?

I think this is clear next step in the investigations.

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


Re: [Haskell-cafe] Hand calculation of Bird's definition of zip using foldr

2009-03-12 Thread Miguel Mitrofanov
zip [1,2,3] [4,5,6] = zip (1:2:3:[]) (4:5:6:[]) = foldr f e (1:2:3:[])  
(4:5:6:[]) = f 1 (foldr f e (2:3:[])) (4:5:6:[]) = (1, 4) : foldr f e  
(2:3:[]) (5:6:[]) = (1, 4) : f 2 (foldr f e (3:[])) (5:6:[]) = (1,  
4) : (2, 5) : foldr f e (3:[]) (6:[]) = (1, 4) : (2, 5) : f 3 (foldr f  
e []) (6:[]) = (1, 4) : (2, 5) : (3, 6) : foldr f e [] [] = (1, 4) :  
(2, 5) : (3, 6) : e [] = (1, 4) : (2, 5) : (3, 6) : [] = [(1, 4), (2,  
5), (3, 6)]


On 12 Mar 2009, at 20:01, R J wrote:

Can someone provide a complete hand calculation of zip [1,2,3]  
[4,5,6] using the following definition of zip, based on foldr:


zip::[a] -> [b] -> [(a, b)]
zip=foldr f e
where
e ys=[]
f x g [ ]=[]
f x g (y : ys)=(x , y) : g ys


foldr::(a -> b -> b) -> b -> ([a] -> b)
foldr _ e []=e
foldr f e (x : xs)=f x (foldr f e xs)


This implementation of zip produces the expected result [(1, 4), (2,  
5), (3, 6)], but I'm unable to do the hand calculation and don't  
understand why it works.  Part of my problem is that "e" is defined  
as a function that takes one argument, I don't see how that fits in  
with the usual scheme for foldr, which, as I understand it, is:


foldr f e [x1, x2, ...] = f x1 (f x2 (f x3 ...(f xn e)))...

Thanks, as always, to all in this great community.


Windows Live™: Keep your life in sync. Check it  
out.___

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] Hand calculation of Bird's definition of zip using foldr

2009-03-12 Thread R J

Can someone provide a complete hand calculation of zip [1,2,3] [4,5,6] using 
the following definition of zip, based on foldr:

zip::[a] -> [b] -> [(a, b)]

zip=foldr f e

where 

e ys=[]

f x g [ ]=[]

f x g (y : ys)=(x , y) : g ys 





foldr::(a -> b -> b) -> b -> ([a] -> b)
foldr _ e []=e
foldr f e (x : xs)=f x (foldr f e xs)


This implementation of zip produces the expected result [(1, 4), (2, 5), (3, 
6)], but I'm unable to do the hand calculation and don't understand why it 
works.  Part of my problem is that "e" is defined as a function that takes one 
argument, I don't see how that fits in with the usual scheme for foldr, which, 
as I understand it, is:

foldr f e [x1, x2, ...] = f x1 (f x2 (f x3 ...(f xn e)))...

Thanks, as always, to all in this great community.


_
Windows Live™: Life without walls.
http://windowslive.com/explore?ocid=TXT_TAGLM_WL_allup_1a_explore_032009___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dynamically typing TH.Exp at runtime

2009-03-12 Thread Martin Hofmann
This is what hint does, isn't it? However, this still leaves it to me to
infer what type [|a|] in [| reverse (a:b:[]) = (b:a:[]) |] is. 

Thanks a lot anyway.

Martin

On Thu, 2009-03-12 at 12:59 -0200, Daniel Gorín wrote:
> would using ghc-as-a-library to type (strings with) haskell  
> expressions at runtime help?
> 
> On Mar 12, 2009, at 12:37 PM, Martin Hofmann wrote:
> 
> > I am doing meta-programming at runtime. So my program gets a full
> > Haskell declaration in expression quotation ([d|...|]) modifies it and
> > returns the modified expression. Therefore, I need type information of
> > this expression, and any subexpression, at _runtime_ !  For example:
> >
> > [d| reverse x1 = y1 |]
> >
> >  - rewrites_to ->
> >
> > [d| reverse x2:xs = y2:ys |]
> >
> >  - rewrites_to ->
> >
> > [d| reverse x:xs = reverse xs ++  [x] |]
> >
> > reverse :: [a] -> [a] implies
> > x2,y2 :: a
> > x1,y1,xs,ys :: [a]
> >
> > TH.reify is not applicable, because I need the information at runtime
> > and I am in IO. I suppose Data.Dynamic does not work either, because  
> > [|
> > xs|] :: ExpQ and not [a].
> >
> > So it looks like I need my own type checker and inference and tag each
> > subexpression with its type. If so, I can even omit TH and use my own
> > data type for the abstract syntax tree. This annoys me a bit, because
> > for me it seems that all I need is already there.
> >
> > Did anybody have similar problems, because I shouldn't be the only one
> > doing dynamic typing in a static language? Is there a Haskell
> > implementation of the paper "Typing Dynamic Typing" by Baars and
> > Swierstra (http://people.cs.uu.nl/arthurb/dynamic.html ), so I can try
> > out if this helps me?
> >
> > Any help, comments, and how-to-suggestions are highly welcome.
> >
> > Thanks a lot,
> >
> > Martin
> >
> >
> >
> > ___
> > 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] Re: Data.Binary patches?

2009-03-12 Thread Don Stewart
Send it to the maintainer...
Explain what the patch is for, and why it should be applied.

dbueno:
> On Wed, Mar 11, 2009 at 20:54, Denis Bueno  wrote:
> > I've got a small patch for Data.Binary.  Should I post it here, or is
> > there some more appropriate forum?
> 
> In case whoever reads this is a Data.Binary maintainer, the patch is
> now attached, to save you some work.
> 
> The .patch file is the output of darcs send -a --output=.
> 
>   Denis


> ___
> 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] ThreadScope: Request for features for the performance tuning of parallel and concurrent Haskell programs

2009-03-12 Thread Don Stewart
marlowsd:
> Ben Lippmeier wrote:
>
>>
>> On 12/03/2009, at 12:24 AM, Satnam Singh wrote:
>>> Before making the release I thought it would be an idea to ask people 
>>> what other features people would find useful or performance tuning. 
>>> So if you have any suggestions please do let us know!
>>>
>>
>> Is it available in a branch somewhere to try out?
>
> There are three parts to it:
>
>  - some patches to GHC to generate the log files.  The patches are
>not yet in, but I hope to get them in in the next couple of weeks.

Just as a meta-point, it makes a *lot* of sense for the runtime to
support proper logging -- it's practically a microkernel after all, so
logging makes as much sense for GHC's rts as it does for regular
kernels.

Now we just need a /proc for the rts, so I can peek at GC stats live.

>  - a Haskell library for parsing the log files.  This will be up
>on Hackage soon.  You can use this to write your own analysis
>tools, visualisers, or whatever.
>
>  - The ThreadScope viewer itself, which will also be up on Hackage
>as soon as its ready.
>
> So we fully intend to get this out there ASAP, although until GHC 6.12 is 
> released you will need to use a GHC snapshot to generate the log files.

Sweet. This should have many many applications for work projects ...
"attach a viewer to a remote Haskell server to see what's it's up to"...
"heartbeat monitoring of the rts" ...

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


[Haskell-cafe] "The Curse of Our Times" in different languages

2009-03-12 Thread Jamie
See Black-Scholes model/option formula being implemented in different 
languages including Haskell.


http://www.espenhaug.com/black_scholes.html

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


[Haskell-cafe] Haskell-Wiki Account registration

2009-03-12 Thread Henning Thielemann


How long will the Wiki account registration be disabled? Would it be 
possible to ask a question, that real Haskellers could easily answer, but 
a spambot cannot? E.g. "What's Haskell's surname?"

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


Re: [Haskell-cafe] monadic logo

2009-03-12 Thread Anton van Straaten

Gregg Reynolds wrote:
What is distinctive about Haskell it's use of the monad.  The 
The Pythagorean monad symbol is wonderfully simple:


http://en.wikipedia.org/wiki/Monad_(Greek_philosophy) 


It has the added benefit that if you put a pair of those on the chest of 
a suitably curvy cartoon character, you've got yourself one sexy mascot.



Hey, at least it isn't cute.


De gustibus non est disputandum!

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


Re: [Haskell-cafe] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Jeff Heard
Oh, I know it's not specific to parsec, it just seems like parsec's
used enough and well understood enough that it would make a good
tutorial.

On Thu, Mar 12, 2009 at 11:36 AM, Martijn van Steenbergen
 wrote:
> Jeff Heard wrote:
>>
>> Come to think of it, I've never seen an applicative tutorial of
>> Parsec, only a monadic one.  Does such a beast exist
>
> Here's something that comes close:
>
> http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-044.pdf
>
> It's not specific to Parsec; instead, a parser type is defined on the fly,
> based on Philip Wadler's list of successes. The applicative and monadic
> approaches are clearly separated.
>
> Martijn.
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Andrew Wagner
I was thinking the same thing. If I remember correctly, RWH does a parser in
an applicative style, but I'll have to look when I get home to be sure. If
so, then maybe we could try doing the same thing in a monadic style, for
comparison and contrast purposes.

On Thu, Mar 12, 2009 at 11:29 AM, Jeff Heard wrote:

> Come to think of it, I've never seen an applicative tutorial of
> Parsec, only a monadic one.  Does such a beast exist, and if so, maybe
> we could merge the two together, work the same example in both, and
> thus help the programmer make the shift from monadic to applicative,
> from order of parsing to describing the grammar.
>
> -- Jeff
>
> 2009/3/12 Conal Elliott :
> > Thank you Bob!  I'll throw in another 2 cents:
> >
> > Yes, *one* aspect of Haskell is that it's a power tool for imperative
> > programming -- a clever way to keep plugging away at the old sequential
> von
> > Neumann paradigm.  C.
> >
> > I'd rather we strongly encourage Haskell-newbies toward shifting out of
> the
> > imperative paradigm to thinking and programming *functionally*.  It's a
> big
> > shift, to make, and imperative-Haskell is a relatively easy substitute.
> >
> >- Conal
> >
> > On Thu, Mar 12, 2009 at 7:28 AM, Thomas Davie 
> wrote:
> >>
> >> On 12 Mar 2009, at 15:16, Andrew Wagner wrote:
> >>
> >>> Can you expand on this a bit? I'm curious why you think this.
> >>
> >> For two reasons:
> >>
> >> Firstly, I often find that people use the Monadic interface when one of
> >> the less powerful ones is both powerful enough and more convenient,
> parsec
> >> is a wonderful example of this.  When the applicative instance is used
> >> instead of the monadic one, programs rapidly become more readable,
> because
> >> they stop describing the order in which things should be parsed, and
> start
> >> describing the grammar of the language being parsed instead.
> >>
> >> Secondly, It seems relatively common now for beginners to be told about
> >> the IO monad, and start writing imperative code in it, and thinking that
> >> this is what Haskell programming is.  I have no problem with people
> writing
> >> imperative code in Haskell, it's an excellent imperative language.
>  However,
> >> beginners seeing this, and picking it up is usually counter productive –
> >> they never learn how to write things in a functional way, and miss out
> on
> >> most of the benefits of doing so.
> >>
> >> Hope that clarifies what I meant :)
> >>
> >> Bob___
> >> 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
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Martijn van Steenbergen

Jeff Heard wrote:

Come to think of it, I've never seen an applicative tutorial of
Parsec, only a monadic one.  Does such a beast exist


Here's something that comes close:

http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-044.pdf

It's not specific to Parsec; instead, a parser type is defined on the 
fly, based on Philip Wadler's list of successes. The applicative and 
monadic approaches are clearly separated.


Martijn.

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


Re: [Haskell-cafe] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Jeff Heard
Come to think of it, I've never seen an applicative tutorial of
Parsec, only a monadic one.  Does such a beast exist, and if so, maybe
we could merge the two together, work the same example in both, and
thus help the programmer make the shift from monadic to applicative,
from order of parsing to describing the grammar.

-- Jeff

2009/3/12 Conal Elliott :
> Thank you Bob!  I'll throw in another 2 cents:
>
> Yes, *one* aspect of Haskell is that it's a power tool for imperative
> programming -- a clever way to keep plugging away at the old sequential von
> Neumann paradigm.  C.
>
> I'd rather we strongly encourage Haskell-newbies toward shifting out of the
> imperative paradigm to thinking and programming *functionally*.  It's a big
> shift, to make, and imperative-Haskell is a relatively easy substitute.
>
>    - Conal
>
> On Thu, Mar 12, 2009 at 7:28 AM, Thomas Davie  wrote:
>>
>> On 12 Mar 2009, at 15:16, Andrew Wagner wrote:
>>
>>> Can you expand on this a bit? I'm curious why you think this.
>>
>> For two reasons:
>>
>> Firstly, I often find that people use the Monadic interface when one of
>> the less powerful ones is both powerful enough and more convenient, parsec
>> is a wonderful example of this.  When the applicative instance is used
>> instead of the monadic one, programs rapidly become more readable, because
>> they stop describing the order in which things should be parsed, and start
>> describing the grammar of the language being parsed instead.
>>
>> Secondly, It seems relatively common now for beginners to be told about
>> the IO monad, and start writing imperative code in it, and thinking that
>> this is what Haskell programming is.  I have no problem with people writing
>> imperative code in Haskell, it's an excellent imperative language.  However,
>> beginners seeing this, and picking it up is usually counter productive –
>> they never learn how to write things in a functional way, and miss out on
>> most of the benefits of doing so.
>>
>> Hope that clarifies what I meant :)
>>
>> Bob___
>> 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] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Andrew Wagner
Conal,Do you think imperative Haskell can be a sort of "gateway drug" to
"real" haskell?

On Thu, Mar 12, 2009 at 11:25 AM, Conal Elliott  wrote:

> Thank you Bob!  I'll throw in another 2 cents:
>
> Yes, *one* aspect of Haskell is that it's a power tool for imperative
> programming -- a clever way to keep plugging away at the old sequential von
> Neumann paradigm.  C.
>
> I'd rather we strongly encourage Haskell-newbies toward shifting out of the
> imperative paradigm to thinking and programming *functionally*.  It's a big
> shift, to make, and imperative-Haskell is a relatively easy substitute.
>
>- Conal
>
> On Thu, Mar 12, 2009 at 7:28 AM, Thomas Davie  wrote:
>
>>
>> On 12 Mar 2009, at 15:16, Andrew Wagner wrote:
>>
>>  Can you expand on this a bit? I'm curious why you think this.
>>>
>>
>> For two reasons:
>>
>> Firstly, I often find that people use the Monadic interface when one of
>> the less powerful ones is both powerful enough and more convenient, parsec
>> is a wonderful example of this.  When the applicative instance is used
>> instead of the monadic one, programs rapidly become more readable, because
>> they stop describing the order in which things should be parsed, and start
>> describing the grammar of the language being parsed instead.
>>
>> Secondly, It seems relatively common now for beginners to be told about
>> the IO monad, and start writing imperative code in it, and thinking that
>> this is what Haskell programming is.  I have no problem with people writing
>> imperative code in Haskell, it's an excellent imperative language.  However,
>> beginners seeing this, and picking it up is usually counter productive –
>> they never learn how to write things in a functional way, and miss out on
>> most of the benefits of doing so.
>>
>> Hope that clarifies what I meant :)
>>
>>
>> Bob___
>> 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] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Conal Elliott
Thank you Bob!  I'll throw in another 2 cents:

Yes, *one* aspect of Haskell is that it's a power tool for imperative
programming -- a clever way to keep plugging away at the old sequential von
Neumann paradigm.  C.

I'd rather we strongly encourage Haskell-newbies toward shifting out of the
imperative paradigm to thinking and programming *functionally*.  It's a big
shift, to make, and imperative-Haskell is a relatively easy substitute.

   - Conal

On Thu, Mar 12, 2009 at 7:28 AM, Thomas Davie  wrote:

>
> On 12 Mar 2009, at 15:16, Andrew Wagner wrote:
>
>  Can you expand on this a bit? I'm curious why you think this.
>>
>
> For two reasons:
>
> Firstly, I often find that people use the Monadic interface when one of the
> less powerful ones is both powerful enough and more convenient, parsec is a
> wonderful example of this.  When the applicative instance is used instead of
> the monadic one, programs rapidly become more readable, because they stop
> describing the order in which things should be parsed, and start describing
> the grammar of the language being parsed instead.
>
> Secondly, It seems relatively common now for beginners to be told about the
> IO monad, and start writing imperative code in it, and thinking that this is
> what Haskell programming is.  I have no problem with people writing
> imperative code in Haskell, it's an excellent imperative language.  However,
> beginners seeing this, and picking it up is usually counter productive –
> they never learn how to write things in a functional way, and miss out on
> most of the benefits of doing so.
>
> Hope that clarifies what I meant :)
>
>
> Bob___
> 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] Haxr doesn't compile from cabal (HTTP > 4000 breaks it)

2009-03-12 Thread Jeff Heard
The haxr cabal library dependencies seem to be off.  I wonder, since
haxr would benefit highly from the HTTP 4k series of performance
improvements, is it trivial to make it compatible with the latest
library?

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


Re: [Haskell-cafe] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Andrew Wagner
Hmm, perhaps what we need is another monad tutorial that.err...never
mind. Actually, I'd like to see more written about Applicatives. I think
they just finally clicked with me when reading the Typeclassopedia, and
seeing the intended way to use them. Before it was always like "ok...so, if
I've got a function already in my functor, I could use this, but...why would
I have that?"

On Thu, Mar 12, 2009 at 10:28 AM, Thomas Davie  wrote:

>
> On 12 Mar 2009, at 15:16, Andrew Wagner wrote:
>
>  Can you expand on this a bit? I'm curious why you think this.
>>
>
> For two reasons:
>
> Firstly, I often find that people use the Monadic interface when one of the
> less powerful ones is both powerful enough and more convenient, parsec is a
> wonderful example of this.  When the applicative instance is used instead of
> the monadic one, programs rapidly become more readable, because they stop
> describing the order in which things should be parsed, and start describing
> the grammar of the language being parsed instead.
>
> Secondly, It seems relatively common now for beginners to be told about the
> IO monad, and start writing imperative code in it, and thinking that this is
> what Haskell programming is.  I have no problem with people writing
> imperative code in Haskell, it's an excellent imperative language.  However,
> beginners seeing this, and picking it up is usually counter productive –
> they never learn how to write things in a functional way, and miss out on
> most of the benefits of doing so.
>
> Hope that clarifies what I meant :)
>
> Bob
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abuse of the monad

2009-03-12 Thread Colin Paul Adams

> That's interesting.
>
> I recently used parsec 3. I wrote using the monadic interface because
> I could understand (just about) how to do so. I was looking at the
> examples in RWH, and I could follow the explanation of the monadic
> interface much easier.
> Perhaps this was because RWH shows how to write using the monadic
> interface, and then shows how to convert this to the applicative
> interface.
> It's hard to follow a tutorial that shows you how to convert from
> something you aren't starting with.

>>I suspect that this is an interesting corner case of both my two
>>reasons – firstly, Monads are too powerful here, and secondly, you
>>perhaps found it easier to think about the operational aspects of the
>>parser than to think about the denotation of what the parser should
>>parse.

>>Is that somewhere accurate?

I don't know.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ThreadScope: Request for features for the performance tuning of parallel and concurrent Haskell programs

2009-03-12 Thread Simon Marlow

Ben Lippmeier wrote:



On 12/03/2009, at 12:24 AM, Satnam Singh wrote:
Before making the release I thought it would be an idea to ask people 
what other features people would find useful or performance tuning. So 
if you have any suggestions please do let us know!




Is it available in a branch somewhere to try out?


There are three parts to it:

 - some patches to GHC to generate the log files.  The patches are
   not yet in, but I hope to get them in in the next couple of weeks.

 - a Haskell library for parsing the log files.  This will be up
   on Hackage soon.  You can use this to write your own analysis
   tools, visualisers, or whatever.

 - The ThreadScope viewer itself, which will also be up on Hackage
   as soon as its ready.

So we fully intend to get this out there ASAP, although until GHC 6.12 is 
released you will need to use a GHC snapshot to generate the log files.


Cheers,
Simon

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


Re: [Haskell-cafe] Abuse of the monad

2009-03-12 Thread Thomas Davie


On 12 Mar 2009, at 15:33, Colin Paul Adams wrote:


"Thomas" == Thomas Davie  writes:


   Thomas> On 12 Mar 2009, at 15:16, Andrew Wagner wrote:


Can you expand on this a bit? I'm curious why you think this.


   Thomas> For two reasons:

   Thomas> Firstly, I often find that people use the Monadic
   Thomas> interface when one of the less powerful ones is both
   Thomas> powerful enough and more convenient, parsec is a wonderful
   Thomas> example of this.  When the applicative instance is used
   Thomas> instead of the monadic one, programs rapidly become more
   Thomas> readable, because they stop describing the order in which
   Thomas> things should be parsed, and start describing the grammar
   Thomas> of the language being parsed instead.

That's interesting.

I recently used parsec 3. I wrote using the monadic interface because
I could understand (just about) how to do so. I was looking at the
examples in RWH, and I could follow the explanation of the monadic
interface much easier.
Perhaps this was because RWH shows how to write using the monadic
interface, and then shows how to convert this to the applicative
interface.
It's hard to follow a tutorial that shows you how to convert from
something you aren't starting with.


I suspect that this is an interesting corner case of both my two  
reasons – firstly, Monads are too powerful here, and secondly, you  
perhaps found it easier to think about the operational aspects of the  
parser than to think about the denotation of what the parser should  
parse.


Is that somewhere accurate?

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


[Haskell-cafe] Dynamically typing TH.Exp at runtime

2009-03-12 Thread Martin Hofmann
I am doing meta-programming at runtime. So my program gets a full
Haskell declaration in expression quotation ([d|...|]) modifies it and
returns the modified expression. Therefore, I need type information of
this expression, and any subexpression, at _runtime_ !  For example:

[d| reverse x1 = y1 |]

  - rewrites_to ->

[d| reverse x2:xs = y2:ys |]

  - rewrites_to ->

[d| reverse x:xs = reverse xs ++  [x] |]

reverse :: [a] -> [a] implies
x2,y2 :: a
x1,y1,xs,ys :: [a]

TH.reify is not applicable, because I need the information at runtime
and I am in IO. I suppose Data.Dynamic does not work either, because [|
xs|] :: ExpQ and not [a].

So it looks like I need my own type checker and inference and tag each
subexpression with its type. If so, I can even omit TH and use my own
data type for the abstract syntax tree. This annoys me a bit, because
for me it seems that all I need is already there.

Did anybody have similar problems, because I shouldn't be the only one
doing dynamic typing in a static language? Is there a Haskell
implementation of the paper "Typing Dynamic Typing" by Baars and
Swierstra (http://people.cs.uu.nl/arthurb/dynamic.html ), so I can try
out if this helps me?

Any help, comments, and how-to-suggestions are highly welcome.

Thanks a lot,

Martin



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


Re: [Haskell-cafe] Abuse of the monad

2009-03-12 Thread Colin Paul Adams
> "Thomas" == Thomas Davie  writes:

Thomas> On 12 Mar 2009, at 15:16, Andrew Wagner wrote:

> Can you expand on this a bit? I'm curious why you think this.

Thomas> For two reasons:

Thomas> Firstly, I often find that people use the Monadic
Thomas> interface when one of the less powerful ones is both
Thomas> powerful enough and more convenient, parsec is a wonderful
Thomas> example of this.  When the applicative instance is used
Thomas> instead of the monadic one, programs rapidly become more
Thomas> readable, because they stop describing the order in which
Thomas> things should be parsed, and start describing the grammar
Thomas> of the language being parsed instead.

That's interesting.

I recently used parsec 3. I wrote using the monadic interface because
I could understand (just about) how to do so. I was looking at the
examples in RWH, and I could follow the explanation of the monadic
interface much easier.
Perhaps this was because RWH shows how to write using the monadic
interface, and then shows how to convert this to the applicative
interface. 
It's hard to follow a tutorial that shows you how to convert from
something you aren't starting with.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Request: warn about language extensions that are not used

2009-03-12 Thread Sittampalam, Ganesh
As I understand it the current scheme is that you vote for a bug by
adding yourself to the CC list.



From: haskell-cafe-boun...@haskell.org
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Peter Verswyvelen
Sent: 12 March 2009 14:27
To: Conal Elliott
Cc: haskell mailing list
Subject: Re: [Haskell-cafe] Request: warn about language extensions that
are not used


Thanks Conal. 


For people interested, here's the ticket. 


http://hackage.haskell.org/trac/ghc/ticket/3085
 



Martijn Van Steenbergen indirectly revealed a feature request to the
feature request feature of the feature database :-) Okay, I'll stop the
nonsense: it would be nice if the community could rate the popularity of
a feature request, which Martijn now just did by adding a comment.



On Thu, Mar 12, 2009 at 3:12 PM, Conal Elliott  wrote:


Thanks Peter.  I'd love to have this feature also.  I go back
every so often and try removing each of the extensions listed in my
LANGUAGE pragma.  Didn't occur to me that the compiler could be doing it
for me.  Regards,  - Conal


2009/3/11 Peter Verswyvelen 


Okay, I submitted it as a GHC feature request. Thanks
for the feedback. 

On Wed, Mar 11, 2009 at 5:16 PM, Creighton Hogg
 wrote:


2009/3/11 Peter Verswyvelen :

> When I put
> {-# OPTIONS_GHC -Wall -Werror #-}
> in my source file, I don't get compiler (GHC)
warnings about redundant
> language extensions that I enabled.
> It would be nice if the compiler gave warnings
about this, since after
> refactoring, some language extensions might
not be needed anymore, and hence
> should be removed since fewer language
extensions mean more stable and
> portable code no?
> What do you think?


So you mean something like if you put {-#
LANGUAGE
GeneralizedNewtypeDeriving #-} in a file, but
never do newtype
deriving, it would warn you?

I have no idea how hard that'd be to implement,
but that sounds kind
of cool.  Useful for both refactoring and when
you've inherited old
code.

Cheers,
C




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

http://www.haskell.org/mailman/listinfo/haskell-cafe






=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Thomas Davie


On 12 Mar 2009, at 15:16, Andrew Wagner wrote:


Can you expand on this a bit? I'm curious why you think this.


For two reasons:

Firstly, I often find that people use the Monadic interface when one  
of the less powerful ones is both powerful enough and more convenient,  
parsec is a wonderful example of this.  When the applicative instance  
is used instead of the monadic one, programs rapidly become more  
readable, because they stop describing the order in which things  
should be parsed, and start describing the grammar of the language  
being parsed instead.


Secondly, It seems relatively common now for beginners to be told  
about the IO monad, and start writing imperative code in it, and  
thinking that this is what Haskell programming is.  I have no problem  
with people writing imperative code in Haskell, it's an excellent  
imperative language.  However, beginners seeing this, and picking it  
up is usually counter productive – they never learn how to write  
things in a functional way, and miss out on most of the benefits of  
doing so.


Hope that clarifies what I meant :)

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


Re: [Haskell-cafe] Request: warn about language extensions that are not used

2009-03-12 Thread Peter Verswyvelen
Thanks Conal.

For people interested, here's the ticket.

http://hackage.haskell.org/trac/ghc/ticket/3085

Martijn Van Steenbergen indirectly revealed a feature request to the feature
request feature of the feature database :-) Okay, I'll stop the nonsense: it
would be nice if the community could rate the popularity of a feature
request, which Martijn now just did by adding a comment.


On Thu, Mar 12, 2009 at 3:12 PM, Conal Elliott  wrote:

> Thanks Peter.  I'd love to have this feature also.  I go back every so
> often and try removing each of the extensions listed in my LANGUAGE pragma.
> Didn't occur to me that the compiler could be doing it for me.  Regards,  -
> Conal
>
> 2009/3/11 Peter Verswyvelen 
>
>> Okay, I submitted it as a GHC feature request. Thanks for the feedback.
>> On Wed, Mar 11, 2009 at 5:16 PM, Creighton Hogg  wrote:
>>
>>> 2009/3/11 Peter Verswyvelen :
>>> > When I put
>>> > {-# OPTIONS_GHC -Wall -Werror #-}
>>> > in my source file, I don't get compiler (GHC) warnings about redundant
>>> > language extensions that I enabled.
>>> > It would be nice if the compiler gave warnings about this, since after
>>> > refactoring, some language extensions might not be needed anymore, and
>>> hence
>>> > should be removed since fewer language extensions mean more stable and
>>> > portable code no?
>>> > What do you think?
>>>
>>> So you mean something like if you put {-# LANGUAGE
>>> GeneralizedNewtypeDeriving #-} in a file, but never do newtype
>>> deriving, it would warn you?
>>>
>>> I have no idea how hard that'd be to implement, but that sounds kind
>>> of cool.  Useful for both refactoring and when you've inherited old
>>> code.
>>>
>>> Cheers,
>>> C
>>>
>>
>>
>> ___
>> 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] Abuse of the monad [was: monadic logo]

2009-03-12 Thread Andrew Wagner
Can you expand on this a bit? I'm curious why you think this.

On Thu, Mar 12, 2009 at 10:13 AM, Thomas Davie  wrote:

>
> On 12 Mar 2009, at 15:04, Gregg Reynolds wrote:
>
>  At risk of becoming the most hated man in all Haskelldom, I'd like to
>> suggest that the Haskell logo not use lambda symbols.  Or at least not as
>> the central element.  Sorry, I know I'm late to the party, but the thing is
>> there is nothing distinctive about lambda; it's common to all FPLs.
>>  Besides, Lisp/Scheme already have that franchise.
>>
>> What is distinctive about Haskell it's use of the monad.  The Pythagorean
>> monad symbol is wonderfully simple:
>>
> No, what's distinctive about Haskell is usually the abuse of the monad.
>
> Encouraging people to think Haskell is all about monadic programming even
> more is a recipe for disaster.
>
> Just my 2¢
>
> Bob___
>
> 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] monadic logo

2009-03-12 Thread Thomas Davie


On 12 Mar 2009, at 15:04, Gregg Reynolds wrote:

At risk of becoming the most hated man in all Haskelldom, I'd like  
to suggest that the Haskell logo not use lambda symbols.  Or at  
least not as the central element.  Sorry, I know I'm late to the  
party, but the thing is there is nothing distinctive about lambda;  
it's common to all FPLs.  Besides, Lisp/Scheme already have that  
franchise.


What is distinctive about Haskell it's use of the monad.  The  
Pythagorean monad symbol is wonderfully simple:

No, what's distinctive about Haskell is usually the abuse of the monad.

Encouraging people to think Haskell is all about monadic programming  
even more is a recipe for disaster.


Just my 2¢

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


Re: [Haskell-cafe] Request: warn about language extensions that are not used

2009-03-12 Thread Conal Elliott
Thanks Peter.  I'd love to have this feature also.  I go back every so often
and try removing each of the extensions listed in my LANGUAGE pragma.
Didn't occur to me that the compiler could be doing it for me.  Regards,  -
Conal

2009/3/11 Peter Verswyvelen 

> Okay, I submitted it as a GHC feature request. Thanks for the feedback.
> On Wed, Mar 11, 2009 at 5:16 PM, Creighton Hogg  wrote:
>
>> 2009/3/11 Peter Verswyvelen :
>> > When I put
>> > {-# OPTIONS_GHC -Wall -Werror #-}
>> > in my source file, I don't get compiler (GHC) warnings about redundant
>> > language extensions that I enabled.
>> > It would be nice if the compiler gave warnings about this, since after
>> > refactoring, some language extensions might not be needed anymore, and
>> hence
>> > should be removed since fewer language extensions mean more stable and
>> > portable code no?
>> > What do you think?
>>
>> So you mean something like if you put {-# LANGUAGE
>> GeneralizedNewtypeDeriving #-} in a file, but never do newtype
>> deriving, it would warn you?
>>
>> I have no idea how hard that'd be to implement, but that sounds kind
>> of cool.  Useful for both refactoring and when you've inherited old
>> code.
>>
>> Cheers,
>> C
>>
>
>
> ___
> 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] Re: Against cuteness

2009-03-12 Thread Gregg Reynolds
On Thu, Mar 12, 2009 at 7:07 AM, Benjamin L. Russell
 wrote:
>
> Here, there are a lot of Japanese Haskell fans who love the beauty of
> Haskell, and you will risk losing a lot of them if you choose a mascot
> without any cuteness factor.  A lot of my friends meet together every

I don't think so.  Bad design will lose them (and many others), but
good design and cuteness are two different things.

>
> You can still distinguish yourself from O'Reilly without losing the
> cuteness factor with a logo like one of the following:
>

We must have vastly different ideas of cute.  I don't consider those
examples cute.  How about this as a criterion:  if it makes 13-year
old Japanese girls squeal "kawa!" then it's too cute.  Also if it
involves the color pink.

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


[Haskell-cafe] monadic logo

2009-03-12 Thread Gregg Reynolds
At risk of becoming the most hated man in all Haskelldom, I'd like to
suggest that the Haskell logo not use lambda symbols.  Or at least not as
the central element.  Sorry, I know I'm late to the party, but the thing is
there is nothing distinctive about lambda; it's common to all FPLs.
Besides, Lisp/Scheme already have that franchise.

What is distinctive about Haskell it's use of the monad.  The Pythagorean
monad symbol is wonderfully simple:

http://en.wikipedia.org/wiki/Monad_(Greek_philosophy).
Something might also be done with the triad to reflect the fact that the
monad in cat theory is actually a triple (
http://en.wikipedia.org/wiki/Triad_(Greek_philosophy)
).

The "Cup or Monad" (http://www.sacred-texts.com/chr/herm/hermes4.htm), with
a little bit of work, could be turned into an amusing Haskell manifesto.
Lots of interesting imagery from the gnostic tradition (
http://www.sacred-texts.com/gno/th2/index.htm), although SICP seems already
to have  used something similar (
http://mitpress.mit.edu/images/products/books/0262011530-f30.jpg).  Hermes
Trismegistus = Thrice-great Hermes -> Haskell Trismegistus, Thrice-Glorious
Haskell, etc.  Might be too cute.

There's also Leibniz' monadology - I can't think of any visual imagery to go
with it, but he did end up with the "best of all possible worlds"
hypothesis, which gives us a slogan sure to irritate:  "Haskell - the best
of all possible languages".  Not to mention "Haskell Monadology" as a name
for the official Haskell definition, etc.

Hey, at least it isn't cute.

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


Re: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Claus Reinke
I agree that looking for a mascot that is inspired by "laziness" is a bad idea 
from a P.R. perspective (I am tired of people walking out the room when I 
give Haskell talks to general audiences and explain lazy evaluation).


Do they walk out when you mention it or when you explain it?-)

Lazy evaluation -as an optimization of non-strict evaluation- seems
like an unambiguosly good idea. Lazy evaluation -as one efficient
form of non-strict evaluation- has its pros and cons: neither strict
nor non-strict evaluation fit all purposes, and the real trick is to
find the right middle ground. It just so happens that non-strict is
a safe default from which to try and reach that middle ground. In
other words, even in non-PR terms, laziness is a stepping stone,
not the ultimate goal.

Your remark reminded me of some old slides of mine, where I
tried to offer one perspective on the problems of "communicating 
fp ideas to general audiences". In brief, successful communication 
assumes some shared background, and if that doesn't exist,
communication is difficult at best and usually fails. 

Haskellers often resort to formal maths models, which is fine for 
those with a shared background, not so fine for general audiences. 
In that old talk I suggested using a model that general audiences, 
and business folks in particular, are familiar with, and started to 
outline an initial "dictionary of fp terms" - the translation worked

well enough to show that neither strict nor non-strict evaluation
make for good business models, and that we're really looking for
some form of "just in time" evaluation (of course, you have to keep 
in mind that my understanding of business terms is only that of an 
average general audience;-). 

I've temporarily put the slides here (note that the contact info, 
from one of my previous lives, is years out of date):


http://www.cs.kent.ac.uk/~cr3/tmp/slides.pdf

Perhaps you find some of the ideas useful? And now that we 
actually have some more business folks amongst us, perhaps 
some of them would like to comment on the suitability or

otherwise of these ideas?-).

Claus

-- Lazy evaluation: been there, done that.

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


Re: [Haskell-cafe] Re: Against cuteness

2009-03-12 Thread Ketil Malde
Benjamin L.Russell  writes:

>>Regarding logos/mascots:  nothing personal folks, but I would like to cast a
>>loud firm vote against all forms of cuteness, especially small furry animal

> Sorry, but I cannot agree with you.  I actually moved from New York to
> Tokyo partly because of the cuteness culture

> Here, there are a lot of Japanese Haskell fans who love the beauty of
> Haskell, and you will risk losing a lot of them if you choose a mascot
> without any cuteness factor.

So it seems we'll either lose the cuteness-loving Japanese, or the
slick and cool New Yorkers.  A solution would be to find something
that is interpreted as cute in Japan, and chiq in New York - but as we
don't want everybody else to leave either, we probably want to avoid
anything pornographic.  Tricky.

> You can still distinguish yourself from O'Reilly without losing the
> cuteness factor with a logo like one of the following:

 [...]

> a three-dimensional lambda^2 logo stand, with the same logo in a
> transparent green upper portion an aluminum lower portion
> http://home.comcast.net/~flyingsquids/BlogStuff/HL2Logo2.jpg

Hmm...perhaps this is the solution we're looking for: shiny lambda
handcuffs!  Obsce^H^H^H^H^HSophisticated enough for the New Yorkers,
cute enough for the Japanese, and avoiding the unfortunate laziness
connotations by focusing on strictness and discipline instead.

This definitely gets my vote.  (If I still have one.)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Lennart Augustsson
I thought evil dictators was covered by the Stalin Scheme implementation.
(We can always discuss which is the worse name of Stalin and Bigloo.)

I don't see why we need a mascot at all.  We've managed so far without one.

On Thu, Mar 12, 2009 at 10:12 AM, Bulat Ziganshin
 wrote:
> Hello Satnam,
>
> Thursday, March 12, 2009, 1:08:58 PM, you wrote:
>
>> Perhaps this is just an indication of my dark and violent side, but
>> choosing an animal with a killer instinct might be a better idea. A
>> creature that would eat something small and furry as a mid afternoon snack
>
> why not choose Hitler or Mao? this will clearly indicate our
> intentions :D
>
> --
> Best regards,
>  Bulat                            mailto:bulat.zigans...@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


[Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Maurí­cio

Hehe, I love it. Sloth is a synonym for Lazyness in English
too, and they're so freaking cute... :)


I wouldn't say it was an exact synonym. Though the
dictionary definitions are similar, sloth has a more
negative connotation than laziness; the fourth deadly sin is
called "sloth" rather than "laziness".



'Preguiça', the name in Portuguese, is also the
name of that deadly sin. But then I would quote
Brazilian writter Mário Quintana:

"A preguiça é a mãe do progresso. Se o homem não
tivesse preguiça de caminhar, não teria inventado
a roda." [book: Na Volta da Esquina]

My translation: "Sloth is the mother of progress. If
not for the sloth of walking, mankind wouldn't have
invented the wheel".

Best,
Maurício

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


[Haskell-cafe] Re: Against cuteness

2009-03-12 Thread Benjamin L . Russell
On Wed, 11 Mar 2009 05:17:41 -0500, Gregg Reynolds 
wrote:

>Regarding logos/mascots:  nothing personal folks, but I would like to cast a
>loud firm vote against all forms of cuteness, especially small furry animal
>cuteness.  It's been done half to death, and we are not O'Reilly.  Of all
>the billions of images from all the cultures in the world available to us we
>can surely find something that is witty or charming without being cute.

Sorry, but I cannot agree with you.  I actually moved from New York to
Tokyo partly because of the cuteness culture in Japan (and lack of it
in New York--everything has to be black there to be cool for some
reason), and I absolutely will not stand for any mascot that isn't
cute.

Here, there are a lot of Japanese Haskell fans who love the beauty of
Haskell, and you will risk losing a lot of them if you choose a mascot
without any cuteness factor.  A lot of my friends meet together every
month to study category theory and Haskel in a Category Theory Study
Group (see
http://www.sampou.org/cgi-bin/haskell.cgi?CategoryTheory%3A%B7%F7%CF%C0%CA%D9%B6%AF%B2%F1),
and we all love Haskell for its simplicity and beauty.  We like to
think monadically.

You can still distinguish yourself from O'Reilly without losing the
cuteness factor with a logo like one of the following:

An aqua lambda symbol superimposed on Planet Earth, representing a
Haskellian Planet Earth:
http://wikicompany.org/fs/img/haskell.png

a three-dimensional lambda^2 logo stand, with the same logo in a
transparent green upper portion an aluminum lower portion
http://home.comcast.net/~flyingsquids/BlogStuff/HL2Logo2.jpg

lambda -> theta tau, represented in Greek symbols of two colors:
http://qthaskell.sourceforge.net/

Different from anything on O'Reilly, potentially Haskellian in spirit,
and not animal mascots, but still cute.

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 

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


RE: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Bayley, Alistair
> From: haskell-cafe-boun...@haskell.org 
> [mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Deniz Dogan
> 
> Python already uses a snake and it reminds me too much of vi and
> viper-mode etc.  If so many people are reluctant towards the sloth,
> why don't we just go for the narwhal?  They're predators, they have
> built-in swords and they're just bad ass in general.  Then of course,
> there's the downside that there's no connection to the language itself
> in any way.


Something wrong with the Hercules beetle, used on the cover of Real
World Haskell?

http://book.realworldhaskell.org/

This book is already creating an association between the Hercules beetle
and Haskell, so it seems quite reasonable to continue down that path.
Isn't that how Perl got its camel?

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

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


Re: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Deniz Dogan
2009/3/12 Colin Paul Adams :
>> "Deniz" == Deniz Dogan  writes:
>
>    Deniz> 2009/3/12 Satnam Singh :
>    >> I agree that looking for a mascot that is inspired by
>    >> "laziness" is a bad idea from a P.R. perspective (I am tired of
>    >> people walking out the room when I give Haskell talks to
>    >> general audiences and explain lazy evaluation).
>    >>
>    >> Perhaps this is just an indication of my dark and violent side,
>    >> but choosing an animal with a killer instinct might be a better
>    >> idea. A creature that would eat something small and furry as a
>    >> mid afternoon snack
>    >>
>    >> How about a viper?
>    >> 
> http://viperfashion.com/wp-content/uploads/2008/12/5742_coiled_up_viper_snake_sticking_tongue_out.jpg
>
>    Deniz> Python already uses a snake and it reminds me too much of
>    Deniz> vi and viper-mode etc.  If so many people are reluctant
>    Deniz> towards the sloth, why don't we just go for the narwhal?
>    Deniz> They're predators, they have built-in swords and they're
>    Deniz> just bad ass in general.  Then of course, there's the
>    Deniz> downside that there's no connection to the language itself
>    Deniz> in any way.
>
> Why not just dispense with a mascot? It's rather childish.
>
> New motto for Haskell:
>
> "Avoid mascots at all cost".

Let's have a vote about the official Haskell motto!

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


Re: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Colin Paul Adams
> "Deniz" == Deniz Dogan  writes:

Deniz> 2009/3/12 Satnam Singh :
>> I agree that looking for a mascot that is inspired by
>> "laziness" is a bad idea from a P.R. perspective (I am tired of
>> people walking out the room when I give Haskell talks to
>> general audiences and explain lazy evaluation).
>> 
>> Perhaps this is just an indication of my dark and violent side,
>> but choosing an animal with a killer instinct might be a better
>> idea. A creature that would eat something small and furry as a
>> mid afternoon snack
>> 
>> How about a viper?
>> 
http://viperfashion.com/wp-content/uploads/2008/12/5742_coiled_up_viper_snake_sticking_tongue_out.jpg

Deniz> Python already uses a snake and it reminds me too much of
Deniz> vi and viper-mode etc.  If so many people are reluctant
Deniz> towards the sloth, why don't we just go for the narwhal?
Deniz> They're predators, they have built-in swords and they're
Deniz> just bad ass in general.  Then of course, there's the
Deniz> downside that there's no connection to the language itself
Deniz> in any way.

Why not just dispense with a mascot? It's rather childish.

New motto for Haskell:

"Avoid mascots at all cost".
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Deniz Dogan
2009/3/12 Satnam Singh :
> I agree that looking for a mascot that is inspired by "laziness" is a bad 
> idea from a P.R. perspective (I am tired of people walking out the room when 
> I give Haskell talks to general audiences and explain lazy evaluation).
>
> Perhaps this is just an indication of my dark and violent side, but choosing 
> an animal with a killer instinct might be a better idea. A creature that 
> would eat something small and furry as a mid afternoon snack
>
> How about a viper? 
> http://viperfashion.com/wp-content/uploads/2008/12/5742_coiled_up_viper_snake_sticking_tongue_out.jpg

Python already uses a snake and it reminds me too much of vi and
viper-mode etc.  If so many people are reluctant towards the sloth,
why don't we just go for the narwhal?  They're predators, they have
built-in swords and they're just bad ass in general.  Then of course,
there's the downside that there's no connection to the language itself
in any way.

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


[Haskell-cafe] Haskell SDL

2009-03-12 Thread michael millard

hi,
  im having trouble setting up the haskell sdl bindings for windows vista im 
trying to install using minGW but its just not installing correctly. does 
anyone know any good tutorials for this?

_
Get 30 Free Emoticons for your Windows Live Messenger
http://www.livemessenger-emoticons.com/funfamily/en-ie/___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] State monad is missing Applicative instance

2009-03-12 Thread Peter Verswyvelen
I think. Or is it defined in some other package?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sugestion for a Haskell mascot

2009-03-12 Thread Aapo Lehtinen

Peter Verswyvelen wrote:

In Dutch it is "luiaard' and that also means "lazy person".




On Wed, Mar 11, 2009 at 2:52 PM, Deniz Dogan 
mailto:deniz.a.m.do...@gmail.com>> wrote:


2009/3/11 minh thu mailto:not...@gmail.com>>:
> 2009/3/11 Bulat Ziganshin mailto:bulat.zigans...@gmail.com>>:
>> Hello Wolfgang,
>>
>> Wednesday, March 11, 2009, 1:06:37 PM, you wrote:
>>
 Hehe, I love it. Sloth is a synonym for Lazyness in English
too, and
 they're so freaking cute... :)
>>
>>> Same in German: The german “Faultier” means “lazy animal”.
>>
>> russian too, if that matter. i was really amazed by this idea.
>> pure, lazy and fun! :)
>
> Same in french : 'paresseux' just means lazy.
>
> Thu

In Swedish it translates to "late walker" (?) and in Turkish it's
"lazy animal".

Deniz
___
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
  
Meaning is same in Finnish, "laiskiainen", where "laiska" translates to 
"lazy".

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


Re[2]: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Bulat Ziganshin
Hello Satnam,

Thursday, March 12, 2009, 1:08:58 PM, you wrote:

> Perhaps this is just an indication of my dark and violent side, but
> choosing an animal with a killer instinct might be a better idea. A
> creature that would eat something small and furry as a mid afternoon snack

why not choose Hitler or Mao? this will clearly indicate our
intentions :D

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


RE: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Satnam Singh
I agree that looking for a mascot that is inspired by "laziness" is a bad idea 
from a P.R. perspective (I am tired of people walking out the room when I give 
Haskell talks to general audiences and explain lazy evaluation).

Perhaps this is just an indication of my dark and violent side, but choosing an 
animal with a killer instinct might be a better idea. A creature that would eat 
something small and furry as a mid afternoon snack

How about a viper? 
http://viperfashion.com/wp-content/uploads/2008/12/5742_coiled_up_viper_snake_sticking_tongue_out.jpg
 

Cheers,

Satnam

-Original Message-
From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Jon Fairbairn
Sent: 12 March 2009 09:50
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Re: Sugestion for a Haskell mascot

Joe Fredette  writes:

> Hehe, I love it. Sloth is a synonym for Lazyness in English
> too, and they're so freaking cute... :)

I wouldn't say it was an exact synonym. Though the
dictionary definitions are similar, sloth has a more
negative connotation than laziness; the fourth deadly sin is
called "sloth" rather than "laziness".

I think using it as a mascot is a bad idea: "Haskell is so
slow, they even chose a sloth as the mascot".

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2009-01-31)

___
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] Re: Sugestion for a Haskell mascot

2009-03-12 Thread minh thu
2009/3/12 Bulat Ziganshin :
> Hello Jon,
>
> Thursday, March 12, 2009, 12:49:35 PM, you wrote:
>
>> I think using it as a mascot is a bad idea: "Haskell is so
>> slow, they even chose a sloth as the mascot".
>
> and it will be absolute truth :)

Anyway, choosing a programming language based on its logo is
quite childish. And wasn't the moto "Avoid success at all cost" ?

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


Re: [Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Bulat Ziganshin
Hello Jon,

Thursday, March 12, 2009, 12:49:35 PM, you wrote:

> I think using it as a mascot is a bad idea: "Haskell is so
> slow, they even chose a sloth as the mascot".

and it will be absolute truth :)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] How to get program command line arguments in Unicode-aware way (Unix/Linux)?

2009-03-12 Thread Bulat Ziganshin
Hello Dimitry,

Thursday, March 12, 2009, 5:42:14 AM, you wrote:

depends on your OS. for windows i use this code:

myGetArgs = do
   alloca $ \p_argc -> do
   p_argv_w <- commandLineToArgvW getCommandLineW p_argc
   argc <- peek p_argc
   argv_w   <- peekArray (i argc) p_argv_w
   mapM peekTString argv_w >>== tail

foreign import stdcall unsafe "windows.h GetCommandLineW"
  getCommandLineW :: LPTSTR

foreign import stdcall unsafe "windows.h CommandLineToArgvW"
  commandLineToArgvW :: LPCWSTR -> Ptr CInt -> IO (Ptr LPWSTR)


note that it doesn't skip over +RTS sections. btw, i plan to make
unicode-aware version of System.Directory module to solve all these problems

> I am trying to process command line arguments that may contain Unicode
> (cyrillic in this example) characters.

> The standard GHC's getArgs seems to pass whatever was obtained from
> the underlying C library
> without any regard to encoding, e. g the following program (testarg.hs):

> module Main where

> import System.Environment

> main = do
>   x <- getArgs
>   mapM (putStrLn . show) x

> being invoked (ghc 6.10.1)

> runghc testarg -T 'при<в>ет'

> prints the following:

> "-T"
> "\208\191\209\128\208\184<\208\178>\208\181\209\130"

> (not correct, all bytes were passed without proper encoding)

> Is there any way to get program arguments in GHC Unicode-aware? Or at
> least assuming that they are always in UTF-8?
> Something like System.IO.UTF8, but for command line arguments?

> Thanks.

> PS: BTW  runhugs testarg -T 'при<в>ет' prints:

> "-T"
> "\1087\1088\1080<\1074>\1077\1090"

> which is correct.




-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Re: Sugestion for a Haskell mascot

2009-03-12 Thread Jon Fairbairn
Joe Fredette  writes:

> Hehe, I love it. Sloth is a synonym for Lazyness in English
> too, and they're so freaking cute... :)

I wouldn't say it was an exact synonym. Though the
dictionary definitions are similar, sloth has a more
negative connotation than laziness; the fourth deadly sin is
called "sloth" rather than "laziness".

I think using it as a mascot is a bad idea: "Haskell is so
slow, they even chose a sloth as the mascot".

-- 
Jón Fairbairn jon.fairba...@cl.cam.ac.uk
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2009-01-31)

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