Re: [Haskell-cafe] Python vs Haskell in tying the knot

2009-07-15 Thread Matthew Brecknell
Robert Greayer wrote:
> Isn't tying the knot (in the way 'fib' does) straightforward with closures
> a la Python/Ruby/Smalltalk (without mutation)?
> Even in a syntactically clumsy language like Java, a
> tying-the-knot implementation equivalent to the canonical Haskell one is
> not difficult, e.g.
> 
> static L fibs = new L() {
> public int head() { return 1; }
> public L tail() {
> return  new L() {
> public int head() { return 1; }
> public L tail() {
> return new L() {
> public int head() { return fibs.head() +
> fibs.tail().head(); }
> public L tail() { return zip(fibs.tail(),
> fibs.tail().tail()); }
> };
> }
> };
> }
> };
> 
> Given a definition of list L and zip...
> 
> interface L { int head(); L tail(); }
> static L zip(final L l0, final L l1) {
> return new L() {
> public int head() { return l0.head() + l1.head(); }
> public L tail() { return zip(l0.tail(), l1.tail()); }
> };
> }

Are you sure there's not a super-linear time complexity hidden in there?

Unless Java compilers are clever enough to memoize this kind of code, I
think each subsequent call to the head() will just recurse all the way
down to the bottom an exponentially increasing number of times.

To simulate laziness, I think you would need to actually store fibs *as
data* somewhere, and you'd presumably need to simulate the process of
replacing a thunk with its value on its first evaluation.

In python, for example:

class value:
  def __init__(self, *value):
self.value = value
  def __call__(self):
return self.value

class thunk:
  def __init__(self, susp):
self.susp = susp
  def __call__(self):
try: return self.result
except:
  self.result = self.susp()
  del self.susp
  return self.result

def tail(xs):
  x,r = xs()
  return r

def zipWithPlus(xs,ys):
  x,xr = xs()
  y,yr = ys()
  return x+y, thunk(lambda: zipWithPlus(xr,yr))

