Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Philippa Cowderoy
On Tue, 25 Sep 2007, Lennart Augustsson wrote:

> It's reasonably easy to read.
> But you could make it more readable.  Type signatures, naming the first
> lambda...
> 

It might be reasonable to define something like mapMatrix that happens to 
be map . map, too. Along with at least a type synonym for matrices. Name 
domain constructs rather than expecting people to reconstruct them from 
their implementations, in other words.

-- 
[EMAIL PROTECTED]

The task of the academic is not to scale great
intellectual mountains, but to flatten them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Lennart Augustsson
Text.printf only has one type.  But it is a bit involved.  Just use it
without worrying exactly how it works. :)

Like 's ++ printtf "%g*x%d" x i'

On 9/25/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
>
> Chaddaï Fouché wrote:
> > 2007/9/25, Andrew Coppin <[EMAIL PROTECTED]>:
> >
> >>> printf don't always perform IO : if you ask it for a String it will
> >>> happily turn into sprintf for you, if you use it in the IO Monad, it
> >>> will indeed perform IO, but there's nothing fundamentally IO bound in
> >>> printf logic.
> >>>
> >>>
> >> That's even *more* impossible... o_O
> >>
> >
> > Why ?
> >
>
> How can one function have more than one type signature?
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Lennart Augustsson
It's reasonably easy to read.
But you could make it more readable.  Type signatures, naming the first
lambda...

On 9/25/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
>
> While using Haskell, I often find myself writing convoluted
> constructions such as this:
>
> show_system =
>   unlines .
>   zipWith
> (\l ms ->
>   "Eq" ++
>   show l ++
>   ": " ++
>   (concat $ intersperse " + " $ zipWith (\n x -> x ++ " x" ++ show
> n) [1..] (init ms)) ++
>   " = " ++
>   last ms
> )
> [1..] .
>   map (map (take 8 . show))
>
> And people complain that *Perl* is bad? This function is quite obviously
> absurd. I mean, it works, but can *you* figure out what it does without
> running it? The question is, can anybody think of a better way to write
> this function? (And more generally, functions like it.)
>
> ___
> 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] Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH


On Sep 25, 2007, at 7:25 , Andrew Coppin wrote:


Chaddaï Fouché wrote:

2007/9/25, Andrew Coppin <[EMAIL PROTECTED]>:


printf don't always perform IO : if you ask it for a String it will
happily turn into sprintf for you, if you use it in the IO  
Monad, it
will indeed perform IO, but there's nothing fundamentally IO  
bound in

printf logic.


That's even *more* impossible... o_O


Why ?


How can one function have more than one type signature?


Polymorphism via typeclasses.  PrintfType is rather hairy, as I said,  
but it can do the job by having instances for IsString (itself a hack  
of sorts) and IO.


--
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] Very crazy

2007-09-25 Thread Miguel Mitrofanov
> How can one function have more than one type signature?

It's called "polymorphism".
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin

Chaddaï Fouché wrote:

2007/9/25, Andrew Coppin <[EMAIL PROTECTED]>:
  

printf don't always perform IO : if you ask it for a String it will
happily turn into sprintf for you, if you use it in the IO Monad, it
will indeed perform IO, but there's nothing fundamentally IO bound in
printf logic.

  

That's even *more* impossible... o_O



Why ?
  


How can one function have more than one type signature?

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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin

Chaddaï Fouché wrote:

2007/9/25, Andrew Coppin <[EMAIL PROTECTED]>:
  

Forget PrintfType - I can't even understand the haddoc page yet!

(printf performs I/O, yet it is outside the I/O monad. It seems to
accept an arbitrary number of arguments, which is obviously impossible.
It's *almost* as scary as the original. Although the original will crash
your program is you use it wr... oh, so does this one. Cool.)



printf don't always perform IO : if you ask it for a String it will
happily turn into sprintf for you, if you use it in the IO Monad, it
will indeed perform IO, but there's nothing fundamentally IO bound in
printf logic.
  


That's even *more* impossible... o_O


Well printf crash your program because it can't check if you're
arguments correspond to the chain at compile time (quite obviously
since the chain itself can be dynamic), but it won't corrupt memory or
anything from this kind, so it's arguably much better than the C one.
  


