[Haskell-cafe] Which regular syntax does Text.Regex use?

2007-06-11 Thread L.Guo
Hi All:

I wrote this func :

  match = matchRegex . mkRegex

And when using it, I found that I have not even know the syntax of Regex.

Eager for your hint.

Regards
--
L.Guo
2007-06-11

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


[Haskell-cafe] Shim missing Distribution.Verbosity

2007-06-11 Thread Johan Grönqvist

Hi,

I am trying to install shim (http://shim.haskellco.de/trac/wiki) on 
windows XP (GHC 6.6.1). When I run ./Setup.lhs build, ghc tells me 
that the module Distribution.Verbosity can not be found. The module is 
imported by Shim.GhcCompat.


ghcii also tells me that Distribution.Verbosity can not be found. When I 
look at 
http://www.haskell.org/ghc/docs/latest/html/libraries/index.html, I do 
not see Distribution.Verbosity there either.


I have no idea how to proceed.

Thanks for any help,

Johan

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


Re: [Haskell-cafe] Shim missing Distribution.Verbosity

2007-06-11 Thread Pepe Iborra
Thanks for the report. That was an error I introduced in a previous  
patch, just pushed the fix.


By the way, there is a Shim mailing list at

http://shim.haskellco.de

Cheers
pepe

On 11/06/2007, at 9:22, Johan Grönqvist wrote:


Hi,

I am trying to install shim (http://shim.haskellco.de/trac/wiki) on  
windows XP (GHC 6.6.1). When I run ./Setup.lhs build, ghc tells  
me that the module Distribution.Verbosity can not be found. The  
module is imported by Shim.GhcCompat.


ghcii also tells me that Distribution.Verbosity can not be found.  
When I look at http://www.haskell.org/ghc/docs/latest/html/ 
libraries/index.html, I do not see Distribution.Verbosity there  
either.


I have no idea how to proceed.

Thanks for any help,

Johan

___
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] Which regular syntax does Text.Regex use?

2007-06-11 Thread haskell
L.Guo wrote:
 Hi All:
 
 I wrote this func :
 
   match = matchRegex . mkRegex
 
 And when using it, I found that I have not even know the syntax of Regex.
 
 Eager for your hint.
 

The Text.Regex documentation at
http://www.haskell.org/ghc/docs/latest/html/libraries/regex-compat/Text-Regex.html
merely explains that it uses Uses the POSIX regular expression interface.
The Posix regular expressions are also called extended regular expressions to
distinguish
them from the very old basic regular expressions.

An online copy of a the relevant manual page is at
http://www.wellho.net/regex/posix.html

The specification is at
http://www.opengroup.org/onlinepubs/009695399/basedefs/xbd_chap09.html

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


Re: [Haskell-cafe] Just curios

2007-06-11 Thread Paul Hudak




As reported in the recent HOPL paper, A History of Haskell,
Haskell Brooks Curry actually didn't like his first name! I learned
this when I visited his wife, Virginia Curry, at the time when we
decided to name a language after her husband.

By the way, Haskell Curry's mother's name was Anna Baright and his
father's name was
Samuel Silas Curry. Samuel was the President of the School of
_expression_ in Boston and Anna was the Dean of the school. Haskell met
a student at the School of _expression_ whose name was Mary Virginia
Wheatly, who would later become his bride.

(Silas Curry's school was one of the motivations for naming my book --
the other being that Haskell programs are just expressions :-)

You can learn more about Haskell Curry at:
http://www-groups.dcs.st-and.ac.uk/~history/Biographies/Curry.html

 -Paul


Andrew Coppin wrote:
OK,
so this doesn't actually have anything to do with programming in
Haskell, but...
  
  
How in the name of God does a human being end up walking around with a
name like "Haskell B. Curry"?
  




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


Re: [Haskell-cafe] OSCON 2007, who's going?

2007-06-11 Thread Christopher Milton
--- Evan Lenz [EMAIL PROTECTED] wrote:
 I'll be there for the Haskell tutorial (and Damian Conway's Vim 
 tutorial). I've been to OSCON one other time (2005) and that was to 
 present a tutorial on XSLT. I won't be staying for the conference though.
 
 Portland is nice. I live in Seattle, and we make it down there every so 
 often.
 
 Evan

