Re: [Haskell-cafe] Type families and GADTs in 6.9

2008-04-14 Thread Manuel M T Chakravarty

Dan,

I've been playing around with type families off and on in 6.8, but,  
what with
the implementation therein being reportedly incomplete, it's hard to  
know
what I'm getting right and wrong, or what should work but doesn't  
and so on.
So, I finally decided to take the plunge and install 6.9 (which,  
perhaps,
isn't yet safe in that regard either, but, such is life :)). But,  
when I
loaded up one of my programs, I got a type error. The subject is  
inductively

defined tuples:

[..]

However, proj results in a
type error:

   Occurs check: cannot construct the infinite type:
 t = Lookup (t ::: ts) fn
   In the pattern: v ::: vs
   In the definition of `proj': proj FZ (v ::: vs) = v


Sorry, but looks like a bug in 6.9 to me.  Could you add it to the GHC  
bug tracker?


Thanks,
Manuel

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


Embedding newlines into a string? [Was: Re: [Haskell-cafe] Separate a string into a list of strings]

2008-04-14 Thread Benjamin L. Russell
A friend and I were working on a Haskell version of
Towers of Hanoi yesterday, and I tried writing out the
program today, but got stuck on outputting newlines as
part of the string; viz:

hanoi :: Int - String
hanoi n = hanoi_helper 'a' 'b' 'c' n
  
hanoi_helper :: Char - Char - Char - Int - String
hanoi_helper source using dest n
| n == 1 = putStrLn Move  ++ show source ++  to
 ++ show dest ++ . ++ show '\n'
| otherwise = hanoi_helper source dest using (n-1)

  ++ hanoi_helper source using dest 1
 ++ hanoi_helper using source
dest (n-1)

The problem is that the newlines ('\n') get embedded
as escaped newlines into the output string, instead of
as newlines.

E.g., 

Hugs :load hanoi.hs
Main hanoi 2
Move 'a' to 'b'.'\\n'Move 'a' to 'c'.'\\n'Move 'b' to
'c'.'\\n'

Instead, what I want is the following:

Hugs :load hanoi.hs
Main hanoi 2
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.


However, when I try to use putStrLn to avoid this
problem, as follows:

| n == 1 = putStrLn Move  ++ show source ++  to
 ++ show dest ++ . ++ show '\n'

the compiler generates the following error:

ERROR file:hanoi.hs:6 - Type error in application
*** Expression : putStrLn Move  ++ show source
++  to  ++ show dest ++ . ++ show '\n'
*** Term   : putStrLn Move 
*** Type   : IO ()
*** Does not match : [Char]

Simply changing the type signature does not solve this
problem.

I searched through the past messages on this list, and
came up with the message below, but simply quoting the
newlines as '\n' doesn't seem to help.

Does anybody know a way to embed a newline into a
string as output of type String of a function so that
the newline characters are not escaped?

Benjamin L. Russell

--- Jared Updike [EMAIL PROTECTED] wrote:

 Funny. I have a module called Useful.hs with some of
 these same sorts
 of functions. (coming from Python where I used
 .split(',') and
 .replace('\r', '') and such a lot):
 
 --
 module Useful where
 
 import List ( intersperse, tails )
 import Numeric ( readHex )
 
 hex2num :: (Num a) = String - a
 hex2num s = let (result, _):_ = readHex s in result
 
 toEnv s = map tuple (split ';' s)
 
 tuple :: String - (String, String)
 tuple line = case split '=' line of
a:b:_ - (a,b)
a:_   - (a,)
_ - (,) -- not good, probably won't
 happen for my typical usage...
 
 split   :: Char - String - [String]
 split _   =  []
 split c s   =  let (l, s') = break (== c) s
  in  l : case s' of
[]  - []
(_:s'') - split c s''
 
 beginsWith []   [] = True
 beginsWith _[] = True
 beginsWith []   _  = False
 beginsWith (a:aa)   (b:bb)
 | a == b   = aa `beginsWith` bb
 | otherwise= False
 
 dropping [] [] = []
 dropping [] _  = []
 dropping x  [] = x
 dropping s@(a:aa) (b:bb) | a == b= dropping aa
 bb
  | otherwise = s
 
 -- replace all occurrences of 'this' with 'that' in
 the string 'str'
 -- like Python replace
 replace __[]  = []
 replace this that str
 | str `beginsWith` this = let after = (str
 `dropping` this)
in  that ++ replace
 this that after
 | otherwise =
 let x:xs = str
   in x : replace this that xs
 
 eat s = replace s 
 
 -- sometimes newlines get out of hand on the end of
 form POST submissions,
 -- so trim all the end newlines and add a single
 newline
 fixEndingNewlines = reverse . ('\n':) . dropWhile
 (=='\n') . reverse .
 filter (/= '\r')
 
 endsWith a b = beginsWith (reverse a) (reverse b)
 
 a `contains` b = any (`beginsWith` b) $ tails a
 --
 
   Jared.
 
 On 6/12/06, Neil Mitchell [EMAIL PROTECTED]
 wrote:
  Hi,
 
  I tend to use the module TextUtil (or Util.Text)
 from Yhc for these
  kind of string manipulations:
 
 

http://www-users.cs.york.ac.uk/~malcolm/cgi-bin/darcsweb.cgi?r=yhc;a=headblob;f=/src/compiler98/Util/Text.hs
 
  separate = splitList ,
 
  I am currently thinking about making this module
 into a standalone
  library with some other useful functions, if
 people have any opinions
  on this then please let me know.
 
  Thanks
 
  Neil
 
 
  On 6/12/06, Sara Kenedy [EMAIL PROTECTED]
 wrote:
   Hi all,
  
   I want to write a function to separate a string
 into a list of strings
   separated by commas.
  
   Example:
   separate :: String - [String]
  
   separate Haskell, Haskell, and Haskell =
 [Haskell, Haskell, and Haskell]
  
   If anyone has some ideas, please share with me.
 Thanks.
  
   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
 
 

Re: Embedding newlines into a string? [Was: Re: [Haskell-cafe] Separate a string into a list of strings]

2008-04-14 Thread Neil Mitchell
Hi



On Mon, Apr 14, 2008 at 8:22 AM, Benjamin L. Russell
[EMAIL PROTECTED] wrote:
 A friend and I were working on a Haskell version of
  Towers of Hanoi yesterday, and I tried writing out the
  program today, but got stuck on outputting newlines as
  part of the string; viz:

 | n == 1 = putStrLn (Move  ++ show source ++  to
   ++ show dest ++ . ++ show '\n')

show '\n' = \\n

\n == \n

Therefore:

 | n == 1 = putStrLn (Move  ++ show source ++  to
   ++ show dest ++ . ++ \n)

Note that you need the brackets, an in general don't call show on a
String or a Char.

Thanks

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


[Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Tillmann Rendel

Benjamin L. Russell wrote:

but got stuck on outputting newlines as part of the string;


quoting is done by the show function in Haskell, so you have to take 
care to avoid calling show. your code calls show at two positions:

(1) when you insert the newline into the string
(2) when you output the string

with respect to (1):

you use (show '\n') to create a newline-only string, which produces a 
machine-readable (!) textual representation of '\n'. try the difference 
between


   '\n'

and

   show '\n'

to see what I mean. instead of using (show '\n'), you should simply use 
\n to encode the string of length 1 containing a newline character.


with respect to (2):

the type of your top-level expression is String, which is automatically 
print'ed by the interpreter. but print x = putStrLn (show x), so there 
is another call to show at this point. to avoid this call, write an IO 
action yourself. try the difference between


  putStrLn (hanoi ...)

and

  print (hanoi ...)

to see what I mean.

Last, but not least, I would like to point out a different aproach to 
multiline output which is often used by Haskell programmers: The worker 
functions in this aproach produces a list of strings, which is joined 
together with newlines by the unlines function. In your case:


  hanoi_helper :: ... - [String]
| ... = [Move  ++ ...]
| otherwise = hanoi_helper ... ++ hanoi_helper ...

  hanoi n = hanoi_helper 'a' 'b' 'c' n

and in the interpreter one of these:

   hanoi 2 -- outputs a list
   mapM_ putStrLn (hanoi 2) -- outputs each move in a new line
   putStrLn (unlines (hanoi 2)) -- same as previous line

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Benjamin L. Russell
Ok; much better.  Here's my new type signature and
definition:

hanoi.hs:
hanoi :: Int - IO ()
hanoi n = mapM_ putStrLn (hanoi_helper 'a' 'b' 'c' n)
  
hanoi_helper :: Char - Char - Char - Int -
[String]
hanoi_helper source using dest n
| n == 1 = [Move  ++ show source ++  to  ++
show dest ++ .]
| otherwise = hanoi_helper source dest using (n-1)

  ++ hanoi_helper source using dest 1
 ++ hanoi_helper using source
dest (n-1)

Then in WinHugs (Version Sep 2006):

Hugs :load hanoi.hs
Main hanoi 2
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Great!

One minor question:  I tried out both of your
following suggestions:

 mapM_ putStrLn (hanoi 2) -- outputs each move
 in a new line
 putStrLn (unlines (hanoi 2)) -- same as
 previous line

and discovered that putStrLn with unlines (the lower
option) in fact generates one extra blank line at the
end.  Just curious as to why

Benjamin L. Russell

--- Tillmann Rendel [EMAIL PROTECTED] wrote:

 Benjamin L. Russell wrote:
  but got stuck on outputting newlines as part of
 the string;
 
 quoting is done by the show function in Haskell, so
 you have to take 
 care to avoid calling show. your code calls show at
 two positions:
 (1) when you insert the newline into the string
 (2) when you output the string
 
 with respect to (1):
 
 you use (show '\n') to create a newline-only string,
 which produces a 
 machine-readable (!) textual representation of '\n'.
 try the difference 
 between
 
 '\n'
 
 and
 
 show '\n'
 
 to see what I mean. instead of using (show '\n'),
 you should simply use 
 \n to encode the string of length 1 containing a
 newline character.
 
 with respect to (2):
 
 the type of your top-level expression is String,
 which is automatically 
 print'ed by the interpreter. but print x = putStrLn
 (show x), so there 
 is another call to show at this point. to avoid this
 call, write an IO 
 action yourself. try the difference between
 
putStrLn (hanoi ...)
 
 and
 
print (hanoi ...)
 
 to see what I mean.
 
 Last, but not least, I would like to point out a
 different aproach to 
 multiline output which is often used by Haskell
 programmers: The worker 
 functions in this aproach produces a list of
 strings, which is joined 
 together with newlines by the unlines function. In
 your case:
 
hanoi_helper :: ... - [String]
  | ... = [Move  ++ ...]
  | otherwise = hanoi_helper ... ++ hanoi_helper
 ...
 
hanoi n = hanoi_helper 'a' 'b' 'c' n
 
 and in the interpreter one of these:
 
 hanoi 2 -- outputs a list
 mapM_ putStrLn (hanoi 2) -- outputs each move
 in a new line
 putStrLn (unlines (hanoi 2)) -- same as
 previous line
 
 Tillmann
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


Re: [Haskell-cafe] ANNOUNCE: Generic Haskell 1.80 (Emerald)

2008-04-14 Thread Thomas van Noort

Pablo Nogueira wrote:

This has certainly been taken into account when comparing approaches to
 generic programming. I quote from page 18/19 from the work you and Bulat


Indeed I was not aware of it. Missed that. Thanks for pointing it out!


 Thus, full reflexivity of an approach is taken into account. This suggests
 constrained types are part of Haskell98. So, I'm a bit confused at the
 moment as well.


After reading the Haskell 98 report more carefully I think constrained
types are part of Haskell98. The syntax for algebraic datatype
declarations given is:

  data cx = T u1 ... uk = K1 t11 ... t1k1 | ...| Kn tn1 ... tnkn

Certainly, they are implemented in a peculiar way, with constraints
associated with value constructors and not the type, perhaps to keep
the class and kinds orthogonal (eg, the BinTree type has * - * kind
instead of Ord - * kind).


You are completely right, constraints are optional for data and newtype 
declarations in Haskell98:


http://www.haskell.org/onlinereport/syntax-iso.html#sect9.5

In addition, GHC supports liberalised type synonyms which allows you to 
define constraints:


http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#type-synonyms

Seems like the mystery is solved now..



At any rate, this has been discussed before in other threads.
Thanks Thomas for your help
P.


You're welcome,
Thomas

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Neil Mitchell
Hi

   mapM_ putStrLn (hanoi 2) -- outputs each move
   in a new line
   putStrLn (unlines (hanoi 2)) -- same as
   previous line

putStr (unlines (hanoi 2))

is what you want. Unlines puts a trailing new line at the end of every
line, including the final one. putStrLn puts an additional trailing
new line, so you get 2 at the end.

mapM_ putStrLn == putStr . unlines

Thanks

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Tillmann Rendel

Benjamin L. Russell wrote:

Ok; much better.  Here's my new type signature and
definition:

hanoi :: Int - IO ()   
hanoi_helper :: Char - Char - Char - Int - [String]


If you want, you can separate the algorithm and the output processing 
even more by providing three functions of these types:


hanoi :: Int - [(Char, Char)]
hanoi_helper :: Char - Char - Char - Int - [(Char, Char)]
hanoi_shower :: [(Char, Char)] - String

and at the interpreter level:

   putStr (hanoi_shower (hanoi 2))

added value: you can easily use the output of hanoi for automated 
processing (e.g. testing, controlling a robot, producing an animation, 
counting the number of steps).


You can go one step further if you consider that towers don't have to be 
named by single characters, but can be named by everything:


hanoi :: a - a - a - Int - [(a, a)]
hanoi_helper :: a - a - a - Int - [(a, a)]
hanoi_shower :: Show a = [(a, a)] - String

now you can use

   putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))

to get the same result as above, but you are also allowed to write

   putStr (hanoi_shower (hanoi 1 2 3 2))

if you want to use numeric tower names.

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Neil Mitchell
Hi

  mapM_ putStrLn == putStr . unlines
 

  I'm wondering which (==) you mean here ;)

Expression equality, defined by:

instance (Arbitrary a, Eq b) = Eq (a - b) where
f == g = forall x :: a, f x == g x

Using QuickCheck to generate the values, and an Eq over IO (), which
can be defined using the IO test modelling thing at last years Haskell
Workshop.

There are answers to all these things, even if Haskell can't express
all of them quite like this :)

Thanks

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Tillmann Rendel

Neil Mitchell wrote:

Unlines puts a trailing new line at the end of every
line, including the final one. putStrLn puts an additional trailing
new line, so you get 2 at the end.


Thanks for that clarification.


mapM_ putStrLn == putStr . unlines


I'm wondering which (==) you mean here ;)

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


Re: [Haskell-cafe] ANNOUNCE: Generic Haskell 1.80 (Emerald)

2008-04-14 Thread Pablo Nogueira
 This has certainly been taken into account when comparing approaches to
  generic programming. I quote from page 18/19 from the work you and Bulat

Indeed I was not aware of it. Missed that. Thanks for pointing it out!

  Thus, full reflexivity of an approach is taken into account. This suggests
  constrained types are part of Haskell98. So, I'm a bit confused at the
  moment as well.

After reading the Haskell 98 report more carefully I think constrained
types are part of Haskell98. The syntax for algebraic datatype
declarations given is:

  data cx = T u1 ... uk = K1 t11 ... t1k1 | ...| Kn tn1 ... tnkn

Certainly, they are implemented in a peculiar way, with constraints
associated with value constructors and not the type, perhaps to keep
the class and kinds orthogonal (eg, the BinTree type has * - * kind
instead of Ord - * kind).

At any rate, this has been discussed before in other threads.
Thanks Thomas for your help
P.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] retrospective on 'seq' - 'unsafeSeq' ?

2008-04-14 Thread Henning Thielemann


When reading the section 10.3 Controlling Evaluation Order in History 
of Haskell I thought that the example that justified the 'seq' to be 
unrestricted polymorphic was mainly a debugging problem. I wondered if the 
better solution would have been to provide an 'unsafeSeq' which has no 
type restriction but must be absent from production code just like 
'trace'. With 'unsafeSeq' one could nicely play around until time and 
space behaviour is as wanted and then one can replace all 'unsafeSeq's by 
'seq' while adding type constraints accordingly. (Analogously there could 
be an unsafeShow that allows showing offending values in an 'error' 
without adding a Show constraint to the type signature.)

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


Re: [Haskell-cafe] retrospective on 'seq' - 'unsafeSeq' ?

2008-04-14 Thread Neil Mitchell
Hi

 unrestricted polymorphic was mainly a debugging problem. I wondered if the
 better solution would have been to provide an 'unsafeSeq' which has no type
 restriction but must be absent from production code just like 'trace'.

That would be very neat!

 type constraints accordingly. (Analogously there could be an unsafeShow that
 allows showing offending values in an 'error' without adding a Show
 constraint to the type signature.)

Ideally, unsafeShow could also show types as they are underneath, not
as a pretty-printing Show might show them. I have often wanted to
overload Show to print things in a readable way, but to have a showRaw
which shows things as they are, for debugging purposes. I have even
written such code for Yhc:
http://www.cs.york.ac.uk/fp/yhc/snapshot/docs/Yhc-Core-ShowRaw.html

I think unsafeShow is a fantastic idea - and would be much more useful
to me than unsafeSeq - plus is a non-breaking change. I think Hugs
already has 90% of the code to support this, and GHCi's debugger I
think has a fair chunk of it, so it could be added given not too much
work.

Thanks

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


RE: [Haskell-cafe] retrospective on 'seq' - 'unsafeSeq' ?

2008-04-14 Thread Simon Peyton-Jones
|  type constraints accordingly. (Analogously there could be an unsafeShow that
|  allows showing offending values in an 'error' without adding a Show
|  constraint to the type signature.)
|
| Ideally, unsafeShow could also show types as they are underneath, not
| as a pretty-printing Show might show them. I have often wanted to
| overload Show to print things in a readable way, but to have a showRaw
| which shows things as they are, for debugging purposes. I have even
| written such code for Yhc:
| http://www.cs.york.ac.uk/fp/yhc/snapshot/docs/Yhc-Core-ShowRaw.html
|
| I think unsafeShow is a fantastic idea - and would be much more useful
| to me than unsafeSeq - plus is a non-breaking change. I think Hugs
| already has 90% of the code to support this, and GHCi's debugger I
| think has a fair chunk of it, so it could be added given not too much
| work.

Yes, as you say, the debugger has most of the machinery.  I just don't know 
what it'd take to make it a callable function. Pepe?

Someone might want to make a feature-request ticket for this, with as much 
background and/or suggested design as poss.

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


Re: [Haskell-cafe] retrospective on 'seq' - 'unsafeSeq' ?

2008-04-14 Thread pepe


On 14/04/2008, at 12:19, Simon Peyton-Jones wrote:
|  type constraints accordingly. (Analogously there could be an  
unsafeShow that
|  allows showing offending values in an 'error' without adding a  
Show

|  constraint to the type signature.)
|
| Ideally, unsafeShow could also show types as they are underneath,  
not

| as a pretty-printing Show might show them. I have often wanted to
| overload Show to print things in a readable way, but to have a  
showRaw

| which shows things as they are, for debugging purposes. I have even
| written such code for Yhc:
| http://www.cs.york.ac.uk/fp/yhc/snapshot/docs/Yhc-Core-ShowRaw.html
|
| I think unsafeShow is a fantastic idea - and would be much more  
useful

| to me than unsafeSeq - plus is a non-breaking change. I think Hugs
| already has 90% of the code to support this, and GHCi's debugger I
| think has a fair chunk of it, so it could be added given not too  
much

| work.

Yes, as you say, the debugger has most of the machinery.  I just  
don't know what it'd take to make it a callable function. Pepe?


Someone might want to make a feature-request ticket for this, with  
as much background and/or suggested design as poss.


unsafeShow sounds quite useful, especially to avoid adding a Show  
constraint in function signatures only for debugging (of course a  
decent refactoring tool for Haskell would help with this too, so I  
hope the HaRe SoC project proposal gets accepted and done!).


:print has the code for doing this, but it needs the type information  
collected by the compiler. In GHC API speak, it needs the HscEnv from  
the Session object. If we can expose the Session created for GHCi  
(how? exporting it from GHC.Main? in a thread-local object? FFI  
trickery?), then this would need nearly zero work, albeit it would  
print things only when working in GHCi of course. But you can still  
compile all your modules to object code and call main from GHCi, so I  
don't think this is a big restriction considering unsafeShow is only  
for debugging purposes.


Another question is where in the package hierarchy would this function  
live. Since the code it would use is in the ghc package, it would  
introduce a dependency on it. And I am fairly sure that there is no  
package in the standard ghc distribution which depends on the ghc  
package. Ian, can it be made to live in ghc-prim without creating a  
dependency on the ghc package?



Alternatively, with some effort one can create a type-agnostic version  
of unsafeShow, which would print things in a more raw format, but  
probably sufficient anyway. I don't think it would work with unboxed  
values in general, although it can be made to work with the standard  
types. Actually, Bernie Pope wrote some code for this [1, see GHC Heap  
Printing library] some time ago, although with the new primitives and  
changes made for :print in GHC 6.8, this would be way easier nowadays.  
No need to use StablePtrs, no need to turn on profiling, and above  
all, no C needed :)

And as a bonus this would work out of GHCi too.


If there is a clean way to access the Session object, the first option  
means less implementation work, less code to maintain in GHC, and  
better functionality. What does the GHC team think?



[1] - http://www.cs.mu.oz.au/~bjpop/code.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Benjamin L. Russell
Wow, that's very general.  So you want to divide hanoi
into a main function, a helper function, and a display
function.

I tried it out, and got this far so far:

hanoi :: a - a - a - Int - [(a, a)]
hanoi a b c n = hanoi_helper a b c n
  
hanoi_helper :: a - a - a - Int - [(a, a)]
hanoi_helper source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi_helper source dest using (n-1)

  ++ hanoi_helper source using dest 1
 ++ hanoi_helper using source
dest (n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [(a, b)] = Move  ++ show a ++  to  ++
show b ++ .

However, when I tried to run the code in WinHugs, this
is what I got:

Hugs :load hanoi_general.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))

Program error: pattern match failure: hanoi_shower
[('a','b'),('a','c')] ++ ([] ++ hanoi_helper 'b' 'a'
'c' (2 - 1))

There seems to be a bug in hanoi_shower.

I'm still trying to debug hanoi_shower, but I need to
stop for today and continue on this tomorrow.

Thanks for your help so far!  Perhaps I can get this
general version fully working tomorrow.

Benjamin L. Russell

--- Tillmann Rendel [EMAIL PROTECTED] wrote:

 Benjamin L. Russell wrote:
  Ok; much better.  Here's my new type signature and
  definition:
  
  hanoi :: Int - IO ()   
  hanoi_helper :: Char - Char - Char - Int -
 [String]
 
 If you want, you can separate the algorithm and the
 output processing 
 even more by providing three functions of these
 types:
 
 hanoi :: Int - [(Char, Char)]
 hanoi_helper :: Char - Char - Char - Int -
 [(Char, Char)]
 hanoi_shower :: [(Char, Char)] - String
 
 and at the interpreter level:
 
 putStr (hanoi_shower (hanoi 2))
 
 added value: you can easily use the output of hanoi
 for automated 
 processing (e.g. testing, controlling a robot,
 producing an animation, 
 counting the number of steps).
 
 You can go one step further if you consider that
 towers don't have to be 
 named by single characters, but can be named by
 everything:
 
 hanoi :: a - a - a - Int - [(a, a)]
 hanoi_helper :: a - a - a - Int - [(a, a)]
 hanoi_shower :: Show a = [(a, a)] - String
 
 now you can use
 
 putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
 
 to get the same result as above, but you are also
 allowed to write
 
 putStr (hanoi_shower (hanoi 1 2 3 2))
 
 if you want to use numeric tower names.
 
Tillmann
 ___
 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: RFC: A standardized interface between web servers and applications or frameworks (ala WSGI)

2008-04-14 Thread Daniel Yokomizo
On Mon, Apr 14, 2008 at 3:27 AM, Adam Langley [EMAIL PROTECTED] wrote:
 On Sun, Apr 13, 2008 at 6:32 PM, Chris Smith [EMAIL PROTECTED] wrote:
Does old code that handled these headers stop working, just because it
was looking in the other section, but now needs to check a field
dedicated to that header?

  Yes, but it would be very sad if we couldn't do common header parsing
  because of this.

  I'd suggest that all the headers given in RFC 2616 be parsed and
  nothing else.

Both request and response accept any entity headers and 7.1 (of RFC
2616) says that a valid entity header is an extension header, which
can be any kind of header.

 That leaves the question of how we would handle the
  addition of any extra ones in the future. Firstly, packages could
  depend on a given version of this interface and we declare that the
  set of handled headers doesn't change within a major version.

  Better would be some static assertion that the interface doesn't
  handle some set of headers. Maybe there's a type trick to do this, but
  I can't think of one, so we might have to settle for a non static:

  checkUnparsedHeaders :: [String] - IO ()

  Which can be put in 'main' (or equivalent) and can call error if
  there's a mismatch.

Most of the times a Header makes sense in some scenarios and doesn't
in others, so a package level checking is too coarse grained.

IMHO it would be better to create a two layered approach. The bottom
layer handles the request as a bunch of strings, just checks for
structural correctness (i.e. break the headers by line and such)
without checking if the headers are correct. The top layer provides a
bunch of parser combinators to validate, parse and sanitize the
request so a library can create its own contract:

newtype Contract e a = Contract (HttpRequest - e a)

contract :: Contract Maybe MyRequest
contract = do pragma - parseHeader Pragma (\header - ...)
  ...
  return $ MyRequest pragma ...

main =
   do request - readHttpRequest
sanitized - enforce contract request
...


Such approach would be more flexible and extensible. Later other
packages could provide specialized combinators for other RFCs. HTTP is
regularly extended, in RFCs and by private parties experimenting
before writing an RFC, it would be bad if the primary Haskell library
for HTTP didn't support this behavior. Also it's important to notice
that the HTTP spec defines things to be mostly orthogonal, so most of
the headers stand on their own and can be used in combination with
many methods and other headers, every once in a while someone finds a
combination that makes sense and wasn't thought of before.

  AGL

  --
  Adam Langley [EMAIL PROTECTED] http://www.imperialviolet.org


Best regards,
Daniel Yokomizo.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] semi-closed handles

2008-04-14 Thread Abhay Parvate
Hello,

In describing the Handle type, the GHC documentation says (in the System.IO
documentation):

GHC note: a Handle will be automatically closed when the garbage collector
detects that it has become unreferenced by the program. However, relying on
this behaviour is not generally recommended: the garbage collector is
unpredictable. If possible, use explicit an explicit hClose to close Handles
when they are no longer required. GHC does not currently attempt to free up
file descriptors when they have run out, it is your responsibility to ensure
that this doesn't happen.

But one cannot call hClose on Handles on which something like hGetContents
has been called; it just terminates the character list at the point till
which it has already read. Further the manual says that hGetContents puts
the handle in the semi-closed state, and further,

A semi-closed handle becomes closed:

   - if hClose is applied to it;
   - if an I/O error occurs when reading an item from the handle;
   - or once the entire contents of the handle has been read.

So do I safely assume here, according to the third point above, that it's
fine if I do not call hClose explicitly as far as I am consuming all the
contents returned by hGetContents?

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Abhay Parvate
Yes, they are. That's what perhaps Neil Mitchell means by

mapM_ putStrLn == putStr . unlines

And whether the trailing newline is to be called the last blank line depends
upon the convention; The string that is output in both the cases contains a
single newline character. Are you calling that a blank line at end?

And I actually meant to reply to haskell-cafe as well; omitted haskell-cafe
by mistake. Anyway, you got the same answer from two people! This time I am
including haskell-cafe in the recipients.

Regards,
Abhay

On Mon, Apr 14, 2008 at 4:05 PM, Benjamin L. Russell [EMAIL PROTECTED]
wrote:

 Abhay Parvate,

 Thank you; that answered my question.

 Then, the following two lines of code should be
 equivalent:

 In hanoi.hs:
 hanoi n = mapM_ putStrLn (hanoi_helper 'a' 'b' 'c' n)

 In hanoi_unlines.hs:
 hanoi n = putStr (unlines(hanoi_helper 'a' 'b' 'c' n))

 I tested them both out on WinHugs (Version Sep 2006);
 they both generated one blank line at the end.

 Benjamin L. Russell

 --- Abhay Parvate [EMAIL PROTECTED] wrote:

  unlines puts newline after each string; putStrLn
  puts newline after the
  given string. As a result, the output contains two
  newlines in the end. You
  can use putStr instead, since the resultant string
  from 'unlines' will have
  a newline at the end.
 
  On Mon, Apr 14, 2008 at 2:12 PM, Benjamin L. Russell
  [EMAIL PROTECTED]
  wrote:
 
   Ok; much better.  Here's my new type signature and
   definition:
  
   hanoi.hs:
   hanoi :: Int - IO ()
   hanoi n = mapM_ putStrLn (hanoi_helper 'a' 'b' 'c'
  n)
  
   hanoi_helper :: Char - Char - Char - Int -
   [String]
   hanoi_helper source using dest n
  | n == 1 = [Move  ++ show source ++  to  ++
   show dest ++ .]
  | otherwise = hanoi_helper source dest using
  (n-1)
  
++ hanoi_helper source using dest
  1
   ++ hanoi_helper using
  source
   dest (n-1)
  
   Then in WinHugs (Version Sep 2006):
  
   Hugs :load hanoi.hs
   Main hanoi 2
   Move 'a' to 'b'.
   Move 'a' to 'c'.
   Move 'b' to 'c'.
  
   Great!
  
   One minor question:  I tried out both of your
   following suggestions:
  
mapM_ putStrLn (hanoi 2) -- outputs each
  move
in a new line
putStrLn (unlines (hanoi 2)) -- same as
previous line
  
   and discovered that putStrLn with unlines (the
  lower
   option) in fact generates one extra blank line at
  the
   end.  Just curious as to why
  
   Benjamin L. Russell
  
   --- Tillmann Rendel [EMAIL PROTECTED] wrote:
  
Benjamin L. Russell wrote:
 but got stuck on outputting newlines as part
  of
the string;
   
quoting is done by the show function in Haskell,
  so
you have to take
care to avoid calling show. your code calls show
  at
two positions:
(1) when you insert the newline into the string
(2) when you output the string
   
with respect to (1):
   
you use (show '\n') to create a newline-only
  string,
which produces a
machine-readable (!) textual representation of
  '\n'.
try the difference
between
   
'\n'
   
and
   
show '\n'
   
to see what I mean. instead of using (show
  '\n'),
you should simply use
\n to encode the string of length 1 containing
  a
newline character.
   
with respect to (2):
   
the type of your top-level expression is String,
which is automatically
print'ed by the interpreter. but print x =
  putStrLn
(show x), so there
is another call to show at this point. to avoid
  this
call, write an IO
action yourself. try the difference between
   
   putStrLn (hanoi ...)
   
and
   
   print (hanoi ...)
   
to see what I mean.
   
Last, but not least, I would like to point out a
different aproach to
multiline output which is often used by Haskell
programmers: The worker
functions in this aproach produces a list of
strings, which is joined
together with newlines by the unlines function.
  In
your case:
   
   hanoi_helper :: ... - [String]
 | ... = [Move  ++ ...]
 | otherwise = hanoi_helper ... ++
  hanoi_helper
...
   
   hanoi n = hanoi_helper 'a' 'b' 'c' n
   
and in the interpreter one of these:
   
hanoi 2 -- outputs a list
mapM_ putStrLn (hanoi 2) -- outputs each
  move
in a new line
putStrLn (unlines (hanoi 2)) -- same as
previous line
   
Tillmann
___
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] Re: Embedding newlines into a string?

2008-04-14 Thread Brandon S. Allbery KF8NH


On Apr 14, 2008, at 7:51 , Benjamin L. Russell wrote:

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [(a, b)] = Move  ++ show a ++  to  ++ show b ++ .


You've just specified via pattern match that hanoi_shower always gets  
a 1-element list.  Is that really what you intended?


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Neil Mitchell
Hi

   hanoi_shower [] = ...
   hanoi_shower ((a, b) : moves) = ...

  or (preferably) with map

  hanoi_shower moves = unlines (map show_move moves) where
   show_move (a, b) = ...

A nice list comprehension works wonders in these situations:

hanoi_shower moves = unlines [Move  ++ show a ++  to  ++ show b ++
. | (a,b) - moves]

I would personally remove the . from the end, as its a list of
commands, not sentences - but that is personal choice. I'd also use
unwords, as its slightly shorter:

hanoi_shower moves = unlines [unwords [Move, show a, to, show b] |
(a,b) - moves]

Thanks

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Tillmann Rendel

Benjamin L. Russell wrote:

Wow, that's very general.  So you want to divide hanoi
into a main function, a helper function, and a display
function.

I tried it out, and got this far so far:

[...]

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [(a, b)] = Move  ++ show a ++  to  ++
show b ++ .


That's exactly what I was thinking about, but your hanoi_shower only
handles list of exactly one action, but you have to handle longer lists,
too. This could be done with explicit recursion

  hanoi_shower [] = ...
  hanoi_shower ((a, b) : moves) = ...

or (preferably) with map

hanoi_shower moves = unlines (map show_move moves) where
  show_move (a, b) = ...

Note the use of unlines again. I decided to use where to introduce a
local binding to avoid cluttering the top-level scope with function names.

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


[Haskell-cafe] Re: RFC: A standardized interface between web servers and applications or frameworks (ala WSGI)

2008-04-14 Thread Adam Langley
On Mon, Apr 14, 2008 at 4:54 AM, Daniel Yokomizo
[EMAIL PROTECTED] wrote:
  Both request and response accept any entity headers and 7.1 (of RFC
  2616) says that a valid entity header is an extension header, which
  can be any kind of header.

Is wasn't suggesting that other headers be dropped, just that they
remain as strings.

  IMHO it would be better to create a two layered approach. The bottom
  layer handles the request as a bunch of strings, just checks for
  structural correctness (i.e. break the headers by line and such)
  without checking if the headers are correct. The top layer provides a
  bunch of parser combinators to validate, parse and sanitize the
  request so a library can create its own contract:

Ok, I think I'm convinced by this argument. I'd hope that a standard
set of header parsers be defined, and that an application which only
cares about 2616 headers can do call a single function to parse them
all, but I no longer advocate that the base interface use parsed forms
of headers.

Also, parsing URLs seems to be pretty uncontroversial (maybe parsing
key, value pairs from the path, maybe not)

AGL

-- 
Adam Langley [EMAIL PROTECTED] http://www.imperialviolet.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HTTP and file upload

2008-04-14 Thread Adam Smyczek

Is form based file upload supported in HTTP module (HTTP-3001.0.4)?

Adam


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


Re: [Haskell-cafe] semi-closed handles

2008-04-14 Thread Brent Yorgey
2008/4/14 Abhay Parvate [EMAIL PROTECTED]:

 Hello,

 In describing the Handle type, the GHC documentation says (in the
 System.IO documentation):

 GHC note: a Handle will be automatically closed when the garbage collector
 detects that it has become unreferenced by the program. However, relying on
 this behaviour is not generally recommended: the garbage collector is
 unpredictable. If possible, use explicit an explicit hClose to close Handles
 when they are no longer required. GHC does not currently attempt to free up
 file descriptors when they have run out, it is your responsibility to ensure
 that this doesn't happen.

 But one cannot call hClose on Handles on which something like hGetContents
 has been called; it just terminates the character list at the point till
 which it has already read. Further the manual says that hGetContents puts
 the handle in the semi-closed state, and further,

 A semi-closed handle becomes closed:

- if hClose is applied to it;
- if an I/O error occurs when reading an item from the handle;
- or once the entire contents of the handle has been read.

 So do I safely assume here, according to the third point above, that it's
 fine if I do not call hClose explicitly as far as I am consuming all the
 contents returned by hGetContents?


Yes, not only is it fine, it's recommended!  Calling hClose explicitly on a
handle after calling hGetContents is a sure way to introduce bugs.

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Brent Yorgey

 hanoi :: a - a - a - Int - [(a, a)]
 hanoi a b c n = hanoi_helper a b c n


Note that now hanoi is exactly the same function as hanoi_helper, so you may
as well just get rid of hanoi_helper. =)

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


[Haskell-cafe] ANN: darcswatch, a way to track your contributions

2008-04-14 Thread Joachim Breitner
Hi Haskellers,

today I scrached an itch that was icking for a while: When I submit
patches to some project or person, I’m never sure that I won’t forget
checking that the patch will actually be applied. But if I forget, and
the maitainer forgets (or decides against), my patch would be lost.

Therefore I wrote a little haskell program darcswatch, which has a bunch
of patches to track, and a bunch of repositories to watch, and shows you
what patches have to be applied where. You see it in action here:

   http://darcswatch.nomeata.de/

To use it conveniently, I have put this in my ~/.darcs/defaults:

send sign
send cc [EMAIL PROTECTED]

so all patches I send will be signed and copied to that address. For
security reasons, only mails signed by allowed gpg keys are accepted and
the webpage is updated. It is also updated every hour by a cronjob.

As you can see the program is ready to track patches by several authors.
If you want to try it out and help debug it, just drop me a (signed)
note with your gpg key-id, also listing all repositories you want to be
tracked.

I would also appreciate any help with programming darcswatch. There is a
darcs repository on http://darcs.nomeata.de/darcswatch/ (with DarcsWeb
at http://darcs.nomeata.de/cgi-bin/darcsweb.cgi?r=darcswatch;a=summary).

There is a lot to do yet, I quote the TODO list on
http://darcs.nomeata.de/darcswatch/README :

  * Support for tagged repositories (fetching older inventories)
  * Cache the inventories and only update when needed, by issuing a HEAD 
request.
  * Add a download link to each pach
  * Add the diff to each patch, with some javascript hiding/unhiding.
  * Cabalize the program.
  * Detect inverted patches and treat specially (e.g. an unapplied
patch where the user also submitted an inverted patch can be
considered obsolete)
  * Nicer output (CSS magic!)
  * (Maybe) Add repositores per gpg signed command

Haskell projects could also make use of darcswatch by tracking patches
that were submitted to a bugtracker (e.g. for xmonad) or via the mailing
list, to make sure no contribution is lost. I could also imagine that it
might be a service that, if proven reliable, could be run on
community.haskell.org or similar. 

As always, comments are appreciated.

Enjoy,
Joachim

-- 
Joachim nomeata Breitner
  mail: [EMAIL PROTECTED] | ICQ# 74513189 | GPG-Key: 4743206C
  JID: [EMAIL PROTECTED] | http://www.joachim-breitner.de/
  Debian Developer: [EMAIL PROTECTED]


signature.asc
Description: Dies ist ein digital signierter Nachrichtenteil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad proof

2008-04-14 Thread harke
Here's part of a pencil-and-paper proof of laws for a state monad.

Before doing so, I've got a question of my own about the *other* laws:
Is there a place where somebody has explicitly written the laws that
non-proper morphisms of commonly used monads?

Back to the original question...

Beware.  What I'm about to say doesn't quite work in Haskell, for two
reasons.  First, you can't make my definition into an instance of the
class Monad without inserting type constructors into inconvenient places.
Second, due to the way undefined works in Haskell, the state monad
doesn't obey all the laws.

Assume we don't have non-termination, and assume we don't care about
overloading (=) and return (so we don't need to shoe-horn our monad
into the monad type class).

Preliminaries.  From the Prelude we have:
curry   :: ((a,b) - c) - a - b - c
uncurry :: (a - b - c) - (a,b) - c
id  :: a - a

We define the state monad to be a synonym for a function returning a
pair:

M a = s - (a,s)

Define morphisms

return  = curry id -- where id is specialized to type (a,s) - (a,s)
m = k = (uncurry k) . m
get = \s - (s,s)
put s   = \_ - ((),s)

Now check the laws.  Of the basic 3, I'll only do associativity.
The other 2 are easier.

Take the two sides of the conjectured law and unfold the definition
of = (and return), then use properties of uncurry (and curry) to
massage them into the same form.  If you can do so, the law holds.
(I'm going to avoid unfolding the definition of (un)curry so I can
stay at a higher level of abstraction, though the following might be
shorter if I did unfold them.)

LHS
== (p = q) = r
== uncurry r . (p = q)
== uncurry r . (uncurry q . p)

RHS =
== p = (\x - q x = r)
== uncurry (\x - q x = r) . p
== uncurry (\x - uncurry r . q x) . p
== uncurry (\x s - (uncurry r . q x) s) . p
== uncurry (\x s - uncurry r (q x s)) . p
== (\xs - uncurry r (q (fst xs) (snd xs))) . p
== (\xs - uncurry r (uncurry q xs)) . p
== (\xs - (uncurry r . uncurry q) xs) . p
== (uncurry r . uncurry q) . p

Now, one thing that's equally interesting (and perhaps not spoken of
often enough) is the laws that the non-proper morphisms obey.
In the case of state:

put a  get == put a  return a

  where each side reduces to \_ - (a,a)

get  get == get

  where each side reduces to \s - ((),s)

BTW, in a proof assistant like Coq, Isabelle or Agda these identities
can be verified much more easily (though a badly done proof script
may be unreadable.)


On Fri, Apr 11, 2008 at 02:35:28PM -0300, Rafael C. de Almeida wrote:
 Hello,

 I was studying Monads and I was trying to think about new Monads I could  
 define. So, a question poped into my mind: how is proof regarding the 3 
 Monad laws handled? I know that, aside from testing all the possible values 
 (and there can be a lot of them), there's no general way to prove it. 
 Nonetheless, I think that it would be insightful to see how people write 
 those proofs for their monads -- specially for new user monads. Is there 
 some article or some notes on proving that Monads are implemented 
 correctly?

 []'s
 Rafael

-- 
Tom Harke
Portland State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad proof

2008-04-14 Thread Derek Elkins
On Mon, 2008-04-14 at 16:52 -0700, [EMAIL PROTECTED] wrote:
 Here's part of a pencil-and-paper proof of laws for a state monad.
 
 Before doing so, I've got a question of my own about the *other* laws:
 Is there a place where somebody has explicitly written the laws that
 non-proper morphisms of commonly used monads?
 
 Back to the original question...
 
 Beware.  What I'm about to say doesn't quite work in Haskell, for two
 reasons.  First, you can't make my definition into an instance of the
 class Monad without inserting type constructors into inconvenient places.
 Second, due to the way undefined works in Haskell, the state monad
 doesn't obey all the laws.
 
 Assume we don't have non-termination, and assume we don't care about
 overloading (=) and return (so we don't need to shoe-horn our monad
 into the monad type class).
 
 Preliminaries.  From the Prelude we have:
 curry   :: ((a,b) - c) - a - b - c
 uncurry :: (a - b - c) - (a,b) - c
 id  :: a - a
 

A shorter version.  First, verify that curry and uncurry make an
isomorphism.  (They don't in Haskell because of seq, this is where we
close our eyes and stick our fingers in our ears.)  Then curry and
uncurry define an adjunction: (,) a -| (-) a
State is the monad of that adjunction.  QED.


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


[Haskell-cafe] Help understanding sharing

2008-04-14 Thread Patrick Surry
I'm new to Haskell and trying to get a better understanding of sharing
(and ultimately memoization).  I've read SOE and various of the
tutorials, as well as browsing around the wiki and old mailing lists.  

 

Most of the examples of memoization seem to revolve around Fibonacci,
and are based either on the fact that a list defined within the function
will get shared between calls, or on doing some 'unsafeIO' (which I
haven't dug too deeply into.)   

 

I've read various discussions that explain why function calls are
generally not automatically memoized (e.g. f x  gets recalculated rather
than looked up based on the prior result).  The rationale for that (big
space leak and no guarantee of improved performance) makes sense.
(Though I did like one poster's suggestion of a compiler pragma that
hints that a particular function should be memoized.)

 

I've seen other discussions that suggest that lists are always shared
while in scope (so the fibs trick works).  But is that just a feature of
the standard compilers, or is it somewhere mandated in the Hakell spec
(I don't see anything obvious in the Haskell Report tho haven't read it
cover to cover)? 

 

The wiki page http://www.haskell.org/haskellwiki/Performance/Strictness
says laziness == non-strictness + sharing but again nowhere gives a set
of rules that guarantees what will be shared and what won't.  I was
hoping I might find it here: http://www.haskell.org/haskellwiki/Sharing
but no such luck.  Or are there no guarantees and you just have to know
how your particular compiler works??

 

Cheers,

Patrick

 



DISCLAIMER: This e-mail is intended only for the addressee named above. As this 
e-mail may contain confidential or privileged information, if you are not the 
named addressee, you are not authorised to retain, read, copy or disseminate 
this message or any part of it. If you received this email in error, please 
notify the sender and delete the message from your computer.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help understanding sharing

2008-04-14 Thread Albert Y. C. Lai

Patrick Surry wrote:
I've seen other discussions that suggest that lists are always shared 
while in scope (so the fibs trick works).  But is that just a feature of 
the standard compilers, or is it somewhere mandated in the Hakell spec 
(I don't see anything obvious in the Haskell Report tho haven't read it 
cover to cover)?


It is just a feature of most compilers. The Haskell Report does not 
specify sharing.


For most compilers, a sufficient condition for sharing is aliasing, e.g.,

let y = f x in (y,y,y,y,y)

you can be sure that most compilers share one copy of f x for those 
five mentions of y.


As another example,

let x = 0:x in x

you can be sure that most compilers create a tight cyclic graph for that.

In contrast, most compilers may create redundantly new expressions for 
the following:


(f x, f x, f x, f x, f x)

-- given the definition: recurse f = f (recurse f)
recurse (\x - 0:x)

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Benjamin L. Russell
Now it works; viz (in response to Brent Yorgey's
suggestion, I have merged hanoi and hanoi_helper):

hanoi_general_list_comprehension_unwords.hs (based on
Neil Mitchell's suggestion, except for the trailing
'.'):

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines [unwords [Move, show a,
to, show b, .] | (a, b) - moves]

Then, in WinHugs:

Main :load
hanoi_general_list_comprehension_unwords.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b' .
Move 'a' to 'c' .
Move 'b' to 'c' .

Main putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2 .
Move 1 to 3 .
Move 2 to 3 .

Notwithstanding Neil's advice on removing the trailing
'.', which I appreciate, I would still prefer to
retain it, because, in the interests of literate
programming, I would like a sequence of English
sentences as commands acceptable even to an English
teacher.

So, to be pedantic and remove the ' ' before the '.'
at each line:

hanoi_shower portion of
hanoi_general_list_comprehension_unlines.hs (based on
Neil Mitchell's suggestion):

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines [Move  ++ show a ++ 
to ++ show b ++ . | (a, b) - moves]

Then, in WinHugs:

Main :load
hanoi_general_list_comprehension_unlines.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Main putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2.
Move 1 to 3.
Move 2 to 3.

Splendid!

Now, just for fun, let's see what other versions also
work:

hanoi_shower portion of hanoi_general_map_unlines.hs
(based on Tillman Rendel's suggestion):

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines (map move moves)
 where move (a, b) = Move  ++
show a ++  to ++ show b ++ .

Then, in WinHugs:

Main :load hanoi_general_map_unlines.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Main putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2.
Move 1 to 3.
Move 2 to 3.

Wonderful!  Thanks especially to Neil Mitchell and
Tillman Rendel for their constructive suggestions.

Nevertheless, I'm still working on the recursive
version.  So far, I've gotten this far:

hanoi_shower portion of hanoi_general_recursive.hs
(based on Tillman Rendel's suggestion):

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower ((a, b) : moves) 
| null moves = Move  ++ show a ++  to ++ show
b ++ .
| otherwise == Move  ++ show a ++  to ++ show
b ++ . ++ hanoi_shower moves

However, in WinHugs, I get the following error:

Hugs :load hanoi_general_recursive.hs
ERROR file:hanoi_general_recursive.hs:11 - Syntax
error in declaration (unexpected `}', possibly due to
bad layout)