All I know is that in C, any attempt to use printf() has an 80% 
probability of causing the machine to dump the entire contents of RAM to 
stdout until it happens upon a zero byte. Probably the most annoying 
part was all the 0x07 bytes in there. Do you know what a room full of 
beeping PCs is like? I do... Sometimes when we got bored, we would 
"race" our PCs to see which one would stop beeping first. (But they 
stopped that when I worked out how to make mine "win" every race...)



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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Tristan Allwood
On Tue, Sep 25, 2007 at 10:53:55AM +0100, Andrew Coppin wrote:
> Tristan Allwood wrote:
>>
>> Just to follow those sentiments, the version I knocked out quickly
>> looked like:
>> (It's not quite the same as the original function, I think I'm lacking a
>> map (map (take 8)) on the first line).
>>
>> showSystems :: Show a => [[a]] -> String
>> showSystems = unlines . zipWith showSystem [1..]   
>>   where
>> showSystem n as = "Eq" ++ (show n) ++ ": " ++ sum ++ " = " ++ val
>>   where
>> sum = concat . intersperse " + " . zipWith showNum [1..] $ (init 
>> as)
>> val = show . last $ as
>> showNum n a = show a ++ " x" ++ show n
>>
>>   
>
> I'm puzzled - do we have 2 seperate where clauses?

Yes there are 2 and no they arn't seperate.  The second where clause is
nested and is a set of definitioins local to showSystem, and as such can
use the bound values of n and as. (But it can also "see" any values
bound by showSystems and its where clause (which in this case is just
the definition of showSystem).

Clear as mud?

T
-- 
Tristan Allwood
PhD Student
Department of Computing
Imperial College London
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH


On Sep 25, 2007, at 5:45 , Andrew Coppin wrote:

Still, since Haskell seems to be devoid of any more advanced way of  
formatting numbers beyond low-level character jiggling...


Text.Printf.printf is your friend.

--
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] Very crazy

2007-09-25 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:


On Sep 25, 2007, at 5:56 , Andrew Coppin wrote:

More seriously, I have no idea how you'd implement this in Haskell. 
Presumably the standard show instance for Int, Double, etc. is in 
native C? You could probably reimplement it in Haskell for the 
integer case, but not for floating-point...


Actually, Text.Printf is pure Haskell.  (Very *scary* Haskell:  deep 
type hackery is needed to make it work.  Don't try to understand 
PrintfType.  :)



Forget PrintfType - I can't even understand the haddoc page yet!

(printf performs I/O, yet it is outside the I/O monad. It seems to 
accept an arbitrary number of arguments, which is obviously impossible. 
It's *almost* as scary as the original. Although the original will crash 
your program is you use it wr... oh, so does this one. Cool.)


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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH


On Sep 25, 2007, at 5:56 , Andrew Coppin wrote:

More seriously, I have no idea how you'd implement this in Haskell.  
Presumably the standard show instance for Int, Double, etc. is in  
native C? You could probably reimplement it in Haskell for the  
integer case, but not for floating-point...


Actually, Text.Printf is pure Haskell.  (Very *scary* Haskell:  deep  
type hackery is needed to make it work.  Don't try to understand  
PrintfType.  :)


--
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] Very crazy

2007-09-25 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:


On Sep 25, 2007, at 5:48 , Andrew Coppin wrote:

You've got to be kidding... I went to all the trouble of learning a 
"scary logic programming language [sic]" just to avoid that damned 
printf() function! :-/


Enh.  :)  On the other hand, I do wonder that nobody's written a 
combinator-based numeric formatting library.


They probably have - it's probably based on Peano integers though. :-P

More seriously, I have no idea how you'd implement this in Haskell. 
Presumably the standard show instance for Int, Double, etc. is in native 
C? You could probably reimplement it in Haskell for the integer case, 
but not for floating-point...


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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin

Tristan Allwood wrote:


Just to follow those sentiments, the version I knocked out quickly
looked like:
(It's not quite the same as the original function, I think I'm lacking a
map (map (take 8)) on the first line).