fibs = value(0, value(1, thunk(lambda: zipWithPlus(fibs, tail(fibs)

def fibgen():
  g = fibs
  while True:
x,g = g()
yield x

Needless to say: I prefer the Haskell!


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


Re: [Haskell-cafe] Python vs Haskell in tying the knot

2009-07-15 Thread Robert Greayer
On Wed, Jul 15, 2009 at 2:18 PM, Max Rabkin wrote:
> On Wed, Jul 15, 2009 at 7:33 PM, Cristiano
> Paris wrote:
>> fib = 1:1:fib `plus` (tail fib) where plus = zipWith (+)
> ...
> ...
> This indicates that you think tying the knot should be impossible in
> Python. In my opinion this is not the case. By my definition of tying
> the knot, one needs *either* mutable variables or laziness (at least
> in simple cases). Since Python has the former, it is possible to tie
> the knot in Python.

Isn't tying the knot (in the way 'fib' does) straightforward with closures
a la Python/Ruby/Smalltalk (without mutation)?
Even in a syntactically clumsy language like Java, a
tying-the-knot implementation equivalent to the canonical Haskell one is
not difficult, e.g.

static L fibs = new L() {
public int head() { return 1; }
public L tail() {
return  new L() {
public int head() { return 1; }
public L tail() {
return new L() {
public int head() { return fibs.head() +
fibs.tail().head(); }
public L tail() { return zip(fibs.tail(),
fibs.tail().tail()); }
};
}
};
}
};

Given a definition of list L and zip...

interface L { int head(); L tail(); }
static L zip(final L l0, final L l1) {
return new L() {
public int head() { return l0.head() + l1.head(); }
public L tail() { return zip(l0.tail(), l1.tail()); }
};
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Richard O'Keefe


On Jul 15, 2009, at 9:57 PM, Magicloud Magiclouds wrote:


Hi,
 I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
could not be compiled, parse error.


I apologise to everyone for my previous message in this
thread.  There was a Haskell message in amongst some Erlang
messages, and I thought this was an Erlang problem.

There are some programming languages, including Erlang,
in which  ++  IS accepted as a
.  Haskell is not one of them.  It could be,
and there would be no ambiguity in elementary cases,
and it would no more involve matching against ++ than
n+1 involves matching against +.  Since the pattern on
the left of the ++ is required to be an explicit list,
there is no the slightest question of backtracking or
anything more general than ordinary pattern matching.

Consider
[a,b,c]++xs
 a:b:c:xs

The second is in general shorter (though less clear; it is
a real pity that Haskell syntax doesn't include something
like Clean's [head:tail], the inconsistency is irritating).
It's not the general case that this syntax was invented for,
but the case where the list is a string.

"abc"++xs
'a':'b':'c':xs

One of the arguments advanced against n+k patterns is
"which scope should + be looked up in? what if the + in
the standard prelude is not in scope?"

The same question can be asked about list++tail patterns;
what should it mean if the prelude's ++ was not in scope?

Programmers who have met "abc"++Xs sometimes turn around
and ask for Xs++"abc".  Perhaps it is better to keep the
camel's nose out of the tent.

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


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Richard O'Keefe


On Jul 15, 2009, at 9:59 PM, minh thu wrote:


2009/7/15 Magicloud Magiclouds :

Hi,
I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
could not be compiled, parse error.


++ is a function; you can't pattern-match on that.


Doesn't matter, it's not trying to.
Part of Erlang syntax is that in a pattern
[c1,...,cn] ++ P
is equivalent to
[c1,...,cn|P]

For example,
wee(X) ->
F = fun ([0,1] ++ L) -> L end,
F(X).
is perfectly legal.

The problem might be the "xs", or it might be the "=".
Presumably it should be

fun ([0,1] ++ Xs) -> ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: 20 years ago

2009-07-15 Thread Richard O'Keefe


On Jul 15, 2009, at 5:25 PM, Benjamin L.Russell wrote:

it interesting that you should use the biological term "disease";
according to a post [1] entitled "Re: Re: Smalltalk Data Structures
and Algorithms," by K. K. Subramaniam, dated "Mon, 29 Jun 2009
11:25:34 +0530," on the squeak-beginners mailing list (see
http://lists.squeakfoundation.org/pipermail/beginners/2009-June/006270.html) 
,

Concepts in Squeak [a dialect and implementation of Smalltalk] have

their origins

in biology rather than in computational math


That posting is wrong.

Smalltalk's roots are very firmly planted in Lisp,
with perhaps a touch of Logo (which also had its roots in Lisp).
The classic Smalltalk-76 paper even contains a meta-circular
interpreter, which I found reminiscent of the old Lisp one.
The "biological" metaphor in Smalltalk is actually a SOCIAL
metaphor: sending and receiving messages, and a "social"
model of agents with memory exchanging messages naturally
leads to anthropomorphisms.

The other classic OO language, which inspired C++, which
inspired Java, which inspired C#, is Simula 67, which has
its roots in Algol 60.  While Simula 67 was sometimes used
for simulating biological processes, the main background
was discrete event systems like factories and shops; there
are no biological metaphors in Simula.


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


[Haskell-cafe] Re: Mixing C and Haskell code in the same file

2009-07-15 Thread Maurí­cio

#def inline int signof(int x) {return x<0?-1:x>0?1:0;}
foreign import ccall safe ""
  signof :: CInt -> CInt


Is it possible to get that #def as a result of
a macro? Say, something like this:

---

(WARNING: invalid code)

#define ret(name,value,type) \
  #def inline type name (void) {return value;}

---

Thanks,
Maurício

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


[Haskell-cafe] Re: Problems with nested Monads

2009-07-15 Thread John Lato
If M is a monad transformer (e.g. StateT) and able to be parameterised
over an arbitrary monad, you can do something related, which may
actually be more useful to you.

Given the definition of StateT from mtl:

newtype StateT s m a = StateT {
runStateT :: s -> m (a, s)
}

you could define this join-like function:

join2 :: (Monad n) => n (StateT s n a) -> StateT s n a
join2 m = StateT (\state -> m >>= flip runStateT state)

(I don't know a good name for this function; it's called "joinIM" in iteratee)

Perhaps this would apply to your situation?

Cheers,
John Lato


>
> Message: 18
> Date: Fri, 10 Jul 2009 17:25:55 -0400
> From: Job Vranish 
> Subject: Re: [Haskell-cafe] Problems with nested Monads
> To: Edward Kmett 
> Cc: Haskell Cafe mailing list 
> Message-ID:
>        
> Content-Type: text/plain; charset="iso-8859-1"
>
> Yeah, I think the problem with my case is that while M is a specific monad
> (essentially StateT), N can be an arbitrary monad, which I think destroys my
> changes of making a valid joinInner/joinOuter/distribute.
> Maybe someday Haskell will infer valid joinInner/joinOuter for simple cases
> :D
> Thanks for you help. I'll definitely have to see if I can find that paper.
>
> - Job Vranish
>
> On Fri, Jul 10, 2009 at 3:09 PM, Edward Kmett  wrote:
>
>> The problem you have is that monad composition isn't defined in general.
>> You would need some form of distributive law either for your monads in
>> general, or for your particular monads wrapped around this particular kind
>> of value.
>>
>> What I would look for is a function of the form of one of:
>>
>> distribute :: N (M a) -> M (N a)
>> joinInner :: M (N (M a)) -> M (N a)
>> joinOuter :: N (M (N a)) -> M (N a)
>>
>> that holds for your partiular monads M and N.
>>
>> IIRC Mark P. Jones wrote a paper or a lib back around '93 that used these
>> forms of distributive laws to derive monads from the composition of a monad
>> and a pointed endofunctor.
>>
>> -Edward Kmett
>>
>> On Fri, Jul 10, 2009 at 11:34 AM, Job Vranish  wrote:
>>
>>> I'm trying to make a function that uses another monadic function inside a
>>> preexisting monad, and I'm having trouble.
>>> Basically my problem boils down to this. I have three monadic functions
>>> with the following types:
>>> f :: A -> M B
>>> g :: B -> N C
>>> h :: C -> M D
>>> (M and N are in the monad class)
>>> I want a function i where
>>> i :: A -> M (N D)
>>>
>>> the best I can come up with is:
>>> i :: A -> M (N (M D))
>>> i a = liftM (liftM h) =<< (return . g) (f a)
>>>
>>> I'm starting to feel pretty sure that what I'm going for is impossible. Is
>>> this the case?
>>> ___
>>> 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] Debugging methods for haskell

2009-07-15 Thread Anton van Straaten

Fernan Bolando wrote:

Program error: Prelude.!!: index too large

This is not very informative. It did not give me a hint which function
was causing this. 


In addition to the debugging methods that have been mentioned, the 
"Safe" library provides a way to write the code more robustly and/or 
informatively:


  http://hackage.haskell.org/package/safe
  http://community.haskell.org/~ndm/safe/

Among other things, it provides replacements for the (!!) operator which 
would have likely have helped in this case.


Anton

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


Re: [Haskell-cafe] homomorphic encryption and monads?

2009-07-15 Thread Dan Weston

I think there may be a problem here.

"Homomorphic encryption is a form of encryption where one can perform a 
specific algebraic operation on the plaintext by performing a (possibly 
different) algebraic operation on the ciphertext. "


The word "specific" means that the functor is discrete, not continuous. 
Only Integer can be encoded. Also, the arrow mapping is partial: fmap 
does not accept arbitrary any (a -> b) but only a natural transformation 
pair (in,out).


That would make Encryption an indexed arrow, something like

class Arrow a => In a b where
  in :: a b Integer

class Arrow a => Out a c where
  out :: a Integer c

instance (In a b, Out a c) => Arrow a b c where
 arr f = in >>> f >>> out

Dan

Max Rabkin wrote:

On Wed, Jul 15, 2009 at 11:54 PM, Jason Dagit wrote:

Hello,

I have just a very vague understanding of what homomorphic encryption is,
but I was wondering if homomorphic encryption behaves as a one-way monad
(like IO).


An interesting idea. Let's see where this leads.


I could be mistaken about the way this works, but it seems that isSpam can't
return a plain 'Bool' because then you could know things about the encrypted
data without having to decrypt it first.  So that is why I think it has to
return "Cypher Bool".


Yes, this is the idea behind homomorphic encryption: you can do some
work on an encrypted input, and get an encrypted output.

Your categorical spidey-sense should be tingling right now, and indeed
it did, but you interpreted it wrong (but it's a common trap)


And because it's a homomorphic encryption, you could have something like
doWork:
doWork :: Cypher a -> (a -> b) -> Cypher b


Looks good. This type should send your spidey-sense into the red.


Which we could use to implement isSpam:

isSpam s = doWork s spamTest
  where spamTest :: String -> Bool

Thinking about it a bit more, since we never have to decrypt the
data to work with it, it seems that (a -> b) is wrong as well, because we
don't have the key or whatever to do the decrypting.


(a -> b) is not wrong. Homomorphic encryption gives you exactly this
*magic* function that takes an ordinary f :: a -> b, and applies it to
a Cypher a, giving you a Cypher b. No deciphering happens. The
function get lifted/mapped into Cypher.


So, then it seems reasonable that the only type for doWork is this:
doWork :: Cypher a -> (Cypher a -> Cypher b) -> Cypher b

Which doesn't really seem all that useful now.


Indeed. That is just (a restricted version of) the type of 'flip ($)',
a rather uninteresting (though not useless) function.


On the other hand, maybe we have an algorithm which can take a function on
normal values and gives us a function on Cypher values:

enCypher :: (a -> b) -> Cypher a -> Cypher b


This is exactly what you have. This is just the flipped version of
your first doWork.

And this function is better known as fmap. Cypher is a Functor.

Because they have special syntax, are widely used in IO, and have a
scary name (and perhaps for other, better reasons too), Monads seem to
attract special attention.

Functor and Applicative get much less love, but both are valuable and
interesting typeclasses (they form a hierarchy: every monad is an
applicative functor, and ever applicative functor is a functor). And
hopefully your spidey-sense now has a Functor-detector :)

I was planning to show that Cypher can't be a monad or an applicative
functor, but their seems to be a hole in my thinking. Hopefully I can
fix it, and hopefully everything I've said up to now has been correct.

--Max
___
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] Debugging methods for haskell

2009-07-15 Thread Marc Weber
Of course !! is only one cause for this kind of errror. Another is
ghci> head []
*** Exception: Prelude.head: empty list

Unfortunately this kind of bug is very hard to debug due to the lazy
nature of haskell. You don't have a stack trace as in Java, PHP, ..
Example:

data D = D String

a,b :: [String]
a = head []
b = head []

main = do
  let first = a
  second = b

  print first -- both will cause the same error but a different head caused the 
exception
  print second


One solution is using interlude from hackage. I'm not sure wether it
supports !!

Also try this haskell-cafe search (you may have to up to page 20 or so)
http://search.gmane.org/?query=empty+list+head&author=&group=gmane.comp.lang.haskell.cafe&sort=relevance&DEFAULTOP=and&xP=Zempti%09Zlist&xFILTERS=Gcomp.lang.haskell.cafe---A

This reveals this thread for example:
http://article.gmane.org/gmane.comp.lang.haskell.cafe/14921/match=empty+list+head
http://article.gmane.org/gmane.comp.lang.haskell.cafe/6719/match=empty+list+head

I recall there was another method. Yeah, I even found it (using ghci and set 
-fbreak-on-exception)
http://donsbot.wordpress.com/2007/11/14/no-more-exceptions-debugging-haskell-code-with-ghci/

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


[Haskell-cafe] ANNOUNCE: generator

2009-07-15 Thread Yair Chuchem

A new "generator" package has been uploaded to Hackage.

It implements an alternative list monad transformer, a list class, and  
related functions.


The difference from mtl/transformers's ListT is that
mtl is a monadic action that returns a list:
newtype ListT m a = ListT { runListT :: m [a] }
generator's is a monadic list:
data ListItem l a =  Nil | Cons { headL :: a, tailL :: l a }
newtype ListT m a = ListT { runListT :: m (ListItem (ListT m) a) }
A short example program which reads numbers from the user and  
interactively sums them up:

import Control.Monad.ListT (ListT)
import Data.List.Class (execute, joinM, repeat, scanl, takeWhile)
import Prelude hiding (repeat, scanl, takeWhile)

main =
  execute . joinM . fmap print .
  scanl (+) 0 .
  fmap (fst . head) .
  takeWhile (not . null) .
  fmap reads .
  joinM $ (repeat getLine :: ListT IO (IO String))
I also wrote an example/blog-post about using ListT to add an undo  
option to the classic game of "hamurabi":

http://mashebali.blogspot.com/2009/07/charlemagne-disraeli-and-jefferson.html

Another interesting observation is that "ListT [] a" is a tree of "a"s.
The module Data.List.Tree includes functions to prune and search such  
trees (dfs, bfs, bestFirstSearchOn, etc).
This can be useful for modularizing code that uses the list monad for  
combinatoric search by decoupling tree creation from processing and  
pruning.


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


Re: [Haskell-cafe] homomorphic encryption and monads?

2009-07-15 Thread Max Rabkin
On Wed, Jul 15, 2009 at 11:54 PM, Jason Dagit wrote:
> Hello,
>
> I have just a very vague understanding of what homomorphic encryption is,
> but I was wondering if homomorphic encryption behaves as a one-way monad
> (like IO).

An interesting idea. Let's see where this leads.

> I could be mistaken about the way this works, but it seems that isSpam can't
> return a plain 'Bool' because then you could know things about the encrypted
> data without having to decrypt it first.  So that is why I think it has to
> return "Cypher Bool".

Yes, this is the idea behind homomorphic encryption: you can do some
work on an encrypted input, and get an encrypted output.

Your categorical spidey-sense should be tingling right now, and indeed
it did, but you interpreted it wrong (but it's a common trap)

> And because it's a homomorphic encryption, you could have something like
> doWork:
> doWork :: Cypher a -> (a -> b) -> Cypher b

Looks good. This type should send your spidey-sense into the red.

> Which we could use to implement isSpam:
>
> isSpam s = doWork s spamTest
>   where spamTest :: String -> Bool
>
> Thinking about it a bit more, since we never have to decrypt the
> data to work with it, it seems that (a -> b) is wrong as well, because we
> don't have the key or whatever to do the decrypting.

(a -> b) is not wrong. Homomorphic encryption gives you exactly this
*magic* function that takes an ordinary f :: a -> b, and applies it to
a Cypher a, giving you a Cypher b. No deciphering happens. The
function get lifted/mapped into Cypher.

> So, then it seems reasonable that the only type for doWork is this:
> doWork :: Cypher a -> (Cypher a -> Cypher b) -> Cypher b
>
> Which doesn't really seem all that useful now.

Indeed. That is just (a restricted version of) the type of 'flip ($)',
a rather uninteresting (though not useless) function.

> On the other hand, maybe we have an algorithm which can take a function on
> normal values and gives us a function on Cypher values:
>
> enCypher :: (a -> b) -> Cypher a -> Cypher b

This is exactly what you have. This is just the flipped version of
your first doWork.

And this function is better known as fmap. Cypher is a Functor.

Because they have special syntax, are widely used in IO, and have a
scary name (and perhaps for other, better reasons too), Monads seem to
attract special attention.

Functor and Applicative get much less love, but both are valuable and
interesting typeclasses (they form a hierarchy: every monad is an
applicative functor, and ever applicative functor is a functor). And
hopefully your spidey-sense now has a Functor-detector :)

I was planning to show that Cypher can't be a monad or an applicative
functor, but their seems to be a hole in my thinking. Hopefully I can
fix it, and hopefully everything I've said up to now has been correct.

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


Re: [Haskell-cafe] Debugging methods for haskell

2009-07-15 Thread Don Stewart
fernanbolando:
> Hi all
> 
> I recently used 2 hours of work looking for a bug that was causing
> 
> Program error: Prelude.!!: index too large
> 
> This is not very informative. It did not give me a hint which function
> was causing this. In C adding a few printf would have helped me, but
> in haskell I was not sure how to do that. Can anybody point me to some
> debuggin method everyone uses.

You could:

* use Debug.Trace.trace  (equivalent of printf debugging)
* use asserts: the 'assert' function
* use the GHCi debugger to construct a stack trace
* use profiling to construct a stack trace.
* use the GHC head branch for first class stack traces, described
  in, "Finding the needle: Stack Traces for GHC"

http://pubs.doc.ic.ac.uk/finding-the-needle/finding-the-needle.pdf

-- Don

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


[Haskell-cafe] Debugging methods for haskell

2009-07-15 Thread Fernan Bolando
Hi all

I recently used 2 hours of work looking for a bug that was causing

Program error: Prelude.!!: index too large

This is not very informative. It did not give me a hint which function
was causing this. In C adding a few printf would have helped me, but
in haskell I was not sure how to do that. Can anybody point me to some
debuggin method everyone uses.

After 2 hours I did find the bug eventually. The code can be viewed here.
Maybe some reformatting of the code would make finding bugs easier?
http://plan9.bell-labs.com/sources/contrib/fernan/escomma/

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


[Haskell-cafe] homomorphic encryption and monads?

2009-07-15 Thread Jason Dagit
Hello,

I have just a very vague understanding of what homomorphic encryption is,
but I was wondering if homomorphic encryption behaves as a one-way monad
(like IO).

So for example, suppose you wrote a function that worked on encrypted email
to determine if it spam, maybe it looks like this:
isSpam :: Cypher String -> Cypher Bool

I could be mistaken about the way this works, but it seems that isSpam can't
return a plain 'Bool' because then you could know things about the encrypted
data without having to decrypt it first.  So that is why I think it has to
return "Cypher Bool".

And because it's a homomorphic encryption, you could have something like
doWork:
doWork :: Cypher a -> (a -> b) -> Cypher b

Which we could use to implement isSpam:

isSpam s = doWork s spamTest
  where spamTest :: String -> Bool

I initially thought that doWork should be (>>=), but it seems the type of
the function should either be (a -> b) or (Cypher a -> Cypher b).  That is,
return :: a -> Cypher a, is not available.  All the data should already be
encrypted.  Thinking about it a bit more, since we never have to decrypt the
data to work with it, it seems that (a -> b) is wrong as well, because we
don't have the key or whatever to do the decrypting.

So, then it seems reasonable that the only type for doWork is this:
doWork :: Cypher a -> (Cypher a -> Cypher b) -> Cypher b

Which doesn't really seem all that useful now.

On the other hand, maybe we have an algorithm which can take a function on
normal values and gives us a function on Cypher values:

enCypher :: (a -> b) -> Cypher a -> Cypher b

Or perhaps, it should be:

enCypher :: (a -> b) -> Cypher (a -> b)

Which would match the type of return.

If that is the type of return, then we probably want:
(>>=) :: Cypher (a -> b) -> ((a -> b) -> Cypher (c -> d)) -> Cypher (c -> d)

At this point, I'm not actually sure if the second type for enCypher makes
any sense.  But, if it does, then I think it says the purpose of the monad
is to act on the transformations and not the data.  That is, instead of
focusing on the data as being held in the cypher, we are thinking of the
functions as being transformed into a cypher space.

Has anyone else been thinking about this?

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


Re: [Haskell-cafe] Python vs Haskell in tying the knot

2009-07-15 Thread Max Rabkin
On Wed, Jul 15, 2009 at 7:33 PM, Cristiano
Paris wrote:
> fib = 1:1:fib `plus` (tail fib) where plus = zipWith (+)
>
> Of course, this was something I already encountered when exploring the
> Y-combinator. Anyhow, I tried to translate this implementation to
> Python using Iterators and this is what I wrote:
>
> def fib():
>  yield 1
>  yield 1
>
>  p = plus(fib(),tail(fib()))
>
>  while True:
>    yield p.next()
>
> def plus(x,y):
>  while True:
>    yield x.next() + y.next()
>
> print take(5,fib())

I'm not convinced that this is the "same" program as the Haskell version.

No knot is tied in the Python version. To tie the knot, a data
structure must contain or refer to itself. In the python version, the
function which creates the data structure refers to itself, but many
copies of the data structure are created.

> So my considerations are:
>
> 1 - The Fibonacci generator is not an example of TTK at all and then
> it can be translated to Python.

This indicates that you think tying the knot should be impossible in
Python. In my opinion this is not the case. By my definition of tying
the knot, one needs *either* mutable variables or laziness (at least
in simple cases). Since Python has the former, it is possible to tie
the knot in Python.

To me the simplest example of TTK in Python (not possible in Haskell
because it has an infinite type):

x = []
x.append(x)

(If you try to print this list, one gets [[...]] in the standard REPL
and [] in ipython)

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


[Haskell-cafe] Re: Haskell Zippers on Wikibooks: teasing! :)

2009-07-15 Thread Jon Fairbairn
Matthias Görgens  writes:

>> doesn't make much sense to me yet, although I suspect I can read the mu as a
>> lambda on types?
>
> Not really.  The mu has more to do with recursion.

I'd say it's entirely to do with recursion. It's like the Y combinator
(or fix) for types, though it is combined with a lambda.

mu t . t is like fix (\t -> t)

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

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


[Haskell-cafe] ANN: shelltestrunner 0.6 released

2009-07-15 Thread Simon Michael

(and, the original which I didn't cc to -cafe.)

I'm pleased to announce the first release of shelltestrunner: a small  
tool for testing any command-line program by running it through  
"shell" tests defined with a simple file format. Each test can specify  
the command-line arguments, input, expected output, expected stderr  
output, and/or expected exit code.


This was extracted from the hledger project, inspired by the tests in  
John Wiegley's ledger project, and uses Max Bolingbroke's test- 
framework. In some cases you will get a big speedup by using test- 
framework's parallelising feature.


Example:

$ shelltestrunner shelltestrunner *.test -- -j8
:args.test:1: [OK]
:args.test:2: [OK]
:args.test:3: [OK]
:args.test:4: [OK]
:early-j-option.test: [OK]
:help-flag.test: [OK]
etc.

I hope you find it useful. Feedback, patches, or alternate packaging  
suggestions are welcome!


Best,
-Simon

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


[Haskell-cafe] Re: ANN: shelltestrunner 0.6 released

2009-07-15 Thread Simon Michael

And the urls:

home - http://hackage.haskell.org/package/shelltestrunner
darcs repo - http://joyful.com/repos/shelltestrunner


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


Re: [Haskell-cafe] Haskell Zippers on Wikibooks: teasing! :)

2009-07-15 Thread Matthias Görgens
> doesn't make much sense to me yet, although I suspect I can read the mu as a
> lambda on types?

Not really.  The mu has more to do with recursion.

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


[Haskell-cafe] Python vs Haskell in tying the knot

2009-07-15 Thread Cristiano Paris
Hi,

as pointed out in this list, it seems that a "tying the knot" example
would be the one better explaining the power of Haskell's
lazy-by-default approach against Python+Iterator's approach to
laziness.

So, in these days I'm trying to grasp the meaning of this "tying the
knot" concept which seems to be quite hard to understand for me (at
least as much as Monads and Delimited Continuations were).
Specifically, I was looking for a very basic example of TTK and came
up with this implementation of Fibonacci (again!) which might possibly
be a TTK-flavored way for generation:

fib = 1:1:fib `plus` (tail fib) where plus = zipWith (+)

Of course, this was something I already encountered when exploring the
Y-combinator. Anyhow, I tried to translate this implementation to
Python using Iterators and this is what I wrote:

def fib():
  yield 1
  yield 1

  p = plus(fib(),tail(fib()))

  while True:
yield p.next()

def plus(x,y):
  while True:
yield x.next() + y.next()

print take(5,fib())

I've omitted the implementation for tail() and take() for brevity.
Apart from the iterator machinery, this is an direct translation of
the Haskell's fib implementation. More, it's quite modular because fib
lives by itself and is composed with take to get the final result. The
only caveat in the Python code is that it maintains an O(n^2)
Iterator's states, thus making it a very poor implementation.

So my considerations are:

1 - The Fibonacci generator is not an example of TTK at all and then
it can be translated to Python.
2 - The Fibonacci generator is a too simple example of TTK, easy to be
translated to Python.
3 - The O(n^2) state caveat is THE point making the difference between
Haskell and Python, for which Haksell is much more efficient that
Python while remaining very expressive and idiomatic (but that may not
be the case for other TTK examples).

I'm trying to implement myself the doubly linked list example from the
Wikipage, which is "certified" to be a TTK example, but I'd like to
have your comments on this.

Thank you.

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


Re: [Haskell-cafe] laziness blowup exercise

2009-07-15 Thread Ryan Ingram
On Tue, Jul 14, 2009 at 6:02 PM, Thomas Hartman wrote:
> myiterate f x =
>  let nxt = f x
>  in nxt `seq` x : myiterate f nxt

iterate' f x = x `seq` x : iterate' f (f x)
seems better; it doesn't evaluate list elements you don't visit.

> let test = 1 : 2 : 3 : undefined in last $ take 4 $ myiterate (test !!) 0
*** Exception: Prelude.undefined

> let test = 1 : 2 : 3 : undefined in last $ take 4 $ iterate' (test!!) 0
3

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


[Haskell-cafe] Haskell Zippers on Wikibooks: teasing! :)

2009-07-15 Thread Peter Verswyvelen
After my colleague explained me about zippers and how one could derive the
datatype using differential rules, I had to read about it.

So I started reading
http://en.wikibooks.org/wiki/Haskell/Zippers#Mechanical_Differentiation

This page contains the sentence:  *"For a systematic construction, we need
to calculate with types. The basics of structural calculations with types
are outlined in a separate chapter **Generic
Programming*
* and we will heavily rely on this material"*
*
*
However, the generic programming link does not exist yet :-)