I haven't used recursion in Haskell much so far; I've
only used it in Scheme, so I'm not used to it.

I need to go to lunch now, so I'll work on this part
later.  Perhaps I can get it to work after lunch

Benjamin L. Russell

--- Neil Mitchell [EMAIL PROTECTED] wrote:

 Hi
 
hanoi_shower [] = ...
hanoi_shower ((a, b) : moves) = ...
 
   or (preferably) with map
 
   hanoi_shower moves = unlines (map show_move
 moves) where
show_move (a, b) = ...
 
 A nice list comprehension works wonders in these
 situations:
 
 hanoi_shower moves = unlines [Move  ++ show a ++ 
 to  ++ show b ++
 . | (a,b) - moves]
 
 I would personally remove the . from the end, as
 its a list of
 commands, not sentences - but that is personal
 choice. I'd also use
 unwords, as its slightly shorter:
 
 hanoi_shower moves = unlines [unwords [Move, show
 a, to, show b] |
 (a,b) - moves]
 
 Thanks
 
 Neil
 ___
 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] retrospective on 'seq' - 'unsafeSeq' ?

2008-04-14 Thread Bernie Pope

On 14/04/2008, at 9:22 PM, pepe wrote:
Alternatively, with some effort one can create a type-agnostic  
version of unsafeShow, which would print things in a more raw  
format, but probably sufficient anyway. I don't think it would work  
with unboxed values in general, although it can be made to work  
with the standard types. Actually, Bernie Pope wrote some code for  
this [1, see GHC Heap Printing library] some time ago, although  
with the new primitives and changes made for :print in GHC 6.8,  
this would be way easier nowadays. No need to use StablePtrs, no  
need to turn on profiling, and above all, no C needed :)

