[Haskell-cafe] = definition for list monad in ghc

2011-05-16 Thread Michael Vanier
Usually in monad tutorials, the = operator for the list monad is 
defined as:


m = k = concat (map k m)  -- or concatMap k m

but in the GHC sources it's defined as:

m  =  k  =  foldr  ((++)  .  k)  []  m

As far as I can tell, this definition is equivalent to the previous one 
(correct me if I'm wrong), so I was wondering why this definition was chosen 
instead of the other one.  Does anybody know?

Thanks in advance,

Mike






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


[Haskell-cafe] Weird warnings from recent GHC snapshot

2011-03-17 Thread Michael Vanier
I run haskell on Mac OS X (Snow Leopard).  After upgrading my Xcode 
installation to 4.0 I had a tricky time getting ghc working again; the 
version bundled with the Haskell Platform no longer works and I had to 
compile a recent snapshot (ghc-7.1.20110315) from source.  This worked 
fine, but now when I compile my code I keep getting really weird 
warnings.  For instance:


ld: warning: could not create compact unwind for .LFB3: non-standard 
register 5 being saved in prolog


and

SpecConstr
Function `$w$j{v s3hL} [lid]'
  has one call pattern, but the limit is 0
Use -fspec-constr-count=n to set the bound
Use -dppr-debug to see specialisations
SpecConstr
Function `$w$j{v s3ic} [lid]'
  has two call patterns, but the limit is 1
Use -fspec-constr-count=n to set the bound
Use -dppr-debug to see specialisations

The code seems to work, but this is quite irritating.  Is there anything 
that can be done about these warnings?


Thanks,

Mike



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


Re: [Haskell-cafe] Problem with monad transformer stack

2010-10-04 Thread Michael Vanier
 Hmm, it seems like MonadState can be derived even with a non-concrete 
type, for instance:


--

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Monad.Error
import Control.Monad.State
import Data.Typeable

data SomeError =
Error1
  | Error2
  | ErrorFail
  deriving (Eq, Show, Typeable)

data MyData a = MyData [a]

instance Error SomeError where
  noMsg = ErrorFail

newtype MyMonad a b =
  MyMonad ((StateT (MyData a) (Either SomeError) b))
  deriving (Monad,
MonadState (MyData a),
MonadError SomeError,
Typeable)

--

This compiles without errors.  So it looks to me like the real problem 
was the implicit dependency between the type 'a' in MyData and the 
return type 'b' of the monad, which the deriving mechanism couldn't 
enforce if 'b' was 'a'.  I'm finding it hard to get a good conceptual 
understanding of what's really going on here.


Mike






On 10/3/10 7:03 PM, Christopher Done wrote:

On 4 October 2010 03:40, Michael Vaniermvanie...@gmail.com  wrote:

newtype MyMonad a =
  MyMonad ((StateT (MyData a) (Either SomeError) a))
  deriving (Monad,
MonadState (MyData a),
MonadError SomeError,
Typeable)

I think it's the `a'. I think it needs to be a concrete type. E.g. the
following is OK:

newtype MyMonad a =
  MyMonad ((StateT (MyData ()) (Either SomeError) a))
  deriving (Monad,
MonadState (MyData ()),
MonadError SomeError,
Typeable)

But

newtype MyMonad a =
  MyMonad ((StateT (MyData ()) (Either SomeError) [a]))
  deriving (Monad,
MonadState (MyData ()),
MonadError SomeError,
Typeable)

is not. This reminds me of the restriction that impredicative types
remove, but I don't think it's related.


These error messages mean nothing to me.  What's going on?  Can the more
specific code be made to work?  This is with ghc 6.12.3.

It seems like eta-reducing `X' or `x' is enough, but Foo x,, i.e. a
parametrized type with a type variable isn't enough. I think that's
what's going on, but I don't know why.


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


[Haskell-cafe] Problem with monad transformer stack

2010-10-03 Thread Michael Vanier
 I'm having a problem with a simple monad transformer stack that has me 
stumped.  Here's the sample code:


{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Monad.Error
import Control.Monad.State
import Data.Typeable

data SomeError =
Error1
  | Error2
  | ErrorFail
  deriving (Eq, Show, Typeable)

data MyData a = MyData [a]

instance Error SomeError where
  noMsg = ErrorFail

{- This works: -}
{-
newtype StateError e s a =
  StateError ((StateT s (Either e) a))
  deriving (Monad,
MonadState s,
MonadError e,
Typeable)

type MyMonad a = StateError SomeError (MyData a) a
-}

{- This doesn't work: -}
newtype MyMonad a =
  MyMonad ((StateT (MyData a) (Either SomeError) a))
  deriving (Monad,
MonadState (MyData a),
MonadError SomeError,
Typeable)

--

Basically, the more abstracted (commented-out) version works, but the 
more specific one gives this error:


Weird.hs:33:12:
Can't make a derived instance of `Monad MyMonad'
  (even with cunning newtype deriving):
  cannot eta-reduce the representation type enough
In the newtype declaration for `MyMonad'

Weird.hs:34:12:
Cannot eta-reduce to an instance of form
  instance (...) = MonadState (MyData a) MyMonad
In the newtype declaration for `MyMonad'

Weird.hs:35:12:
Can't make a derived instance of `MonadError SomeError MyMonad'
  (even with cunning newtype deriving):
  cannot eta-reduce the representation type enough
In the newtype declaration for `MyMonad'

These error messages mean nothing to me.  What's going on?  Can the more 
specific code be made to work?  This is with ghc 6.12.3.


Thanks,

Mike




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


Re: [Haskell-cafe] Problem with monad transformer stack

2010-10-03 Thread Michael Vanier

 On 10/3/10 7:06 PM, Bryan O'Sullivan wrote:
On Sun, Oct 3, 2010 at 9:40 PM, Michael Vanier mvanie...@gmail.com 
mailto:mvanie...@gmail.com wrote:



{- This doesn't work: -}
newtype MyMonad a =
 MyMonad ((StateT (MyData a) (Either SomeError) a))
 deriving (Monad,
   MonadState (MyData a),
   MonadError SomeError,
   Typeable)


This simply isn't allowed by the generalised newtype derivation 
machinery, because the type variable a appears in one of the classes 
you're deriving.


In fact, I'm not sure how you're hoping for your type to actually work 
as a monad. If you try using (=) on your type synonym that currently 
appears to typecheck, you'll find that the only value that can inhabit 
the state parameter is bottom. Try writing out and using a definition 
of (=) by hand to understand your confusion.

I disagree with your second point.  I have this in working code:

--
newtype StateErrorIO e s a =
  StateErrorIO { runS :: (StateT s (ErrorT e IO) a) }
  deriving (Monad,
MonadIO,
MonadState s,
MonadError e,
Typeable)
--

I can assure you that it works on non-bottom types.

As for the first point, that makes sense.  So if I do this:

--
newtype MyMonadS s a =
  MyMonad ((StateT s (Either SomeError) a))
  deriving (Monad,
MonadState s,
MonadError SomeError,
Typeable)

type MyMonad a = MyMonadS (MyData a) a
--

it type checks.  And yeah, writing out the instances by hand is the best 
way to understand what's going on.


Mike



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


[Haskell-cafe] the overlapping instance that wasn't?

2010-08-24 Thread Michael Vanier

 Hi everyone,

Here's some code that's giving me an error message I don't understand:

{-# LANGUAGE EmptyDataDecls,
 MultiParamTypeClasses,
 UndecidableInstances,
 FlexibleInstances #-}

data Z
data S n

class Nat n where
  toInt :: n - Int

instance Nat Z where
  toInt _ = 0

instance (Nat n) = Nat (S n) where
  toInt _ = 1 + toInt (undefined :: n)

instance (Nat n) = Show n where
  show _ = show $ toInt (undefined :: n)

-- end of code sample

When I run this through ghci, I get this:

test.hs:19:11:
Overlapping instances for Show Int
  arising from a use of `show' at test.hs:19:11-14
Matching instances:
  instance Show Int -- Defined in GHC.Show
  instance (Nat n) = Show n -- Defined at test.hs:18:9-25
In the first argument of `($)', namely `show'
In the expression: show $ toInt (undefined :: n)
In the definition of `show': show _ = show $ toInt (undefined :: n)

Adding OverlappingInstances to the language pragmas fixes the problem.  
My question is: why is this an overlapping instance?  It would make 
sense if Int was an instance of Nat, but it isn't.  Is this just a 
limitation in the way overlapping instances are identified?


Mike

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


Re: [Haskell-cafe] the overlapping instance that wasn't?

2010-08-24 Thread Michael Vanier

 On 8/24/10 1:54 PM, Bartek Æwik³owski wrote:

Hello Michael,

This is because instance selection is solely based on instance heads,
it doesn't consider contexts. There's a nice explanation available
here: http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap

The fix in this case is very easy because there are only two cases
(and you don't want to provide new Nat class instances):

instance Show Z where
 show _ = 0

instance Nat n =  Show (S n) where
 show _ = show $ toInt (undefined :: n) + 1

regards,
Bartek Æwik³owski

OK, thanks!

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


[Haskell-cafe] specifying package name in ghci import?

2010-06-28 Thread Michael Vanier

Hi,

Quick question about ghci: when I do this at the prompt:

ghci :m +Control.Monad.Cont

I get

Ambiguous module name `Control.Monad.Cont':
  it was found in multiple packages: mtl-1.1.0.2 monads-fd-0.0.0.1

Is there any way to fix this from within ghci (i.e. not involving 
mucking with ghc-pkg)?  What I have in mind might be e.g.


ghci :m + mtl Control.Monad.Cont

or something similar.

Thanks,

Mike


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


[Haskell-cafe] name of this monadic combinator?

2010-05-30 Thread Michael Vanier

I stumbled across this monadic combinator:

mcombine :: Monad m = (a - a - a) - m a - m a - m a
mcombine f mx my = do
x - mx
y - my
return (f x y)

I used it to chain the outputs of two Parsec String parsers together 
using this operator:


(++) :: Monad m = m String - m String - m String
(++) = mcombine (++)

mcombine seems like such a basic operation that it should be a library 
function, but I couldn't find one matching it on hoogle.  Is there one?


- Mike




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


Re: [Haskell-cafe] name of this monadic combinator?

2010-05-30 Thread Michael Vanier

On 5/30/10 1:40 AM, Michael Snoyman wrote:



On Sun, May 30, 2010 at 11:35 AM, Michael Vanier mvanie...@gmail.com 
mailto:mvanie...@gmail.com wrote:


I stumbled across this monadic combinator:

mcombine :: Monad m = (a - a - a) - m a - m a - m a
mcombine f mx my = do
   x - mx
   y - my
   return (f x y)

I used it to chain the outputs of two Parsec String parsers
together using this operator:

(++) :: Monad m = m String - m String - m String
(++) = mcombine (++)

mcombine seems like such a basic operation that it should be a
library function, but I couldn't find one matching it on hoogle.
 Is there one?

- Mike

liftM2: 
http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/Control-Monad.html#v%3AliftM2


Strangely, Hayoo didn't turn this one up... anyone know why?

Michael

Ah, cool.  Thanks!

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


Re: [Haskell-cafe] libraries [was GUI haters]

2010-04-02 Thread Michael Vanier
This is a great idea!  IMO this is also one of the main ways that 
GUI-based apps are likely to evolve into in the future.  Cross-platform 
GUIs are a pain in the butt in _any_ language (possibly excluding full 
language platforms like Java/.NET, and I'll bet even those were a 
nightmare for the original implementors).


Mike

aditya siram wrote:

Yes Haskell is not strong on the GUI end of things but have you
considered turning your desktop app into a web app? I've done this for
a few things and really enjoyed the process. Haskell's STM is what
makes this so nice.

Basically the you start a Haskell service on port some-large-number
and make AJAX calls to it from your web browser using a CGI script as
a go-between. In my case all data flows back and forth as JSON
objects. You could just as easily use XML.

For the front-end I used Qooxdoo [1] , an absolutely gorgeous
well-documented Javascript GUI framework but there are plenty to
choose from.

This has a couple of advantages, it encourages MVC by letting the
front-end take care of UI and the back-end does the logic and holds
state. It's easy to deploy- Javascript runs everywhere and so does
Haskell (the non-GUI parts anyway!). And it looks uniform across
platforms.

The disadvantages include security (but you can always restrict users
to localhost), and performance (you probably don't want to visualize
gigabyte size datasets in your browser). Additionally you now need to
add and configure an extra piece of software, namely the web-server.
Also you now have to learn Javascript and add that to the list of
things the maintenance programmer has to worry about. But if you can
learn Haskell, Javascript shouldn't be an issue. I've found that none
of these disadvantages are really show-stoppers.

hth,
deech

[1] http://qooxdoo.org/

On 4/2/10, gladst...@gladstein.com gladst...@gladstein.com wrote:
  

As a working engineer, one of my greatest frustrations is my inability
to use Haskell in the workplace. The unfortunate fact is that my media
industry clients use mostly Windows, some Macs, and no linux except for
servers. The core system works everywhere, but many contributed
libraries don't. GUIs are the big showstopper.

One of the reasons Java won out over Common Lisp is that it had huge
libraries. Franz's libraries were superb but few in number. One diehard
Lisp user converted his lab to Java because Java gives you everything
you want, for free.

That languages are distinct from their libraries escapes a lot of
people; they see each language as a package. I met a COBOL programmer
recently (I'm not making this up) that was looking into Java. He didn't
see how people could use it, he said, because it had thousands of
commands.

I'll stop whining now.

___
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] Books for advanced Haskell

2010-03-04 Thread Michael Vanier

Matthias Görgens wrote:

A shining example are Dan Piponis blog posts. Not his fault, mind. All I see
is that there is something powerful. I also notice that the big brains
construct monads in many different ways and thus giving them entirely
different capabilities. An example of this is some techniques turn CBV to
CBN or CBL while other techniques null this.



What are CBV, CBN and CBL?

  


CBV = Call By Value, essentially strict evaluation
CBN = Call By Name, essentially lazy evaluation
CBL = I don't know.

-- Mike


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


[Haskell-cafe] references for compiler optimizations for functional languages

2010-03-01 Thread Michael Vanier

Hi everyone,

I'm interested in collecting good references for compiler optimizations 
for functional languages (lazy, strict, statically-typed or not).  Any 
suggestions?


Thanks in advance,

Mike


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


Re: [Haskell-cafe] references for compiler optimizations for functional languages

2010-03-01 Thread Michael Vanier

Awesome!  Thanks, Don!

Mike

Don Stewart wrote:

mvanier42:
  

Hi everyone,

I'm interested in collecting good references for compiler optimizations  
for functional languages (lazy, strict, statically-typed or not).  Any  
suggestions?





There's lots for what GHC implements on SimonPJ's site:

http://www.research.microsoft.com/~simonpj/Papers/inlining/index.htm

http://research.microsoft.com/en-us/um/people/simonpj/papers/cpr/index.htm


http://research.microsoft.com/en-us/um/people/simonpj/papers/usage-types/usage.htm


http://research.microsoft.com/en-us/um/people/simonpj/papers/comp-by-trans-scp.ps.gz


http://research.microsoft.com/en-us/um/people/simonpj/papers/andy-thesis.ps.gz


http://research.microsoft.com/en-us/um/people/simonpj/papers/deforestation-short-cut.ps.Z

http://www.cse.unsw.edu.au/~dons/papers/CLS07.html :)

I've collected many of them here:

http://haskell.org/haskellwiki/Research_papers/Compilation#Compiler_Analyses

-- Don
  


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


Re: [Haskell-cafe] Having a look at XMonad window manager

2010-01-18 Thread Michael Vanier
For a completely different approach, I've had good success running 
xmonad from either Ubuntu minimal (which is a bare-bones version of 
Ubuntu that few people realize exists) or Arch Linux.  In either case 
you have to spend more time setting up the system, but the results IMO 
are worth it.  I don't use gdm but use a customized .xinitrc script 
which I invoke myself through startx.


Mike

John Millikin wrote:

I've been quite happy with Ubuntu's xmonad package, though I run it
within a GNOME session.

Have you tried the instructions on the XMonad wiki for inter-operating
with GNOME? http://www.haskell.org/haskellwiki/Xmonad/Using_xmonad_in_Gnome

On Mon, Jan 18, 2010 at 13:40, michael rice nowg...@yahoo.com wrote:
  

Perhaps. Is there a Linux distro that's more XMonad friendly?

Michael

--- On Mon, 1/18/10, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] Having a look at XMonad window manager
To: michael rice nowg...@yahoo.com
Cc: Don Stewart d...@galois.com, haskell-cafe@haskell.org
Date: Monday, January 18, 2010, 4:26 PM

Oh, is Fedora still using a version of GDM that doesn't let you use a
custom .Xsession (or even remember that you want to use something that
isn't called Gnome)?

michael rice nowg...@yahoo.com writes:



Well, for starters the Fedora entry for installing XMonad is blank/empty:
http://www.haskell.org/haskellwiki/Xmonad/Installing_xmonad#Fedora

Some things I've done:

I set up a .xmonad directory in my home directory with this xmonad.hs

[mich...@localhost ~]$ cat ~/.xmonad/xmonad.hs
--
-- An example, simple ~/.xmonad/xmonad.hs file.
-- It overrides a few basic settings, reusing all the other defaults.
--

import XMonad

main = xmonad $ defaultConfig
{ borderWidth= 2
, terminal   = urxvt
, normalBorderColor  = #cc
, focusedBorderColor = #cd8b00 }

[mich...@localhost ~]$

I set up a .xsession directory in my home directory with this in it

[mich...@localhost ~]$ cat .xsession
export WINDOW_MANAGER=/usr/bin/xmonad
exec gnome-session

[mich...@localhost ~]$

Because supposedly X doesn't even check .xsession file without having 
xorg-x11-xinit-session installed, I also downloaded that.

I set up a XMonad.desktop file in /usr/share/applications directory

[mich...@localhost ~]$ cat /usr/share/applications/Xmonad.desktop
[Desktop Entry]
Type=Application
Encoding=UTF-8
Name=Xmonad
# change this path according to your xmonad binary
Exec=/usr/bin/xmonad
NoDisplay=true
X-GNOME-WMName=Xmonad
X-GNOME-Bugzilla-Bugzilla=XMonad
X-GNOME-Bugzilla-Product=xmonad
X-GNOME-Bugzilla-Component=general
X-GNOME-Autostart-Phase=WindowManager
X-GNOME-Provides=windowmanager
X-GNOME-Autostart-Notify=true
[mich...@localhost ~]$

I added /usr/bin/xmonad to startup applications.

All these things were suggested.

Michael

--- On Mon, 1/18/10, Don Stewart d...@galois.com wrote:

From: Don Stewart d...@galois.com
Subject: Re: [Haskell-cafe] Having a look at XMonad window manager
To: michael rice nowg...@yahoo.com
Cc: Ivan Lazar Miljenovic ivan.miljeno...@gmail.com, 
haskell-cafe@haskell.org
Date: Monday, January 18, 2010, 3:30 PM

nowgate:
  

I'd already found a lot of these links and tried some of their suggestions,
without any success. Does anyone who posts here actually use it (what
platform)?


What's the problem exactly?

-- Don




  

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com


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



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


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


Re: [Haskell-cafe] Lisp like symbols in haskell

2009-12-08 Thread Michael Vanier

jean-christophe mincke wrote:

Hello,

Has there already been attempts to introduce lisp like symbols in haskell?


Thank you

Regards

J-C



J-C,

Do you mean symbols as in interned strings with an O(1) string 
comparison method?  I would love to have those, but I don't see an easy 
way to get it without being in the IO or ST monad.


Mike


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


Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2009-10-31 Thread Michael Vanier

Gregory Collins wrote:

Tom Davie tom.da...@gmail.com writes:

  

On 10/31/09, Magicloud Magiclouds magicloud.magiclo...@gmail.com wrote:


After all, I never think OO as an oppsite way to all other things. The
idea is so general that if you say I cannot use it in Haskell at all,
that would make me feel weird. The only difference between languages
is, some are easy to be in OO style, some are not.
  

Wow, someone drank the cool aid!



Doing OO-style programming in Haskell is difficult and unnatural, it's
true (although technically speaking it is possible). That said, nobody's
yet to present a convincing argument to me why Java gets a free pass for
lacking closures and typeclasses.

G.
  
Because most programmers have never heard of closures and typeclasses, 
and thus have no idea how useful they are? :-(


BTW using existential types in Haskell you can mimic OO to a pretty 
decent degree, at least as far as interfaces are concerned.


Mike


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


[Haskell-cafe] How do I fix this error message?

2009-09-04 Thread Michael Vanier

Hi everyone,

I ran into this error when recompiling some code I hadn't worked on in a 
while:


Foo.hs:19:7:
   Could not find module `Control.Monad.Error':
 it was found in multiple packages: monads-fd-0.0.0.1 mtl-1.1.0.2

I gather that monads-fd is supposed to be a replacement for mtl, but I 
have both of them (mtl from the normal GHC 6.10.4 install, monads-fd 
from cabal).  I don't really care which one I use, though mtl has been 
fine in the past.  In the past, I had to manually uninstall cabal 
packages that used incompatible libraries.  Is this still the case?


TIA,

Mike


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


Re: [Haskell-cafe] Haskell's type system compared to CLOS

2009-08-11 Thread Michael Vanier

Matthias-Christian Ott wrote:

Hi,
usually I'm sceptical of programming languages which are not based
on the von Neumann architecture, but recently I got interested in
functional programming languages.

The arrogance of lots of Haskell users, who made me feel that using a
programming language other than Haskell is a waste of time, combined
with vanguard mathematical notation has been very attractive to me
and I have decided to get at least an idea of Haskell and its concepts.

Some weeks ago I learned programming in Dylan and was impressed by its
object system which is basically a stripped version of CLOS. Multiple
dispatch together with a well-thought-out object system is quite
powerful, because it removes the burden of including methods in the
class definition.

At the moment I'm reading the Functional Programming using Standard
ML and I'm in the chapter on data types.

This afternoon it occurred to me that classes and data types are
symmetric. In a class hierarchy you start an abstract super class
(the most abstract is the class object in some languages) and further
specialise them via inheritance; with data types you can start with
specialized versions and abstract them via constructors (I'm not sure
how message sending to a superclass looks like in this analogy).

Anyhow, I also came across an interesting presentation. Andreas Löh
and Ralf Hinze state in their presentation Open data types and open
functions [1]:

* OO languages support extension of data, but not of functionality.
* FP languages support extension of functionality, but not of data.

Their first point refers to the fact that in most object-oriented
languages don't allow the separate definition of classes and their
respective methods. So to add new functions, you have edit the class
definitions.

However, in functional programming languages you can easily add new
functionality via pattern matching, but have to either introduce new
types or new constructors, which again means to modify existing code.

In Dylan (and in Common Lisp) you define methods separate from classes
and have pattern matching based on types. This solves all mentioned
problems.

So my question is, how are algebraic data types in Haskell superior to
CLOS (despite the fact that CLOS is impure)? How do both compare?

What has Haskell to provide what Common Lisp and Dylan haven't?

Thanks!

Regards,
Matthias-Christian


  

Type classes.

Mike



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


Re: [Haskell-cafe] RE: Haskell as a first language?

2009-07-14 Thread Michael Vanier

Simon Peyton-Jones wrote:

Haskell is a great language!  Check out haskell.org.   I'm ccing the Haskell 
Cafe which is read by many people better qualified to answer your question than 
me.   (Since I've been working on Haskell for many years, I am not well 
qualified to say how it seems to a beginner.)

S

| -Original Message-
| From: Charles Turner [mailto:charlie.h.tur...@googlemail.com]
| Sent: 11 July 2009 22:52
| To: Simon Peyton-Jones
| Subject: Haskell as a first language?
| 
| I'll make this short! Do you think Haskell is a good language to start

| with? I am brand new to programming and have been using Scheme, some of
| my peers suggest I should use Haskell. It seems professional to me.
| Has features that a beginner should not worry about. What would you
| suggest. (I'm not worried about bias)
| 
| Thank you very much for your time.
| 
| Charles Turner.


  

Charles,

Haskell is a wonderful language (my favorite language by far) but it is 
pretty difficult for a beginner.  In fact, it is pretty difficult for 
anyone to learn in my experience, because it has so many advanced 
concepts that simply don't exist in other languages, and trying to 
absorb them all at once will likely be overwhelming.  My path into 
Haskell was roughly C - Python - Scheme - Ocaml - Haskell, and I 
think that this has a lot going for it (though for a beginner I would 
recommend Python over Haskell, and Scheme is suitable for beginners with 
the right textbooks, e.g. How To Design Programs and/or Structure and 
Interpretation of Computer Programs).  If you're willing to work really 
hard, and don't mind that it may take you quite a bit longer before you 
are creating real applications in Haskell than it would in e.g. Python, 
you can start with Haskell (check out the book Real World Haskell: 
http://realworldhaskell.org).  But if you get frustrated, feel free to 
shift down the list I gave.  Scheme or Ocaml are good languages to learn 
the basics of functional programming, and then you just have to add on 
the Haskell-specific material (of which there is a lot).  Haskell is 
kind of like a point in the language space that programmers evolve towards.


Mike


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


[Haskell-cafe] Documentation bug -- building ghc from darcs sources

2009-06-12 Thread Michael Vanier
I've been trying to build ghc head from the darcs repo using these 
instructions:


http://hackage.haskell.org/trac/ghc/wiki/Building/GettingTheSources

Unfortunately, when I do

./darcs-all --extra get

as described under Getting more packages it fails because the 
darcs-all script doesn't recognize the --extra option.  Was this removed 
recently, and if so, how do I achieve the same effect?


TIA,

Mike


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


Re: [Haskell-cafe] help with a question

2009-06-09 Thread Michael Vanier

haonan21 wrote:

I'm very new to haskell hugs and would appreciate it if someone could help me
out here. I've been giving 2 questions. 


1.) A and B are two sets of integers. Implement a function to obtain the
integers that belong to both sets.
Test your function fully.

2.) Define and test a function f, which, if A is a set of {x, y, z} then
f(A) = {{},{x}, {y}, {z}, {x, y}, {x,z}, {y,z}, {x, y, z}}

Manage to get the first one.
interset::[Int]-[Int]-[Int]

interset x [] = []

interset [] y = []

interset x@(xs:xt) y@(ys:yt) =
 if xs == ys
 then as:(interset at yt)
 else interset at y

Totally have no clue for the 2nd question. could someone help me out ? 


Many thanks!
  

Haonan,

This looks like homework, but I can offer a few suggestions.  Your 
interset function uses as and at where I think you mean xs and 
xt and the else case is wrong (you need to test the code!).  Anyway, 
it looks like you're assuming that the lists are in ascending order, and 
I don't see that in the problem specification -- it won't work if that 
isn't the case.  More interestingly, you should look at the List (or 
Data.List) library; it contains a library function which can solve your 
problem in one line.  As for the second function, that's a classic 
problem used for teaching recursion: find all subsets of a given list.  
The way to solve it is to first ask what the solution is for the empty 
set (which should be obvious).  Then assume that you have the solution 
for the tail of the list ({y, z}).  How would you use this and the head 
of the list (x) to generate the full solution?


HTH,

Mike



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


[Haskell-cafe] name for monad-like structure?

2009-04-28 Thread Michael Vanier
I've stumbled upon a structure that is like a weaker version of a monad, 
one that supports return and  but not =.  Has anyone seen this 
before, and if so, does it have a standard name?


Mike


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


Re: [Haskell-cafe] name for monad-like structure?

2009-04-28 Thread Michael Vanier

Tony Morris wrote:

Michael Vanier wrote:
  

I've stumbled upon a structure that is like a weaker version of a
monad, one that supports return and  but not =.  Has anyone seen
this before, and if so, does it have a standard name?

Mike


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



Are you sure it supports
() :: m a - m b - m b

and not
mplus :: m a - m a - m a ?

  
Yeah, you're right.  It's basically a monad where the type a is fixed to 
be (), so you just have


() :: m () - m () - m ()

Mike


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


Re: [Haskell-cafe] name for monad-like structure?

2009-04-28 Thread Michael Vanier

Luke Palmer wrote:
On Tue, Apr 28, 2009 at 5:33 PM, Michael Vanier mvanie...@gmail.com 
mailto:mvanie...@gmail.com wrote:


Tony Morris wrote:

Michael Vanier wrote:
  

I've stumbled upon a structure that is like a weaker version of a
monad, one that supports return and  but not =.  Has anyone seen
this before, and if so, does it have a standard name?

Mike


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



Are you sure it supports
() :: m a - m b - m b

and not
mplus :: m a - m a - m a ?

  

Yeah, you're right.  It's basically a monad where the type a is
fixed to be (), so you just have

() :: m () - m () - m ()


That's a monoid.

Luke


Got it.  Thanks.

Mike


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


[Haskell-cafe] using Typeable with STRefs

2009-03-16 Thread Michael Vanier

Hi,

I'm having a problem using Typeable with STRefs.  Basically, I want to 
store STRefs (among other things) in a universal type.  STRef is an 
instance of Typeable2, which means that STRef s a is Typeable if s and a 
are both Typeable.  The problem is that the state type s is opaque and I 
can see no way to make it Typeable (other than making it RealWorld, and 
I don't want to use IO for this).  If this is the case, then AFAICT 
there is no point in having STRefs be instances of Typeable2.  Am I 
missing something?


Here's the code I'd like to write:

import Data.Typeable
import Data.STRef
import Control.Monad.ST

data Value = forall a . Typeable a = V a
 deriving Typeable

getValue :: Typeable a = Value - Maybe a
getValue (V v) = cast v

-- I need the Typeable s constraint for the code to compile, but I'd 
rather leave it out.

test :: Typeable s = ST s Integer
test = do ref - newSTRef (10 :: Integer)
 let refVal = V ref
 case getValue refVal of
   Nothing - error BAD
   Just r - readSTRef r

-- This doesn't compile, because s is not Typeable.   
test2 :: Integer

test2 = runST test

Thanks in advance,

Mike



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


Re: [Haskell-cafe] using Typeable with STRefs

2009-03-16 Thread Michael Vanier

Ryan,

So, if I understand you correctly, my only option is to use an IORef 
instead of an STRef?  What I'm trying to do is implement a mutable box 
type as part of a dynamically-typed language I'm implementing in Haskell 
(which is mainly an exercise to improve my Haskell programming; mission 
accomplished).  It bothers me that I have to use an IORef for this, 
since I don't see what this has to do with I/O.  Similarly, if I wanted 
to have a mutable array type, I couldn't use STArray; I'd have to use 
IOArray.  Or, I suppose I could define a richer Value type that had 
extra constructors for stateful types.


Mike

Ryan Ingram wrote:

Having the state be an instance of Typeable breaks the purity
guarantees of runST; a reference could escape runST:

  let v = runST (V `liftM` newSTRef 0)
  in runST (readSTRef $ fromJust $ getValue v)

Keep in mind that the state actually used by runST is RealWorld;
runST is just a pretty name for unsafePerformIO.  So the state types
are actually the same, and the cast would succeed.

  -- ryan

On Mon, Mar 16, 2009 at 5:48 PM, Michael Vanier mvanie...@gmail.com wrote:
  

Hi,

I'm having a problem using Typeable with STRefs.  Basically, I want to store
STRefs (among other things) in a universal type.  STRef is an instance of
Typeable2, which means that STRef s a is Typeable if s and a are both
Typeable.  The problem is that the state type s is opaque and I can see no
way to make it Typeable (other than making it RealWorld, and I don't want to
use IO for this).  If this is the case, then AFAICT there is no point in
having STRefs be instances of Typeable2.  Am I missing something?

Here's the code I'd like to write:

import Data.Typeable
import Data.STRef
import Control.Monad.ST

data Value = forall a . Typeable a = V a
 deriving Typeable

getValue :: Typeable a = Value - Maybe a
getValue (V v) = cast v

-- I need the Typeable s constraint for the code to compile, but I'd rather
leave it out.
test :: Typeable s = ST s Integer
test = do ref - newSTRef (10 :: Integer)
let refVal = V ref
case getValue refVal of
  Nothing - error BAD
  Just r - readSTRef r

-- This doesn't compile, because s is not Typeable.   test2 :: Integer
test2 = runST test

Thanks in advance,

Mike



___
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] Interesting critique of OCaml

2008-05-08 Thread Michael Vanier

Actually, it's (+) for ints and (+.) for floats.  Which kind of proves your 
point.

Mike

Tim Docker wrote:

| An interesting critique of OCaml.
| 
| http://enfranchisedmind.com/blog/2008/05/07/why-ocaml-sucks/


Interesting to me is that my pet ocaml peeve is not there: namely the
lack of convenient operator overloading. Admittedly I only used ocaml
for 6 months, but I never adapted to needing to write (+) for ints, and
(.+) for floats.


From the F# documentation it would appear that F# does have overloaded

numerical operators, at least. I'm not sure how these fit into its type
system however. (Their type is documented as overloaded).

Tim 


___
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] Why functional programming matters

2008-01-23 Thread Michael Vanier

This is pure general waffle, but I saw the following comment on reddit.com 
which impressed me:

C isn't hard; programming in C is hard. On the other hand: Haskell is hard,
but programming in Haskell is easy.

Mike

Simon Peyton-Jones wrote:

Friends

Over the next few months I'm giving two or three talks to groups of *non* functional 
programmers about why functional programming is interesting and important.  If you like, 
it's the same general goal as John Hughes's famous paper Why functional programming 
matters.

Audience: some are technical managers, some are professional programmers; but 
my base assumption is that none already know anything much about functional 
programming.

Now, I can easily rant on about the glories of functional programming, but I'm a biased 
witness -- I've been doing this stuff too long.  So this message is ask your help, 
especially if you are someone who has a somewhat-recent recollection of realising 
wow, this fp stuff is so cool/useful/powerful/etc.

I'm going to say some general things, of course, about purity and effects, modularity, 
types, testing, reasoning, parallelism and so on. But I hate general waffle, so I want to 
give concrete evidence, and that is what I particularly want your help with.  I'm 
thinking of two sorts of evidence:


1. Small examples of actual code. The goal here is (a) to convey a visceral 
idea of what functional programming *is*, rather than just assume the audience 
knows (they don't), and (b) to convey an idea of why it might be good.  One of 
my favourite examples is quicksort, for reasons explained here: 
http://haskell.org/haskellwiki/Introduction#What.27s_good_about_functional_programming.3F

But I'm sure that you each have a personal favourite or two. Would you like to 
send them to me, along with a paragraph or two about why you found it 
compelling?  For this purpose, a dozen lines of code or so is probably a 
maximum.


2. War stories from real life.  eg In company X in 2004 they rewrote their 
application in Haskell/Caml with result Y.  Again, for my purpose I can't tell very 
long stories; but your message can give a bit more detail than one might actually give in 
a presentation.  The more concrete and specific, the better.  E.g. what, exactly, about 
using a functional language made it a win for you?


If you just reply to me, with evidence of either kind, I'll glue it together 
(regardless of whether I find I can use it in my talks), and put the result on 
a Wiki page somewhere.  In both cases pointers to blog entries are fine.

Quite a lot of this is FP-ish rather than Haskell-ish, but I'm consulting the 
Haskell mailing lists first because I think you'll give me plenty to go on; and 
because at least one of the talks *is* Haskell-specific.  However, feel free to 
reply in F# or Caml if that's easier for you.

Thanks!

Simon
___
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] New slogan for haskell.org

2007-12-12 Thread Michael Vanier

Bayley, Alistair wrote:
From: [EMAIL PROTECTED] 
[mailto:[EMAIL PROTECTED] On Behalf Of Derek Elkins



  

(Not directed at gwern in particular)

I have a better idea.  Let's decide to do nothing.  The 
benefits of this

approach are: 1) it takes zero effort to implement, 2) the number of
people who immediately give up on Haskell from reading that is, I
suspect, neglible (actually I suspect it is zero; I think the 
number of
people who actually read that at all is probably negligible), 
and 3) it
accomplishes the same end as debating endlessly while 
creating much less

list traffic.




Should we set up a haskell-marketing mailing list for people who still
have some passion (or merely stamina) for the discussion? Or is there a
lighter-weight way to take the discussion off-list/to another list?

Alistair
  


This is a great idea!  Other languages have advocacy mailing lists 
and/or newsgroups.  I think Haskell should have one too.  I know if 
there was one I'd be the first person not to subscribe ;-)


Mike, bored of these endless debates


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


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Michael Vanier
I haven't been following this thread closely, but would it be rude to suggest that someone who 
doesn't want to put the effort into learning the (admittedly difficult) concepts that Haskell 
embodies shouldn't be using the language?  Haskell was never intended to be The Next Big Popular 
Language.  It was intended to be a purely functional language for people who want to use purely 
functional languages and who are willing to learn new concepts if it enables them to program in that 
 style.  That now includes IO and monads, so if people aren't willing to learn that, they should go 
on using python or whatever.  That said, of course we should strive to have better teaching 
materials, but there are a number of good IO/monad tutorials on the web.


I used to love programming in python, but then I learned Scheme, then Ocaml, and then Haskell and at 
each stage I absorbed a few new concepts.  Now programming in python feels very primitive to me. 
Haskell is interesting because it enables us to write programs more effectively (in many cases, at 
least) than we can in other languages, but the learning curve is steep -- there ain't no such thing 
as a free lunch.


Mike

David Menendez wrote:
On Dec 10, 2007 1:44 PM, Dan Piponi [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


When someone comes to me and says I have this Python script that
scans through these directories and finds the files that meet these
criteria and generates a report based on this template, could I do it
better in Haskell? it'd be good to have a better answer than to do
this you could use the IO monad, but to do things properly you need to
understand monads so here, learn about the List monad and the Maybe
monad first, understand how this interface abstracts from both, come
back when you've finished that, and then I'll tell you how to read and
write files. 



I thought your blog post about the IO monad for people who don't care 
about monads (yet) was a pretty good start.


As it happens, the IO monad was one of the things that attracted me to 
Haskell. When I was learning SML in college, I wondered how one could do 
I/O in a functional style. SML provides I/O via functions with 
side-effects, which struck me as crude and contrary to the functional 
style.


Years later, I encountered Haskell and learned that it handled I/O tasks 
using something called the IO monad. I had no idea what a monad was, 
but I understood the implications: Haskell could be referentially 
transparent *and* do I/O. This was what inspired me to learn the language.


As I learned more Haskell, I discovered the other monads and the Monad 
class and the full generality of the do notation. Eventually, a light 
came on and monads suddenly made sense.


I don't know if it's best to learn the IO monad before or after other 
monads. I suspect no choice is right for everyone. An experienced 
programmer who is new to Haskell is going to have different questions 
than a beginning programmer with no preconceived notions.


--
Dave Menendez [EMAIL PROTECTED] mailto:[EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/ http://www.eyrie.org/~zednenem/




___
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] Somewhat random history question - chicken and egg

2007-11-11 Thread Michael Vanier



Bernie Pope wrote:


On 12/11/2007, at 4:32 AM, Neil Mitchell wrote:


Hi


bear no resemblence to any machine-level constructs, and it seems
unthinkable that you could possibly write such a compiler in anything
but Haskell itself.



Hugs is written in C.



Really? :-.


Really :-)


(Seriously, how big is Hugs? It must be quite large...)


56111 lines, with an additional 5917 for the WinHugs bit.


If I remember correctly, the early versions of the Clean compiler were 
written in C. Then at some stage they re-wrote it in Clean.


Cheers,
Bernie.



You could say they cleaned it up.

Mike

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


Re: [Haskell-cafe] Somewhat random history question - chicken and egg

2007-11-11 Thread Michael Vanier

I have a copy of COBOL for Dummies which I bought as a joke and have never 
dared read.

Mike

[EMAIL PROTECTED] wrote:

Andrew Coppin writes:

Brent Yorgey wrote:


Expressiveness certainly makes it easier, but nothing (other than
sanity...) stops you from writing a Haskell compiler in, say, COBOL.

*I* would stop you.  Friends don't let friends write in COBOL.


That's the funniest thing I've read today. You literally just woke my 
mum up by making my laugh. Thanks! :-D


I would be the last who wanted to spoil such a good joke.
But... tell me please, ANYONE, who takes part in this inspiring exchange:
How many COBOL programs have you written in your life?
How many programs in Cobol have you actually SEEN?
Jerzy Karczmarczuk

___
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] hoogle broken?

2007-11-06 Thread Michael Vanier

It looks as if hoogle isn't working.  I get 404s whenever I try to do any 
search on hoogle.

Mike

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


[Haskell-cafe] question about throwDyn

2007-10-11 Thread Michael Vanier

In ghci, why does

  throw $ ArithException DivideByZero

print

  *** Exception: divide by zero

while

  throwDyn $ ArithException DivideByZero

print

  *** Exception: (unknown)

?

Mike

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


[Haskell-cafe] symbol type?

2007-10-10 Thread Michael Vanier
Is there an implementation of a symbol type in Haskell i.e. a string which has a constant-time 
comparison operation?


Mike

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


Re: [Haskell-cafe] symbol type?

2007-10-10 Thread Michael Vanier
I'm thinking of a symbol type that can be used for a compiler, so a simple algebraic data type 
wouldn't work.  Unfortunately the GHC datatype isn't part of the GHC haskell libraries AFAICT.


Mike

Yitzchak Gale wrote:

Michael Vanier wrote:

Is there an implementation of a symbol type in Haskell i.e. a string which
has a constant-time comparison operation?


Stefan O'Rear wrote:

Yes, I beleive GHC uses one (utils/FastString.lhs iirs)


In some cases where you would need that in other languages,
you would use an algebraic data type in Haskell, e.g.:

data Color = Red | Orange | Yellow | Green | Blue | Purple
  deriving (Eq, Show)

-Yitz

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


Re: [Haskell-cafe] symbol type?

2007-10-10 Thread Michael Vanier

Hmm, I was hoping for something that didn't involve side effects.

Mike

Yitzchak Gale wrote:

Michael Vanier wrote:

I'm thinking of a symbol type that can be used
for a compiler...


Ah. Perhaps Data.HashTable is what you are looking
for then?

-Yitz

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


Re: [Haskell-cafe] New slogan for haskell.org

2007-10-10 Thread Michael Vanier

I haven't been following this discussion closely, but here's an idea: use 
reverse psychology.

Haskell -- You're probably not smart enough to understand it.

Nothing like appealing to people's machismo to get them interested.

Mike


Seth Gordon wrote:


Aha!  Instead of the lambda surrounded by mathematical stuff as the 
haskell.org logo, we need a picture of a medicine bottle.


Haskell.  Fewer headaches.  No side effects.


Alternatively, a picture of a red pill with an embossed lambda...
___
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] Clarification Please

2007-09-13 Thread Michael Vanier
Define a merge function that merges two sorted lists into a sorted list containing all the elements 
of the two lists.  Then define the msort function, which will be recursive.


Mike

PR Stanley wrote:

Hi
Taken from chapter 6, section 8 of the Hutton book on programming in 
Haskell:

5. Using merge, define a recursive function
msort :: (Ord a) = [a] - [a]
that implements merge sort, in which the empty list and singleton lists 
are already sorted, and any other list is sorted by merging together the 
two lists that result from sorting the two halves of the list separately. :

Hint: first define a function
¬halve :: [a] - [([a], [a])]
¬that splits a list into two halves whose length differs by at most one.

Create a halve function - okay, that's fairly straightforward. The 
rest, I'm afraid, is a little obscure. I'm not looking for the solution; 
I'd like to work that out for meself. However, I'd  really appreciate 
some clues as to the general structure of the algorithm.

Much obliged,
Paul

___
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] Clarification Please

2007-09-13 Thread Michael Vanier
OK, you have the split function, and you have the merge function, and now you have to define the 
msort function.  First write down the base cases (there are two, as you mention), which should be 
obvious.  Then consider the remaining case.  Let's say you split the list into two parts.  Then what 
would you do?


Mike

PR Stanley wrote:
I'm not sure. We start with one list and also, perhaps I should have 
mentioned that I have a merge function which takes two sorted lists with 
similar, now, what do they call it, similar orientation? and merges them 
into one sorted list.

e.g. merge [1, 4,] [2, 3]
[1,2,3,4]
Cheers, Paul
At 04:02 14/09/2007, you wrote:
Define a merge function that merges two sorted lists into a sorted 
list containing all the elements of the two lists.  Then define the 
msort function, which will be recursive.


Mike

PR Stanley wrote:

Hi
Taken from chapter 6, section 8 of the Hutton book on programming in 
Haskell:

5. Using merge, define a recursive function
msort :: (Ord a) = [a] - [a]
that implements merge sort, in which the empty list and singleton 
lists are already sorted, and any other list is sorted by merging 
together the two lists that result from sorting the two halves of the 
list separately. :

Hint: first define a function
¬halve :: [a] - [([a], [a])]
¬that splits a list into two halves whose length differs by at most one.
Create a halve function - okay, that's fairly straightforward. 
The rest, I'm afraid, is a little obscure. I'm not looking for the 
solution; I'd like to work that out for meself. However, I'd  really 
appreciate some clues as to the general structure of the algorithm.

Much obliged,
Paul
___
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] Custom unary operator extension?

2007-09-10 Thread Michael Vanier
APL is fairly obsolete now anyway.  A more modern version of that language is J (www.jsoftware.com), 
which does not use special characters.  I've studied the language a bit, and it's quite interesting, 
but it really doesn't offer much (anything?) over Haskell except a much terser notation and simpler 
mutable array support.  I'd stick to Haskell.


Mike

Peter Verswyvelen wrote:
Nice. Thanks for the info, but the symbolic notation is not the only 
reason for using Haskell, it's also to force them into solving simple 
problems without using mutable variables, so they see this alternative 
functional programming approach BEFORE they are specialist in C++, 
because then they will be in the blob zone ;-) Maybe APL is also a 
functional language, but unfortunately I don't have the time to switch 
to another language anymore. Besides, I'm addicted to Haskell now ;-)


Henning Thielemann:
I have read about APL that it uses a special character set in order to 
get a more mathematical looking notation. Maybe your students should 
check out this language?



___
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] Elevator pitch for Haskell.

2007-09-04 Thread Michael Vanier
It's very nice, but I would say that anyone who needs an elevator pitch shouldn't be using or 
working with Haskell.  Haskell is for people who already get it.  I've had job offers from people 
just because they knew I _liked_ Haskell, even though they weren't asking me to use it for the job.


OTOH, something like this might be useful for pitching Haskell to students, which is where the real 
growth opportunities are (minds not yet closed).


Mike

Paul Johnson wrote:
This page (http://www.npdbd.umn.edu/deliver/elevator.html) has a 
template for an elevator pitch.  This is what you say to someone when 
you have 30 seconds to explain your big idea, for instance if you find 
yourself in an elevator with them.  I thought I'd try instantiating it 
for Haskell.


For software developers who need to produce highly reliable software at 
minimum cost, Haskell is a pure functional programming language that 
reduces line count by 75% through reusable higher order functions and 
detects latent defects with its powerful static type system.  Unlike Ada 
and Java, Haskell allows reusable functions to be combined without the 
overhead of class definitions and inheritance, and its type system 
prevents the hidden side effects that cause many bugs in programs 
written in conventional languages.


Comments?

Paul.

___
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] Elevator pitch for Haskell.

2007-09-04 Thread Michael Vanier

Awesome!

I'm reminded of the IRC post that said that Haskell is bad, it makes you hate other 
languages.

Mike

Dan Weston wrote:

And here's my guide for public health officials...

WARNING: Learning Haskell is dangerous to your health!

Disguised as a fully-functional programming language, Haskell is 
actually a front for a working math-lab, supported by a cult of 
volunteers seeking to ensnare weak-headed but normal programmers 
susceptible to the dogma that laziness is a virtue.


Though cut with syntactic sugar to be more palatable to newbies, each 
Haskell construct is in fact a contagious mix of higher-order functions, 
lambda expressions, and partial applications, a highly addictive gateway 
drug to category theory, initial algebras, and greco-morphisms.


Some users have gotten trapped inside an IO monad unable to get out 
safely, and even gone mad trying to decipher commutative diagrams or 
perfect their own monad tutorial. Signs of addiction include prefixing 
co- to random words or needlessly replacing recursive functions with 
combinators and pointfree notation. The least fixed point of this 
unnatural transformation is the inability to find joy in the use of 
imperative programming languages. In some cases, hackage is irreversible 
and can lead to uncontrolled blogging.


Further study is needed to understand the strong correlation between 
intelligence and Haskell addiction. Meanwhile, those at risk should be 
made to program in teams to suppress their creative drive.


Dan Weston

Paul Johnson wrote:
This page (http://www.npdbd.umn.edu/deliver/elevator.html) has a 
template for an elevator pitch.  This is what you say to someone 
when you have 30 seconds to explain your big idea, for instance if you 
find yourself in an elevator with them.  I thought I'd try 
instantiating it for Haskell.


For software developers who need to produce highly reliable software 
at minimum cost, Haskell is a pure functional programming language 
that reduces line count by 75% through reusable higher order functions 
and detects latent defects with its powerful static type system.  
Unlike Ada and Java, Haskell allows reusable functions to be combined 
without the overhead of class definitions and inheritance, and its 
type system prevents the hidden side effects that cause many bugs in 
programs written in conventional languages.


Comments?

Paul.

___
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] help understanding lazy evaluation

2007-08-22 Thread Michael Vanier

Xavier,

First off, we don't put the () after function names in Haskell.

What's happening is this (experts please correct any mistakes here):

1) You call prime on a number (e.g. 42).

2) In order to evaluate this further, (factors 42) must be evaluated at least
partially to give input to == in prime.  So (factors 42) is evaluated to give 
the first list value,
which is 1.

3) The == in prime compares the 1 at the head of the list generated by (factors 
42) (whose tail
hasn't been evaluated yet) with the 1 at the head of [1, 42], and finds that 
they match, so == can
continue processing.

4) (factors 42) resumes to compute another list value, which is 2 (a factor of 
42).

5) == in prime compares 2 with 42, finds they don't match, and thus (primes 42) 
returns False.

So not all the factors have been computed; in fact, only two of them were 
needed to prove that 42 is
not prime.  The interesting aspect of all this is that laziness allowed us to 
modularize the problem
of primality testing into two separate (simpler) functions, instead of having 
to interleave
generation of factors and testing of factors.  This makes code easier to write 
and more modular.
Hughes' paper Why Functional Programming Matters is a must-read for more on 
this.

Lazy evaluation can be very tricky to wrap your head around, and there are lots 
of subtle issues
that crop up where you think something is lazy but it's not, or you think 
something is strict but
it's not.  There are ways to force lazy/strict behavior, but they're somewhat 
more advanced.

HTH,

Mike


Xavier Noria wrote:
I am learning Haskell with Programming in Haskell (an excellent book 
BTW).


I have background in several languages but none of them has lazy 
evaluation. By now I am getting along with the intuitive idea that 
things are not evaluated until needed, but there's an example I don't 
understand (which means the intuitive idea needs some revision :-).


We have factors(), defined on page 39 like this[*]:

  factors :: Int - [Int]
  factors n = [x | x - [1..n], n `mod` x == 0]

and we base prime() on it this way:

  prime :: Int - Bool
  prime n = factors n == [1, n]

Now, the books says prime does not necessarily compute all of the 
factors of n because of lazy evaluation. Meaning that if n is composite 
as soon as some non-trivial divisor appears we halt computation and 
return False.


My vague intuition said we either need factors or we don't, we do 
because we need to perform the test, so we compute it. That's wrong, so 
a posteriori the explanation must be something like this:


1. someone knows we want factor() to perform an equality test

2. someone knows an equality test between lists is False as soon as we 
have a mismatch, left to right


3. thus, instead of evaluating factors completely we are going to build 
sublists of the result and perform the tests on those ones against [1, n].


That's a lot of *context* about that particular evaluation of factors, 
in particular step puzzles me. Can anyone explain how lazy evaluation 
fits there? I suspect the key is the implementation of == together with 
the fact that list comprehensions are lazy themselves, is that right?


-- fxn

[*] Which notation do you use for functions in text? is f() ok?

___
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] Why monad tutorials don't work

2007-08-14 Thread Michael Vanier

snark
As you know, an arrow tutorial is like a wrapper around a monad tutorial, sort of like a container 
around it that can do extra actions with sufficient lifting.  The appropriate higher-order function 
to convert monad tutorials to arrow tutorials will be left as an exercise to the reader.

/snark

I'm becoming more and more convinced that metaphors for monads do more harm than good.  From now on 
I'm going to describe monads as purely abstract entities that obey certain laws, and that _in 
certain instances_ can be viewed to be like containers, or actions, or donuts, or whatever.  In 
other words, a monad is an abstract thing that can generate things that we can metaphorize, but it's 
pointless (point-free?) to try to capture the entire concept in a single metaphor.  I'm reminded of 
a physics teacher who was having a similar problem explaining the concept of tensors, until he said 
that a tensor is something that transforms like a tensor does!.  So a monad is something that 
behaves like a monad does.


Mike (who obviously hasn't had nearly enough coffee today)

Dougal Stanton wrote:

On 14/08/07, Dan Weston [EMAIL PROTECTED] wrote:

[snips another metaphor for monadic programming]

No offence to Dan, whose post I enjoyed. The concept of wrapping is as
close a metaphor as we seem to get without disagreements. But this has
brought me to a realisation, after Paul Erdos:

The Haskell community is a machine for converting coffee to monad tutorials.

In the spirit of the venture, I will now suggest that someone points
out that they don't like coffee, and that I haven't allowed for arrow
tutorials ;-)

Cheers,

D.
___
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] Explaining monads

2007-08-14 Thread Michael Vanier
For what it's worth, the nature of Haskell is such that you do (at least currently) have to spend a 
lot of time reading research papers to understand what's going on.  Maybe that will change sometime, 
but probably not soon.  This ties in to the open-endedness of Haskell; I sometimes think that really 
understanding all of Haskell is like really understanding all of mathematics.  This is frustrating, 
but it's also what makes the language so rewarding.  I guess what I'm saying is: get used to it, 
it's not so bad.


Mike

Derek Elkins wrote:

On Tue, 2007-08-14 at 12:40 -0500, Lanny Ripple wrote:

Derek Elkins wrote:

What people need to do is stop reading two page blog posts by someone
who's just got monads and read the well-written peer-reviewed papers
I have taught many people to program in group settings and 
individually in my career.  I have referred them to many 
tutorials.  I have used many examples from tutorials I thought 
were useful.  I can't recall a single time I've ever turned to a 
beginner and said, And you really should brush up on the 
peer-reviewed papers to learn this part.


How about a book?  You've never recommended a book?  But even so, where
did I say tutorial?  The -are- good monad tutorials, they are just
horribly out-weighed by bad ones.  Further, having a tutorial as
supplement to person-to-person education is totally different from
trying to learn purely from tutorials.  Also, what is wrong with papers
or recommending them?  Finally, how often have you been part of a
community where the primary mode of documentation is a research paper...


by the people who clearly know what they are talking about.  Luckily,
for monads applied to Haskell we have Wadler, a witty, enjoyable and
clear writer/speaker.  All of Wadler's monad introductions are
readable by anyone with a basic grasp of Haskell.  You certainly don't
need to be even remotely an academic to understand them.  I'm willing to
bet that many people who say they don't understand monads and have read
every tutorial about them haven't read -any- of Wadler's papers.



I'm confused.  Are you praising Wadler or bashing the tutorials 
(or both)?  *I* was carping about the tutorials (and even 
mentioned that Wadler was my breakthrough) so I suspect we are in 
violent agreement.


I'm praising Wadler and bashing the good majority of monad tutorials,
but not all of them.  Mostly I'm pointing out an unreasonable aversion
to reading papers, as if a paper couldn't possibly be understandable.

___
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] Haskell vs GC'd imperative languages, threading, parallelizeability (is that a word? :-D )

2007-08-10 Thread Michael Vanier

Hugh Perkins wrote:


I'm not trolling, despite strong appearances to the contrary ;-)  My 
primary objective/goal is to find a way to make threading easy.  Thread 
management today is like memory management in the early 90s.  We kindof 
had tools (new, delete in C++ for example) to do it.  At some point we 
started to use things like Smart Pointers to make it easier, but none of 
it really worked.  Issues such as circular referential loops caused this 
not to work very well.


At some point, someone came out with the idea of a garbage collector, 
which is really very simple once you know: all it does is walk the graph 
of variables, starting with those we know are definitely used, and 
delete all those objects that didnt get walked on.  Simple, easy, magic.


We should do the same thing for threads.  Threading is going to become a 
major issue soon, maybe not tomorrow, but there is a GPL'd Niagara 2 out 
with 64 threads (I think?), so the time is now.


Haskell solves a huge issue with threads, which is locking, which is a 
total PITA in imperative languages, it's of the same order of magnitude 
of problem as eliminating memory leaks, without deleting something twice 
etc, used to be in pre-GC C++.




Just to get the history right: garbage collectors have been around a _long_ time, since the '60s in 
Lisp systems.  They only became known to most programmers through Java (which is one unarguable good 
thing that Java did).


As for threading, in addition to Haskell's approach you might also look at Erlang, which has a quite 
different (and quite interesting) approach to the whole problem.  I wonder if anyone has tried to 
implement a message-passing style of concurrency in Haskell.


Mike


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


Re: [Haskell-cafe] a regressive view of support for imperative programming in Haskell

2007-08-08 Thread Michael Vanier
I can't agree with your point about Haskell being (just) a prototype language (assuming that's what 
you meant).  If that's the case, it won't last very long.  Languages need to be something you can 
write real, practical applications in.  Fortunately, Haskell isn't just a prototype language.  I'm 
running a Haskell program (xmonad) every minute I'm working on my computer, and it's better than the 
C program (ion) that it replaced (with a code base about 1/40th the size).  I'm sure Haskell isn't 
suitable for all application domains yet, but there's plenty of domains in which it can make its 
mark, and the frontier is going to keep getting pushed back.


Mike

Hugh Perkins wrote:

On 8/9/07, *peterv* [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote:

IMHO and being a newbie having 20 years of professional C/C++/C#
experience but hardly any Haskell experience, I agree with this… I
find the monad syntax very confusing, because it looks so much like
imperative code, but it isn't. Personally I also liked the
Concurrent Clean approach, although this also introduced extra
syntax for the compiler, while 'cmd1 = \x…' does not. You have
to type more, but you see much clearer what is going on.

Yeah, I kind of agree too.  The only way I figured out sortof how to use 
Monads was to write everything out in = syntax.  It was longer and 
uglier, but it made more sense.
 
That said, I sortof see Haskell as a prototype language, whose good 
points will be added into other languages.  Every program needs to have 
a prototype, and Haskell is that.
 
So, whilst I'm tempted to add: an easy language needs to have only a 
single way of doing anything, so throwing away the do syntax makes the 
language easier by reducing the number of things to learn, actually for 
a prototype language, the rule is probably anything goes, and then the 
best ideas get added to the non-prototype language later on.
 





___
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] positive Int

2007-08-02 Thread Michael Vanier

Of course, you can always do this:

data Nat = Zero | Succ Nat

but it's not very much fun to work with, and not very efficient.

Mike

David Roundy wrote:

On Thu, Aug 02, 2007 at 12:29:46PM -0700, brad clawsie wrote:

On Thu, Aug 02, 2007 at 12:17:06PM -0700, brad clawsie wrote:

as far as i know, the haskell standard does not define a basic Int
type that is limited to positive numbers.

would a type of this kind not potentially allow us to make stronger
verification statements about certain functions?

for example, 'length' returns an Int, but in reality it must always
return a value 0 or greater. a potential counter-argument would be the
need to possibly redefine Ord etc for this more narrow type...

i suppose one could also say that the range [0..] of return values is
*implicit* in the function definition, so there is little value in
explicitly typing it given all of the hassle of specifying a new
typeclass etc


This would be a very nice type to have (natural numbers), but is a tricky
type to work with.  Subtraction, for instance, wouldn't be possible as a
complete function... or one might say that if you included subtraction
you're even less safe:  negative results either must throw an exception or
be impossible to catch.  You might point out that overflow in an Int is
similar (uncatchable), but overflow is much harder to accidentally run into
than negative values.

A nicer option would be some sort of extra proof rather than a new type.
But that sort of work is rather tricky, as I understand it.

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


Re: [Haskell-cafe] problem building lambdabot

2007-07-31 Thread Michael Vanier
Stefan just got it working yesterday with ghc 6.6.1 and sent me the patch.  I imagine it'll be in 
the darcs repo soon if it isn't already.


Mike

Thomas Hartman wrote:


Can anybody shout out about the latest version of ghc compatible with 
building lambdabot?


http://www.cse.unsw.edu.au/~dons/lambdabot.html

shows it working on 6.4.1.

can it build under anything more recent?

t.



*Stefan O'Rear [EMAIL PROTECTED]*
Sent by: [EMAIL PROTECTED]

07/30/2007 11:59 PM


To
Michael Vanier [EMAIL PROTECTED]
cc
haskell-cafe@haskell.org haskell-cafe@haskell.org
Subject
Re: [Haskell-cafe] problem building lambdabot








On Mon, Jul 30, 2007 at 08:54:12PM -0700, Michael Vanier wrote:
  So, now that I've got all the libraries installed, the compile fails 
like

  this:
 
  Building lambdabot-4.0...
  [13 of 91] Compiling Lib.Parser   ( Lib/Parser.hs,
  dist/build/lambdabot/lambdabot-tmp/Lib/Parser.o )
 
  Lib/Parser.hs:19:39:
  Module `Language.Haskell.Syntax' does not export `as_name'
 
  Lib/Parser.hs:19:48:
  Module `Language.Haskell.Syntax' does not export `qualified_name'
 
  Lib/Parser.hs:19:64:
  Module `Language.Haskell.Syntax' does not export `hiding_name'
 
  Lib/Parser.hs:19:77:
  Module `Language.Haskell.Syntax' does not export `minus_name'
 
  Lib/Parser.hs:19:89:
  Module `Language.Haskell.Syntax' does not export `pling_name'
 
  I'm using the latest darcs pull of lambdabot along with ghc 6.6.1. 
 Anyone

  have any ideas?
 
  Thanks in advance for all the help,
 
  Mike

Lambdabot is incompatible with GHC 6.6.1, because of changes in
undocumented internal modules that lambdabot really shouldn't be
importing in the first place.  I had an idea for how to avoid the nasty
dependency a few days ago, *tries to implement it*.

Stefan
[attachment signature.asc deleted by Thomas Hartman/ext/dbcom] 
___

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


---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.

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


Re: [Haskell-cafe] problem building lambdabot

2007-07-30 Thread Michael Vanier
Thanks, but this doesn't answer the question.  I can load up the Control.Arrow module fine in ghci. 
 Is there a problem with the packaging information?


I did a google search, and this problem has come up on IRC, but nobody figured out what was causing 
it as far as I can tell.


Mike

Stefan O'Rear wrote:

On Mon, Jul 30, 2007 at 06:57:25PM -0700, Michael Vanier wrote:

When I try to build lambdabot, I get this:

Configuring lambdabot-4.0...
configure: Dependency base-any: using base-2.1.1
configure: Dependency unix-any: using unix-2.1
configure: Dependency network-any: using network-2.0.1
configure: Dependency parsec-any: using parsec-2.0
configure: Dependency mtl-any: using mtl-1.0.1
configure: Dependency haskell-src-any: using haskell-src-1.0.1
configure: Dependency readline-any: using readline-1.0
configure: Dependency QuickCheck-any: using QuickCheck-1.0.1
Setup.hs: cannot satisfy dependency arrows-any

I'm using ghc 6.6.1 compiled from source (by me) on Debian Linux.  I 
thought that arrows were included with the ghc distribution.  Does anyone 
know what's happening and how to fix it?


I don't know what's happening, but you can get arrows easily enough from
http://hackage.haskell.org (our CPAN).

Stefan

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


Re: [Haskell-cafe] problem building lambdabot

2007-07-30 Thread Michael Vanier
OK, Stefan was right.  The arrows package is an extension of Control.Arrow, not a from-scratch 
implementation.  The name confused me.  Perhaps a better name would be arrows-ext or something 
like that.


Mike

Michael Vanier wrote:
Thanks, but this doesn't answer the question.  I can load up the 
Control.Arrow module fine in ghci.  Is there a problem with the 
packaging information?


I did a google search, and this problem has come up on IRC, but nobody 
figured out what was causing it as far as I can tell.


Mike

Stefan O'Rear wrote:

On Mon, Jul 30, 2007 at 06:57:25PM -0700, Michael Vanier wrote:

When I try to build lambdabot, I get this:

Configuring lambdabot-4.0...
configure: Dependency base-any: using base-2.1.1
configure: Dependency unix-any: using unix-2.1
configure: Dependency network-any: using network-2.0.1
configure: Dependency parsec-any: using parsec-2.0
configure: Dependency mtl-any: using mtl-1.0.1
configure: Dependency haskell-src-any: using haskell-src-1.0.1
configure: Dependency readline-any: using readline-1.0
configure: Dependency QuickCheck-any: using QuickCheck-1.0.1
Setup.hs: cannot satisfy dependency arrows-any

I'm using ghc 6.6.1 compiled from source (by me) on Debian Linux.  I 
thought that arrows were included with the ghc distribution.  Does 
anyone know what's happening and how to fix it?


I don't know what's happening, but you can get arrows easily enough from
http://hackage.haskell.org (our CPAN).

Stefan

___
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] problem building lambdabot

2007-07-30 Thread Michael Vanier

So, now that I've got all the libraries installed, the compile fails like this:

Building lambdabot-4.0...
[13 of 91] Compiling Lib.Parser   ( Lib/Parser.hs, 
dist/build/lambdabot/lambdabot-tmp/Lib/Parser.o )

Lib/Parser.hs:19:39:
Module `Language.Haskell.Syntax' does not export `as_name'

Lib/Parser.hs:19:48:
Module `Language.Haskell.Syntax' does not export `qualified_name'

Lib/Parser.hs:19:64:
Module `Language.Haskell.Syntax' does not export `hiding_name'

Lib/Parser.hs:19:77:
Module `Language.Haskell.Syntax' does not export `minus_name'

Lib/Parser.hs:19:89:
Module `Language.Haskell.Syntax' does not export `pling_name'

I'm using the latest darcs pull of lambdabot along with ghc 6.6.1.  Anyone have 
any ideas?

Thanks in advance for all the help,

Mike


Michael Vanier wrote:
OK, Stefan was right.  The arrows package is an extension of 
Control.Arrow, not a from-scratch implementation.  The name confused 
me.  Perhaps a better name would be arrows-ext or something like that.


Mike

Michael Vanier wrote:
Thanks, but this doesn't answer the question.  I can load up the 
Control.Arrow module fine in ghci.  Is there a problem with the 
packaging information?


I did a google search, and this problem has come up on IRC, but nobody 
figured out what was causing it as far as I can tell.


Mike

Stefan O'Rear wrote:

On Mon, Jul 30, 2007 at 06:57:25PM -0700, Michael Vanier wrote:

When I try to build lambdabot, I get this:

Configuring lambdabot-4.0...
configure: Dependency base-any: using base-2.1.1
configure: Dependency unix-any: using unix-2.1
configure: Dependency network-any: using network-2.0.1
configure: Dependency parsec-any: using parsec-2.0
configure: Dependency mtl-any: using mtl-1.0.1
configure: Dependency haskell-src-any: using haskell-src-1.0.1
configure: Dependency readline-any: using readline-1.0
configure: Dependency QuickCheck-any: using QuickCheck-1.0.1
Setup.hs: cannot satisfy dependency arrows-any

I'm using ghc 6.6.1 compiled from source (by me) on Debian Linux.  I 
thought that arrows were included with the ghc distribution.  Does 
anyone know what's happening and how to fix it?


I don't know what's happening, but you can get arrows easily enough from
http://hackage.haskell.org (our CPAN).

Stefan

___
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] Another analogy

2007-07-23 Thread Michael Vanier

I submit my own attempts for consideration:

http://www.cs.caltech.edu/~mvanier/hacking/rants/cars.html

Mike

Andrew Coppin wrote:
 From the guy who brought you data in Haskell is like an undead quantum 
cat, I present the following:


If programming languages were like vehicles, C would be a Ferrari, C++ 
would be a Porshe, Java would be a BWM and Haskell would be a hovercraft.


It doesn't even have WHEELS! There is no steering wheel, no gearbox, no 
clutch... it doesn't even have BRAKES!!!


It completely turns the rules upside down. I mean, it moves by PUSHING 
AIR. That's just crazy! It even STEERS by pushing air. It sounds so 
absurd, it couldn't possibly work...


...oh, but it DOES work. Very well, actually. In fact, a hovercraft can 
do some things that the others can't. It works on water. It can go 
sideways. It can REALLY turn on the spot.


Insert whitty replies here...

___
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] historical question about Haskell and Haskell Curry

2007-07-18 Thread Michael Vanier
We always say that Haskell is named for Haskell Curry because his work provided the 
logical/computational foundations for the language.  How exactly is this the case?  Specifically, 
does anyone claim that Curry's combinatorial logic is more relevant to the theoretical foundations 
of Haskell than e.g. Church's lambda calculus?  If not, why isn't Haskell called Alonzo? ;-)


Mike

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


Re: [Haskell-cafe] problem with IO, strictness, and let

2007-07-13 Thread Michael Vanier

Albert,

Thanks for the very detailed reply!  That's the great thing about this mailing 
list.

I find your description of seq somewhat disturbing.  Is this behavior documented in the API?  I 
can't find it there.  It suggests that perhaps there should be a 
really-truly-absolutely-I-mean-right-now-seq function that evaluates the first argument strictly no 
matter what (not that this should be something that gets used very frequently).  Or are there 
reasons why this is not feasible?


Sorry to belabor this.  Learning to think lazily is IMO one of the hardest 
aspects of learning Haskell.

Mike

Albert Y. C. Lai wrote:

Brandon Michael Moore wrote:

Calling hClose after hGetContents is the root of the problem, but this is
a good example for understanding seq better too.


To further this end, I'll take issue :) with the final version that 
has been tested to work, and show that it still won't work.


First, the program in question:

import System.IO
import System.Environment

process_file :: FilePath - IO ()
process_file filename =
do h - openFile filename ReadMode
   c - hGetContents h
   cs - return $! lines c
   hClose h
   putStrLn $ show $ length cs

It will give a wrong answer to a file large enough. The short 
explanation is that seq, or its friend $!, does not evaluate its 
argument (lines c) entirely; it only evaluates so much. The jargon is 
weak head normal form, but concretely here are some examples: for Int, 
it evaluates until you have an actual number, which is all good and 
expected; for lists, it evaluates only until the first cons cell emerges 
(let's say we know the list will be non-empty). It will not hunt down 
the rest of the list. (Moreover, it will not even hunt down what's in 
the cons cell, e.g., the details of the first item of the list. But this 
is not too important for now.)


It still happens to give the right answer to a file small enough, thanks 
to buffering.


So here is a chronicle of execution, with confusing details - confusing 
because two wrongs conspire to make a right, almost:


0. open file, hGetContents. Remember that block buffering with a pretty 
large buffer is the default.


1. $! evalutes lines c for the first cons cell. To do that, latent code 
(the jargon is thunk) installed by hGetContents is invoked and it 
reads something. It is in block buffering mode, so it reads blockful. 
The first cons cell will only emerge when the first line break is found, 
so it reads blocks until a block contains a line break. But it does not 
read more blocks.


Whatever has been read will be accessible to cs. Maybe not immediately 
in the form of lists of strings. Part of it is already in that form, the 
other part is in the form of buffer content plus a thunk to convert the 
buffer to lists of strings just in time. That thunk intermingles code 
from the lines function and hGetContent. Perhaps you don't need to know 
that much. The bottomline is that cs has access to one or more blocks 
worth of stuff, which may or may not be the whole file. Exactly how much 
is defined by: as many blocks as to contain the first line break.


2. close file. Henceforth no further reading is possible. cs still has 
access to whatever has been done in the above step; it is already in 
memory and can't be lost. But cs has no access to whatever not in 
memory; it does not exist.


3. count the number of lines accessible to cs.

As examples here are some scenerios:

A. The whole file fits into the buffer. You will get the correct count.

B. Five lines plus a little bit more fit into the buffer. The answer is 
six.


C. The first line is very long, or the buffer is very small. The answer 
is one or two, depending on whether the line break falls in the middle 
or at the boundary of the buffer.


To test for these scenerios, you can fudge the buffer size and have fun:

process_file :: FilePath - IO ()
process_file filename =
do h - openFile filename ReadMode
   hSetBuffering h (BlockBuffering (Just 20))
   c - hGetContents h
   cs - return $! lines c
   hClose h
   putStrLn $ show $ length cs

There are two conclusions you can draw:

For a task satisfied by a single pass, and the task traverses the whole 
file unconditionally: let go of control. Use hGetContents and don't 
bother to hClose yourself (it will be closed just in time).


For a task requiring several passes, and you want the whole file read 
here and now: seq won't cut it. Some people use return $! length c 
for that. There are also other ways. Consider Data.ByteString.


What about a task satisfied by a single pass but it does not necessarily 
traverse the whole file? Automatic close won't kick in. You will hClose 
yourself but where to put it is a long story.

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

___
Haskell-Cafe mailing list

Re: [Haskell-cafe] problem with IO, strictness, and let

2007-07-13 Thread Michael Vanier

Stefan,

Thanks for your comments, as always.

What I meant by really-truly-absolutely-I-mean-right-now-seq is something that would evaluate its 
argument as far as it is possible to do so i.e. something that forces strict evaluation of an 
argument.  That's what I thought seq did, but now I see I was wrong; it only goes one deep as it 
were.  In fact, as you say, seq is not defined in terms of evaluation; all that it guarantees is 
that its first argument is either (a) bottom, in which the result of the entire seq is bottom, or 
(b) not bottom.  To do so it has to evaluate the first argument only far enough to show bottom-ness 
or not, which is not strict evaluation as I understand it.  So am I right in saying that Haskell has 
no way to force strict evaluation?  Or am I confused as to the correct definition of strict?


Mike

Stefan O'Rear wrote:

On Fri, Jul 13, 2007 at 04:29:12PM -0700, Michael Vanier wrote:

Albert,

Thanks for the very detailed reply!  That's the great thing about this 
mailing list.


I find your description of seq somewhat disturbing.  Is this behavior 
documented in the API?  I can't find it there.  It suggests that perhaps 
there should be a really-truly-absolutely-I-mean-right-now-seq function 
that evaluates the first argument strictly no matter what (not that this 
should be something that gets used very frequently).  Or are there reasons 
why this is not feasible?


Sorry to belabor this.  Learning to think lazily is IMO one of the hardest 
aspects of learning Haskell.


Can you clarify what you mean by really-truly-absolutely-I-mean-right-now-seq?


The entire specification of seq is in 
http://haskell.org/onlinereport/basic.html#sect6.2:

The function seq is defined by the equations:

seq ⊥ b = ⊥
seq a b = b, if a ≠ ⊥

In particular, seq is not defined in terms of evaluation.

Even in a lazy model, you cannot assume any *order* of evaluation, only
that both arguments will be demanded if the whole expression is.  *if*
the whole expression is.

Seq is uniform - for ALL data types on the lhs, it evaluates it to WHNF
(seeing the top constructor or lambda).  A recursive seq would not be
uniform, and would require a type class or just specialization.

If you can see why (x `seq` x) is redundant, you probably understand
laziness.

Perhaps it would help to see a definition of seq in Haskell?

class Eval a where
seq :: a - b - b

instance Eval (a,b) where
seq (x,y) b = b
instance Eval [a] where
seq [] b = b
seq (x:xs) b = b
instance Eval (Maybe a) where
seq Nothing b = b
seq (Just x) b = b
instance Eval (Either a b) where
seq (Left x) b = b
seq (Right x) b = b
instance Eval Bool where
seq True b = b
seq False b = b
instance Eval Int where
...
seq (-1) b = b
seq 0 b = b
seq 1 b = b
...

?

Stefan

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


Re: [Haskell-cafe] problem with IO, strictness, and let

2007-07-12 Thread Michael Vanier

That makes sense.  Thanks!

Mike

Stefan O'Rear wrote:

On Thu, Jul 12, 2007 at 09:22:09PM -0700, Michael Vanier wrote:
I stumbled across a problem with IO and strictness that I could fix, but I 
can't understand why the fix works.  I've compressed it down into a program 
which simply computes the number of lines in a file.  Here is a version 
that doesn't work:


module Main where

import System.IO
import System.Environment

process_file :: FilePath - IO ()
process_file filename =
do h - openFile filename ReadMode
   c - hGetContents h
   let cs = unlines $ lines c
   hClose h
   putStrLn $ show $ length cs


The problem is that you're closing the file twice.  When you call any
function of the getContents family, you assign to that function the
responsibility to close the file, no sooner than it is no longer needed.
Don't call hClose yourself, Bad Things will happen.

If you get rid of hClose, laziness will not hurt you - infact it will
help you, by allowing your program to run in constant space.

Stefan

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


[Haskell-cafe] problem with IO, strictness, and let

2007-07-12 Thread Michael Vanier
I stumbled across a problem with IO and strictness that I could fix, but I can't understand why the 
fix works.  I've compressed it down into a program which simply computes the number of lines in a 
file.  Here is a version that doesn't work:


module Main where

import System.IO
import System.Environment

process_file :: FilePath - IO ()
process_file filename =
do h - openFile filename ReadMode
   c - hGetContents h
   let cs = unlines $ lines c
   hClose h
   putStrLn $ show $ length cs

main :: IO ()
main = do args - getArgs
  process_file (args !! 0)

This will return a length of 0 lines for any input file.  Obviously, the let is not being 
evaluated strictly (nor would we expect it to be), so that when the evaluation is requested, the 
file is already closed and the length of the list of lines is 0 (though I might have expected an 
error).  I then tried this:


process_file :: FilePath - IO ()
process_file filename =
do h - openFile filename ReadMode
   c - hGetContents h
   let cs = id $! lines c -- try to strictly evaluate the let binding
   hClose h
   putStrLn $ show $ length cs

which also failed exactly as the previous version did (i.e. always returning 0).  Then I gave up on 
let and did this:


process_file :: FilePath - IO ()
process_file filename =
do h - openFile filename ReadMode
   c - hGetContents h
   cs - return $! lines c
   hClose h
   putStrLn $ show $ length cs

This works.  However, I don't understand why this version works and the previous version doesn't. 
Can anyone walk me through the evaluation?  Also, is there a way to make let strict?


TIA,

Mike


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


[Haskell-cafe] folds with escapes

2007-07-04 Thread Michael Vanier
I'm sure this has been done a hundred times before, but a simple generalization of foldl just 
occurred to me and I wonder if there's anything like it in the standard libraries (I couldn't find 
anything).  Basically, I was trying to define the any function in terms of a fold, and my first 
try was this:


 any :: (a - Bool) - [a] - Bool
 any p = foldl (\b x - b || p x) False

This is inefficient, because if (p x) is ever True the rest of the list is scanned unnecessarily. 
So I wrote a more general foldl with an escape predicate which terminates the evaluation, along 
with a function which tells what to return in that case (given an argument of the running total 'z'):


 foldle :: (b - Bool) - (a - a) - (a - b - a) - a - [b] - a
 foldle _ _ _ z [] = z
 foldle p h f z (x:xs) = if p x then h z else foldle p h f (f z x) xs

Using this function, foldl is:

 foldl' = foldle (const False) id

and any is just:

 any p = foldle p (const True) const False

I also thought of an even more general fold:

 foldle' :: (b - Bool) - (a - b - [b] - a) - (a - b - a) - a - [b] 
- a
 foldle' _ _ _ z [] = z
 foldle' p h f z (x:xs) = if p x then h z x xs else foldle' p h f (f z x) xs

Using this definition, you can write dropWhile as:

 dropWhile :: (a - Bool) - [a] - [a]
 dropWhile p = foldle' (not . p) (\_ x xs - x:xs) const []

Again, I'm sure this has been done before (and no doubt better); I'd appreciate any pointers to 
previous work along these lines.


Mike




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


Re: [Haskell-cafe] folds with escapes

2007-07-04 Thread Michael Vanier

That's cool -- good point.  takeWhile is also trivially defined in terms of 
foldr:

 takeWhile p = foldr (\x r - if p x then x:r else []) []

Can you do dropWhile in terms of foldr?  I don't see how.

Mike

Stefan O'Rear wrote:

On Wed, Jul 04, 2007 at 04:20:20PM -0700, Michael Vanier wrote:
I'm sure this has been done a hundred times before, but a simple 
generalization of foldl just occurred to me and I wonder if there's 
anything like it in the standard libraries (I couldn't find anything).
Basically, I was trying to define the any function in terms of a fold, 
and my first try was this:



any :: (a - Bool) - [a] - Bool
any p = foldl (\b x - b || p x) False
This is inefficient, because if (p x) is ever True the rest of the list is 
scanned unnecessarily.


Rather than create a new escape fold, it's much easier, simpler, and
faster just to use a right fold:

any p = foldr (\x b - p x || b) False

That will short-ciruit well by laziness, and is made tailrecursive by
same.

Stefan

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


[Haskell-cafe] stupid operator question

2007-06-23 Thread Michael Vanier
I noticed that both the Data.Array library and the Data.Map library use the (!) operator for 
different purposes.  How would it be possible to import both libraries usefully in a single module? 
 I guess what I'm really asking is: how do I qualify operator names?


Mike

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


Re: [Haskell-cafe] New book: Real-World Haskell!

2007-05-23 Thread Michael Vanier

That's pretty baa-aa-aad.

Mike

brad clawsie wrote:

On Wed, May 23, 2007 at 12:40:58PM -0700, Dan Weston wrote:
 What power animal have you chosen for the cover of your O'Reilly book? Alas, 
 most of the good ones are gone already!


lamb-da?
___
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] Haskell: the Craft of Functional Programming

2007-05-20 Thread Michael Vanier
I'm not sure what you mean by a lot of transcription work.  It's an excellent book, aimed at 
beginners.


Mike

PR Stanley wrote:

Hi
I've acquired a copy of the above title but it requires a lot of 
transcription work. So, I thought I'd first ensure it's worth the time 
and effort. This edition was published in 1999.

All Opinions on the text, good or bad, would be very welcome.
Thanks,
Paul

___
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] The Trivial Monad