So although I now have a rough idea about it, I don't understand the details
yet, e.g. notation like

[image: \mathit{Node}\,A = \mu X.\,\mathit{NodeF}_A\,X]

doesn't make much sense to me yet, although I suspect I can read the mu as a
lambda on types?

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


[Haskell-cafe] Re: Pattern matching does not work like this?

2009-07-15 Thread Maurí­cio

  I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
could not be compiled, parse error.


Maybe a small abstract can help, as I once also got
confused by that.

* First, syntax without operators

You can only match on constructors. So, if
you have

data Test = Test1 String | Test2 Integer | Test3

you can do

function (Test1 s) = ...
function (Test2 i) = ...
function Test3 = ...

* Second, syntax with operators

Haskell allow constructors made of symbols, but you
have to start them with ':', so this is valid:

data Test = Test1 String | Integer :** String

and then

function (Test1 s) = ...
function (i :** s) = ...

* Third, special syntax

Haskell has special syntax for tuples and lists (and
something else I forgot?). You can ask information
about a name in ghci using ':i ', see what it
says about (,) and []:

data (,) a b = (,) a b
data [] a = [] | a : [a]

As you can see, (,), [] and : are actually constructors,
and you can pattern match on them:

function [] = ...
function (a:b) = ...
function ((:) a b) = ...
function (a,b) = ...
function ((,) a b) = ...