And as a bonus this would work out of GHCi too.


Yes, an almost-universal printer would be possible now that we have  
data constructor names attached to info tables.

I'd sort of planned to do that, and then got side-tracked.
Of course, this won't be able to print functions in any helpful way,  
unless we attach source code information to

functions as well (which may be worth doing anyway?).

One thing to watch out for is cycles in data structures. You may not  
want to try to detect them, but at least you should

be lazy in generating the printable representation of values.

And then there is the question of whether to evaluate thunks during  
printing.


Perhaps such a printer would also be useful for the GHCi debugger in  
cases where it can't infer the right types?


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


[Haskell-cafe] Strange message from GHC

2008-04-14 Thread Chris Smith
I'm running into this in some code I wrote.  What does it mean?  It says 
to look at -fspec-constr-count, but that flag doesn't seem to be in the 
GHC documentation.

This isn't critical; the code still seems to work fine.  It just makes 
the build uglier.

Thanks.  Message below.


SpecConstr: too many specialisations for one function (see -fspec-constr-
count):
Function: main:Expr.simplifyTerm{v rqC} [lid]
Specialisations: [([sc_s2wb{v} [lid], sc_s2wc{v} [lid],
sc_s2wd{v} [lid], sc_s2we{v} [lid], sc_s2wf{v} 
[lid],
sc_s2wg{v} [lid]],
   [main:Expr.Graph{v r51} [gid]
  sc_s2wg{v} [lid]
  sc_s2wf{v} [lid]
  sc_s2we{v} [lid]
  sc_s2wd{v} [lid],
base:GHC.Base.:{(w) v 65} [gid]
  @ main:Expr.Gen{tc r53}
  (main:Expr.Edge{v r4Q} [gid] sc_s2wc{v} [lid])
  sc_s2wb{v} [lid]]),
  ([sc_s2wh{v} [lid], sc_s2wi{v} [lid], sc_s2wj{v} 
[lid],
sc_s2wk{v} [lid], sc_s2wl{v} [lid], sc_s2wm{v} 
[lid]],
   [main:Expr.Graph{v r51} [gid]
  sc_s2wm{v} [lid]
  sc_s2wl{v} [lid]
  sc_s2wk{v} [lid]
  sc_s2wj{v} [lid],
base:GHC.Base.:{(w) v 65} [gid]
  @ main:Expr.Gen{tc r53}
  (main:Expr.Ghost{v r4P} [gid] sc_s2wi{v} [lid])
  sc_s2wh{v} [lid]]),
  ([sc_s2wR{v} [lid], sc_s2wS{v} [lid], sc_s2wT{v} 
[lid]],
   [sc_s2wT{v} [lid],
base:GHC.Base.:{(w) v 65} [gid]
  @ main:Expr.Gen{tc r53}
  (main:Expr.Vertex{v r4R} [gid] sc_s2wS{v} [lid])
  sc_s2wR{v} [lid]]),
  ([sc_s2wU{v} [lid], sc_s2wV{v} [lid], sc_s2wW{v} 
[lid]],
   [sc_s2wW{v} [lid],
base:GHC.Base.:{(w) v 65} [gid]
  @ main:Expr.Gen{tc r53}
  (main:Expr.Vertex{v r4R} [gid]
 (base:GHC.Base.I#{(w) v 6d} [gid] sc_s2wV{v} 
[lid]))
  sc_s2wU{v} [lid]])]


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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Brandon S. Allbery KF8NH


On Apr 14, 2008, at 23:45 , Benjamin L. Russell wrote:


hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower ((a, b) : moves)
| null moves = Move  ++ show a ++  to ++ show b ++ .
| otherwise == Move  ++ show a ++  to ++ show b ++ . ++  
hanoi_shower moves


`==' after the `otherwise'?  (I think the error involving `}' is a  
side effect of the single ugliest part of Haskell syntax, which  
specifies the parser inserting `}' as necessary to try to get a parse.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Luke Palmer
On Tue, Apr 15, 2008 at 3:45 AM, Benjamin L. Russell
[EMAIL PROTECTED] wrote:
 hanoi_shower ((a, b) : moves)
 | null moves = Move  ++ show a ++  to ++ show
  b ++ .
 | otherwise == Move  ++ show a ++  to ++ show
  b ++ . ++ hanoi_shower moves

More idiomatic pedantry:  the way you will see most Haskellers write
this style of function is by pattern matching rather than guards:

hanoi_shower [] = 
hanoi_shower ((a,b):moves) = Move  ++ show a ++  to  ++ show b ++
.\n ++ hanoi_shower moves

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