XSLT is what I do at my dayjob, too. I just presented
a quick tutorial (one hour) on how we like our XSLT
to be done and how to use XPath in the company. None
of the developers who needed to be there showed up.
Next week I do one to show how I use XSLT to route
messages around the company. The support guys asked
for that, since it will help them debug message flows.

Your XSLT 1.0 Pocket Reference is very helpful, but
I wish people would buy their own and stop borrowing
mine all the time. :-D

Today I get to see if we can use Java classes created
by a mapping tool, because their XSLT would not run on
our infrastructure (IBM's WebSphere Message Broker).
The XSLT compiled to bad Java classes, but since the
XSLT was created from Java classes, maybe the original
Java classes might work???

I've been considering both those tutorials as well as
Higher-order Perl and Intro to Rails, but I'll probably
end up in whatever isn't full when I get to registering.
At least my flight and hotel are booked. Now my employers
just have not to cancel my vacation.

My next mission, besides convincing people at work that
I know Perl and Java (most of what I was doing before
they hired me), is to get them to switch to Haskell.

 Christopher Milton wrote:
  Are a lot of Haskellers going to be at OSCON, or just
  Simon Peyton Jones and myself?
 
  http://conferences.oreillynet.com/os2007/
 
  I've never been to Portland, Oregon, before.
 
 
  Chris Milton
  AIM: cmiltonperl
  ___
  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] tail recursion ?

2007-06-11 Thread H .
Hello @ all,

Sometimes one has an imperative algorithm, and wants to write a program in 
Haskell which do has the same effect...

So the question is - how a construct as the following can efficiently be 
written?

--
Pseudo code:
  n[1..1] = false
  for (1..1) |i|
for (i,2*i..1) |j|
  n[j] = not n[j]
--

Certainly it is in this special case equivalent to (True where the index is):
map (^2) [1..100]

But I mean the destructive updates in the imperative code in Haskell without 
filling the (many times more than in imperative languages) memory with 
recursively called functions...


The idea, I thought, is tail recursion, so perhaps I just have a big bug in my 
code, caused by the fact, that it needs even for 5000 approximately 100MB 
memory:

--
import Data.Array

main :: IO ()
main = putStr $! unlines $! map show $! filter snd 
   $! zip [1..] $! elems $! calc $! la 5000
  where la x = array (1,x) [(y,False)|y-[1..x]]

calc :: Array Int Bool - Array Int Bool
calc x = f 1 x
  where
  k :: Int
  k = snd $ bounds x
  f :: Int - Array Int Bool - Array Int Bool
  f !a !x | a  k = f (a+1) $! g a x
  | otherwise = g a x
  g !a !x = x//[(j,not (x!j))|j-[a,a*2..k]]
--


--
Thanks for you answers in advance
H.

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


Re: [Haskell-cafe] Just curios

2007-06-11 Thread Stephen Forrest

On 6/10/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:



You're pretty close, actually :)  Names derived from Hebrew were
fairly common in the Bible belt back when he was born.  (Haskell
from השקל, wisdom.  I half suspect Curry has a Biblical origin
as well, from קרי.)




Bible belt?  Curry was born in Millis, Massachusetts, and grew up in Boston.

The word Haskell seems to occur much more frequently as a surname,
originating in the British Isles.  It seems more plausible that he got the
name Haskell from some relative or family friend somewhere than ascribing
a Hebrew origin for his name.

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


Re: [Haskell-cafe] LaTeX

2007-06-11 Thread tom

I got this from the Literate Haskell page on the Emacs Wiki[1]:

\usepackage{listings}
\lstloadlanguages{Haskell}
\lstnewenvironment{code}
  {\lstset{}%
\csname [EMAIL PROTECTED]
  {\csname [EMAIL PROTECTED]
  \lstset{
basicstyle=\small\ttfamily,
flexiblecolumns=false,
basewidth={0.5em,0.45em},
literate={+}{{$+$}}1 {/}{{$/$}}1 {*}{{$*$}}1 {=}{{$=$}}1
 {}{{$$}}1 {}{{$$}}1 {\\}{{$\lambda$}}1
 {-}{{$\rightarrow$}}2 {=}{{$\geq$}}2 {-}{{$\leftarrow$}}2
 {=}{{$\leq$}}2 {=}{{$\Rightarrow$}}2
 {\ .}{{$\circ$}}2 {\ .\ }{{$\circ$}}2
 {}{{}}2 {=}{{=}}2
 {|}{{$\mid$}}1
  }

That replaces various strings (including ++) with their symbol
equivalents and generally makes things quite pretty.

Tom

[1]: http://haskell.org/hawiki/LiterateProgramming

On 6/8/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Does anybody know what the magical LaTeX command is to turn (say) ++
into two overprinted pluses? (As seems to be fashionable...)

___
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] Head and tail matching question

2007-06-11 Thread Olivier Boudry

Hi all,

I'm trying to write a untab function that would split a string on tabs
and return a list. Code is here.

import Data.List (break, unfoldr)
import Data.Char (String)

untab :: String - [String]
untab s = unfoldr untab' s

untab' :: String - Maybe (String, String)
untab' s | s ==  = Nothing
| otherwise = Just (h, ts)
where (h, t:ts) = break (== '\t') s

This code raises an exception when handling the last portion of the
string. Break returns a (something, ) and t:ts cannot match on .

I was wondering if there way a clean way of handling this last case
without adding tons of code. Some kind of idiomatic expression ;-)

Thanks,

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


Re: [Haskell-cafe] Examples of OpenAL and ALUT?

2007-06-11 Thread Henning Thielemann

On Thu, 7 Jun 2007, Dan Piponi wrote:

 Does anyone have any sample Haskell code they'd like to share for
 doing things like creating a waveform from a list of samples or a
 mathematical function and playing them using these libraries (or
 indeed any easy to install on MacOS X Haskell library)?

I use to listen to real functions by Sox' play command:
 http://darcs.haskell.org/synthesizer/src/Sox/Play.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Head and tail matching question

2007-06-11 Thread Jules Bean

Olivier Boudry wrote:

Hi all,

I'm trying to write a untab function that would split a string on tabs
and return a list. Code is here.

import Data.List (break, unfoldr)
import Data.Char (String)

untab :: String - [String]
untab s = unfoldr untab' s

untab' :: String - Maybe (String, String)
untab' s | s ==  = Nothing
| otherwise = Just (h, ts)
where (h, t:ts) = break (== '\t') s

This code raises an exception when handling the last portion of the
string. Break returns a (something, ) and t:ts cannot match on .



untab' [] = Nothing
untab' s  = Just (h , drop 1 t)
  where (h,t) = break (== '\t') s
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: tail recursion ?

2007-06-11 Thread Jon Fairbairn
H. [EMAIL PROTECTED] writes:

 Hello @ all,
 
 Sometimes one has an imperative algorithm, and wants to write a program in 
 Haskell which do has the same effect...
 
 So the question is - how a construct as the following can efficiently be 
 written?
 
 --
 Pseudo code:
   n[1..1] = false
   for (1..1) |i|
 for (i,2*i..1) |j|
   n[j] = not n[j]
 --
 
 Certainly it is in this special case equivalent to (True where the index is):
 map (^2) [1..100]
 
 But I mean the destructive updates in the imperative code in Haskell without 
 filling the (many times more than in imperative languages) memory with 
 recursively called functions...

The idea in Haskell is not to think of stepping through the
array.  Look at accumArray and ixmap.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: [Haskell-cafe] More on the random idea