Best,
Maurício

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


Re: [Haskell-cafe] Problems with nested Monads

2009-07-15 Thread Sjoerd Visscher
Actually, you can make a joinInner for the State monad. However, it  
does not allow the inner function (h) to change the state, because how  
state is threaded through a monad N is different for each N.


i :: (Monad n) => (a -> State s b) -> (b -> n c) -> (c -> State s d) - 
> (a -> State s (n d))

i f g h = joinInnerState . liftM (liftM h . g) . f

joinInnerState :: Monad n => State s (n (State s a)) -> State s (n a)
joinInnerState (State g) = State $ joinInnerAsReader . g
  where
joinInnerAsReader (n, s) = (liftM (fst . ($ s) . runState) n, s)

joinInner is the only one of the 3 that works, because the outer M  
gives you an initial state to work with.


Sjoerd

On Jul 10, 2009, at 11:25 PM, Job Vranish wrote:

Yeah, I think the problem with my case is that while M is a specific  
monad (essentially StateT), N can be an arbitrary monad, which I  
think destroys my changes of making a valid joinInner/joinOuter/ 
distribute.
Maybe someday Haskell will infer valid joinInner/joinOuter for  
simple cases :D
Thanks for you help. I'll definitely have to see if I can find that  
paper.


- Job Vranish