2007-05-04 Thread Michael Vanier

The - in type signatures associates to the right, so the type signatures

 fmap :: (a - b) - (W a - W b)
 bind :: (a - W b) - (W a - W b)

are the same as:

 fmap :: (a - b) - W a - W b
 bind :: (a - W b) - W a - W b

Sometimes people put in the extra parentheses because they want to 
emphasize a particular way to use the function.


I'm assuming you understand that a function that takes two arguments and 
returns a (possibly non-function) value is equivalent to a function that 
takes one argument that returns a function that takes the other argument 
and returns a value.


HTH,

Mike



Adrian Neumann wrote:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA512

I've read this blogpost about the trivial monad
http://sigfpe.blogspot.com/2007/04/trivial-monad.html, because I still
don't understand what this monad thingy is all about.

The author defines three functions:

data W a = W a deriving Show

return :: a - W a
return x = W x

fmap :: (a - b) - (W a - W b)
fmap f (W x) = W (f x)

bind :: (a - W b) - (W a - W b)
bind f (W x) = f x

and asks the reader to prove the tree monad laws for them. However I
don't understand the type signatures for bind and fmap. I'd say (and
ghci's type inference agrees) that bind and fmap have the type

bind:: (a-W b) - W a - W b
fmap:: (a-b) - W a - W b

They take a function f and something and return what f does to that. I
don't see why they should return a function.

This of course makes it hard for me to prove the monad laws. The first
however works nonetheless:

1) bind f (return a)= f a