2007-06-11 Thread John Meacham
On Sat, May 26, 2007 at 10:59:10AM +0100, Andrew Coppin wrote:
 However, when you consider that the result type could be IO () or IO 
 String or IO [Either (Maybe Int, (String, Bool)) [Either (Int - 
 String) (Complex Integer)]], and the expression itself may well contain 
 the :: sequence... you see we have a nontrivial parsing task here! 
 (Get the parsing wrong and somebody might be able to do Evil Things to 
 the box.)

I think the easiest way to handle this would be to use the module
system. just write a custom prelude that exports everything but 'IO' and
don't allow arbitrary 'imports'. 

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Head and tail matching question

2007-06-11 Thread Simon Brenner

Why not do something like this instead?

untab [] = []
untab xs = head : untab (drop 1 tail)
   where (head, tail) = break (== '\t') xs

BTW, going the extra step through unfoldr seems unnecessary to me - is
there any special reason to prefer unfolds over simple recursive
functions here? (Of course, you do get rid of the explicit recursive
call to untab - but in turn you have to run it all through unfoldr..)

Another, more pointless way is:

untab [] = []
untab xs = uncurry (:) $ second (untab . drop 1) $ break (== '\t') xs

(needs the additional import of Control.Arrow to get second)

On 6/11/07, Jules Bean [EMAIL PROTECTED] wrote:

Olivier Boudry wrote:
 Hi all,

 I'm trying to write a untab function that would split a string on tabs
 and return a list. Code is here.

 import Data.List (break, unfoldr)
 import Data.Char (String)

 untab :: String - [String]
 untab s = unfoldr untab' s

 untab' :: String - Maybe (String, String)
 untab' s | s ==  = Nothing
 | otherwise = Just (h, ts)
 where (h, t:ts) = break (== '\t') s

 This code raises an exception when handling the last portion of the
 string. Break returns a (something, ) and t:ts cannot match on .


untab' [] = Nothing
untab' s  = Just (h , drop 1 t)
   where (h,t) = break (== '\t') s
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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


[Haskell-cafe] Re: tail recursion ?

2007-06-11 Thread H .
Jon Fairbairn jon.fairbairn at cl.cam.ac.uk writes:
 The idea in Haskell is not to think of stepping through the
 array.  Look at accumArray and ixmap.

Thanks for your answer.

But I can't really see how the calc-function can be written more efficiently 
with accumArray or ixmap, perhaps you can write it as an example?

--
Regards,
H.

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


Re: [Haskell-cafe] Just curios

2007-06-11 Thread Fritz Ruehr
For what it's worth, a handful of people who have ordered Haskell  
merchandise from the CafePress store over the years have had  
Haskell as a surname. I assume they look at the designs before they  
buy, and I can't imagine what they think of some of them, but I guess  
the allure of having your (fairly obscure) name on a shirt can be  
irresistible.


Then again, I suppose they could be functional programmers who just  
happen to have Haskell as a surname.


  --  Fritz

PS: In other CafePress-Haskell Shop trivia, 277 items have been sold  
since the turn of the century, at a total price of just over one  
thousand dollars ... but, of course, no profit. (This last seems to  
be a slight problem with our business model.) The most curious order  
to date was a canceled one for 60 junior baby doll t-shirts: I like  
to imagine that some sort of big chorus number was planned for an ill- 
fated Broadway revue, but who can tell?


On Mon 11 Jun 07, at 7:35 am, Stephen Forrest wrote:


On 6/10/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:

You're pretty close, actually :)  Names derived from Hebrew were
fairly common in the Bible belt back when he was born.  (Haskell
from השקל, wisdom.  I half suspect Curry has a Biblical origin
as well, from קרי.)


Bible belt?  Curry was born in Millis, Massachusetts, and grew up  
in Boston.


The word Haskell seems to occur much more frequently as a  
surname, originating in the British Isles.  It seems more plausible  
that he got the name Haskell from some relative or family friend  
somewhere than ascribing a Hebrew origin for his name.


Steve
___
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] Just curios

2007-06-11 Thread Tom Schrijvers

On Mon, 11 Jun 2007, Stephen Forrest wrote:


On 6/10/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:



You're pretty close, actually :)  Names derived from Hebrew were
fairly common in the Bible belt back when he was born.  (Haskell
from , wisdom.  I half suspect Curry has a Biblical origin
as well, from .)




Bible belt?  Curry was born in Millis, Massachusetts, and grew up in Boston.

The word Haskell seems to occur much more frequently as a surname,
originating in the British Isles.  It seems more plausible that he got the
name Haskell from some relative or family friend somewhere than ascribing
a Hebrew origin for his name.


I found this:

HASKEL:  Hebrew name meaning intellect.  Variant, Haskell, exists.

in a list name explanations:

http://www.smcm.edu/users/saquade/names.html

Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: tail recursion ?

2007-06-11 Thread Jon Fairbairn
H. [EMAIL PROTECTED] writes:

 Jon Fairbairn jon.fairbairn at cl.cam.ac.uk writes:
  The idea in Haskell is not to think of stepping through the
  array.  Look at accumArray and ixmap.
 
 Thanks for your answer.
 
 But I can't really see how the calc-function can be written more efficiently 
 with accumArray or ixmap, perhaps you can write it as an example?

Well, for your example, neither is needed since you could
write something like:

 upb = 1
 listArray (1,upb) (repeat False)
   //map (\n-(2^n,True)) [1..floor (logBase 2 $ fromIntegral upb)]

or

 a = listArray (1,upb) (repeat False)
 b = a//map (\n-(2^n,not (a!(2^n [1..floor (logBase 2 $ fromIntegral upb)]

but the first one is obviously better,
so it depends on what you really want to do.


-- 
Jón Fairbairn [EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2007-05-07)

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


Re: [Haskell-cafe] Re: tail recursion ?

2007-06-11 Thread Simon Brenner

The key is letting haskell be lazy and produce the output one item at
a time. My solution below generates a list of all indices to be
inversed (with indices being duplicated as appropriate), then for each
index in that list inverses the corresponding element in the array.
The list can be written compactly using either list comprehensions or
list monads.

Using list monads:


listOfIndices ubound = [1..ubound] = \i - [i,(2*i) .. ubound]


and using list comprehension and concatenation - slightly longer but
probably more readable:


listOfIndices' ubound = concat [ [i,(2*i) .. ubound] | i - [1..ubound] ]


const . not == (\x _ - (not x)), i.e. a function that discards the
second argument and returns the complement of the first.


calc ubound = accumArray (const.not) False (1,ubound) $
[(x,False) | x - listOfIndices ubound]


zip [1..] (elems arr) == assocs arr
putStrLn . unlines . map show ~~ mapM_ print

main = mapM_ print $ filter snd $ assocs $ calc 10


This solution goes up to 100k in 25M of heap and up to 400k in 200M of
heap. While working better, the space requirement seems to be (at
least almost) quadratic, so this is probably not a complete solution
to your problem (unless all you really needed was those 10k elements,
or at most 400k).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: tail recursion ?

2007-06-11 Thread Jon Fairbairn
Simon Brenner [EMAIL PROTECTED] writes:

 The key is letting haskell be lazy and produce the output one item at
 a time.

True.
 This solution goes up to 100k in 25M of heap and up to 400k in 200M of
 heap. While working better, the space requirement seems to be (at
 least almost) quadratic, so this is probably not a complete solution
 to your problem (unless all you really needed was those 10k elements,
 or at most 400k).

Hmmm... what were you testing?

 :m Data.Array
Prelude Data.Array let test upb = let a = listArray (1,upb) (repeat False) in  
a//map (\n-(2^n,not (a!(2^n [1..floor (logBase 2 $ fromIntegral upb)] ! 
upb 
(0.02 secs, 1567316 bytes)
Prelude Data.Array test 10
False
(0.02 secs, 1310876 bytes)
Prelude Data.Array test 40
False
(0.09 secs, 3710792 bytes)
Prelude Data.Array test 80
False
(0.16 secs, 6913864 bytes)
Prelude Data.Array 



-- 
Jón Fairbairn [EMAIL PROTECTED]


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


[Haskell-cafe] Thought for today