On Fri, Jul 10, 2009 at 3:09 PM, Edward Kmett   
wrote:
The problem you have is that monad composition isn't defined in  
general. You would need some form of distributive law either for  
your monads in general, or for your particular monads wrapped around  
this particular kind of value.


What I would look for is a function of the form of one of:

distribute :: N (M a) -> M (N a)
joinInner :: M (N (M a)) -> M (N a)
joinOuter :: N (M (N a)) -> M (N a)

that holds for your partiular monads M and N.

IIRC Mark P. Jones wrote a paper or a lib back around '93 that used  
these forms of distributive laws to derive monads from the  
composition of a monad and a pointed endofunctor.


-Edward Kmett

On Fri, Jul 10, 2009 at 11:34 AM, Job Vranish   
wrote:
I'm trying to make a function that uses another monadic function  
inside a preexisting monad, and I'm having trouble.
Basically my problem boils down to this. I have three monadic  
functions with the following types:

f :: A -> M B
g :: B -> N C
h :: C -> M D
(M and N are in the monad class)
I want a function i where
i :: A -> M (N D)

the best I can come up with is:
i :: A -> M (N (M D))
i a = liftM (liftM h) =<< (return . g) (f a)

I'm starting to feel pretty sure that what I'm going for is  
impossible. Is this the case?