= bind f (return a)= bind f (W a) = f a

Can someone explain bind and fmap (and possible law 2 and 3)?

Thanks,

Adrian
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGOuQS11V8mqIQMRsRCmngAJ9NwQMwXeS/PSM1NUsVA8gxPuA0KACfSLiA
ItqRZW5a4XyQ099bhMtSWmU=
=/8i/
-END PGP SIGNATURE-
___
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] Tutorial on Haskell

2007-04-18 Thread Michael Vanier
As one who teaches programming in a lot of different languages, I can 
state unequivocally that strong static typing of the Haskell or Ocaml 
variety is (in addition to all its other benefits) a godsend to the 
instructor.  So many incorrect ways of writing programs are simply ruled 
out right at the start that it makes it easier to concentrate on what 
really matters.  The downside is that sometimes you get programmers from 
an imperative languages background who cannot figure out why some simple 
code is giving them a type error (for instance, by not putting in an 
else clause in an if statement).


Mike



Neil Davies wrote:


Yep - I've seen it in course work I've set in the past - random walk
through the arrangement of symbols in the language (it was a process
algebra work and proof system to check deadlock freedom).

... but ...

Haskell even helps those people - if you've created something that
works (and you are at least sensible to create a test suite be it
regression or property based) - then there is more confidence that
they've coded a solution (if not a good one).