2007-06-11 Thread Andrew Coppin
Data in Haskell is like Schrodinger's famous undead cat - it doesn't 
'exist' until you 'obverse' it.



I just thought I'd share this useful (?) metaphore for describing to 
people what lazy evaluation is all about. ;-)


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


Re: [Haskell-cafe] Just curios

2007-06-11 Thread Andrew Coppin

Paul Hudak wrote:
As reported in the recent HOPL paper, /A History of Haskell/, Haskell 
Brooks Curry actually didn't like his first name!  I learned this when 
I visited his wife, Virginia Curry, at the time when we decided to 
name a language after her husband.


Yes... I recall reading that somewhere. (Irony, eh? Name something after 
somebody and find they hated the name anyway...)



I *also* distinctly recall reading somewhere the following words:

 Of course, our biggest mistake was using the word 'monad'. We should 
have called it 'warm fuzzy thing'...


Damned if I can remember who said that or where they said it though! _

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


Re: [Haskell-cafe] Just curios

2007-06-11 Thread Thomas Schilling

On 6/11/07, Andrew Coppin [EMAIL PROTECTED] wrote:

  Of course, our biggest mistake was using the word 'monad'. We should
have called it 'warm fuzzy thing'...


You know that thing called Google? ;)

 http://lambda-the-ultimate.org/node/92

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


[Haskell-cafe] Re: Existentials and type var escaping

2007-06-11 Thread Ben Rudiak-Gould

Roberto Zunino wrote:

foo, as defined above does not work (lazy patterns not allowed), and in

foo y = E (case y of E x - x)

a variable escapes. I also tried with CPS with no success.

Is foo definable at all? I'm starting to think that it is not, and that
there must be a very good reason for that...


It's not definable, and there is a good reason. Existential boxes in 
principle contain an extra field storing their hidden type, and the type 
language is strongly normalizing. If you make the type argument explicit, 
you have


  foo (E t x) = E t x
  foo _|_ = E ??? _|_

The ??? can't be a divergent type term, because there aren't any; it must be 
a type, but no suitable type is available (foo has no type argument). You 
can't even use some default dummy type like (), even though _|_ does have 
that type, because you'd have to solve the halting problem to tell when it's 
safe to default.


I'm less clear on how important it is that type terms don't diverge. I think 
it may be possible to write cast :: a - b if this restriction is removed, 
but I don't actually know how to do it.


-- Ben

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


[Haskell-cafe] found monad in a comic

2007-06-11 Thread Marc A. Ziegert

http://xkcd.com/c248.html
( join /= coreturn )

IMHO this could be a beautiful and easy way to explain monads.
comments?

- marc




pgpTFyuRioL8Y.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] found monad in a comic

2007-06-11 Thread Derek Elkins
On Tue, 2007-06-12 at 04:16 +0200, Marc A. Ziegert wrote:
 http://xkcd.com/c248.html
 ( join /= coreturn )
 
 IMHO this could be a beautiful and easy way to explain monads.
 comments?
 
 - marc

Reader IceCream

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


[Haskell-cafe] Monad Transformer (Was: Just curios)

2007-06-11 Thread Henning Thielemann

On Mon, 11 Jun 2007, Andrew Coppin wrote:

 Paul Hudak wrote:
  As reported in the recent HOPL paper, /A History of Haskell/, Haskell
  Brooks Curry actually didn't like his first name!  I learned this when
  I visited his wife, Virginia Curry, at the time when we decided to
  name a language after her husband.

 Yes... I recall reading that somewhere. (Irony, eh? Name something after
 somebody and find they hated the name anyway...)


 I *also* distinctly recall reading somewhere the following words:

   Of course, our biggest mistake was using the word 'monad'. We should
 have called it 'warm fuzzy thing'...

This is no longer a problem, because you can visit a web with (almost) no
monads:
  
http://saxophone.jpberlin.de/MonadTransformer?source=http%3A%2F%2Fwww%2Ehaskell%2Eorg%2Fhaskellwiki%2FCategory%3AMonad

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