___
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


--
Sjoerd Visscher
sjo...@w3future.com



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


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Felipe Lessa
On Wed, Jul 15, 2009 at 08:09:37AM -0400, Andrew Wagner wrote:
> Err, technically, aren't functions and constructors mutually exclusive? So
> if something is a function, it's, by definition, not a constructor?

I guess what Eugene Kirpichov meant was that not being a function
(and being a constructor) isn't sufficient, it must also be a
constructor of the correct type, e.g.

  f Nothing = ...
  f (x:xs)  = ...

isn't correct, however it pattern matches on constructors only.

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


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Hans Aberg

On 15 Jul 2009, at 13:22, Luke Palmer wrote:


If ++ could be pattern matched, what should have been the result of
"let (x++y)=[1,2,3] in (x,y)"?

It will branch. In terms of unification, you get a list of  
substitutions.


f :: [a] -> ([a],[a])
f (x ++ y) = (x,y)


For an argument s, any pair (x, y) satisfying s = x ++ y will match.  
That is, if s = [s_1, ..., s_k], the solutions j = 0, ..., k, x =  
[s_1, ..., s_j], y = [s_(j+1), ..., s_k]. And for each one, a  
potentially different value could given. That is, s could produce  
multiple values.


If this pattern branches, it could hardly be considered a function  
which takes lists and returns pairs.  It would have to return  
something else.