showSystems :: Show a => [[a]] -> String
showSystems = unlines . zipWith showSystem [1..] 
  where

showSystem n as = "Eq" ++ (show n) ++ ": " ++ sum ++ " = " ++ val
  where
sum = concat . intersperse " + " . zipWith showNum [1..] $ (init as)
val = show . last $ as
showNum n a = show a ++ " x" ++ show n

  


I'm puzzled - do we have 2 seperate where clauses?


Pointsfree and explicit lambda notation I find can be very concise in
places, but make it quite hard to reuse or refactor code later - if you
can't read it, make a function/variable with a useful name so you can
later.
  


Mmm, so just like every other programming language. Theoretically you 
could write a ten thousand line Pascal program on 1 line - but please 
don't! Hehe.


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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Brandon S. Allbery KF8NH


On Sep 25, 2007, at 5:48 , Andrew Coppin wrote:


Dougal Stanton wrote:

In this instance I would suggest:

(1) Text.Printf



You've got to be kidding... I went to all the trouble of learning a  
"scary logic programming language [sic]" just to avoid that damned  
printf() function! :-/


Enh.  :)  On the other hand, I do wonder that nobody's written a  
combinator-based numeric formatting library.


--
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] Very crazy

2007-09-25 Thread Andrew Coppin

Dougal Stanton wrote:

In this instance I would suggest:

(1) Text.Printf
  


You've got to be kidding... I went to all the trouble of learning a 
"scary logic programming language [sic]" just to avoid that damned 
printf() function! :-/



(2) Pull out some of those things into separate functions with
where/let clauses.

If it's a matrix you should probably have something like

  

showMatrix = concatMap showRow



Since you'll be applying the same procedures to each line of digits.
  


Well, actually more like

 show_matrix = concat . zipWith show_row [1..]

but yeah, this would probably simplify things somewhat.

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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin

Neil Mitchell wrote:

Hi

A nice auxiliary would help:

showEqn :: Int -> [Double] -> String
showEqn i vs = ...
where
  (add,ans) = (init vs, last vs)

Then you can half the complexity. There are probably a few useful
functions that aren't in the standard libraries (consperse, joinWith
etc) that you could make use of.
  


OK, I'll give that a go...

(Actually, at present it's an "augmented matrix", represented as 
[[Double]]. I'm thinking by making it a matrix and seperate vector, I 
could reduce the runtime quite significantly by making it much faster to 
get hold of the RHS.)


BTW, one *extremely* common function that I've never seen mentioned 
anywhere is this one:


 map2 :: (a -> b) -> [[a]] -> [[b]]
 map2 f = map (map f)

I cannot understand why this isn't already in the standard libraries...


You seem to be doing take 8 on the double - what if the double prints
out more information than this as the result of show?
100 could end up a bit smaller.
  


The contents of the matrix are random numbers between 0 and 100. The 
problems happen if one of the numbers turns out to be something like 
"3.5847368473587e-27" or something. Then it will look many thousands of 
times BIGGER! ;-)


Still, since Haskell seems to be devoid of any more advanced way of 
formatting numbers beyond low-level character jiggling...


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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Tristan Allwood
On Tue, Sep 25, 2007 at 10:31:34AM +0100, Dougal Stanton wrote:
> On 25/09/2007, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> In this instance I would suggest:
> 
> (1) Text.Printf
> (2) Pull out some of those things into separate functions with
> where/let clauses.
> 
> If it's a matrix you should probably have something like
> 
> > showMatrix = concatMap showRow
> 
> Since you'll be applying the same procedures to each line of digits.

Just to follow those sentiments, the version I knocked out quickly
looked like:
(It's not quite the same as the original function, I think I'm lacking a
map (map (take 8)) on the first line).

showSystems :: Show a => [[a]] -> String
showSystems = unlines . zipWith showSystem [1..] 
  where
showSystem n as = "Eq" ++ (show n) ++ ": " ++ sum ++ " = " ++ val
  where
sum = concat . intersperse " + " . zipWith showNum [1..] $ (init as)
val = show . last $ as
showNum n a = show a ++ " x" ++ show n