Haskell raises the value of formality (both ecomomically and in terms
of its caché) - changin the mindset of the masses - creating the
meme - that's tricky. Especialy if they're really off the B Ark!
(http://www.bbc.co.uk/cult/hitchhikers/guide/golgafrincham.shtml)

Neil

On 18/04/07, Michael Vanier [EMAIL PROTECTED] wrote:


R Hayes wrote:




 On Apr 17, 2007, at 4:46 PM, David Brown wrote:

 R Hayes wrote:

 They *enjoy* debugging ...


 I have to say this is one of the best things I've found for catching
 bad programmers during interviews, no matter what kind of system 
it is

 for.  I learned this the hard way after watching someone who never
 really understood her program, but just kept thwacking at it with a
 debugger until it at least partially worked.


 I've seen this too, but I would not use the word debugging to describe
 it.  I don't think I agree that enjoying debugging is a sufficient
 symptom for diagnosing this condition.  There are many people that
 love the puzzle-box aspect of debugging.  Some of them are very
 talented developers.

 R Hayes
 rfhayes@/reillyhayes.com


 Dave

I agree with the latter sentiment.  I call the thwacking at it
approach random programming or shotgun programming, the latter
suggesting that it's like shooting at the problem randomly until it
dies.  I prefer not having to debug, but when I do have to I find it fun
(up to a point).

Mike



___
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] Tutorial on Haskell