So this would be a multi-valued function, which sometime is useful as  
a concept. But if the choices are indexed, they can be reduced to a  
single valued function. Like g(x,y) with the requirement that if x ++  
y = x' ++ y', then g(x, y) = g(x', y').


This branching is what would happen if one tries to make a type theory  
based on sets. (It is possible to implement Horn clauses as  
unification branching.) The selection of branches correspond to a  
choice in the proof tree.


  Hans


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


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Miguel Mitrofanov

No. Most constructors are functions, e.g. Just :: a -> Maybe a - a function.

On the other hand, Nothing :: Maybe a is a constructor, but not a function.

Andrew Wagner wrote:
Err, technically, aren't functions and constructors mutually exclusive? 
So if something is a function, it's, by definition, not a constructor?


On Wed, Jul 15, 2009 at 6:25 AM, Eugene Kirpichov > wrote:


Technically, the reason is not that (++) is a function, but that it is
not a constructor of the [] type.

And, not only is it not a constructor, but it also *can't* be one,
because the main characteristic of pattern matching in Haskell is that
it is (contrary to Prolog's unification) unambiguous (unambiguity of
constructors is guaranteed by the semantics of Haskell's algebraic
datatypes).

If ++ could be pattern matched, what should have been the result of
"let (x++y)=[1,2,3] in (x,y)"?

2009/7/15 minh thu mailto:not...@gmail.com>>:
 > 2009/7/15 Magicloud Magiclouds mailto:magicloud.magiclo...@gmail.com>>:
 >> Hi,
 >>  I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
 >> could not be compiled, parse error.
 >
 > ++ is a function; you can't pattern-match on that.
 >
 > Cheers,
 > Thu
 > ___
 > Haskell-Cafe mailing list
 > Haskell-Cafe@haskell.org 
 > http://www.haskell.org/mailman/listinfo/haskell-cafe
 >



--
Eugene Kirpichov
Web IR developer, market.yandex.ru 
___
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] Pattern matching does not work like this?

2009-07-15 Thread Andrew Wagner
Err, technically, aren't functions and constructors mutually exclusive? So
if something is a function, it's, by definition, not a constructor?

On Wed, Jul 15, 2009 at 6:25 AM, Eugene Kirpichov wrote:

> Technically, the reason is not that (++) is a function, but that it is
> not a constructor of the [] type.
>
> And, not only is it not a constructor, but it also *can't* be one,
> because the main characteristic of pattern matching in Haskell is that
> it is (contrary to Prolog's unification) unambiguous (unambiguity of
> constructors is guaranteed by the semantics of Haskell's algebraic
> datatypes).
>
> If ++ could be pattern matched, what should have been the result of
> "let (x++y)=[1,2,3] in (x,y)"?
>
> 2009/7/15 minh thu :
> > 2009/7/15 Magicloud Magiclouds :
> >> Hi,
> >>  I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
> >> could not be compiled, parse error.
> >
> > ++ is a function; you can't pattern-match on that.
> >
> > Cheers,
> > Thu
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
>
>
> --
> Eugene Kirpichov
> Web IR developer, market.yandex.ru
> ___
> 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] Pattern matching does not work like this?

2009-07-15 Thread Luke Palmer
On Wed, Jul 15, 2009 at 3:08 AM, Hans Aberg  wrote:

> On 15 Jul 2009, at 12:25, Eugene Kirpichov wrote:
>
>  If ++ could be pattern matched, what should have been the result of
>> "let (x++y)=[1,2,3] in (x,y)"?
>>
>
> It will branch. In terms of unification, you get a list of substitutions.


f :: [a] -> ([a],[a])
f (x ++ y) = (x,y)

If this pattern branches, it could hardly be considered a *function *which
takes lists and returns pairs.  It would have to return something else.

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