Pointsfree and explicit lambda notation I find can be very concise in
places, but make it quite hard to reuse or refactor code later - if you
can't read it, make a function/variable with a useful name so you can
later.

Regards,

T

-- 
Tristan Allwood
PhD Student
Department of Computing
Imperial College London
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Neil Mitchell
Hi

> complex. The input is quite simple (it's a bunch of numbers), the output
> is quite simple (it's a neatly formatted string), but the process in the
> middle is... a mess. I'd like to find a more readable way of doing stuff
> like this. It's not just this specific function; any general hints would
> be good. ;-)

A nice auxiliary would help:

showEqn :: Int -> [Double] -> String
showEqn i vs = ...
where
  (add,ans) = (init vs, last vs)

Then you can half the complexity. There are probably a few useful
functions that aren't in the standard libraries (consperse, joinWith
etc) that you could make use of.

You seem to be doing take 8 on the double - what if the double prints
out more information than this as the result of show?
100 could end up a bit smaller.

Thanks

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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Dougal Stanton
On 25/09/2007, Andrew Coppin <[EMAIL PROTECTED]> wrote:

> Type signature is
>
>   show_system :: [[Double]] -> String
>
> It takes a matrix representing a system of equations, and pretty prints
> it. Unfortunately, doing complex formatting like that is... well,
> complex. The input is quite simple (it's a bunch of numbers), the output
> is quite simple (it's a neatly formatted string), but the process in the
> middle is... a mess. I'd like to find a more readable way of doing stuff
> like this. It's not just this specific function; any general hints would
> be good. ;-)

In this instance I would suggest:

(1) Text.Printf
(2) Pull out some of those things into separate functions with
where/let clauses.

If it's a matrix you should probably have something like

> showMatrix = concatMap showRow

Since you'll be applying the same procedures to each line of digits.

Cheers,

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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin

Neil Mitchell wrote:

Hi

  

And people complain that *Perl* is bad? This function is quite obviously
absurd. I mean, it works, but can *you* figure out what it does without
running it?



No. Can you say what the intention of this code is? Maybe a few
examples? The type signature? That way I think people will be more
able to give you hints.
  


Type signature is

 show_system :: [[Double]] -> String

It takes a matrix representing a system of equations, and pretty prints 
it. Unfortunately, doing complex formatting like that is... well, 
complex. The input is quite simple (it's a bunch of numbers), the output 
is quite simple (it's a neatly formatted string), but the process in the 
middle is... a mess. I'd like to find a more readable way of doing stuff 
like this. It's not just this specific function; any general hints would 
be good. ;-)


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


Re: [Haskell-cafe] Very crazy

2007-09-25 Thread Neil Mitchell
Hi

> show_system =
>   unlines .
>   zipWith
> (\l ms ->
>   "Eq" ++
>   show l ++
>   ": " ++
>   (concat $ intersperse " + " $ zipWith (\n x -> x ++ " x" ++ show
> n) [1..] (init ms)) ++
>   " = " ++
>   last ms
> )
> [1..] .
>   map (map (take 8 . show))
>
> And people complain that *Perl* is bad? This function is quite obviously
> absurd. I mean, it works, but can *you* figure out what it does without
> running it?

No. Can you say what the intention of this code is? Maybe a few
examples? The type signature? That way I think people will be more
able to give you hints.

Generally, I find list comprehensions to be a good way out of general
listy mess.

Thanks

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


[Haskell-cafe] Very crazy

2007-09-25 Thread Andrew Coppin
While using Haskell, I often find myself writing convoluted 
constructions such as this:


show_system =
 unlines .
 zipWith
   (\l ms ->
 "Eq" ++
 show l ++
 ": " ++
 (concat $ intersperse " + " $ zipWith (\n x -> x ++ " x" ++ show 
n) [1..] (init ms)) ++

 " = " ++
 last ms
   )
   [1..] .
 map (map (take 8 . show))

And people complain that *Perl* is bad? This function is quite obviously 
absurd. I mean, it works, but can *you* figure out what it does without 
running it? The question is, can anybody think of a better way to write 
this function? (And more generally, functions like it.)


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