2007-04-17 Thread Michael Vanier

R Hayes wrote:





On Apr 17, 2007, at 4:46 PM, David Brown wrote:


R Hayes wrote:


They *enjoy* debugging ...



I have to say this is one of the best things I've found for catching
bad programmers during interviews, no matter what kind of system it is
for.  I learned this the hard way after watching someone who never
really understood her program, but just kept thwacking at it with a
debugger until it at least partially worked.



I've seen this too, but I would not use the word debugging to describe 
it.  I don't think I agree that enjoying debugging is a sufficient 
symptom for diagnosing this condition.  There are many people that 
love the puzzle-box aspect of debugging.  Some of them are very 
talented developers.


R Hayes
rfhayes@/reillyhayes.com



Dave


I agree with the latter sentiment.  I call the thwacking at it
approach random programming or shotgun programming, the latter
suggesting that it's like shooting at the problem randomly until it
dies.  I prefer not having to debug, but when I do have to I find it fun
(up to a point).

Mike



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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Michael Vanier



P. R. Stanley wrote:

Brandon, Chris, Don,
gentlemen,
Thank you all for your swift and well-written answers.
I should point out that I'm coming to functional programming with a 
strong background in programming in C and C-type languages. I am also 
very new to the whole philosophy of functional programming. Hence my 
bafflement at some of the very elementary attributes of Haskell. I 
thought that would give you chaps a better idea of where I'm coming from 
with my queries.

Back to mylen. Here is the definition once more:
mylen [] = 0
mylen (x:y) = 1 + mylen y
The base case, if that is the right terminology, stipulates that the 
recursion ends with an empty list and returns 0. Simple though one 
question - why does mylen require the parentheses even when it is 
evaluating the length of [...]? I can understand the need for them when 
dealing with x:... because of the list construction function precedence 
but not with [2,3,etc]. I thought a [e] was treated as a distinct token.


I'm assuming that the interpreter/compiler is equipped to determine the 
type and value of xs subsequent to which it calls itself and passes the 
object minus the first element as argument unless the object is an empty 
list.


I think what you're asking here is why you need the parens around (x:y) in the 
second case.  Function application doesn't use parentheses, but it has a very 
high precedence, so mylen x:y would be parsed as (mylen x) : y, since the 
: constructor has a lower precedence.




going back to Don's formal definition of the list data structure:
data [a] = [] | a : [a]
A list is either empty or contains an element of type a? Correct, wrong 
or very wrong?


A list is either empty, or consists of the first object, which is of type a 
(just called a here) and the rest of the list, which is also a list of type a 
(called [a] here).  The syntax is an impediment to understanding here; a 
clearer version of the list type would be


data List a = Empty | Cons a (List a)

The left-hand case says that a list can be just Empty.  The right-hand case says 
that a list can also be a Cons of a value of type a (the first element) and a 
List of type a (the rest of the list).


So, for instance, in my definition these are all lists:

Empty
Cons 10 Empty  -- list of Int
Cons 10 (Cons 20 Empty)
Cons foo (Cons bar (Cons baz Empty))  -- list of String

Using normal Haskell lists these are:

[]
10 : Empty  -- also written as [10]
10 : 20 : Empty -- also written as [10, 20]
foo : bar : baz : Empty -- also written as [foo, bar, baz]

The list syntax e.g. [1, 2, 3] is just syntactic sugar; the real syntax would 
be with the : operator e.g. 1 : 2 : 3 : [].  We use the sugar because it's 
easier to read and write.




By the way, what branch of discrete math - other than the obvious ones 
such as logic and set theory - does functional programming fall under?




The usual answer to this is category theory which is an extremely abstract 
branch of mathematics.  But you don't really need to know category theory to 
program in Haskell (though it helps for reading Haskell papers).  Also, lambda 
calculus is useful, and there is a field called type theory which is also 
useful.  Pierce's book _Types and Programming Languages_ will get you up to 
speed on lambda calculus and type theory, though it doesn't use Haskell.


Mike

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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Michael Vanier



Brandon S. Allbery KF8NH wrote:


On Feb 18, 2007, at 21:44 , Michael Vanier wrote:

I think what you're asking here is why you need the parens around 
(x:y) in the second case.  Function application doesn't use parentheses


Function application never applies to pattern matching.


You're right; I take it back.  However, : is not an acceptable variable name 
as such either:


ghci let foo x : y = x
interactive:1:4: Parse error in pattern

: needs to be surrounded by parens to be treated as a function; otherwise it's 
an operator.  OK, we can try:


ghci let foo x (:) y = x

interactive:1:10:
Constructor `:' should have 2 arguments, but has been given 0
In the pattern: :
In the definition of `foo': foo x : y = x

Bottom line: foo x:y is not a valid pattern.

The usual answer to this is category theory which is an extremely 
abstract branch of mathematics.  But you


Actually, no; my understanding is that category theory as applied to 
Haskell is a retcon introduced when the notion of monads was imported 
from category theory, and the original theoretical foundation of Haskell 
came from a different branch of mathematics.




Nevertheless, a lot of Haskell papers do refer to category theory, and lambda 
calculus can be put into that framework as well, so I don't think my statement 
is invalid.  But as you say, it's a bit of an after-the-fact realization.


Mike


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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Michael Vanier

P. R. Stanley wrote:


What are the pre-requisites for Lambda calculus?
Thanks
Paul



Learning lambda calculus requires no prerequisites other than the ability to 
think clearly.  However, don't think that you need to understand all about 
lambda calculus in order to learn Haskell.  It's more like the other way around: 
by the time you've learned Haskell, you've already unwittingly absorbed a good 
deal of lambda calculus.  Once again, I recommend Pierces _Types and Programming 
Languages_ as a reference if you really feel you need to learn this now.


For absorbing the functional style of programming (which is what you really 
should be working on at this point), the book _Structure and Interpretation of 
Computer Programs_ by Abelson and Sussman (which uses Scheme, not Haskell) is 
very valuable.  For learning about recursion, the book _The Little Schemer_ by 
Friedman and Felleisen is also very good (and quite short); it also uses Scheme. 
 However, most of the insights of both books carry over into Haskell (with a 
change of syntax, of course).


Mike

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


Re: [Haskell-cafe] OT: any haskell-friendly / functional programming friendly comp sci programs? (for a 30s guy who did his undergrad in liberal arts)

2007-02-05 Thread Michael Vanier
FYI we teach and do a fair amount of functional programming here at Caltech.  We 
have courses using scheme, ocaml, and haskell with more on the way.


Mike

Greg Fitzgerald wrote:

Thomas,

Here's a good place to start, although I'm not sure how up to date it is:
http://haskell.org/haskellwiki/Haskell_in_education

I too am interested in an FP-related, higher education in California.  
Could you please send another post with whatever information you find?


Thanks,
Greg


On 2/5/07, * Thomas Hartman* [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


haskellers, I'm contemplating returning to school after a decade as a
worker bee, and almost that long as a worker bee doing computer
consulting / miscelaneous tech stuff.

Ideally I'd like to get a masters, but I don't know if that's feasible
this late in the game. If it's not, I might settle for a lesser degree
and worry about the masters later.

Part of my desire to return to school is that after encountering
functional programming over the past year or so (first through lisp,
then haskell), I've found something that I'm really interested in, but
that it feels the amount of learning I can do around a job just won't
cut it to get to the level that I want. That's the personal reason;
the practical reason is that I think it would be a good networking
opportunity (hankering to start my own company, and not meeting the
right kinds of people), and obviously increase my chance of getting
better paying, but especially more *interesting* jobs. I have some
savings, figure loans would cover the rest, and no wife or kids.

So I'll make a rather open ended request for advice. Are there decent
comp sci master's programs out there that will take someone who didn't
do a hard science in undergrad, but has lots of work-related
experience with programming? If not, what's the next best thing? Get a
quick bachelor's? Spend six months cramming for the GREs and then try
for a master's?

Whether master's, bachelor's, or other, I am specifically interested
in programs that are functional friendly. In other words, I don't
want to just go and study algorithms in java for two years. Ideally,
I'd like to go somewhere where I could really explore and get good at
the functional languages, with haskell my current favorite but also
open to others. (For what it's worth, most of my experience is in
perl, but I take it seriously as a language and try not to write the
kind of throwaway crap that mean people make fun of.)

My background is that I have a liberal arts bachelors from an american
ivy. Though I enjoyed the program very much, it probably wasn't the
wisest financial decision, given the type of career I subsequently
gravitated to. But hey, maybe that gives me a different kind of
perspective that has its own kind of value. Since, then, there;s
mainly work work work for me, with some time off bumming around
europe. And, on my own time: learn learn learn. I'm now 31.

I've been living in germany for a few years, mainly freelancing as a
computer consultant, and am open to programs in europe -- probably
either england or germany. Largely because programs out here seem to
be significantly cheaper than programs in the states, and being a
somewhat older student seems to be less unusual out here. However,
truth be told, I have a hankering for my homeland, the good old USA.
And if possible somewhere in california, where my extended family is
based, or it not that new york, where I have a good network. (But open
to other locations as well; cali and new york would just be my top
choices.)

Distance learning is okay if the program is really good, but doing the
campus thing again, perhaps while working part or semi-full time,
would be the ideal (though perhaps I'm pushing the age limit there?).

This has gotten rather long, so I'll leave it at that.

Sorry about going off topic, and thanks in advance for any advice.

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





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

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


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-02-03 Thread Michael Vanier

Lennart,

Now you've made me curious. Which paper is this?  Is it available for download 
anywhere?


Mike

Lennart Augustsson wrote:

On Jan 29, 2007, at 03:01 , Alexy Khrabrov wrote:


How do people stumble on Haskell?


Well, I didn't really stumble on it.  I was at the 1987 meeting
when we decided to define Haskell.

But I stumbled on functional programming in the first place.
I had to learn it because it was part of a course in denotational
semantics.  The language was SASL.  And then I read David Turners
paper on combinators, and I was hooked.

-- Lennart

___
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] multiline strings in haskell?

2006-01-11 Thread Michael Vanier
Is there any support for multi-line string literals in Haskell?  I've 
done a web search and come up empty.  I'm thinking of using Haskell to 
generate web pages and having multi-line strings would be very useful.


Mike

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


Re: [Haskell-cafe] multiline strings in haskell?

2006-01-11 Thread Michael Vanier

Yes, just like that ;-)  Thanks!

Now if somebody has a string interpolation library, I'd be a pretty 
happy camper ;-)


Mike



mvanier:
Is there any support for multi-line string literals in Haskell?  I've 
done a web search and come up empty.  I'm thinking of using Haskell to 
generate web pages and having multi-line strings would be very useful.


Do you mean like this:

string =  line one\n\
 \   line two is here\n\
 \   line three is this line\n


$ echo 'putStr string' | ghci A.hs
 line one
   line two is here
   line three is this line

-- Don

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


Re: [Haskell-cafe] multiline strings in haskell?

2006-01-11 Thread Michael Vanier

Excellent! Thanks.

Mike

Donald Bruce Stewart wrote:

Oh, like this (by Stefan Wehr):
http://www.cse.unsw.edu.au/~dons/code/icfp05/tests/unit-tests/VariableExpansion.hs


$ ghci -fth VariableExpansion.hs
*VariableExpansion let x = 7 in $( expand ${x} )
7
*VariableExpansion let url = http://www.google.com;
*VariableExpansion $( expand Here is my url: ${url}. Do you like it? )
Here is my url: \http://www.google.com\;. Do you like it?

Cheers,
  Don

mvanier:

Yes, just like that ;-)  Thanks!

Now if somebody has a string interpolation library, I'd be a pretty 
happy camper ;-)


Mike



mvanier:
Is there any support for multi-line string literals in Haskell?  I've 
done a web search and come up empty.  I'm thinking of using Haskell to 
generate web pages and having multi-line strings would be very useful.

Do you mean like this:

   string =  line one\n\
\   line two is here\n\
\   line three is this line\n


$ echo 'putStr string' | ghci A.hs
line one
  line two is here
  line three is this line

-- Don

___
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] Category theory monad ---- Haskell monad

2005-08-18 Thread Michael Vanier

The explanation given below might be a bit heavy for someone who didn't know 
much
about category theory.  For those individuals I'd recommend Phil Wadler's
papers:

http://homepages.inf.ed.ac.uk/wadler/topics/monads.html

I especially recommend Monads for Functional Programming, The Essence of
Functional Programming and Comprehending Monads.

Basically, though, the Haskell implementation _is_ the category theoretic
definition of monad, with bind/return used instead of (f)map/join/return as
described below.

Mike

 Date: Thu, 18 Aug 2005 20:39:37 -0400
 From: Cale Gibbard [EMAIL PROTECTED]
 Cc: haskell-cafe@haskell.org
 
 On 14/08/05, Carl Marks [EMAIL PROTECTED] wrote:
  Is there any text/article which makes precise/rigorous/explicit the 
  connection
  between the category theoretic definition of monad with the haskell
  implementation?
 
 Well, a monad over a category C is an endofunctor T on C, together
 with a pair of natural transformations eta: 1 - T, and mu: T^2 - T
 such that
 1) mu . (mu . T) = mu . (T . mu)
 2) mu . (T . eta) = mu . (eta . T) = id_C
 
 In Haskell, a monad is an endofunctor on the category of all Haskell
 types and Haskell functions between them. Application of the
 endofunctor to an object is given by applying a type constructor (the
 one which is made an instance of the Monad class). Application of the
 endofunctor to a function is carried out by fmap or liftM. The natural
 transformation eta is called return, and mu is called join (found in
 the Monad library).
 
 Haskell uses a somewhat different (but equivalent) basis for a monad,
 in that it is not map, return, and join which need defining to make a
 type an instance of the Monad class, but return and (=), called
 bind or extend.
 
 One can define bind in terms of fmap, and join as
 x = f = join (fmap f x)
 
 and one can get back join and fmap from return and bind:
 join x = x = id
 fmap f x = x = (return . f)
 
 hope this helps,
 - Cale
 ___
 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] G machine in FORTH

2005-06-01 Thread Michael Vanier

I always thought Forth was way cool, but I've never managed to get anything
significant written in it.  I think that Forth has echoes of the
point-free style in Haskell, but Haskell is a lot friendlier.

Is the Forth environment part of the hardware?  If your Forth is just a
threaded interpreter written in software then it seems wasteful to compile
Haskell down to an interpreted environment.  If it's part of the hardware
then I think it would be (at the very least) an interesting exercise.

Mike

 Date: Wed, 1 Jun 2005 17:25:24 -0400
 From: Andrew Harris [EMAIL PROTECTED]
 Reply-To: Andrew Harris [EMAIL PROTECTED]
 
 Hi -
 
Brace yourself... I work in an environment where FORTH is still used.
 
I've been thinking about writing a G-machine interpreter in FORTH
 so that one could write Haskell like programs that would compile down
 and run graph-reduction style on the FORTH machine.
 
Many developers think FORTH is nice, but the language is so, shall
 we say, terse.
 
I'm curious about what people think about this; having the
 expressiveness of a Haskell-like language that compiles to this
 environment might provide the best of both worlds, simple hardware
 architecture and an advanced programming language.
 
 let me know what you think,
 -andrew

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


[Haskell-cafe] terrible Haskell pun

2005-05-22 Thread Michael Vanier

I came up with a terrible Haskell pun that I had to share with this list:

  Haskell provides special syntactic support for monads in terms of the do
  notation.  There is a straightforward translation between this notation
  and the core language, which constitutes its do-notational semantics,
  as it were.

Sorry,

Mike



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


Re: [Haskell-cafe] Python?

2005-05-11 Thread Michael Vanier
 Date: Wed, 11 May 2005 13:06:51 +0200
 From: Jerzy Karczmarczuk [EMAIL PROTECTED]
 
 Michael Vanier comments my defense of Matlab:
 
 I used objects, and even a lot of functional
 constructs. I don't see any reason to call it a creeping horror.
 It is quite homogeneous and simple, and is decently interfaced.
 
 
 
 
 It's incredibly inconsistent.  To cite just one example, the syntax is
 geared towards the notion that everything is a two-dimensional matrices of
 double-precision floating point numbers.  If you want to have a
 three-dimensional array, you can do that, but the syntax is not going to be
 nearly as elegant, because matlab's array syntax doesn't scale at all.  
 
 Come on...
 Matlab has cells and the full object-oriented layer nowadays. There
 are short ints, strings, complex numbers, etc. The extensibility is
 good. The overall consistency is reasonable.
 
 Syntax for 3D arrays?
 Give me one single language where this is natural and immediate.
 We are 2D readers/writers, our way of presenting information is
 2D within a text editor, and similar problems hit everywhere. I used
 3D matrices for the image synthesis, for colour  image processing,
 for simulations of physical systems. It wasn't worse, and even better
 than in many other languages.

Python:

# 2-d array:
print a[0][0]

# 3-d array:
print a[0][0][0]

This also applies to most languages, including C.

If you like matlab, go right ahead and use it.  The same goes for Visual
Basic.  I could care less what programming languages you use.  But if you
think matlab is an elegant language, we will have to agree to disagree.
And that is the last word I will say on this subject, since this is a
Haskell mailing list.

Mike

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


Re: [Haskell-cafe] Python?

2005-05-10 Thread Michael Vanier
 Date: Tue, 10 May 2005 19:02:33 -0400
 From: Daniel Carrera [EMAIL PROTECTED]
 
 Hello,
 
 This might be a strange question to ask on a Haskell list, but I do want 
 to hear your opinions. What do you think of Python?
 
 To explain where this question is comming from:
 
 I have a lady friend who wants to learn how to program. I just decided 
 to teach her Python for practical reasons:
 
 1) Python has a nice IDE-ish thing. It's called idle. It includes both 
 a shell and an editor. The interface is simple and clear.
 
 2) I can't get Helium to compile (since I can't get ghc to run) on Solaris.
 
 3) Python has some nice introductory documentation. The Haskell 
 documentation is more advanced.
 
 4) She's interested in writing an OOo plugin some day. Python can do that.
 
 But I do hesitate. I would like to teach her Haskell because I think 
 it's a better language. But I just don't seem to have the tools to teach 
 it to a complete beginner (idle, documentation).
 

Trying to teach Haskell to non-programmers is, IMNSHO as someone who
teaches programming to very smart kids as my job, a *very* bad idea.  It's
simply too rich and difficult a language for beginning programmers.  The
conceptual barriers are formidable even for most experienced programmers,
and there are much easier ways to accomplish the goal of learning
functional programming (including Haskell), if that's what you want.  The
sequence I recommend for that is Scheme - Ocaml - Haskell, which involves
picking up a few new concepts at each stage.  You could also go Scheme -
Haskell for very bright and ambitious students.  However, Scheme is not
currently a very practical language compared to (say) python, and python
does contain some functional aspects as well.  So python is a decent first
language both for practical programming and for would-be functional
programmers.  I've noticed that most of the hard-core FP types I know also
use python occasionally as their imperative language of choice -- it's
simply less distasteful than most of the alternatives.

Here at Caltech we teach Scheme first (for programming concepts), then
students can go in several different directions.  Learning java or C is a
common next step.  Python generally comes after java and C, though it
doesn't have to, and most students have no trouble picking it up.  Ocaml
and Haskell come later, and only a few really hard-core types learn those.

Eventually I hope that functional languages will become more mainstream and
practical, because they're just better.  But for someone who wants to get
a practical language under her belt, starting with Haskell is not the way
to go.  I have enough problems convincing people to learn Scheme.  I've
even had people beg me to teach them Matlab as a first programming
language, because that is the only language that they needed to get their
work done.  Telling them that Matlab's programming language is a creeping
horror doesn't sway them at all.

Mike



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


Re: [Haskell-cafe] Comparison with Clean?

2005-05-04 Thread Michael Vanier
 From: Benjamin Franksen [EMAIL PROTECTED]
 Date: Wed, 4 May 2005 22:47:21 +0200
 
 On Wednesday 04 May 2005 22:22, [EMAIL PROTECTED] wrote:
  Bryce Bockman writes:
   Scheme is strict, so it lacks some of the flexibility (and drawbacks)
   that come from Laziness, but in the book they teach you how to build a
   Lazy version of Scheme, which is instructive in understanding what's
   really going on in Lazy evaluation.
 
  Don't confuse categories please. SICP doesn't say how to make a lazy
  variant of Scheme. Applicative protocol is not normal protocol, the
  reduction is, as it is. 
 
 We may have a different copy of SICP, but in mine (2nd edition) there is 
 Chapter 4.2 Variantions on a Scheme -- Lazy Evaluation and in particular 
 4.2.2 An Interpreter with Lazy Evaluation.
 
 Ben

To be completely accurate: the evaluation order is Scheme is strict, not
lazy, forever and ever, amen.  That doesn't change.  What SICP shows you
how to do in chapter 4 (brilliantly, I think) is how to write a
metacircular evaluator which is a Scheme interpreter written in Scheme
itself.  Of course, because you have a Scheme interpreter running on top of
another Scheme interpreter, the (outer) interpreter is going to be pretty
slow, but the point of the chapter is not to build a useful interpreter but
to really understand how interpreters work.  Once you understand that, they
show that it's relatively easy to build a different kind of Scheme
interpreter, one that uses lazy evaluation instead of strict evaluation.
That's not real Scheme by any means, but it can be used to do real
computations.  Check out http://mitpress.mit.edu/sicp for the whole story.

We now return you to your regularly-scheduled language...

Mike


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


Re: [Haskell-cafe] Re: Haskell vs OCaml

2005-05-03 Thread Michael Vanier

Marcin gives a good capsule description of the differences between ocaml
and haskell.  Let me add my two cents.

I also learned ocaml before learning haskell, and the biggest single
difference I found is that haskell is a lazy, purely functional language
and ocaml is a strict, mostly functional language.  So all the IO monad
stuff in haskell doesn't exist in ocaml -- writing imperative code in ocaml
is much like writing imperative code in C, albeit with different syntax.
This makes it much easier to transition to for C or python programmers, but
it's easy for side-effects to work their way into your program without you
realizing it, which means you lose a lot of the advantages of functional
programming -- unless you take a lot of care to make sure that most of your
functions are in fact purely functional (and the compiler won't help you
with that).

Another big difference between ocaml and haskell is that haskell has type
classes and ocaml does not.  You can't imagine how great type classes are
until you start using them.  They mirror so much of what you intend a
function to be in the type of the function, and they also allow you to use
functions in a much broader domain than you would expect.  Basically (if
you don't know this already), type classes give you overloading of
functions and operators on new data types, all done at compile time.
Ocaml, in contrast, has functors which allow you to create customized
versions of data structures parameterized on almost anything, but the data
structure you create is a full module.  This is also pretty elegant, but
IMO is much more heavyweight and doesn't have the syntactic advantages of
haskell's type classes.

Since ocaml doesn't have monads at all, a lot of the more advanced monadic
programming that haskellers like to do is much more cumbersome to do in
ocaml.

However, the biggest advantage that ocaml has over haskell is that for most
applications, an ocaml program will run faster, perhaps a lot faster, than
an equivalent haskell program (although the haskell program may be much
smaller, have fewer bugs, be prettier, etc.).  That's because lazy
evaluation in haskell requires the system to wrap closures around
unevaluated code and evaluate it later.  This has a cost, and it simply
isn't there in ocaml.

If you find functional programming *completely* baffling, learning haskell
off the bat is like jumping into the deep end of the swimming pool.
Learning a language like ocaml first can be a good stepping stone to
haskell, since many of the core concepts (like algebraic data types) are
basically the same.  Scheme is another great language to learn FP from,
preferably in conjunction with a good textbook like _How to Design
Programs_ (http://www.htdp.org) or _Structure and Interpretation of
Computer Programs_ (http://mitpress.mit.edu/sicp).  My progression was
scheme - ocaml - haskell, which was nice because I didn't have to add
nearly as much new material at each stage as I would have had to had I
learned e.g. haskell before learning scheme or ocaml.

Mike



 From: Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED]
 Mail-Followup-To: haskell-cafe@haskell.org
 Date: Tue, 03 May 2005 20:38:14 +0200
 
 John Goerzen [EMAIL PROTECTED] writes:
 
  I'd say that there are probably no features OCaml has that Haskell
  lacks that are worth mentioning.
 
 Its type system has some interesting features: polymorphic variants,
 parametric modules, labeled and optional arguments, objects, variance
 annotations of type parameters used for explicit subtyping.
 
 It has more convenient exceptions: the exn type can be extended with
 new cases which look like variants of algebraic types.
 
 There is camlp4 for extending the syntax or changing it completely.
 
 OTOH Haskell provides type classes, better integrated arbitrary
 precision integer type, type variables with kinds other than *,
 polymorphic recursion, much better FFI, and with GHC extensions:
 universal and existential quantifiers in function types (OTOH OCaml
 recently got universal quantifiers in record fields), GADTs, implicit
 parameters, template Haskell.
 
 -- 
__( Marcin Kowalczyk
\__/   [EMAIL PROTECTED]
 ^^ http://qrnik.knm.org.pl/~qrczak/
 ___
 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: Solution to Thompson's Exercise 4.4

2005-03-13 Thread Michael Vanier
 Date: Sun, 13 Mar 2005 00:01:17 -0800
 From: Sean Perry [EMAIL PROTECTED]
 Cc: 
 
 Michael Vanier wrote:
 Date: Sat, 12 Mar 2005 23:39:21 -0800
 From: Sean Perry [EMAIL PROTECTED]
 Cc: Haskell-Cafe@haskell.org
 
 As an aside, I kept all of the exercises in revision control. So I can 
 look back at what I first wrote and my later changes. A habit I plan to 
 keep as I move on to other programming texts and languages.
  
  
  That's a nice approach.  But I can't resist asking: once you've learned
  Haskell, what is there left to move on to? ;-)
  
 
 (-:
 
 I try to learn a new language every other year or so. Lisp and I have 
 butted heads many times. So I thought I would try Haskell -- already 
 love Python and the two are clearly siblings with divorced parents.
 
 Unfortunately since Haskell is neither C nor Perl, I will probably only 
 dabble in it, much like Python. Not a fact I like, but one that the 
 corporate world keeps making me swallow.
 

Actually, haskell and python share little except some syntactic
similarities.  But haskell shares a lot with lisp/scheme.  There are some
good books on scheme e.g. SICP (http://mitpress.mit.edu/~sicp) and How to
Design Programs (http://www.htdp.org) which would be very helpful for the
beginning haskell programmer to absorb (you have to learn to walk before
you can write monadic parser combinators ;-)).  OTOH lisp and scheme are
strict languages, like ocaml, unlike haskell, which is lazy.  That makes a
big difference in practice.

As for C or Perl, try using haskell to generate C or Perl and don't tell
your employers where the C/perl code came from ;-)

Even though I'm just a haskell newbie myself, I think it's the most
interesting language around, by a pretty wide margin.

Mike


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


Re: [Haskell-cafe] Re: Solution to Thompson's Exercise 4.4

2005-03-12 Thread Michael Vanier
 Date: Sat, 12 Mar 2005 23:39:21 -0800
 From: Sean Perry [EMAIL PROTECTED]
 Cc: Haskell-Cafe@haskell.org
 
 As an aside, I kept all of the exercises in revision control. So I can 
 look back at what I first wrote and my later changes. A habit I plan to 
 keep as I move on to other programming texts and languages.

That's a nice approach.  But I can't resist asking: once you've learned
Haskell, what is there left to move on to? ;-)

Mike


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