[Haskell-cafe] ANN: darcs 2.3 beta 4

2009-07-15 Thread Petr Rockai
Hi again!

We have decided to delay the release cycle slightly for 2.3 and release another
beta. The primary reason for this is our Windows support -- I would like to
invite all Windows users to install darcs-beta and give it a ride. If you have
a working cabal-install, all you need to do is run:

$ cabal update
$ cabal install darcs-beta

(this works on all platforms; you may need to use -f-curl, if you don't have
the cURL headers available -- this is often the case on Windows). If you do not
have cabal-install, please follow the instructions near the end of this
message, "Installing on Windows".

In addition to using cabal-install, you can also download a tarball from
http://repos.mornfall.net/darcs/darcs-2.2.98.4.tar.gz and build manually (see
the build instructions in README inside the tarball).

Feedback


To make the darcs 2.3 release a good one, we still need testing feedback:
please drop a note to darcs-users@ if you have installed darcs-beta, or failed
to install it. If you run into any bugs, we need to know about them.

Thanks!

The question of GHC 6.8
---

Using GHC 6.10.3 or newer is *strongly recommended*. You may compile darcs with
GHC 6.8, but there are several caveats. If you are using 6.8.2 or older, please
disable mmap support (pass -f-mmap to cabal install or runghc Setup configure
below). Note that the GHC 6.8.2 that ships with Debian Lenny is not affected
and it should be safe to keep mmap enabled. It is also recommended to disable
use of Hackage zlib when compiling with GHC 6.8.2 (including the Debian Lenny
version): pass -f-zlib to cabal. When using zlib, we have seen occasional
crashes with error messages like "openBinaryFile: file locked" -- this is a
known GHC 6.8.2 bug (and is fixed in GHC 6.8.3). Last, if you are using a
64-bit system, darcs may hang when you exit a pager when compiled with GHC
older than 6.10.3. Although this is harmless, it is quite inconvenient.

Overall, the status of GHC 6.8 is "semi-supported": for many cases, things will
work just fine, especially if you take a little extra caution with compilation
flags.

Installing on Windows
-

To install darcs on Windows systems from scratch, please download the Haskell
Platform and MSYS:

 * 
http://hackage.haskell.org/platform/2009.2.0.1/HaskellPlatform-2009.2.0.1-setup.exe
 * 
http://sourceforge.net/projects/mingw/files/MSYS+Base+System/MSYS-1.0.11-rc-1.exe/download

After installing both, you should have an "MSYS" icon: run MSYS and in the
terminal window type:

$ cabal update  
$ cabal install darcs-beta -f-curl

This should download, compile and install all required dependencies and
darcs-beta itself. The resulting darcs executable will be placed into the
Haskell Platform executables folder, and should be accessible from the MSYS
shell (just type "darcs --version" to check).

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


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Hans Aberg

On 15 Jul 2009, at 12:25, Eugene Kirpichov wrote:


If ++ could be pattern matched, what should have been the result of
"let (x++y)=[1,2,3] in (x,y)"?


It will branch. In terms of unification, you get a list of  
substitutions.


  Hans


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


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Eugene Kirpichov
Technically, the reason is not that (++) is a function, but that it is
not a constructor of the [] type.

And, not only is it not a constructor, but it also *can't* be one,
because the main characteristic of pattern matching in Haskell is that
it is (contrary to Prolog's unification) unambiguous (unambiguity of
constructors is guaranteed by the semantics of Haskell's algebraic
datatypes).

If ++ could be pattern matched, what should have been the result of
"let (x++y)=[1,2,3] in (x,y)"?

2009/7/15 minh thu :
> 2009/7/15 Magicloud Magiclouds :
>> Hi,
>>  I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
>> could not be compiled, parse error.
>
> ++ is a function; you can't pattern-match on that.
>
> Cheers,
> Thu
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread minh thu
2009/7/15 minh thu :
> 2009/7/15 Magicloud Magiclouds :
>> Hi,
>>  I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
>> could not be compiled, parse error.
>
> ++ is a function; you can't pattern-match on that.

But here you can match against (0:1:xs).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread minh thu
2009/7/15 Magicloud Magiclouds :
> Hi,
>  I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
> could not be compiled, parse error.

++ is a function; you can't pattern-match on that.

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


[Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Magicloud Magiclouds
Hi,
  I do not notice this before. "fun ([0, 1] ++ xs) = .." in my code
could not be compiled, parse error.

-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Build 32-bit apps on 64-bit Windows?

2009-07-15 Thread Magnus Therning
On Tue, Jul 14, 2009 at 11:27 PM, Lyle Kopnicky wrote:
> If I am running GHC on 64-bit Windows, do I have a choice of building a
> 32-bit or 64-bit app? On a cursory glance through the command-line options,
> I didn't find anything.

I don't think there are cross-compiling version of GHC to be
downloaded out there.  You might be able to install both a 64-bit and
32-bit GHC compiler on the same system though.  Personally I use
virtualisation for all my 32-bit needs nowadays.

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] laziness blowup exercise

2009-07-15 Thread Bas van Dijk
On Wed, Jul 15, 2009 at 3:02 AM, Thomas Hartman wrote:
> Please suggest more of these types of exercises if you have them and
> maybe we can collect the folk wisdom into a wiki page and/or exercise
> page for beginners.

My 'stream' library[1] also has some examples. Look at the following
functions in 'Data.Stream':

* mapAccum'
* scan'
* iterate'
* unfold'

There are similar examples in 'Control.Monad.StreamT'.

[1] http://code.haskell.org/~basvandijk/code/stream/  (Not on Hackage)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe