[Haskell-cafe] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Nicholls, Mark
Hello,

I largely don't know what I'm doing or even trying to do, it is a voyage into 
the unknownbutif I go...

 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 class Foo x y | x - y, y - x
 instance Foo Integer Integer

That seems to workand my head seems to say...your created some sort of 
binary relation between 2 types...and made Integer,Integer a member of it...

Something like that anyway

Then I go

 data Bar

 instance Foo Bar x

Error!but I'm think I understand thisI can't claim that Bar,x is a 
member of Foo and Integer,Integer is member of Foo and preserve my functional 
dependencies, because Bar,Integer is now a member of Foo..

Bad programmer...


So how I naively go


 class NotAnInteger a

 instance (NotAnInteger x) = Foo Bar x

I haven't declared integer to be NotAnIntegerso (in a closed 
world)this would seem to exclude the contradictionbut...


Functional dependencies conflict between instance declarations:
  instance Foo Integer Integer -- Defined at liam1.lhs:7:12
  instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12

So

i)I clearly don't understand something about the type 
system.

ii)   I don't know how to restrict type variables in instance 
declarationsi.e. how do I use the notion of Foo across different 
combinations of types, without them colliding.







CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% secure and carries risks such as delay, data 
corruption, non-delivery, wrongful interception and unauthorised amendment. If 
you communicate with us by e-mail, you acknowledge and assume these risks, and 
you agree to take appropriate measures to minimise these risks when e-mailing 
us.

MTV Networks International, MTV Networks UK  Ireland, Greenhouse, Nickelodeon 
Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be 
Viacom, Viacom International Media Networks and VIMN and Comedy Central are all 
trading names of MTV Networks Europe.  MTV Networks Europe is a partnership 
between MTV Networks Europe Inc. and Viacom Networks Europe Inc.  Address for 
service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Erik Hesselink
The constraint on an instance never influences which instance is
selected. So as far as instance selection goes, 'instance Foo x' and
'instance C x = Foo x' are the same. The constraint is only checked
after the instance is selected.

Erik

On Fri, Jul 5, 2013 at 2:43 PM, Nicholls, Mark nicholls.m...@vimn.com wrote:
 Hello,



 I largely don’t know what I’m doing or even trying to do, it is a voyage
 into the unknown….but….if I go…



 {-# LANGUAGE MultiParamTypeClasses #-}

 {-# LANGUAGE FunctionalDependencies #-}

 {-# LANGUAGE FlexibleInstances #-}

 {-# LANGUAGE UndecidableInstances #-}



 class Foo x y | x - y, y - x

 instance Foo Integer Integer



 That seems to work….and my head seems to say…your created some sort of
 binary relation between 2 types…and made Integer,Integer a member of it…



 Something like that anyway….



 Then I go….



 data Bar



 instance Foo Bar x



 Error!but I’m think I understand this….I can’t claim that Bar,x is a
 member of Foo and Integer,Integer is member of Foo and preserve my
 functional dependencies, because Bar,Integer is now a member of Foo..



 Bad programmer…….





 So how I naively go….





 class NotAnInteger a



 instance (NotAnInteger x) = Foo Bar x



 I haven’t declared integer to be “NotAnInteger”….so (in a closed
 world)….this would seem to exclude the contradiction….but…





 Functional dependencies conflict between instance declarations:

   instance Foo Integer Integer -- Defined at liam1.lhs:7:12

   instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12



 So

 i)I clearly don’t understand something about the type
 system.

 ii)   I don’t know how to restrict type variables in
 instance declarations….i.e. how do I use the notion of “Foo” across
 different combinations of types, without them colliding.

















 CONFIDENTIALITY NOTICE

 This e-mail (and any attached files) is confidential and protected by
 copyright (and other intellectual property rights). If you are not the
 intended recipient please e-mail the sender and then delete the email and
 any attached files immediately. Any further use or dissemination is
 prohibited.

 While MTV Networks Europe has taken steps to ensure that this email and any
 attachments are virus free, it is your responsibility to ensure that this
 message and any attachments are virus free and do not affect your systems /
 data.

 Communicating by email is not 100% secure and carries risks such as delay,
 data corruption, non-delivery, wrongful interception and unauthorised
 amendment. If you communicate with us by e-mail, you acknowledge and assume
 these risks, and you agree to take appropriate measures to minimise these
 risks when e-mailing us.

 MTV Networks International, MTV Networks UK  Ireland, Greenhouse,
 Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions
 International, Be Viacom, Viacom International Media Networks and VIMN and
 Comedy Central are all trading names of MTV Networks Europe.  MTV Networks
 Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks
 Europe Inc.  Address for service in Great Britain is 17-29 Hawley Crescent,
 London, NW1 8TT.


 ___
 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] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Tikhon Jelvis
You're running into the open worldassumption--anybody could come along
and make Integer part of your NotAnInteger class, and there's nothing you
can do to stop them. This is a design tradeoff for typeclasses: typeclass
instances are always global and are exported to all other modules you use.
This means you cannot ensure a type is *not* part of a typeclass. (Or, at
the very least, you can't convince GHC of this fact.)

For more information about this, take a look at the following StackOverflow
question:
http://stackoverflow.com/questions/8728596/explicitly-import-instances
On Jul 5, 2013 8:47 AM, Nicholls, Mark nicholls.m...@vimn.com wrote:

  Hello,

 ** **

 I largely don’t know what I’m doing or even trying to do, it is a voyage
 into the unknown….but….if I go…

 ** **

  {-# LANGUAGE MultiParamTypeClasses #-}

  {-# LANGUAGE FunctionalDependencies #-}

  {-# LANGUAGE FlexibleInstances #-}

  {-# LANGUAGE UndecidableInstances #-}

 ** **

  class Foo x y | x - y, y - x

  instance Foo Integer Integer

 ** **

 That seems to work….and my head seems to say…your created some sort of
 binary relation between 2 types…and made Integer,Integer a member of it…
 

 ** **

 Something like that anyway….

 ** **

 Then I go….

 ** **

  data Bar

 ** **

  instance Foo Bar x

 ** **

 Error!but I’m think I understand this….I can’t claim that Bar,x is a
 member of Foo and Integer,Integer is member of Foo and preserve my
 functional dependencies, because Bar,Integer is now a member of Foo..***
 *

 ** **

 Bad programmer…….

 ** **

 ** **

 So how I naively go….

 ** **

 ** **

  class NotAnInteger a

 ** **

  instance (NotAnInteger x) = Foo Bar x

 ** **

 I haven’t declared integer to be “NotAnInteger”….so (in a closed
 world)….this would seem to exclude the contradiction….but…

 ** **

 ** **

 Functional dependencies conflict between instance declarations:

   instance Foo Integer Integer -- Defined at liam1.lhs:7:12

   instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12**
 **

 ** **

 So 

 **i)**I clearly don’t understand something about the
 type system.

 **ii)   **I don’t know how to restrict type variables in
 instance declarations….i.e. how do I use the notion of “Foo” across
 different combinations of types, without them colliding.

 ** **

 ** **

 ** **

 ** **

 ** **

 ** **

 ** **



 CONFIDENTIALITY NOTICE

 This e-mail (and any attached files) is confidential and protected by
 copyright (and other intellectual property rights). If you are not the
 intended recipient please e-mail the sender and then delete the email and
 any attached files immediately. Any further use or dissemination is
 prohibited.

 While MTV Networks Europe has taken steps to ensure that this email and
 any attachments are virus free, it is your responsibility to ensure that
 this message and any attachments are virus free and do not affect your
 systems / data.

 Communicating by email is not 100% secure and carries risks such as delay,
 data corruption, non-delivery, wrongful interception and unauthorised
 amendment. If you communicate with us by e-mail, you acknowledge and assume
 these risks, and you agree to take appropriate measures to minimise these
 risks when e-mailing us.

 MTV Networks International, MTV Networks UK  Ireland, Greenhouse,
 Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions
 International, Be Viacom, Viacom International Media Networks and VIMN and
 Comedy Central are all trading names of MTV Networks Europe.  MTV Networks
 Europe is a partnership between MTV Networks Europe Inc. and Viacom
 Networks Europe Inc.  Address for service in Great Britain is 17-29 Hawley
 Crescent, London, NW1 8TT.

 ___
 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] newbie question about Functional dependencies conflict between instance declarations:.....

2013-07-05 Thread Nicholls, Mark
Ah

So it isn't a closed world

So how do I stop my instances clashing?

The x in

instance Foo Bar x

is never intended to be Integer.



Mark Nicholls | Lead broadcast  corporate architect, Programmes  Development 
- Viacom International Media Networks
A: 17-29 Hawley Crescent London NW1 8TT | e: 
nicholls.m...@vimn.commailto:m...@vimn.com T: +44 (0)203 580 2223

[Description: cid:image001.png@01CD488D.9204D030]

From: Tikhon Jelvis [mailto:tik...@jelv.is]
Sent: 05 July 2013 2:08 PM
To: Nicholls, Mark
Cc: haskell-cafe
Subject: Re: [Haskell-cafe] newbie question about Functional dependencies 
conflict between instance declarations:.


You're running into the open worldassumption--anybody could come along and 
make Integer part of your NotAnInteger class, and there's nothing you can do to 
stop them. This is a design tradeoff for typeclasses: typeclass instances are 
always global and are exported to all other modules you use. This means you 
cannot ensure a type is *not* part of a typeclass. (Or, at the very least, you 
can't convince GHC of this fact.)

For more information about this, take a look at the following StackOverflow 
question: http://stackoverflow.com/questions/8728596/explicitly-import-instances
On Jul 5, 2013 8:47 AM, Nicholls, Mark 
nicholls.m...@vimn.commailto:nicholls.m...@vimn.com wrote:
Hello,

I largely don't know what I'm doing or even trying to do, it is a voyage into 
the unknownbutif I go...

 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}

 class Foo x y | x - y, y - x
 instance Foo Integer Integer

That seems to workand my head seems to say...your created some sort of 
binary relation between 2 types...and made Integer,Integer a member of it...

Something like that anyway

Then I go

 data Bar

 instance Foo Bar x

Error!but I'm think I understand thisI can't claim that Bar,x is a 
member of Foo and Integer,Integer is member of Foo and preserve my functional 
dependencies, because Bar,Integer is now a member of Foo..

Bad programmer...


So how I naively go


 class NotAnInteger a

 instance (NotAnInteger x) = Foo Bar x

I haven't declared integer to be NotAnIntegerso (in a closed 
world)this would seem to exclude the contradictionbut...


Functional dependencies conflict between instance declarations:
  instance Foo Integer Integer -- Defined at liam1.lhs:7:12
  instance NotAnInteger x = Foo Bar x -- Defined at liam1.lhs:13:12

So

i)I clearly don't understand something about the type 
system.

ii)   I don't know how to restrict type variables in instance 
declarationsi.e. how do I use the notion of Foo across different 
combinations of types, without them colliding.









CONFIDENTIALITY NOTICE

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100% secure and carries risks such as delay, data 
corruption, non-delivery, wrongful interception and unauthorised amendment. If 
you communicate with us by e-mail, you acknowledge and assume these risks, and 
you agree to take appropriate measures to minimise these risks when e-mailing 
us.

MTV Networks International, MTV Networks UK  Ireland, Greenhouse, Nickelodeon 
Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be 
Viacom, Viacom International Media Networks and VIMN and Comedy Central are all 
trading names of MTV Networks Europe.  MTV Networks Europe is a partnership 
between MTV Networks Europe Inc. and Viacom Networks Europe Inc.  Address for 
service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.

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

This e-mail (and any attached files) is confidential and protected by copyright 
(and other intellectual property rights). If you are not the intended recipient 
please e-mail the sender and then delete the email and any attached files 
immediately. Any further use or dissemination is prohibited.

While MTV Networks Europe has taken steps to ensure that this email and any 
attachments are virus free, it is your responsibility to ensure that this 
message and any attachments are virus free and do not affect your systems / 
data.

Communicating by email is not 100

[Haskell-cafe] Newbie Question

2010-12-31 Thread Chionidis Ioannis

Hello everybody!

I am quite new to haskell programming. I am trying to make a gui for a 
drumming project made in euterpea and I want to do something like this :

  b - button f [text := Run! , on command := (test mambo_orig)]
test mambo_orig is executed from ghci but I want It to be able to 
execute each time the user presses the button.


Hope I didn't mess it up in the explaination,
Giannis Chionidis

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


Re: [Haskell-cafe] Newbie Question

2010-12-31 Thread Henk-Jan van Tuyl
On Fri, 31 Dec 2010 12:32:06 +0100, Chionidis Ioannis  
j...@echidna-band.com wrote:



Hello everybody!

I am quite new to haskell programming. I am trying to make a gui for a  
drumming project made in euterpea and I want to do something like this :

   b - button f [text := Run! , on command := (test mambo_orig)]
test mambo_orig is executed from ghci but I want It to be able to  
execute each time the user presses the button.


Hope I didn't mess it up in the explaination,
Giannis Chionidis



This should work as expected, but GHCi does not play nice with wxHaskell;  
the problem is being worked on. Try compiling your program.


Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
--

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


[Haskell-cafe] Newbie question about using WinGHCi

2010-07-01 Thread Christopher Tauss
Hello -

I just a day or so ago downloaded Hakell and am playing around with it, and
I came upon this problem with WinGHCi:

I am able to enter a multi-line do statement that works if I use brackets
and semi-colon like so:

Prelude :{
Prelude| let main2 = do {
Prelude| putStrLn Please enter your name: ;
Prelude| name - getLine;
Prelude| putStrLn (Hello,  ++ name ++ , how are you?) }
Prelude| :}
Prelude main2
Please enter your name:
CT
Hello, CT, how are you?
Prelude

Note there is no indentation.  This makes sense to me because the :{  :}
just take all the lines in between and make it one line.

But it seems to me to be IMPOSSIBLE to input this into WinGHCi using
indentation like most of the code samples seem to do.

Should I just be satisfied that it works using brackets/ semi-colons?  Or is
there something obvious that I am missing that allows for indentation?

Thanks in advance. It's issues lik this that keep me up into the depths of
night.

Best Regards,

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


Re: [Haskell-cafe] Newbie question about using WinGHCi

2010-07-01 Thread Ivan Miljenovic
On 1 July 2010 16:04, Christopher Tauss ctau...@gmail.com wrote:
 Hello -

 I just a day or so ago downloaded Hakell and am playing around with it, and
 I came upon this problem with WinGHCi:

 I am able to enter a multi-line do statement that works if I use brackets
 and semi-colon like so:

 Prelude :{
 Prelude| let main2 = do {
 Prelude| putStrLn Please enter your name: ;
 Prelude| name - getLine;
 Prelude| putStrLn (Hello,  ++ name ++ , how are you?) }
 Prelude| :}
 Prelude main2
 Please enter your name:
 CT
 Hello, CT, how are you?
 Prelude

 Note there is no indentation.  This makes sense to me because the :{  :}
 just take all the lines in between and make it one line.

 But it seems to me to be IMPOSSIBLE to input this into WinGHCi using
 indentation like most of the code samples seem to do.

 Should I just be satisfied that it works using brackets/ semi-colons?  Or is
 there something obvious that I am missing that allows for indentation?

Typically, ghci (including WinGHCI) and Hugs are used to evaluate and
experiment with code, rather than writing it.  Write your actual code
in a file and load it with :load (or :l for short) into ghci.

In this sense, they aren't real REPLs in that you can't define new
data types, classes, etc. in them (you can write functions with a let
statement, but it gets cumbersome for long functions).

It might be better off thinking of the prompt as being individual
lines in a big do-block for a specialised version of the IO monad (in
the sense that normally just entering 5+4 wouldn't typecheck let
alone print the result, etc.).

 Thanks in advance. It's issues lik this that keep me up into the depths of
 night.

Hopefully you can now get to sleep ;-)

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie question how to pass data

2010-04-20 Thread Stephen Tetley
Hi

If you are working with characteristic functions (Point - Bool or
Point - Colour...) the common way to do this is to manufacture a Num
instance for functions. This gives you syntax overloading of the (+,
-, *) operators. Similarly you might want to overload (or have to
overload) Floating, Fractional...

Examples using this technique are Jerzy Karczmarczuk's Clastic, Conal
Elliott's Vertigo, Tangible Values, Pan etc.

To overload Num you have to define Show and Eq instances for functions
as well. Something along the lines of this is adequate:

type CF = (Double,Double) - Bool

instance Show CF where
  show _ = function

instance Eq CF where
 (==) _ _ = error No Eq on  Characteristic functions

instance Num CF where
  f + g = \pt - f pt + g pt
  -- ...
  negate f = \(x,y) - f (negate x, negate y)

  -- ... rest follows this pattern, Floating, Fractional similar

If you characteristic function is Point - Bool then you also need a
Num instance for Bool.

All that said, I think your formulation of func above is slightly
wrong to fit this style. Its forming a function (- Point) to point
rather than a characteristic function Point - Bool.

Best wishes

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


Re: [Haskell-cafe] newbie question how to pass data

2010-04-20 Thread Mujtaba Boori
Great job Stephen.
Thank for explaining . I got it to work.


On Tue, Apr 20, 2010 at 9:21 AM, Stephen Tetley stephen.tet...@gmail.comwrote:

 Hi

 If you are working with characteristic functions (Point - Bool or
 Point - Colour...) the common way to do this is to manufacture a Num
 instance for functions. This gives you syntax overloading of the (+,
 -, *) operators. Similarly you might want to overload (or have to
 overload) Floating, Fractional...

 Examples using this technique are Jerzy Karczmarczuk's Clastic, Conal
 Elliott's Vertigo, Tangible Values, Pan etc.

 To overload Num you have to define Show and Eq instances for functions
 as well. Something along the lines of this is adequate:

 type CF = (Double,Double) - Bool

 instance Show CF where
  show _ = function

 instance Eq CF where
  (==) _ _ = error No Eq on  Characteristic functions

 instance Num CF where
  f + g = \pt - f pt + g pt
  -- ...
  negate f = \(x,y) - f (negate x, negate y)

  -- ... rest follows this pattern, Floating, Fractional similar

 If you characteristic function is Point - Bool then you also need a
 Num instance for Bool.

 All that said, I think your formulation of func above is slightly
 wrong to fit this style. Its forming a function (- Point) to point
 rather than a characteristic function Point - Bool.

 Best wishes

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




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


[Haskell-cafe] newbie question how to pass data

2010-04-19 Thread Mujtaba Boori
Hello

I am sorry for the silly question.

I have a function as the following

func:: ((Float,Float) -Bool) - Float - ((Float,Float) - Bool)

I am trying to make calculation in this type ((Float,Float) -Bool)  with
Float and then pass the information to ((Float,Float) - Bool)


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


Re: [Haskell-cafe] newbie question how to pass data

2010-04-19 Thread Ozgur Akgun
Can you at least give an example of how you intend to use this func?
Since you do not describe it's behaviour, it is very hard to make a useful
comment (at least for me)

Best,

On 19 April 2010 16:54, Mujtaba Boori mujtaba.bo...@gmail.com wrote:

 Hello
 I am sorry for the silly question.

 I have a function as the following
 func:: ((Float,Float) -Bool) - Float - ((Float,Float) - Bool)
 I am trying to make calculation in this type ((Float,Float) -Bool)  with 
 Float and then pass the information to ((Float,Float) - Bool)

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




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


Re: [Haskell-cafe] newbie question how to pass data

2010-04-19 Thread Mujtaba Boori
sorry

ok I am trying to make these calculation

func  (x,y) s dg  =((x*(cos dg) - y*(sin dg)),(x*(sin dg) - y*(cos dg)))

This work for type (Float - Float)

but how can make it work with ((Float - Float) - Bool)

because my main function that I want use with.  it takes (Float,Float)
-Bool)  I need to return the same type ((Float,Float) -Bool)  so it could
be used with other function.


On Mon, Apr 19, 2010 at 5:54 PM, Ozgur Akgun ozgurak...@gmail.com wrote:

 Can you at least give an example of how you intend to use this func?
 Since you do not describe it's behaviour, it is very hard to make a useful
 comment (at least for me)

 Best,

 On 19 April 2010 16:54, Mujtaba Boori mujtaba.bo...@gmail.com wrote:
 
  Hello
  I am sorry for the silly question.
 
  I have a function as the following
  func:: ((Float,Float) -Bool) - Float - ((Float,Float) - Bool)
  I am trying to make calculation in this type ((Float,Float) -Bool)  with
 Float and then pass the information to ((Float,Float) - Bool)
 
  Thank again appreciated.
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Ozgur Akgun




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


Re: [Haskell-cafe] newbie question how to pass data

2010-04-19 Thread Dan Weston

First of all, your function
func  (x,y) s dg  =((x*(cos dg) - y*(sin dg)),(x*(sin dg) - y*(cos dg)))
does NOT work for type (Float - Float), unless you mean that that is 
the type of the unused parameter s. Also, your desired type ((Float - 
Float) - Bool) itself looks suspicious. It must accept any function 
(without something to apply it to) and arbitrarily return True or False. 
How will you decide which? I suspect you need another parameter for this 
function.


Second, on the off chance you are trying to calculate the position on a 
circle scaled then rotated an angle dg from (x,y), that new position is


f (x,y) s dg = (s*(x*(cos dg) - y*(sin dg)),s*(x*(sin dg) + y*(cos dg)))

in which case you are missing the s and the last minus sign in your 
formula should be a plus sign.
If so, this can be evaluated with greater clarity (and probably 
accuracy) in polar coordinates:


g (x,y) s dg = (r * cos a, r * sin a)
  where r  = s * sqrt (x^2 + y^2)
   a  = atan2 y x + dg

Third, if you did not need the scale, I would use an underscore to make 
that clear:


h (x,y) _ dg = (r * cos a, r * sin a)
  where r  = sqrt (x^2 + y^2)
   a  = atan2 y x + dg

That's all the observations I can make unless you describe the problem 
more clearly. Sorry.


Dan

Mujtaba Boori wrote:
sorry 

ok I am trying to make these calculation 


func  (x,y) s dg  =((x*(cos dg) - y*(sin dg)),(x*(sin dg) - y*(cos dg)))

This work for type (Float - Float)

but how can make it work with ((Float - Float) - Bool)

because my main function that I want use with.  it takes (Float,Float) 
-Bool)  I need to return the same type ((Float,Float) -Bool)  so it 
could be used with other function. 



On Mon, Apr 19, 2010 at 5:54 PM, Ozgur Akgun ozgurak...@gmail.com 
mailto:ozgurak...@gmail.com wrote:


Can you at least give an example of how you intend to use this func?
Since you do not describe it's behaviour, it is very hard to make a
useful
comment (at least for me)

Best,

On 19 April 2010 16:54, Mujtaba Boori mujtaba.bo...@gmail.com
mailto:mujtaba.bo...@gmail.com wrote:
 
  Hello
  I am sorry for the silly question.
 
  I have a function as the following
  func:: ((Float,Float) -Bool) - Float - ((Float,Float) - Bool)
  I am trying to make calculation in this type ((Float,Float)
-Bool)  with Float and then pass the information to ((Float,Float)
- Bool)
 
  Thank again appreciated.
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



--
Ozgur Akgun




--
Mujtaba Ali Alboori



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


Re: [Haskell-cafe] newbie question how to pass data

2010-04-19 Thread Mujtaba Boori
Thanks Dan. Great help

but my problem has not solved yet
This doesn't work for type ((Float - Float)-Bool)

to make it easier ignore the rotation and suppose I want just multiplay with
whatever (x ,y) and return the result to this type ((Float - Float)-Bool)

note this type is shorten and replace by t
Type Point = (Float, Float)
Type Bitmap = Point - Bool

so the function type actually
func :: Bitmap - Float - Bitmap

I want to take Bitmap do some calculation on Bitmap  the return it
as Bitmap.

GHCi response for Dan method is this
Couldn't match expected type `Bitmap'
   against inferred type `(a, b)'
so it is missing a Bool.

hopefully it is clear .

On Mon, Apr 19, 2010 at 7:02 PM, Dan Weston weston...@imageworks.comwrote:

 First of all, your function






 func  (x,y) s dg  =((x*(cos dg) - y*(sin dg)),(x*(sin dg) - y*(cos dg)))
 does NOT work for type (Float - Float), unless you mean that that is the
 type of the unused parameter s. Also, your desired type ((Float - Float) -
 Bool) itself looks suspicious. It must accept any function (without
 something to apply it to) and arbitrarily return True or False. How will you
 decide which? I suspect you need another parameter for this function.

 Second, on the off chance you are trying to calculate the position on a
 circle scaled then rotated an angle dg from (x,y), that new position is

 f (x,y) s dg = (s*(x*(cos dg) - y*(sin dg)),s*(x*(sin dg) + y*(cos dg)))

 in which case you are missing the s and the last minus sign in your formula
 should be a plus sign.
 If so, this can be evaluated with greater clarity (and probably accuracy)
 in polar coordinates:

 g (x,y) s dg = (r * cos a, r * sin a)
  where r  = s * sqrt (x^2 + y^2)
   a  = atan2 y x + dg

 Third, if you did not need the scale, I would use an underscore to make
 that clear:

 h (x,y) _ dg = (r * cos a, r * sin a)
  where r  = sqrt (x^2 + y^2)
   a  = atan2 y x + dg

 That's all the observations I can make unless you describe the problem more
 clearly. Sorry.

 Dan

 Mujtaba Boori wrote:

 sorry
 ok I am trying to make these calculation
 func  (x,y) s dg  =((x*(cos dg) - y*(sin dg)),(x*(sin dg) - y*(cos dg)))

 This work for type (Float - Float)

 but how can make it work with ((Float - Float) - Bool)

 because my main function that I want use with.  it takes (Float,Float)
 -Bool)  I need to return the same type ((Float,Float) -Bool)  so it could
 be used with other function.

 On Mon, Apr 19, 2010 at 5:54 PM, Ozgur Akgun ozgurak...@gmail.commailto:
 ozgurak...@gmail.com wrote:

Can you at least give an example of how you intend to use this func?
Since you do not describe it's behaviour, it is very hard to make a
useful
comment (at least for me)

Best,

On 19 April 2010 16:54, Mujtaba Boori mujtaba.bo...@gmail.com
mailto:mujtaba.bo...@gmail.com wrote:
 
  Hello
  I am sorry for the silly question.
 
  I have a function as the following
  func:: ((Float,Float) -Bool) - Float - ((Float,Float) - Bool)
  I am trying to make calculation in this type ((Float,Float)
-Bool)  with Float and then pass the information to ((Float,Float)
- Bool)
 
  Thank again appreciated.
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org

  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



--
Ozgur Akgun




 --
 Mujtaba Ali Alboori




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


[Haskell-cafe] Newbie question about Parsec

2010-01-18 Thread david fries
Hey everybody

I've been playing around with Parsec a little bit lately. I like it a
lot, but now I've hit a bit of a challenge. Suppose I have to parse a
variable length string representing a time interval. Depending on how
many fields there are, the time is either interpreted as seconds,
minutes and seconds or hours, minutes and seconds. 

For example:

... 31 ... would be parsed as 31 seconds.
... 05:31 ... would be parsed as 5 minutes and 31 seconds.
... 01:05:31 ... would be parsed as 1 hour, 5 minutes and 31 seconds. 

I've come up with the following solution using optionMaybe to deal with
the problem:

data ElapsedTime = ElapsedTime {
 hours :: Int,
 minutes :: Int,
 seconds :: Int
} deriving (Show, Eq, Ord)

p_elapsed_time :: CharParser () ElapsedTime
p_elapsed_time = toElapsedTime $ (optionMaybe p_Int) 
   * (optionMaybe (char ':' * p_Int))
   * (optionMaybe (char ':' * p_Int *
skipSpaces))
where toElapsedTime Nothing Nothing Nothing = ElapsedTime 0 0 0
  toElapsedTime (Just s) Nothing Nothing = ElapsedTime 0 0 s
  toElapsedTime (Just m) (Just s) Nothing = ElapsedTime 0 m s
  toElapsedTime (Just h) (Just m) (Just s) = ElapsedTime h m s


Where p_Int simply parses a sequence of digits as an Int and skipSpaces
does just that.

This works correctly, but it also feels kinda clumsy. For one the
compiler rightly complains about non-exhaustive pattern matches in the
definition of the toElapsedTime function, although I believe that's
negligible in that particular case. 
Is there a better i.e. more elegant way to tackle such a problem? 

regards,
david 

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


Re: [Haskell-cafe] Newbie question about Parsec

2010-01-18 Thread Daniel Fischer
Am Montag 18 Januar 2010 19:09:23 schrieb david fries:
 Hey everybody

 I've been playing around with Parsec a little bit lately. I like it a
 lot, but now I've hit a bit of a challenge. Suppose I have to parse a
 variable length string representing a time interval. Depending on how
 many fields there are, the time is either interpreted as seconds,
 minutes and seconds or hours, minutes and seconds.

 For example:

 ... 31 ... would be parsed as 31 seconds.
 ... 05:31 ... would be parsed as 5 minutes and 31 seconds.
 ... 01:05:31 ... would be parsed as 1 hour, 5 minutes and 31 seconds.

 I've come up with the following solution using optionMaybe to deal with
 the problem:

 data ElapsedTime = ElapsedTime {
  hours :: Int,
  minutes :: Int,
  seconds :: Int
 } deriving (Show, Eq, Ord)

 p_elapsed_time :: CharParser () ElapsedTime
 p_elapsed_time = toElapsedTime $ (optionMaybe p_Int)
* (optionMaybe (char ':' * p_Int))
* (optionMaybe (char ':' * p_Int *
 skipSpaces))
 where toElapsedTime Nothing Nothing Nothing = ElapsedTime 0 0 0
   toElapsedTime (Just s) Nothing Nothing = ElapsedTime 0 0 s
   toElapsedTime (Just m) (Just s) Nothing = ElapsedTime 0 m s
   toElapsedTime (Just h) (Just m) (Just s) = ElapsedTime h m s


p_elapsed_time = toElapsedTime $ sepBy p_int (char ':')
   where
  toElapsedTime (h:m:s:_) = ElapsedTime h m s
  toElapsedTime [m,s] = ElapsedTime 0 m s
  toElapsedTime [s]   = ElapsedTime 0 0 s
  toElapsedTime []= ElapsedTime 0 0 0

You can replace the first pattern for toElapsedTime with [h,m,s] and add a 
failure case if sepBy p_int (char ':') parses more than three ints (or 
write a combinator that parses up to n results of p separated by sep).

Or

p_elapsed_time = do
s - p_int
et - cont_elapsed_time (ElapsedTime 0 0 s)

cont_elapsed_time et@(ElapsedTime h m s) = do
char ':'
n - p_int
cont_elapsed_time (ElapsedTime m s n)
   | return et


 Where p_Int simply parses a sequence of digits as an Int and skipSpaces
 does just that.

 This works correctly, but it also feels kinda clumsy. For one the
 compiler rightly complains about non-exhaustive pattern matches in the
 definition of the toElapsedTime function, although I believe that's
 negligible in that particular case.
 Is there a better i.e. more elegant way to tackle such a problem?

 regards,
 david


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


Re: [Haskell-cafe] [Newbie question] -- Looping stdin until condition is met

2008-06-02 Thread Ryan Ingram
On 5/30/08, Martin Blais [EMAIL PROTECTED] wrote:
 Dear Philip, could you point your virtual finger towards a
 reference/paper/book/any-bleeping-thing that would help this simple
 beginner understand why it doesn't work in this case? I'm trying to
 picture why a read function that terminates the program would be
 useful anywhere. In fact, any library function other than something like
 UNIX's exit or kill which terminates my program is not really
 welcome in any of my computer programs, but then again, I haven't yet
 been illuminated by the genie of pure functional languages.  A reference
 would be awesome.

As others have pointed out, the reason why it doesn't work is due to
lazy evaluation; the exception is hidden in a pure value and isn't
triggered until some other bit of code causes the pure value to be
evaluated.  You can force the exception to be generated in your catch
block by using seq (or $!, which is implemented using seq).
This forces the evaluation to happen at that point, although there are
a lot of gotchas involved; for Int it works fine, though.

Your question, then, requires asking why would you want to hide an
exception in a pure value?  The answer to that is quite interesting,
but here's a simpler example that might enlighten you:

head :: [a] - a
head (x:_) = x
head _ = error head: empty list

Just as you are required to prove before calling head that you
aren't passing an empty list, for your program to be total, you should
prove before calling read that the string parses properly.  If you
can't provide that proof (because, in this case, the string is
provided by the user), you should be using another function for
parsing.

Don suggested reads to implement maybeRead, which seems like a
great idea to me.

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


Re: [Haskell-cafe] [Newbie question] -- Looping stdin until condition is met

2008-06-02 Thread Neil Mitchell
Hi

 The best thing to do is bypass read and use 'reads' to define your
 own safe read.

maybeRead :: Read a = String - Maybe a
maybeRead s = case reads s of
[(x, )] - Just x
_ - Nothing

Or just use the Safe package:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/safe

http://hackage.haskell.org/packages/archive/safe/0.2/doc/html/Safe.html#v%3AreadMay

Thanks

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


[Haskell-cafe] [Newbie question] -- Looping stdin until condition is met

2008-05-30 Thread Martin Blais
Allright, this is a definitely a newbie question.

I'm learning Haskell and going through the exercises in the
beautiful Hutton book, and one of them requires for me to
write a loop that queries a line from the user (stdin),
looping until the user enters a valid integer (at least
that's how I want to implement the interface to the
exercise). I have tried tons of variants and modifications
of code, and I can't find the way to implement this. Here is
what my emacs buffer is at now::

  import Text.Read
  import System.IO
  import qualified Control.Exception as C

  getNum :: IO Int
  getNum = do line - (hGetLine stdin)
  x - (C.catch (do return (read line :: Int)) (\e - getNum))
  return x

  main = do x - getNum
putStr ((show x) ++ \n)

Now, I've tried the Prelude's catch, the Control.Exception
catch, I've tried moving it at the top of getnum, I've tried
without catch, I've tried a ton of other shtuff, so much
that I'm starting to think that Emacs is going to run out of
electrons soon. I asked some half-newbie friends who are
insanely enthousiastic about Haskell and they can't do it
either (I'm starting to think that those enthousiastic
friends are dating a beautiful girl with 3 PhDs, but she has
a 2-inch thick green and gooey wart smack on her nose and
they're so blindly in love that they can't admit that she
does). I've asked some university profs and they sidetrack
my question by saying I shouldn't do I/O so early. Can
anyone here restore my faith in the Haskell section of
humanity?

1. How do I catch the exception that is raised from read?

2. Where do I find the appropriate information I need in
   order to fix this? I'm probably just not searching in the
   right place. (Yes, I've seen the GHC docs, and it doesn't
   help, maybe I'm missing some background info.)

3. Please do not tell me I should solve the problem
   differently. Here is the problem I'm trying to solve, and
   nothing else:

 Write a program that reads a line from the user,
 looping the query until the line contains a valid
 integer.

It shouldn't be too hard i think. The best answer would be a
two-liner code example that'll make me feel even more stupid
than I already do.

Thanks in advance.

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


Re: [Haskell-cafe] [Newbie question] -- Looping stdin until condition is met

2008-05-30 Thread Philip Weaver
On Fri, May 30, 2008 at 5:28 PM, Martin Blais [EMAIL PROTECTED] wrote:
 Allright, this is a definitely a newbie question.

 I'm learning Haskell and going through the exercises in the
 beautiful Hutton book, and one of them requires for me to
 write a loop that queries a line from the user (stdin),
 looping until the user enters a valid integer (at least
 that's how I want to implement the interface to the
 exercise). I have tried tons of variants and modifications
 of code, and I can't find the way to implement this. Here is
 what my emacs buffer is at now::

  import Text.Read
  import System.IO
  import qualified Control.Exception as C

  getNum :: IO Int
  getNum = do line - (hGetLine stdin)
  x - (C.catch (do return (read line :: Int)) (\e - getNum))
  return x

  main = do x - getNum
putStr ((show x) ++ \n)

 Now, I've tried the Prelude's catch, the Control.Exception
 catch, I've tried moving it at the top of getnum, I've tried
 without catch, I've tried a ton of other shtuff, so much
 that I'm starting to think that Emacs is going to run out of
 electrons soon. I asked some half-newbie friends who are
 insanely enthousiastic about Haskell and they can't do it
 either (I'm starting to think that those enthousiastic
 friends are dating a beautiful girl with 3 PhDs, but she has
 a 2-inch thick green and gooey wart smack on her nose and
 they're so blindly in love that they can't admit that she
 does). I've asked some university profs and they sidetrack
 my question by saying I shouldn't do I/O so early. Can
 anyone here restore my faith in the Haskell section of
 humanity?

 1. How do I catch the exception that is raised from read?

I think you want readIO, which yields a computation in the IO monad,
so it can be caught.

 2. Where do I find the appropriate information I need in
   order to fix this? I'm probably just not searching in the
   right place. (Yes, I've seen the GHC docs, and it doesn't
   help, maybe I'm missing some background info.)

In this particular case, I am not sure where you'd find this
information.  It's not very intuitive to a beginner why read doesn't
work in this case.

 3. Please do not tell me I should solve the problem
   differently. Here is the problem I'm trying to solve, and
   nothing else:

 Write a program that reads a line from the user,
 looping the query until the line contains a valid
 integer.

 It shouldn't be too hard i think. The best answer would be a
 two-liner code example that'll make me feel even more stupid
 than I already do.

 Thanks in advance.

 ___
 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] [Newbie question] -- Looping stdin until condition is met

2008-05-30 Thread Don Stewart
blais:
 Allright, this is a definitely a newbie question.
 
 I'm learning Haskell and going through the exercises in the
 beautiful Hutton book, and one of them requires for me to
 write a loop that queries a line from the user (stdin),
 looping until the user enters a valid integer (at least
 that's how I want to implement the interface to the
 exercise).
  
 1. How do I catch the exception that is raised from read?

The best thing to do is bypass read and use 'reads' to define your
own safe read.

maybeRead :: Read a = String - Maybe a
maybeRead s = case reads s of
[(x, )] - Just x
_ - Nothing


For example, yielding:


import System.IO

main = do
x - getNum
print x

getNum :: IO Integer
getNum = do
n - getLine
case maybeRead n of
Nothing - getNum
Just n  - return n

 2. Where do I find the appropriate information I need in
order to fix this? I'm probably just not searching in the
right place. (Yes, I've seen the GHC docs, and it doesn't
help, maybe I'm missing some background info.)

I think Control.Exception.catch should be fine here.
  
 3. Please do not tell me I should solve the problem
differently. Here is the problem I'm trying to solve, and
nothing else:
 
  Write a program that reads a line from the user,
  looping the query until the line contains a valid
  integer.
 
 It shouldn't be too hard i think. The best answer would be a
 two-liner code example that'll make me feel even more stupid
 than I already do.

Of course, it's easy. You can have fun now abstracting out the loop
form in getNum using say, MaybeT or friends. But a loop is simple and easy.

If you want to write it with explict exception handling of the
read parse failure, it's more tedious, as you need to ensure
the read exception is thrown within the body of the enclosing catch.

For example,

import System.IO
import qualified Control.Exception as C

main = do
x - getNum
print x

getNum :: IO Integer
getNum = do
y - maybeRead
case y of
Nothing - getNum
Just n  - return n

maybeRead :: Read a = IO (Maybe a)
maybeRead = C.catch
(do x - getLine
let n = read x
n `seq` return (Just n)) -- ensure any exception is thrown here
(const (return Nothing))

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


Re: [Haskell-cafe] [Newbie question] -- Looping stdin until condition is met

2008-05-30 Thread Don Stewart
philip.weaver:
 
  1. How do I catch the exception that is raised from read?
 
 I think you want readIO, which yields a computation in the IO monad,
 so it can be caught.

Ah, that's a third option, sequence the effect using readIO,

import System.IO
import qualified Control.Exception as C

main = do
x - getNum
print x

getNum :: IO Integer
getNum = do
y - maybeRead
case y of
Nothing - getNum
Just n  - return n

maybeRead :: Read a = IO (Maybe a)
maybeRead = C.catch
(do x - getLine
n - readIO x
return (Just n)) -- ensure any exception is thrown here
(const (return Nothing))

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


Re: [Haskell-cafe] [Newbie question] -- Looping stdin until condition is met

2008-05-30 Thread Martin Blais
On Fri, 30 May 2008 16:54:18 -0700, Philip Weaver
[EMAIL PROTECTED] said:
  1. How do I catch the exception that is raised from read?
 
 I think you want readIO, which yields a computation in the IO monad,
 so it can be caught.

Holy schmoly, there it is, words of wisdom, written as clearly as can
be, from the docs:

  The readIO function is similar to read except that it signals parse
  failure to the IO monad instead of terminating the program.

I'll be prosternating on the floor towards my web browser for the next
four hours. 
Thank you very much Philip.

(And thank you Don for the verbose examples.)



  2. Where do I find the appropriate information I need in
order to fix this? I'm probably just not searching in the
right place. (Yes, I've seen the GHC docs, and it doesn't
help, maybe I'm missing some background info.)
 
 In this particular case, I am not sure where you'd find this
 information.  It's not very intuitive to a beginner why read doesn't
 work in this case.

Dear Philip, could you point your virtual finger towards a
reference/paper/book/any-bleeping-thing that would help this simple
beginner understand why it doesn't work in this case? I'm trying to
picture why a read function that terminates the program would be
useful anywhere. In fact, any library function other than something like
UNIX's exit or kill which terminates my program is not really
welcome in any of my computer programs, but then again, I haven't yet
been illuminated by the genie of pure functional languages.  A reference
would be awesome.


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


Re: [Haskell-cafe] [Newbie question] -- Looping stdin until condition is met

2008-05-30 Thread Philip Weaver
On Fri, May 30, 2008 at 5:14 PM, Martin Blais [EMAIL PROTECTED] wrote:
 On Fri, 30 May 2008 16:54:18 -0700, Philip Weaver
 [EMAIL PROTECTED] said:
  1. How do I catch the exception that is raised from read?
 
 I think you want readIO, which yields a computation in the IO monad,
 so it can be caught.

 Holy schmoly, there it is, words of wisdom, written as clearly as can
 be, from the docs:

  The readIO function is similar to read except that it signals parse
  failure to the IO monad instead of terminating the program.

 I'll be prosternating on the floor towards my web browser for the next
 four hours.
 Thank you very much Philip.

 (And thank you Don for the verbose examples.)



  2. Where do I find the appropriate information I need in
order to fix this? I'm probably just not searching in the
right place. (Yes, I've seen the GHC docs, and it doesn't
help, maybe I'm missing some background info.)
 
 In this particular case, I am not sure where you'd find this
 information.  It's not very intuitive to a beginner why read doesn't
 work in this case.

 Dear Philip, could you point your virtual finger towards a
 reference/paper/book/any-bleeping-thing that would help this simple
 beginner understand why it doesn't work in this case? I'm trying to
 picture why a read function that terminates the program would be
 useful anywhere. In fact, any library function other than something like
 UNIX's exit or kill which terminates my program is not really
 welcome in any of my computer programs, but then again, I haven't yet
 been illuminated by the genie of pure functional languages.  A reference
 would be awesome.

Sorry, I wouldn't know where to point you, other than stating the
simple rule that you can't catch exceptions in pure code.  Others may
be able to enlighten you better.

By the way, the example that Dons gave may look more verbose, but
(when possible) it's a probably a better idea to capture failure in a
Maybe than in IO.  I gave you readIO because it fit in to the
exception handling that you were trying to do, and because you said
you didn't want anyone to tell you you were doing things wrong :).



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


Re: [Haskell-cafe] [Newbie question] -- Looping stdin until condition is met

2008-05-30 Thread Martin Blais
On Fri, 30 May 2008 17:19:54 -0700, Philip Weaver
[EMAIL PROTECTED] said:
  Dear Philip, could you point your virtual finger towards a
  reference/paper/book/any-bleeping-thing that would help this simple
  beginner understand why it doesn't work in this case? I'm trying to
  picture why a read function that terminates the program would be
  useful anywhere. In fact, any library function other than something like
  UNIX's exit or kill which terminates my program is not really
  welcome in any of my computer programs, but then again, I haven't yet
  been illuminated by the genie of pure functional languages.  A reference
  would be awesome.
 
 Sorry, I wouldn't know where to point you, other than stating the
 simple rule that you can't catch exceptions in pure code.  Others may
 be able to enlighten you better.
 
 By the way, the example that Dons gave may look more verbose, but
 (when possible) it's a probably a better idea to capture failure in a
 Maybe than in IO.  I gave you readIO because it fit in to the
 exception handling that you were trying to do, and because you said
 you didn't want anyone to tell you you were doing things wrong :).

Here is a private reply from another user, which is more explanatory,
the problem was that the read function wasn't getting called at a point
where it could have been caught (I'll have to look into that into more
detail):


All you need is a little strictness,
x - (C.catch (return $! read line :: Int) (\e - getNum))
works. Another option is using evaluate instead of return.
The problem is that (read line :: Int) is not evaluated until it is
needed,
that is when it's going to be printed, but then it's too late to catch
the
exception.

Some general remarks:
hGetLine stdin === getLine
do x - action
   return x
is the same as
action




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


Re: [Haskell-cafe] Newbie Question: Using Haskell Functions in a C Program

2008-05-11 Thread Luke Palmer
On Thu, May 8, 2008 at 5:09 PM, Philip Müller [EMAIL PROTECTED] wrote:
 Thanks for all the answers. I'm testing this right now and simples cases
 work as expected. However from what I've read it seems it'll get ugly once I
 try to pass a C array to a Haskell function.

  Well, maybe arrays in C have been ugly before trying to pass them to
 Haskell functions ;)

  To elaborate a bit about the C program, it's a small game using OpenGL for
 output and mouse and keyboard for input.

The SDL package
(http://hackage.haskell.org/cgi-bin/hackage-scripts/package/SDL) is
quite nice for input handling and window making and whatnot.  I have
heard it is a bitch to get working on Windows, though.

The OpenGL package
(http://hackage.haskell.org/cgi-bin/hackage-scripts/package/OpenGL) is
good, but can be a real pain to get going because the documentation
layout is terrible.

To toot my own horn, if your graphics are simple enough (specifically,
2D), you can use graphics-drawingcombinators
(http://hackage.haskell.org/cgi-bin/hackage-scripts/package/graphics-drawingcombinators),
which has a simple interface, for output.  It depends on SDL, so above
caveat applies.

But once you learn the pattern, I/O is basically a transliteration
from C.  The reason I struggle with such C-like libraries in Haskell
is that I spend all my time trying to clean them up and make them more
Haskell-like.   I definitely consider FFI more of a pain (when you
want to do anything sophisticated) than the OpenGL package, though.

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


[Haskell-cafe] Newbie Question: Using Haskell Functions in a C Program

2008-05-08 Thread Philip Müller

Hi,

I'm in the process of writing a C program, but I can't stop thinking 
about how some functions would be much nicer implemented in Haskell.


Is there a way to write some of the functions in Haskell and then use 
them in my C code via some kind of interface?


BTW yes, I have been thinking about writing the whole program in 
Haskell, but I just don't have the level of experience in Haskell 
programming for that, since it's really heavy on IO.


Thanks in advance for the answers!

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


Re: [Haskell-cafe] Newbie Question: Using Haskell Functions in a C Program

2008-05-08 Thread Bulat Ziganshin
Hello Philip,

Friday, May 9, 2008, 2:17:41 AM, you wrote:

 Is there a way to write some of the functions in Haskell and then use
 them in my C code via some kind of interface?

http://haskell.org/haskellwiki/IO_inside#Interfacing_with_foreign_evil_.28under_development.29

and then entries 1,6,7 in 
http://haskell.org/haskellwiki/IO_inside#Further_reading


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Newbie Question: Using Haskell Functions in a C Program

2008-05-08 Thread Don Stewart
mail:
 Is there a way to write some of the functions in Haskell and then use 
 them in my C code via some kind of interface?

Using C just for IO is a bit weird -- perhaps you could illustrate
the kind of IO you're doing?  Learning how to do IO in Haskell is 
a much safer solution that linking the Haskell runtime into your
C program.

That said, this is done by using 'foreign export' declarations
in your Haskell code, then linking the compiled Haskell objects 
into your C code, as follows:


We define the fibonacci function in Haskell:


{-# LANGUAGE ForeignFunctionInterface #-}

module Safe where

import Foreign.C.Types

fibonacci :: Int - Int
fibonacci n = fibs !! n
where fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

fibonacci_hs :: CInt - CInt
fibonacci_hs = fromIntegral . fibonacci . fromIntegral

foreign export ccall fibonacci_hs :: CInt - CInt


And call it from C:

#include A_stub.h
#include stdio.h

int main(int argc, char *argv[]) {
   int i;
   hs_init(argc, argv);

   i = fibonacci_hs(42);
   printf(Fibonacci: %d\n, i);

   hs_exit();
   return 0;
}

Now, first compile the Haskell file:

$ ghc -c -O A.hs

Which creates some *.c and *.h headers, which you import into
your C program. Now compile your C code with ghc (!), passing
the Haskell objects on the command line:

$ ghc -optc-O test.c A.o A_stub.o -o test

How run your C code:

$ ./test 
Fibonacci: 267914296

And that's it.

-- Don

P.S. Its easier to learn how to do IO in Haskell :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie Question: Using Haskell Functions in a C Program

2008-05-08 Thread Philip Müller
Thanks for all the answers. I'm testing this right now and simples cases 
work as expected. However from what I've read it seems it'll get ugly 
once I try to pass a C array to a Haskell function.


Well, maybe arrays in C have been ugly before trying to pass them to 
Haskell functions ;)


To elaborate a bit about the C program, it's a small game using OpenGL 
for output and mouse and keyboard for input.
I just don't know how to do that in Haskell - my knowledge is quite 
basic in nature ;)


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


Re: [Haskell-cafe] Newbie Question: Using Haskell Functions in a C Program

2008-05-08 Thread Don Stewart
mail:
 Thanks for all the answers. I'm testing this right now and simples 
 cases work as expected. However from what I've read it seems it'll 
 get ugly once I try to pass a C array to a Haskell function.

Right, passing arrays back and forth is going to get tiring.
  
 Well, maybe arrays in C have been ugly before trying to pass them to 
 Haskell functions ;)
 
 To elaborate a bit about the C program, it's a small game using 
 OpenGL for output and mouse and keyboard for input.
 I just don't know how to do that in Haskell - my knowledge is quite 
 basic in nature ;)

Oh, then you'll want to use the Haskell OpenGL bindings.

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/OpenGL

There's a few OpenGL-based games in Haskell, here:

http://haskell.org/haskellwiki/Applications_and_libraries/Games

and a section of blog articles on using the OpenGL bindings:

http://haskell.org/haskellwiki/Blog_articles/Graphics#OpenGL

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


Re[2]: [Haskell-cafe] Newbie Question: Using Haskell Functions in a C Program

2008-05-08 Thread Bulat Ziganshin
Hello Philip,

Friday, May 9, 2008, 3:09:33 AM, you wrote:

 Thanks for all the answers. I'm testing this right now and simples cases
 work as expected. However from what I've read it seems it'll get ugly 
 once I try to pass a C array to a Haskell function.

http://haskell.org/haskellwiki/Modern_array_libraries

read about foreign arrays

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] Newbie question: mutually exclusive strict / lazy

2008-02-11 Thread Peter Verswyvelen
Yes, sorry, GHC's strictness analyzer. 

 

What I meant with this email is that I guess that for a strictness analyzer,
the information that a function is strict in an argument *independent from
the other arguments* would not be good enough in itself for optimization, it
would be better to also use the dependencies between the arguments (as in
the case of the if.then.else). 

 

It seems one can indicate in GHC that an argument is strict using
annotiations, but I don't see a way of specifying these dependencies (maybe
this does not make sense, and this is all newbie nonsense). Of course, with
whole program optimization this would not be necessary, but if the compiler
just sees the function signature, he must assume that a lazy argument is
always lazy, independent of the value of other strict arguments no?

 

Cheers,

Peter

 

From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On
Behalf Of Lennart Augustsson
Sent: maandag 11 februari 2008 0:28
To: Peter Verswyvelen
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question: mutually exclusive strict /
lazy

 

I'm not sure what you mean by the strictness analyzer.  GHC's strictness
analyzer?
I don't know, but I would hope so since it was done already in 1980 by Alan
Mycroft.

  -- Lennart

On Sat, Feb 9, 2008 at 4:33 PM, Peter Verswyvelen [EMAIL PROTECTED] wrote:

Consider the function

cond x y z = if x then y else z

I guess we can certainly say cond is strict in x.

But what about y and z?

If x is true,  then cond is strict in y
If x is false, then cond is strict in z

So we can't really say cond is lazy nor strict in its second or third
argument.

Of course, this is the case for many more functions, but in  the case of the
if-then-else primitive, does the strictness analyzer make use of this
mutually exclusive strictness fact?

Cheers,
Peter









___
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] Newbie question: mutually exclusive strict / lazy

2008-02-11 Thread Loup Vaillant
2008/2/11, Peter Verswyvelen [EMAIL PROTECTED]:

 Yes, sorry, GHC's strictness analyzer.

 What I meant with this email is that I guess that for a strictness analyzer,
 the information that a function is strict in an argument *independent from
 the other arguments* would not be good enough in itself for optimization, it
 would be better to also use the dependencies between the arguments (as in
 the case of the if…then…else).

 It seems one can indicate in GHC that an argument is strict using
 annotiations, but I don't see a way of specifying these dependencies (maybe
 this does not make sense, and this is all newbie nonsense). Of course, with
 whole program optimization this would not be necessary, but if the compiler
 just sees the function signature, he must assume that a lazy argument is
 always lazy, independent of the value of other strict arguments no?

It may not always be the case, but, here, for your particular example,
what you need is an inline followed by a reduction (dunno which).

Reminder:
 cond x y z = if x then y else z

The translation in core, is this:
cond x y z = case x of
  True  - y
  False - z

So, suppose we know at some call site that x is True. So, the call
cond x e1 e2 -- e1 and e2 are arbitrary expressions

is equivalent to:
cond True e1 e2

An inline replaces the call by this:
cond x e1 e2 = case True of
  True  - e1
  False - e2

In this case, the compiler can easily determine at compile time the
selected branch. Therefore, this case expression is replaced by the
correct branch:
e1

I would be surprised if GHC doesn't already perform this kind of
optimization [1,2]. So, no need for a fancy strictness analyser for
this code. About more complicated cases, I'm clueless, thought.

Cheers,
Loup

[1] http://research.microsoft.com/~simonpj/Papers/inlining/
[2] http://citeseer.ist.psu.edu/jones91unboxed.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie question: mutually exclusive strict / lazy

2008-02-09 Thread Peter Verswyvelen
Consider the function 

cond x y z = if x then y else z

I guess we can certainly say cond is strict in x. 

But what about y and z? 

If x is true,  then cond is strict in y 
If x is false, then cond is strict in z

So we can't really say cond is lazy nor strict in its second or third argument. 

Of course, this is the case for many more functions, but in  the case of the 
if-then-else primitive, does the strictness analyzer make use of this mutually 
exclusive strictness fact? 

Cheers,
Peter









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


Re: [Haskell-cafe] Newbie question: mutually exclusive strict / lazy

2008-02-09 Thread Daniel Fischer
Am Samstag, 9. Februar 2008 17:33 schrieb Peter Verswyvelen:
 Consider the function

 cond x y z = if x then y else z

 I guess we can certainly say cond is strict in x.

 But what about y and z?

 If x is true,  then cond is strict in y
 If x is false, then cond is strict in z

 So we can't really say cond is lazy nor strict in its second or third
 argument.

 Of course, this is the case for many more functions, but in  the case of
 the if-then-else primitive, does the strictness analyzer make use of this
 mutually exclusive strictness fact?

 Cheers,
 Peter

Hope I remember correctly...

A function is strict in an argument, if whenever that argument is _|_, the 
result is _|_, regardless of possible other arguments.

Since 
if True then 0 else _|_ == 0,
if-then-else is nonstrict in the third argument, similarly
if False then _|_ else 0 == 0,
so if-then-else is nonstrict in the second argument.

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


[Haskell-cafe] Newbie question

2008-01-21 Thread Alexander Seliverstov
Hi, I try to undestand why this code dosen't work

f :: (Num a)=Integer-a

f i = i

Integer is an instance of Num, so why does this code produce error:
Couldn't  match expected type 'a' againsta inferred type 'Integer' ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question

2008-01-21 Thread Brent Yorgey
2008/1/21 Alexander Seliverstov [EMAIL PROTECTED]:

 Hi, I try to undestand why this code dosen't work

 f :: (Num a)=Integer-a

 f i = i

 Integer is an instance of Num, so why does this code produce error:
 Couldn't  match expected type 'a' againsta inferred type 'Integer' ...

But the type of this function says that it can return *any* instance of Num
-- that is, the caller gets to choose which particular instance of Num they
want.  This function can only ever return an Integer.

There is actually a function of this type, however; it's called
fromIntegral.  It works because it is a member of the Num type class.

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


Re: [Haskell-cafe] Newbie question

2008-01-21 Thread Alexander Seliverstov
How does caller choose which particular instance of Num they want?

In object-oriented language If function return type is an interface it means
that it can return any implementation of this interface, but caller can't
choose which particular inplementation they want.


What the difference between haskell class and interface in object-oriented
languge such Java or C#?

2008/1/21, Brent Yorgey [EMAIL PROTECTED]:


 2008/1/21 Alexander Seliverstov [EMAIL PROTECTED]:

  Hi, I try to undestand why this code dosen't work
 
  f :: (Num a)=Integer-a
 
  f i = i
 
  Integer is an instance of Num, so why does this code produce error:
  Couldn't  match expected type 'a' againsta inferred type 'Integer' ...
 
 But the type of this function says that it can return *any* instance of
 Num -- that is, the caller gets to choose which particular instance of Num
 they want.  This function can only ever return an Integer.

 There is actually a function of this type, however; it's called
 fromIntegral.  It works because it is a member of the Num type class.

 -Brent

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


Re[2]: [Haskell-cafe] Newbie question

2008-01-21 Thread Bulat Ziganshin
Hello Alexander,

Monday, January 21, 2008, 7:36:18 PM, you wrote:

 How does caller choose which particular instance of Num they want?

 In object-oriented language If function return type is an interface
 it means that it can return any implementation of this interface,
 but caller can't choose which particular inplementation they want. 

but type class isn't an interface! it's just like interface in one
concrete area - it includes method specifications, but not includes
data fields

the type that should ìó returned by function is passed by means of
so-called dictionary and which type should be returned is defined by
type inference process. for example

main = print (length [] + f 1)

here f should return Int because length return Int and you can't add
values of different types (without explicit type conversion). you
should also read something about two-way type inference but i don't
know any good source

please note that in modern OOP languages (latest C# versions, C++ 0x)
support for *one-way* type inference was only added, i.e. they only can
deduce type of expression from types of operands, while Haskell
deduces types in both directions

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-13 Thread jerzy . karczmarczuk
Henning Thielemann writes: 


Caching is not the default, but you can easily code this by yourself:
Define an array and initialize it with all function values. Because of
lazy evaluation the function values are computed only when they are
requested and then they persist in the array.
 One should add this most simple case to the Wiki.


A posteriori thought, when I reread that... 


This is a =part= of the story. Whatever you do with the initial calls, if
there is no automatic memoization, further calls will be executed normally.
The user has to replace his/her calls with the elements of the memo-array. 

Suppose (sorry for the awful Fibonacci again...) we define 

fibs = [fib n | n-[0 ..]] 


fib 0 = 0
fib 1 = 1
fib n = fib(n-1) + fib(n-2) 

If you try to get fibs!!1000 you will die before anyway. 

The solution is obviously to replace the recursive definition of fib by 

fib n = fibs!!(n-1) + fibs!!(n-2) 


This works well. I had a similar problem in physics, perturbation theory
offers often some quite intricate, knotty recurrencies, and the memoization
offers a solution for the worse than exponential complexity. But I had to
use trees, 2_dim lists of lists, etc. in order to sort the order of the
creation of the results appropriately.
So, I agree wholeheartly with the statement that memoization is not a blind
automaton, it should be used consciously, and adapted to concrete needs. 

Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Thomas Davie


On 12 Jan 2008, at 23:16, Hugh Perkins wrote:


On Jan 12, 2008 10:54 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:


On Sat, 12 Jan 2008, Hugh Perkins wrote:


I guess that Haskell's referential transparence means the answers to
the isPerfectSquare will be cached, ie automatically memoized? (not
sure if is correct term?)


http://www.haskell.org/haskellwiki/Memoization



Interesting... but I dont understand... I thought that referential
transparence meant that once the answer to a function has been
calculated once, it will always be the same, and that the interpreter
can, and will, cache this answer?

So, if I call f( 20 ) once, for some, arbitrary, f, it will have to go
away and calculate f(20), but if I call it multiple times, it will
just return the value it already calculated?


No,
  Memorisation has it's costs too... Suppose you wanted to computer  
map f [1..100]?  Each time f was called, your program  
would look up a table of on average 50 results for f.   
That doesn't sound very efficient if f is a simple function. Now  
suppose you're running a program for several hours -- imagine how  
large your table would become, and how slow your lookup would be.


What you can do however, is introduced constants.  Constants are  
evaluated once and only once, so using them, you can tell the compiler  
exactly what should be memorized.


Bob


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


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Felipe Lessa
(While writing this message GMail told me I was too late to answer the
question. Oh well, as I already typed it, let's send =)

On Jan 12, 2008 9:16 PM, Hugh Perkins [EMAIL PROTECTED] wrote:
 Interesting... but I dont understand... I thought that referential
 transparence meant that once the answer to a function has been
 calculated once, it will always be the same, and that the interpreter
 can, and will, cache this answer?

It *can*, but all Haskell implementations I know do not. The reason is
very simple, it would need a veery large amount of memory, and
sometimes searching to see if the answer was already calculated could
be worse than recalculating it (think of (+1) or perhaps (null)).
Polimorphic functions would also complicate the matter, as multiple
different caches would be needed.

 So, if I call f( 20 ) once, for some, arbitrary, f, it will have to go
 away and calculate f(20), but if I call it multiple times, it will
 just return the value it already calculated?

If you do something like

let x = f 20 in x + x

it *probably* will be calculated only once (although it could be
calculated twice). But in the (bad) implementaion of fibonacci below,

fib 0 = 0
fib 1 = 1
fib n = fib (n-1) + fib (n-2)

when calculating (fib 40), (fib 38) will be calculated twice, (fib 37)
will be calculated thrice, etc.

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


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Henning Thielemann

On Sun, 13 Jan 2008, Hugh Perkins wrote:

 On Jan 12, 2008 10:54 PM, Henning Thielemann
 [EMAIL PROTECTED] wrote:
 
  On Sat, 12 Jan 2008, Hugh Perkins wrote:
 
   I guess that Haskell's referential transparence means the answers to
   the isPerfectSquare will be cached, ie automatically memoized? (not
   sure if is correct term?)
 
  http://www.haskell.org/haskellwiki/Memoization

 Interesting... but I dont understand... I thought that referential
 transparence meant that once the answer to a function has been
 calculated once, it will always be the same, and that the interpreter
 can, and will, cache this answer?

 Caching is not the default, but you can easily code this by yourself:
Define an array and initialize it with all function values. Because of
lazy evaluation the function values are computed only when they are
requested and then they persist in the array.
 One should add this most simple case to the Wiki.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Brandon S. Allbery KF8NH


On Jan 12, 2008, at 18:16 , Hugh Perkins wrote:


On Jan 12, 2008 10:54 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:


On Sat, 12 Jan 2008, Hugh Perkins wrote:


I guess that Haskell's referential transparence means the answers to
the isPerfectSquare will be cached, ie automatically memoized? (not
sure if is correct term?)


http://www.haskell.org/haskellwiki/Memoization



Interesting... but I dont understand... I thought that referential
transparence meant that once the answer to a function has been
calculated once, it will always be the same, and that the interpreter
can, and will, cache this answer?


It *can* cache the answer, if it so chooses... but that often turns  
out to be a pessimization, as it caches values that are only used  
once or twice.


--
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] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Hugh Perkins
On Jan 12, 2008 10:54 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 On Sat, 12 Jan 2008, Hugh Perkins wrote:

  I guess that Haskell's referential transparence means the answers to
  the isPerfectSquare will be cached, ie automatically memoized? (not
  sure if is correct term?)

 http://www.haskell.org/haskellwiki/Memoization


Interesting... but I dont understand... I thought that referential
transparence meant that once the answer to a function has been
calculated once, it will always be the same, and that the interpreter
can, and will, cache this answer?

So, if I call f( 20 ) once, for some, arbitrary, f, it will have to go
away and calculate f(20), but if I call it multiple times, it will
just return the value it already calculated?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread David Benbennick
On 1/12/08, Henning Thielemann [EMAIL PROTECTED] wrote:
  Caching is not the default, but you can easily code this by yourself:
 Define an array and initialize it with all function values. Because of
 lazy evaluation the function values are computed only when they are
 requested and then they persist in the array.

But how can I implement memoization for a more complicated function?
For example, perhaps I want to memoize

f :: String - Int - Double - String - Bool

In Python, it's pretty easy to memoize this.  How can I do it in
Haskell?  I suspect the only way would involve changing the function
signature to use IO or ST.

It would be nice if I could just tell the compiler I command you to
memoize this function, and have it produce the required code
automatically.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Jonathan Cast

On 12 Jan 2008, at 3:30 PM, David Benbennick wrote:


On 1/12/08, Henning Thielemann [EMAIL PROTECTED] wrote:
 Caching is not the default, but you can easily code this by  
yourself:
Define an array and initialize it with all function values.  
Because of

lazy evaluation the function values are computed only when they are
requested and then they persist in the array.


But how can I implement memoization for a more complicated function?
For example, perhaps I want to memoize

f :: String - Int - Double - String - Bool

In Python, it's pretty easy to memoize this.  How can I do it in
Haskell?  I suspect the only way would involve changing the function
signature to use IO or ST.

It would be nice if I could just tell the compiler I command you to
memoize this function, and have it produce the required code
automatically.


You can cache anything using mutable hash tables, as you know, and  
googling will find you `function's in Haskell that do this for you.


jcc


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


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Henning Thielemann

On Sat, 12 Jan 2008, David Benbennick wrote:

 On 1/12/08, Henning Thielemann [EMAIL PROTECTED] wrote:
   Caching is not the default, but you can easily code this by yourself:
  Define an array and initialize it with all function values. Because of
  lazy evaluation the function values are computed only when they are
  requested and then they persist in the array.

 But how can I implement memoization for a more complicated function?
 For example, perhaps I want to memoize

 f :: String - Int - Double - String - Bool

There was a long thread about a sophisticated technique called blue
prints, which allows you to use binary search trees as memoizing
structure.
 http://www.haskell.org/pipermail/haskell-cafe/2006-September/018204.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [newbie question] Memoization automatic in Haskell?

2008-01-12 Thread Luke Palmer
On Jan 12, 2008 11:30 PM, David Benbennick [EMAIL PROTECTED] wrote:
 On 1/12/08, Henning Thielemann [EMAIL PROTECTED] wrote:
   Caching is not the default, but you can easily code this by yourself:
  Define an array and initialize it with all function values. Because of
  lazy evaluation the function values are computed only when they are
  requested and then they persist in the array.

 But how can I implement memoization for a more complicated function?
 For example, perhaps I want to memoize

 f :: String - Int - Double - String - Bool

 In Python, it's pretty easy to memoize this.  How can I do it in
 Haskell?  I suspect the only way would involve changing the function
 signature to use IO or ST.

No, that is one way to do it, and probably the easiest to think about.
 Because its
conceptually pure, I wouldn't be opposed to wrapping it in unsafePerformIO (but
that can be, well, unsafe if you do it wrong :-)

But there is a way to do it if you demand to be a purist, but only if you can
code a data structure representing all values of a type.  Doing this for a
particular type is one of my favorite ways to spend a half hour when
I'm bored :-)

For an obvious case, but to illustrate the point, I'll do Bool.

  data BoolCache a = BC a a

  bools :: BoolCache Bool
  bools = BC True False

  lookupBool :: BoolCache a - Bool - a
  lookupBool (BC t f) True  = t
  lookupBool (BC t f) False = f

  memoBool :: (Bool - a) - (Bool - a)
  memoBool f = lookupBool (fmap f bools)

The pattern is the same for any type.  You can do it for types with infinitely
many members, like Integer, but it's trickier (but it's the same pattern, just
a trickier data structure).  The Integer case is scattered here and
there online.
I haven't found any other cases online, but I've implemented a few.

 It would be nice if I could just tell the compiler I command you to
 memoize this function, and have it produce the required code
 automatically.

Tru dat!

But it's not clear what the best way for the compiler writer to do
that is.  For
example, if I know the access patterns of the function, I can design the
aforementioned data structure to favor those.   Also, not every type admits
memoization, for example functions.  But I can certainly envisage a
library providing:

  class Memo a where
memo :: (a - b) - (a - b)

For a bunch of different types.

Hmm, one probably already exists, actually...

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


[Haskell-cafe] Newbie question: the need for parentheses

2008-01-08 Thread Fernando Rodriguez


Hi,

I have this function that sums up a list of numbers:

suma [] = 0
suma (h:t) = h + suma t

However, why do I need the parenthes in the second clause? What does the 
compiler think I'm trying to do when I type

suma [] = 0
suma h:t = h + suma t

Thanks! :-)



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


Re: [Haskell-cafe] Newbie question: the need for parentheses

2008-01-08 Thread Neil Mitchell
Hi

 suma [] = 0
 suma (h:t) = h + suma t

 suma [] = 0
 suma h:t = h + suma t

Infix operators bind less tightly than function application, so the
compiler sees:

(suma h) : t = h + (suma t)

Hence the compiler gets confused.

Thanks

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


Re: [Haskell-cafe] Newbie question: the need for parentheses

2008-01-08 Thread Jules Bean

Fernando Rodriguez wrote:


Hi,

I have this function that sums up a list of numbers:

suma [] = 0
suma (h:t) = h + suma t

However, why do I need the parenthes in the second clause? What does the 
compiler think I'm trying to do when I type

suma [] = 0
suma h:t = h + suma t



Definitions are parsed in very much the same way as expressions. In 
principle they don't need to be, but it makes the language more uniform 
if they are.


If you wrote suma h:t as an expression, it would mean (suma h) : t, 
because function application binds tighter than any infix operator.


So, as a definition:

suma h : t = h + suma t

looks to the compiler like an attempt to redefine the operator ':', 
except that the left parameter is suma h, which looks like a function 
application, and that's not allowed in a definition.


[it also doesn't make sense because ':' is actually a constructor not 
any old operator. But that turns out not to be the key problem here]


Note that you can define operators directly infix, e.g.:

a * b = multiply a b

...and if I try to do that with something like 'suma' on the left...

suma a * b = multiply a b

...I get the same error (parse error in pattern, in GHC).

Hope that helps,

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


Re: [Haskell-cafe] Newbie question: the need for parentheses

2008-01-08 Thread Miguel Mitrofanov
However, why do I need the parenthes in the second clause? What  
does the compiler think I'm trying to do when I type

suma [] = 0
suma h:t = h + suma t


(suma h):t = h + suma t
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie question related to list evaluation

2008-01-06 Thread Sai Hemanth K
Hi,

I am new to functional and lazy programming languages ( that's correct, my
life has been pretty pathetic so far) and am not able to understand GHC's
behaviour for a particular function. Can someone help me please?

I am trying to write a function which would compare two strings (from
reverse) and return the position of first mismatch. This is part of the
right-to-left scan of bayer-moore algorithm.. and it is essential for me to
do it from reverse.
Since my goal is to learn haskell, I am not using Data.ByteString.

My function is as follows:

matchReverse :: String - String -Int-(Bool,Int)
matchReverse [] [] pos = (True,pos)
matchReverse _ [] pos = (False,pos)
matchReverse [] _ pos = (False,pos)
matchReverse (x:xs) (y:ys) pos = let (matched,pos) = matchReverse xs ys (pos
+1)
  in if matched then
((x==y),pos)
 else (False,pos)



The behaviour I expected in four scenarios is as below:
1.matchReverse kapilash kapilash 0 --should return (True,0)
2.matchReverse kapilash kapilast 0 --should return (False,8)
3.matchReverse str1 str2 0  --should return (False,0)
4.matchReverse str1 str1 0  --should return (True,0)

where str1 and str2 are defined as below:
 str1 =  replicate 1000 'a'
 str2 =  'b':(replicate 999 'a')

what confounds me is that it is able to identify the first element of the
tuple in ALL the cases.
Invoking fst on the each of the four calls instantly returns the expected
value.(even for the cases 3 and 4 where, there are thousand elements)
But it seems to go into an infinite loop while calculating the 'snd' of the
tuple. Even for strings containing just one element each.
can someone throw some light on this please? Why does it go into an infinite
loop?

Many thanks
Kapilash


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


Re: [Haskell-cafe] Newbie question related to list evaluation

2008-01-06 Thread Rodrigo Queiro
You have used the name 'pos' twice, for both the parameter and the
returned value of the recursive call. The reason this results in an
infinite loop is that in code like

let x = x + 1

Haskell treats both xs to be references to the same thing, so evaluates:
x
= x + 1
= (x + 1) + 1
= ((x + 1) + 1) + 1
...

which results in the infinite loop.

On 06/01/2008, Sai Hemanth K [EMAIL PROTECTED] wrote:
 Hi,

 I am new to functional and lazy programming languages ( that's correct, my
 life has been pretty pathetic so far) and am not able to understand GHC's
 behaviour for a particular function. Can someone help me please?

 I am trying to write a function which would compare two strings (from
 reverse) and return the position of first mismatch. This is part of the
 right-to-left scan of bayer-moore algorithm.. and it is essential for me to
 do it from reverse.
 Since my goal is to learn haskell, I am not using Data.ByteString.

 My function is as follows:

 matchReverse :: String - String -Int-(Bool,Int)
 matchReverse [] [] pos = (True,pos)
 matchReverse _ [] pos = (False,pos)
 matchReverse [] _ pos = (False,pos)
 matchReverse (x:xs) (y:ys) pos = let (matched,pos) = matchReverse xs ys (pos
 +1)
   in if matched then
 ((x==y),pos)
  else (False,pos)



 The behaviour I expected in four scenarios is as below:
 1.matchReverse kapilash kapilash 0 --should return (True,0)
 2.matchReverse kapilash kapilast 0 --should return (False,8)
 3.matchReverse str1 str2 0  --should return (False,0)
 4.matchReverse str1 str1 0  --should return (True,0)

 where str1 and str2 are defined as below:
  str1 =  replicate 1000 'a'
  str2 =  'b':(replicate 999 'a')

 what confounds me is that it is able to identify the first element of the
 tuple in ALL the cases.
 Invoking fst on the each of the four calls instantly returns the expected
 value.(even for the cases 3 and 4 where, there are thousand elements)
 But it seems to go into an infinite loop while calculating the 'snd' of the
 tuple. Even for strings containing just one element each.
 can someone throw some light on this please? Why does it go into an infinite
 loop?

 Many thanks
 Kapilash


 --
 I drink I am thunk.
 ___
 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] Newbie question related to list evaluation

2008-01-06 Thread Jonathan Cast

On 6 Jan 2008, at 10:34 AM, Sai Hemanth K wrote:


Hi,

I am new to functional and lazy programming languages ( that's  
correct, my life has been pretty pathetic so far) and am not able  
to understand GHC's behaviour for a particular function. Can  
someone help me please?


I am trying to write a function which would compare two strings  
(from reverse) and return the position of first mismatch. This is  
part of the right-to-left scan of bayer-moore algorithm.. and it is  
essential for me to do it from reverse.

Since my goal is to learn haskell, I am not using Data.ByteString.

My function is as follows:

matchReverse :: String - String -Int-(Bool,Int)
matchReverse [] [] pos = (True,pos)
matchReverse _ [] pos = (False,pos)
matchReverse [] _ pos = (False,pos)
matchReverse (x:xs) (y:ys) pos = let (matched,pos) = matchReverse  
xs ys (pos +1)
  in if matched  
then ((x==y),pos)

 else (False,pos)


let is always recursive in Haskell, so this is a recursive definition  
of pos.  To break the recursion, use


matchReverse (x:xs) (y:ys) pos = let (matched, pos') = matchReverse  
xs ys (pos + 1)

 in if matched then ((x==y), pos')
   else (False, pos')






The behaviour I expected in four scenarios is as below:
1.matchReverse kapilash kapilash 0 --should return (True,0)
2.matchReverse kapilash kapilast 0 --should return (False,8)
3.matchReverse str1 str2 0  --should return  
(False,0)
4.matchReverse str1 str1 0  --should return  
(True,0)


where str1 and str2 are defined as below:
 str1 =  replicate 1000 'a'
 str2 =  'b':(replicate 999 'a')

what confounds me is that it is able to identify the first element  
of the tuple in ALL the cases.
Invoking fst on the each of the four calls instantly returns the  
expected value.(even for the cases 3 and 4 where, there are  
thousand elements)
But it seems to go into an infinite loop while calculating the  
'snd' of the tuple. Even for strings containing just one element each.
can someone throw some light on this please? Why does it go into an  
infinite loop?


Many thanks
Kapilash


--
I drink I am thunk.
___
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] Newbie question related to list evaluation

2008-01-06 Thread Felipe Lessa
On Jan 6, 2008 4:40 PM, Jonathan Cast [EMAIL PROTECTED] wrote:
 let is always recursive in Haskell, so this is a recursive definition
 of pos.  To break the recursion, use


 matchReverse (x:xs) (y:ys) pos = let (matched, pos') = matchReverse
 xs ys (pos + 1)
   in if matched then ((x==y), pos')
else (False, pos')

Actually, I think he meant

matchReverse (x:xs) (y:ys) pos =
let (matched, pos') = matchReverse xs ys (pos + 1)
in if matched then ((x==y), pos) else (False, pos')

As as side note, GHC's flag -Wall would have warned about creating a
variable with a name already in scope.

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


Re: [Haskell-cafe] Newbie question related to list evaluation

2008-01-06 Thread Sai Hemanth K
AAh! Thanks a ton!

Hemanth K

On Jan 7, 2008 12:10 AM, Rodrigo Queiro [EMAIL PROTECTED] wrote:

 You have used the name 'pos' twice, for both the parameter and the
 returned value of the recursive call. The reason this results in an
 infinite loop is that in code like

 let x = x + 1

 Haskell treats both xs to be references to the same thing, so evaluates:
 x
 = x + 1
 = (x + 1) + 1
 = ((x + 1) + 1) + 1
 ...

 which results in the infinite loop.

 On 06/01/2008, Sai Hemanth K [EMAIL PROTECTED] wrote:
  Hi,
 
  I am new to functional and lazy programming languages ( that's correct,
 my
  life has been pretty pathetic so far) and am not able to understand
 GHC's
  behaviour for a particular function. Can someone help me please?
 
  I am trying to write a function which would compare two strings (from
  reverse) and return the position of first mismatch. This is part of the
  right-to-left scan of bayer-moore algorithm.. and it is essential for me
 to
  do it from reverse.
  Since my goal is to learn haskell, I am not using Data.ByteString.
 
  My function is as follows:
 
  matchReverse :: String - String -Int-(Bool,Int)
  matchReverse [] [] pos = (True,pos)
  matchReverse _ [] pos = (False,pos)
  matchReverse [] _ pos = (False,pos)
  matchReverse (x:xs) (y:ys) pos = let (matched,pos) = matchReverse xs ys
 (pos
  +1)
in if matched then
  ((x==y),pos)
   else (False,pos)
 
 
 
  The behaviour I expected in four scenarios is as below:
  1.matchReverse kapilash kapilash 0 --should return (True,0)
  2.matchReverse kapilash kapilast 0 --should return (False,8)
  3.matchReverse str1 str2 0  --should return
 (False,0)
  4.matchReverse str1 str1 0  --should return (True,0)
 
  where str1 and str2 are defined as below:
   str1 =  replicate 1000 'a'
   str2 =  'b':(replicate 999 'a')
 
  what confounds me is that it is able to identify the first element of
 the
  tuple in ALL the cases.
  Invoking fst on the each of the four calls instantly returns the
 expected
  value.(even for the cases 3 and 4 where, there are thousand elements)
  But it seems to go into an infinite loop while calculating the 'snd' of
 the
  tuple. Even for strings containing just one element each.
  can someone throw some light on this please? Why does it go into an
 infinite
  loop?
 
  Many thanks
  Kapilash
 
 
  --
  I drink I am thunk.
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 




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


Re: [Haskell-cafe] Newbie question related to list evaluation

2008-01-06 Thread Andrew Coppin

Felipe Lessa wrote:

As as side note, GHC's flag -Wall would have warned about creating a
variable with a name already in scope.
  


*makes a mental note*

I've created bugs like this far too many times...

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


Re: [Haskell-cafe] Newbie question: can laziness lead to space compression?

2008-01-02 Thread Malcolm Wallace
Brian Hurt [EMAIL PROTECTED] wrote:

 But I was wondering if it is possible that lazy evaluation
 could  lead to space compression, especially under heavily persistant
 usage  patterns?
 
 Note that the benefit isn't *big*- we're talking about 40 words of
 memory  when the main data structure is taking up 5K plus words of
 memory- so it's  less than 1% different.  But there is a (small)
 upside in memory usage at  least occassionally, right?

Actually, a lazy evaluation strategy can sometimes change the entire
complexity class of space usage, not just the constant factors.  For
instance, lazy streaming algorithms (where the data is produced and
consumed in lock-step) may use a small constant amount of memory,
independent of the size of the data, whereas an eager strategy would use
memory linearly proportional to the dataset size.

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


[Haskell-cafe] Newbie question: can laziness lead to space compression?

2007-12-29 Thread Brian Hurt


My apologies if this has been beat to death before, I'm still new to 
Haskell.  But I was wondering if it is possible that lazy evaluation could 
lead to space compression, especially under heavily persistant usage 
patterns?


Here's the argument I'm making.  Say we have a tree-based Set with, say, 
1024 values in it.  For ease of math we'll assume that it's perfectly 
balanced.  Say each node in the tree takes 5 words of memory.  So in an 
eager language (for example, Ocaml), adding a new node to this tree 
requires the allocation of 10 new nodes, or 50 words of memory.  In 
Haskell, what would happen (as I understand it) is that just a new lazy 
thunk would be allocated- say, 10 words of memory.  Conceptually, we could 
think of the returned value as the original tree plus a small delta.  The 
lazy implementation is using 40 fewer words of memory than the eager 
implementation.


Note that the benefit isn't *big*- we're talking about 40 words of memory 
when the main data structure is taking up 5K plus words of memory- so it's 
less than 1% different.  But there is a (small) upside in memory usage at 
least occassionally, right?


Brian

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


Re: [Haskell-cafe] Newbie question: can laziness lead to space compression?

2007-12-29 Thread Daniel Fischer
Am Samstag, 29. Dezember 2007 16:00 schrieb Brian Hurt:
 My apologies if this has been beat to death before, I'm still new to
 Haskell.  But I was wondering if it is possible that lazy evaluation could
 lead to space compression, especially under heavily persistant usage
 patterns?

 Here's the argument I'm making.  Say we have a tree-based Set with, say,
 1024 values in it.  For ease of math we'll assume that it's perfectly
 balanced.  Say each node in the tree takes 5 words of memory.  So in an
 eager language (for example, Ocaml), adding a new node to this tree
 requires the allocation of 10 new nodes, or 50 words of memory.  In
 Haskell, what would happen (as I understand it) is that just a new lazy
 thunk would be allocated- say, 10 words of memory.  Conceptually, we could
 think of the returned value as the original tree plus a small delta.  The
 lazy implementation is using 40 fewer words of memory than the eager
 implementation.

 Note that the benefit isn't *big*- we're talking about 40 words of memory
 when the main data structure is taking up 5K plus words of memory- so it's
 less than 1% different.  But there is a (small) upside in memory usage at
 least occassionally, right?

Oh yes. Imagine how much memory an eager language would need for [1 .. ].
But laziness can also induce space leaks. That's not too uncommon either.
Finding out when which case applies is the art to be learned.

 Brian

Cheers,
Daniel

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


Re: [Haskell-cafe] newbie question about list performance

2007-10-29 Thread Jules Bean

John Lato wrote:

I'm working
with moderate-sized files (tens to hundreds of MBs) that have some
ascii header data followed by a bunch of 32-bit ints.



but I don't know if [Int32] is actually the best choice.  It seems to me
that something like a lazy list of strict arrays (analogous to a lazy
bytestring) would be better.  


Depends on your data access pattern. If you access the words strictly 
linearly, from the beginning of the file to the end, and that's all, 
then [Int32] is absolutely fine. A list is a data-structure equivalent 
of a for loop; it's the correct structure if you are dealing with things 
linearly or nearly-linearly. If you were using adjacent words together, 
that would be fine too (as in, e.g., zip xs (tail xs)).


If your data access pattern is more scattered or random-access in style, 
then [Int32] does not scale well to 10s of MBs. If you keep the data 
around, the overhead for [] is inappropriate (around 600-800% memory 
usage overhead on [Int32]) and its performance guarantees are not good 
either, for random access. In this case, as a first approximation, I 
would be inclined to try a library which simple backended onto lazy 
bytestring. For example the 'index' operation to fetch a single word 
would fetch four bytes and bit-twiddle them into a word. If that doesn't 
give the high speed you're after, then perhaps something *like* LBS, 
i.e. foreignptr behind the scenes, but directly accessing word-at-a-time.


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


Re: [Haskell-cafe] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Benjamin L. Russell
One factor that is slightly unusual about this
phenomenon is that it only occurs with GHC, but not
with Hugs 98.  Typing 

:cd D:\From C Drive\Documents and
Settings\DekuDekuplex\Programming
Practice\Haskell\GHC

in Hugs 98 does not cause an error, but typing the
same command in GHC does.  It seems that Hugs 98
allows spaces in filenames/paths, but GHC doesn't.

Is there any way to configure GHC so that it accepts
the same type of filenames/paths as Hugs 98?

Benjamin L. Russell

--- Benjamin L. Russell [EMAIL PROTECTED]
wrote:

 Please pardon this intrusion for an elementary
 question on setting the GHC search path.
 
 I have installed GHC on my work Windows XP machine,
 and would like to be able to search for files in the
 following directory:
 
 D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC
 
 However, when I type the following command into the
 GHC interpreter:
 
 :cd D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC
 
 I get the following error message:
 
 *** Exception: D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC: setCurrentDirectory: invalid
 argument (Invalid argument)
 
 Yet, for testing purposes, when I type the following
 command:
 
 :cd cygwin
 
 I do not get any error message.
 
 There seems to be a problem with the spaces in the
 filename.  However, I would like to be able to use
 the
 D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC directory for GHC programming
 practice, because I keep my practice work for my
 other
 programming languages in the same
 super-super-directory.
 
 Does anybody know a way to specify D:\From C
 Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC as a directory in the search
 path for GHC?
 
 Benjamin L. Russell
 ___
 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] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Stefan O'Rear
On Mon, Oct 29, 2007 at 04:25:45AM -0700, Benjamin L. Russell wrote:
 One factor that is slightly unusual about this
 phenomenon is that it only occurs with GHC, but not
 with Hugs 98.  Typing 
 
 :cd D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC

Are you sure it has anything to do with spaces?  Exactly one of your
test paths has backslashes, and it's not the working one.

Stefan


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


Re: [Haskell-cafe] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Olivier Boudry
In GHC it works without the  and don't work with them:

Prelude :cd C:\Documents and Settings
Prelude :! pwd
C:\Documents and Settings

Olivier.

On 10/29/07, Benjamin L. Russell [EMAIL PROTECTED] wrote:

 Please pardon this intrusion for an elementary
 question on setting the GHC search path.

 I have installed GHC on my work Windows XP machine,
 and would like to be able to search for files in the
 following directory:

 D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming Practice\Haskell\GHC

 However, when I type the following command into the
 GHC interpreter:

 :cd D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC

 I get the following error message:

 *** Exception: D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC: setCurrentDirectory: invalid
 argument (Invalid argument)

 Yet, for testing purposes, when I type the following
 command:

 :cd cygwin

 I do not get any error message.

 There seems to be a problem with the spaces in the
 filename.  However, I would like to be able to use the
 D:\From C Drive\Documents and
 Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC directory for GHC programming
 practice, because I keep my practice work for my other
 programming languages in the same
 super-super-directory.

 Does anybody know a way to specify D:\From C
 Drive\Documents and Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC as a directory in the search
 path for GHC?

 Benjamin L. Russell
 ___
 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] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Benjamin L. Russell
You're right; it works without the double-quotes.

Problem solved.  Thanks!

Benjamin L. Russell

--- Olivier Boudry [EMAIL PROTECTED] wrote:

 In GHC it works without the  and don't work with
 them:
 
 Prelude :cd C:\Documents and Settings
 Prelude :! pwd
 C:\Documents and Settings
 
 Olivier.
 
 On 10/29/07, Benjamin L. Russell
 [EMAIL PROTECTED] wrote:
 
  Please pardon this intrusion for an elementary
  question on setting the GHC search path.
 
  I have installed GHC on my work Windows XP
 machine,
  and would like to be able to search for files in
 the
  following directory:
 
  D:\From C Drive\Documents and
  Settings\DekuDekuplex\Programming
 Practice\Haskell\GHC
 
  However, when I type the following command into
 the
  GHC interpreter:
 
  :cd D:\From C Drive\Documents and
  Settings\DekuDekuplex\Programming
  Practice\Haskell\GHC
 
  I get the following error message:
 
  *** Exception: D:\From C Drive\Documents and
  Settings\DekuDekuplex\Programming
  Practice\Haskell\GHC: setCurrentDirectory:
 invalid
  argument (Invalid argument)
 
  Yet, for testing purposes, when I type the
 following
  command:
 
  :cd cygwin
 
  I do not get any error message.
 
  There seems to be a problem with the spaces in the
  filename.  However, I would like to be able to use
 the
  D:\From C Drive\Documents and
  Settings\DekuDekuplex\Programming
  Practice\Haskell\GHC directory for GHC
 programming
  practice, because I keep my practice work for my
 other
  programming languages in the same
  super-super-directory.
 
  Does anybody know a way to specify D:\From C
  Drive\Documents and
 Settings\DekuDekuplex\Programming
  Practice\Haskell\GHC as a directory in the search
  path for GHC?
 
  Benjamin L. Russell
  ___
  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


[Haskell-cafe] newbie question about list performance

2007-10-28 Thread John Lato
Hello,
I've been following the list optimization thread with great interest,
as it pertains to something I'm working on at the moment.  I'm working
with moderate-sized files (tens to hundreds of MBs) that have some
ascii header data followed by a bunch of 32-bit ints.  I can read the
files into a lazy ByteString (and parse the header), but I'd like some
advice as to the best data type to convert the ints into.  Ideally,
I'd have some functions like this:
decode :: ByteString - (FileFormat, [Int32])
encode :: FileFormat - [Int32] - ByteString

but I don't know if Int32 is actually the best choice.  It seems to me
that something like a lazy list of strict arrays (analogous to a lazy
bytestring) would be better.  Is there a library like this already?
Or is this a case of premature optimization, and I should just try the
list and see if it's good enough?  Any suggestions would be
appreciated.

Also, I'd like to let the maintainers and implementors know that I
really appreciate the work that's been done on optimizing Haskell.  I
haven't used Haskell much yet, but I've fallen in love with the
language and it's great to see that performance even for heavy I/O
tasks can be comparable to or exceed C.

Thank you,
John Lato
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie Question on Setting the GHC Search Path

2007-10-28 Thread Benjamin L. Russell
Please pardon this intrusion for an elementary
question on setting the GHC search path.

I have installed GHC on my work Windows XP machine,
and would like to be able to search for files in the
following directory:

D:\From C Drive\Documents and
Settings\DekuDekuplex\Programming Practice\Haskell\GHC

However, when I type the following command into the
GHC interpreter:

:cd D:\From C Drive\Documents and
Settings\DekuDekuplex\Programming
Practice\Haskell\GHC

I get the following error message:

*** Exception: D:\From C Drive\Documents and
Settings\DekuDekuplex\Programming
Practice\Haskell\GHC: setCurrentDirectory: invalid
argument (Invalid argument)

Yet, for testing purposes, when I type the following
command:

:cd cygwin

I do not get any error message.

There seems to be a problem with the spaces in the
filename.  However, I would like to be able to use the
D:\From C Drive\Documents and
Settings\DekuDekuplex\Programming
Practice\Haskell\GHC directory for GHC programming
practice, because I keep my practice work for my other
programming languages in the same
super-super-directory.

Does anybody know a way to specify D:\From C
Drive\Documents and Settings\DekuDekuplex\Programming
Practice\Haskell\GHC as a directory in the search
path for GHC?

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


Re: [Haskell-cafe] newbie question about list performance

2007-10-28 Thread Don Stewart
jwlato:
 Hello,
 I've been following the list optimization thread with great interest,
 as it pertains to something I'm working on at the moment.  I'm working
 with moderate-sized files (tens to hundreds of MBs) that have some
 ascii header data followed by a bunch of 32-bit ints.  I can read the
 files into a lazy ByteString (and parse the header), but I'd like some
 advice as to the best data type to convert the ints into.  Ideally,
 I'd have some functions like this:
 decode :: ByteString - (FileFormat, [Int32])
 encode :: FileFormat - [Int32] - ByteString
 
 but I don't know if Int32 is actually the best choice.  It seems to me
 that something like a lazy list of strict arrays (analogous to a lazy
 bytestring) would be better.  Is there a library like this already?
 Or is this a case of premature optimization, and I should just try the
 list and see if it's good enough?  Any suggestions would be
 appreciated.

could you use Data.Binary.encode/decode (with custom put and get
instances)? They read fomr lazy bytestrings into custom structures, such
as arrays.

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/binary-0.4.1

 Also, I'd like to let the maintainers and implementors know that I
 really appreciate the work that's been done on optimizing Haskell.  I
 haven't used Haskell much yet, but I've fallen in love with the
 language and it's great to see that performance even for heavy I/O
 tasks can be comparable to or exceed C.

Yay!

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


[Haskell-cafe] Newbie question: Why gfoldl has this strange type?

2007-08-30 Thread Rodrigo Geraldo
Hi!

I am a novice in Haskell, and particularly I have interested in generic
programming. This interest motivated me to read paper Scrap your
boilerplate: A practical design pattern for generic programming, but I
didn't understand the type of the function gfoldl, that was present in class
Term (Data). Somebody could help me to understand the type of this function?

Thanks...

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


Re: [Haskell-cafe] Newbie question: Why gfoldl has this strange type?

2007-08-30 Thread Ryan Ingram
Just so nobody else has to look it up:
Data.Generics.Basics.gfoldl :: Data a = (c (a - b) - a - c b) - (g - c
g) - a - c a

  -- ryan


On 8/30/07, Rodrigo Geraldo [EMAIL PROTECTED] wrote:

 Hi!

 I am a novice in Haskell, and particularly I have interested in generic
 programming. This interest motivated me to read paper Scrap your
 boilerplate: A practical design pattern for generic programming, but I
 didn't understand the type of the function gfoldl, that was present in class
 Term (Data). Somebody could help me to understand the type of this function?

 Thanks...

 Rodrigo

 ___
 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] Newbie question: Why gfoldl has this strange type?

2007-08-30 Thread Ryan Ingram
Actually, it's a higher rank type and that doesn't show up on hoogle's main
page.

gfoldl :: (forall a b . Data a = c (a - b) - a - c b)
- (forall g . g - c g)
- a
- c a
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-23 Thread Bas van Dijk
On 8/20/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 ...
 (I need to find some way to automate making these trails :) )
 ...

I think you can come a long way with the debugger in GHC HEAD. It
provides a :trace command that, when applied to an expression with
some breakpoint in it, remembers the history of evaluation steps. You
can view the history with :hist.

See: 
http://www.haskell.org/ghc/dist/current/docs/users_guide/ghci-debugger.html#tracing

regards,

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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-21 Thread Andrew Coppin

Stefan O'Rear wrote:

sum = sum' 0
sum' k [] = k
sum' k (x:xs) = (sum' $! (k+x)) xs

enum x y | x = y= 0
 | otherwise = x : enum (x+1) y


sum (enum 1 10) =
sum' 0 (enum 1 10)  =
sum' 0 (1 : enum (1+1) 10)  =
(sum' $! (0+1)) (enum (1+1) 10) =
sum' 1 (enum (1+1) 10)  =

sum' 1 (2 : enum (2+1) 10)  =
(sum' $! (1+2)) (enum (2+1) 10) =
sum' 3 (enum (2+1) 10)  =

sum' 3 (3 : enum (3+1) 10)  =
(sum' $! (3+3)) (enum (3+1) 10) =
sum' 6 (enum (3+1) 10)  =

sum' 6 (4 : enum (4+1) 10)  =
(sum' $! (6+4)) (enum (4+1) 10) =
sum' 10 (enum (4+1) 10) =

...


sum' 36 (9 : enum (9+1) 10)  =
(sum' $! (36+9)) (enum (9+1) 10) =
sum' 45 (enum (9+1) 10)  =
sum' 45 []   =
45

(I need to find some way to automate making these trails :) )
  


I did have a fairly small Tcl implementation for this...

I don't have the code now, and I wrote it early in my Haskell career, so 
there's masses of stuff it didn't handle. (*cough* type classes)


Actually, I've often longed for some tool (maybe even integrated into 
Lambdabot) to show the reduction sequence of an arbitrary expression. 
But none exists, AFAIK...


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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-20 Thread Lanny Ripple
Not really more efficient but plays to the language 
implementation's strengths.


Imagine

  take 10 $ foo (10^9)

and

  take 10 $ bar (10^9)

bar wouldn't evaluate until the 10^9 was done.  (And I just 
ground my laptop to a halt checking that.  :)  foo on the other 
hand would run out to 10^6 and then conveniently finish the rest 
of your program waiting for the need of the other 10^9-10 values. 
 If you *always* needed the result of the 10^9 calculations then 
tail-recursion should be better since you won't be holding onto 
the evaluation frames.


  -ljr

Peter Verswyvelen wrote:


Now if I understand this correctly, this just means that when writing
something like:

foo n = if n0 then [] else n : foo (n-1)

bar n = aux 0 [] where
  aux i xs = if in then xs else aux (i+1) (i:xs)

that foo is more efficient than bar because lazy evaluation of foo just puts
the delayed computation in the cdr of the list, while lazy evaluation of
bar has to keep track of all aux calls (the closures) which gives much
more overhead, maybe even stack overflow? Something like that? 


Thanks,
Peter




--
Lanny Ripple [EMAIL PROTECTED]
ScmDB / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-20 Thread Lanny Ripple



Lanny Ripple wrote:
Not really more efficient but plays to the language implementation's 
strengths.


Imagine

  take 10 $ foo (10^9)

and

  take 10 $ bar (10^9)

bar wouldn't evaluate until the 10^9 was done.  (And I just ground my 
laptop to a halt checking that.  :)  foo on the other hand would run out 
to 10^6 and then conveniently finish the rest of your program waiting 


   s/10^6/10/

That's what I get for not proof-reading after making a change 
after the first proof-read.


for the need of the other 10^9-10 values.  If you *always* needed the 
result of the 10^9 calculations then tail-recursion should be better 
since you won't be holding onto the evaluation frames.


  -ljr

Peter Verswyvelen wrote:


Now if I understand this correctly, this just means that when writing
something like:

foo n = if n0 then [] else n : foo (n-1)


bar n = aux 0 [] where
  aux i xs = if in then xs else aux (i+1) (i:xs)

that foo is more efficient than bar because lazy evaluation of foo 
just puts
the delayed computation in the cdr of the list, while lazy 
evaluation of

bar has to keep track of all aux calls (the closures) which gives much
more overhead, maybe even stack overflow? Something like that?
Thanks,
Peter






--
Lanny Ripple [EMAIL PROTECTED]
ScmDB / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 11:21:01AM -0500, Lanny Ripple wrote:
 Not really more efficient but plays to the language implementation's 
 strengths.

 Imagine

   take 10 $ foo (10^9)

 and

   take 10 $ bar (10^9)

 bar wouldn't evaluate until the 10^9 was done.  (And I just ground my 
 laptop to a halt checking that.  :)  foo on the other hand would run out to 
 10^6 and then conveniently finish the rest of your program waiting for the 
 need of the other 10^9-10 values.  If you *always* needed the result of the 
 10^9 calculations then tail-recursion should be better since you won't be 
 holding onto the evaluation frames.

Even if you did, in the presense of laziness it's not useful to make
list producers tail recursive.  Consider:

sum = sum' 0
sum' k [] = k
sum' k (x:xs) = (sum' $! (k+x)) xs

enum x y | x = y= 0
 | otherwise = x : enum (x+1) y


sum (enum 1 10) =
sum' 0 (enum 1 10)  =
sum' 0 (1 : enum (1+1) 10)  =
(sum' $! (0+1)) (enum (1+1) 10) =
sum' 1 (enum (1+1) 10)  =

sum' 1 (2 : enum (2+1) 10)  =
(sum' $! (1+2)) (enum (2+1) 10) =
sum' 3 (enum (2+1) 10)  =

sum' 3 (3 : enum (3+1) 10)  =
(sum' $! (3+3)) (enum (3+1) 10) =
sum' 6 (enum (3+1) 10)  =

sum' 6 (4 : enum (4+1) 10)  =
(sum' $! (6+4)) (enum (4+1) 10) =
sum' 10 (enum (4+1) 10) =

...


sum' 36 (9 : enum (9+1) 10)  =
(sum' $! (36+9)) (enum (9+1) 10) =
sum' 45 (enum (9+1) 10)  =
sum' 45 []   =
45

(I need to find some way to automate making these trails :) )

It runs in constant space, despite the producer's non-tail-recursion.

Stefan


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


RE: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-19 Thread Peter Verswyvelen
Thanks. I got confused because the StackOverflow link on

http://www.haskell.org/haskellwiki/HaWiki_migration

is dead.

-Original Message-
From: Derek Elkins [mailto:[EMAIL PROTECTED] 
Sent: Saturday, August 18, 2007 8:54 PM
To: Peter Verswyvelen
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the
Wiki?

On Sat, 2007-08-18 at 20:35 +0200, Peter Verswyvelen wrote:
 When reading an article about tail recursion

(http://themechanicalbride.blogspot.com/2007/04/haskell-for-c-3-programmers.
 html) I came across the follow statements:
 
 If you can write a non-recursive function that uses the colon syntax it
is
 probably better than a tail recursive one that doesn't. This is because
 Haskell's lazy evaluation enabled you to use the non-tail recursive
version
 on an infinite stream without getting a stack overflow. 
 
 and
 
 Unfortunately, laziness gets in the way. While transforming
 non-tail-recursive code to a tail-recursive form is important and useful
for
 functional programming in general, dealing with laziness requires a little
 more care, and often non-tail-recursive versions are preferrable.
flatten
 is an example of this, the first version is better in many ways. While I
 don't believe it happens in this case, oftentimes naively writing code
 tail-recursively in Haskell will actually -make- it overflow the stack.
 Another (actual) benefit of the first version of flatten is that it will
 work on infinite lists. http://www.haskell.org/hawiki/StackOverflow gives
a
 simple example and some explanation.

That page was migrated here:
http://www.haskell.org/haskellwiki/Stack_overflow


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


[Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-18 Thread Peter Verswyvelen
When reading an article about tail recursion
(http://themechanicalbride.blogspot.com/2007/04/haskell-for-c-3-programmers.
html) I came across the follow statements:

If you can write a non-recursive function that uses the colon syntax it is
probably better than a tail recursive one that doesn't. This is because
Haskell's lazy evaluation enabled you to use the non-tail recursive version
on an infinite stream without getting a stack overflow. 

and

Unfortunately, laziness gets in the way. While transforming
non-tail-recursive code to a tail-recursive form is important and useful for
functional programming in general, dealing with laziness requires a little
more care, and often non-tail-recursive versions are preferrable. flatten
is an example of this, the first version is better in many ways. While I
don't believe it happens in this case, oftentimes naively writing code
tail-recursively in Haskell will actually -make- it overflow the stack.
Another (actual) benefit of the first version of flatten is that it will
work on infinite lists. http://www.haskell.org/hawiki/StackOverflow gives a
simple example and some explanation.

Unfortunately I can't find the StackOverflow page anymore.

Now if I understand this correctly, this just means that when writing
something like:

foo n = if n0 then [] else n : foo (n-1)

bar n = aux 0 [] where
  aux i xs = if in then xs else aux (i+1) (i:xs)

that foo is more efficient than bar because lazy evaluation of foo just puts
the delayed computation in the cdr of the list, while lazy evaluation of
bar has to keep track of all aux calls (the closures) which gives much
more overhead, maybe even stack overflow? Something like that? 

Thanks,
Peter










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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-18 Thread Derek Elkins
On Sat, 2007-08-18 at 20:35 +0200, Peter Verswyvelen wrote:
 When reading an article about tail recursion
 (http://themechanicalbride.blogspot.com/2007/04/haskell-for-c-3-programmers.
 html) I came across the follow statements:
 
 If you can write a non-recursive function that uses the colon syntax it is
 probably better than a tail recursive one that doesn't. This is because
 Haskell's lazy evaluation enabled you to use the non-tail recursive version
 on an infinite stream without getting a stack overflow. 
 
 and
 
 Unfortunately, laziness gets in the way. While transforming
 non-tail-recursive code to a tail-recursive form is important and useful for
 functional programming in general, dealing with laziness requires a little
 more care, and often non-tail-recursive versions are preferrable. flatten
 is an example of this, the first version is better in many ways. While I
 don't believe it happens in this case, oftentimes naively writing code
 tail-recursively in Haskell will actually -make- it overflow the stack.
 Another (actual) benefit of the first version of flatten is that it will
 work on infinite lists. http://www.haskell.org/hawiki/StackOverflow gives a
 simple example and some explanation.

That page was migrated here:
http://www.haskell.org/haskellwiki/Stack_overflow

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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-18 Thread Chaddaï Fouché
 foo n = if n0 then [] else n : foo (n-1)

 bar n = aux 0 [] where
   aux i xs = if in then xs else aux (i+1) (i:xs)

 that foo is more efficient than bar because lazy evaluation of foo just puts
 the delayed computation in the cdr of the list, while lazy evaluation of
 bar has to keep track of all aux calls (the closures) which gives much
 more overhead, maybe even stack overflow? Something like that?

There is absolutely no problem with bar, it will not stack overflow
since it _is_ tail-recursive _and_ the comparison i  n force the
evaluation of i avoiding the risk of constructing a too big thunk for
the first parameter of aux which could bring a stack overflow like in
this example :
nonStrictLength n [] = n
nonStrictLength n (_:xs) = nonStrictLength (n+1) xs

(try nonStrictLength 0 [1..1000] in GHCi to see the stack
overflow, GHC strictness analysis would avoid the problem with -O)

Though foo is still more interesting than bar since it will work on
infinite list, bar is too strict.

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


[Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread peterv
I’m having difficulty to understand what phantom types are good for. Is this
just for improving runtime performance? 

I read the wiki, and it says this is useful if you want to increase the
type-safety of your code, but the code below does not give a compiler error
for the function test1, I get a runtime error, just like test2.

Thanks,
Peter

-- CODE --
-- With phantom types
data T1 a = TI1 Int | TS1 String deriving Show

foo1 :: T1 String - T1 String - T1 String
foo1 (TS1 x) (TS1 y) = TS1 (x++y)

test1 = foo1 (TI1 1) (TI1 2) -- Shouldn't this give a compiler error instead
of a runtime error? 

-- Without phantom types
data T2 = TI2 Int | TS2 String deriving Show

foo2 :: T2 - T2 - T2
foo2 (TS2 x) (TS2 y) = TS2 (x++y)

test2 = foo2 (TI2 1) (TI2 2)



No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.11.8/941 - Release Date: 07/08/2007
16:06
 

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


Re: [Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread Tillmann Rendel

peterv wrote:
I’m having difficulty to understand what phantom types are good for. 


I read the wiki, and it says this is useful if you want to increase the
type-safety of your code, but the code below does not give a compiler error
for the function test1, I get a runtime error, just like test2.



-- With phantom types
data T1 a = TI1 Int | TS1 String deriving Show

foo1 :: T1 String - T1 String - T1 String
foo1 (TS1 x) (TS1 y) = TS1 (x++y)

test1 = foo1 (TI1 1) (TI1 2) -- Shouldn't this give a compiler error instead
 -- of a runtime error? 


You have to manually instantiate the phantom type variable. In your 
code, the type of TI1 1 is just T1 a for an unrestricted type variable 
a. This unifies fine with the expected argument type of foo1, wich is T1 
String, by setting a = String. Consider this variant of your code:


  -- the type of things wich can hold numbers or text
  -- what exactly they hold is encoded dynamically by the
  -- constructor used and statically by the phantom type
  data Container a = NumberContainer Int | TextContainer String

  data Number = Number
  data Text = Text

  -- approbiate smart constructors. only use these for creation
  -- of containers, never use the real constructors.
  number :: Int - Container Number
  number x = NumberContainer x

  text :: String - Container Text
  text x = TextContainer x

  -- a function wich works only on containers holding text
  foo :: Container Text - Container Text - Container Text
  foo (TextContainer a) (TextContainer b) = text (a ++ b)

  -- testing
  test1 = text hello  `foo` text world -- works
  test2 = number 13 `foo` number 19-- static error

This works fine when you can decide statically how to instantiate the 
phantom type variable (by using the approbiate smart constructor). If 
you can't (because you read data from same external source, for 
example), you can restrict the position of dynamic failures to a 
well-defined point in program execution by defining


  asText :: Container a - Maybe (Container Text)
  asText (TextContainer x) = Just $ text x
  asText _ = Nothing

  asNumber :: Container a - Maybe (Container Number)
  asNumber (NumberContainer x) = Just $ number x
  asNumber _ = Nothing

Using these functions, you can lift a dynamic typecheck (is it the right 
constructor?) to a static typecheck (has it the right phantom type?). So 
you can for example check user input once for having the correct form 
and then enter the statically typesafe part of your program, where you 
don't have to worry about people entering numbers instead of text, 
because you statically know that at this point in program execution, the 
dynamic typecheck already suceeded.


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


Re: [Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread Arie Peterson

 I’m having difficulty to understand what phantom types are good for. Is
 this just for improving runtime performance?

No. As the wiki says, you can use them to add static guarantees.

 I read the wiki, and it says this is useful if you want to increase the
 type-safety of your code, but the code below does not give a compiler
 error
 for the function test1, I get a runtime error, just like test2.

It seems you're mixing up GADT's and phantom types.

 -- CODE --
 -- With phantom types
 data T1 a = TI1 Int | TS1 String deriving Show

Here, the 'a' is an extra type parameter, which has no manifestation on
the value level. Note the type of the constructors:

TI1 :: Int - T1 a
TS1 :: String - T1 a

In particular, the 'a' is not related to the 'Int' or 'String' arguments.

 foo1 :: T1 String - T1 String - T1 String
 foo1 (TS1 x) (TS1 y) = TS1 (x++y)

 test1 = foo1 (TI1 1) (TI1 2) -- Shouldn't this give a compiler error
 instead
 of a runtime error?

'TI1 1' has type 'T1 a', so this unifies with 'T1 String' (the type of the
argument of 'foo1'.


The type parameter 'a' can still be useful, but you have to use an
explicit type signature to constrain the type 'a':

ti1 :: Int - T1 Int
ti1 x = TI1 x

Now, 'ti1' will create values with the restricted type 'T1 Int', that you
can't use as arguments for your 'foo1'.


GADTs are perhaps more useful for what you seem to want. Try something
like this:

data T1 :: * - * where -- T1 has one type parameter
  TI1 :: Int - T1 Int
  TS1 :: String - T1 String

Now, the type systems guarantees that all values of the form 'TI1 x' have
type 'T1 Int'.


Greetings,

Arie


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


Re: [Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread David F. Place


On Aug 8, 2007, at 11:16 AM, peterv wrote:

I’m having difficulty to understand what phantom types are good  
for. Is this

just for improving runtime performance?




I found phantom types to be useful in the implementation of bit-wise  
set operations.  You can find the code Edison:


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ 
EdisonCore-1.2.1


in the Data.Edison.Coll.EnumSet module.

David F. Place
mailto:[EMAIL PROTECTED]


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


RE: [Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread peterv
Thanks, that is a much clearer explanation than
http://en.wikibooks.org/wiki/Haskell/Phantom_types

Peter

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Arie Peterson
Sent: Wednesday, August 08, 2007 5:59 PM
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question (again!) about phantom types


 I'm having difficulty to understand what phantom types are good for. Is
 this just for improving runtime performance?

No. As the wiki says, you can use them to add static guarantees.

 I read the wiki, and it says this is useful if you want to increase the
 type-safety of your code, but the code below does not give a compiler
 error
 for the function test1, I get a runtime error, just like test2.

It seems you're mixing up GADT's and phantom types.

 -- CODE --
 -- With phantom types
 data T1 a = TI1 Int | TS1 String deriving Show

Here, the 'a' is an extra type parameter, which has no manifestation on
the value level. Note the type of the constructors:

TI1 :: Int - T1 a
TS1 :: String - T1 a

In particular, the 'a' is not related to the 'Int' or 'String' arguments.

 foo1 :: T1 String - T1 String - T1 String
 foo1 (TS1 x) (TS1 y) = TS1 (x++y)

 test1 = foo1 (TI1 1) (TI1 2) -- Shouldn't this give a compiler error
 instead
 of a runtime error?

'TI1 1' has type 'T1 a', so this unifies with 'T1 String' (the type of the
argument of 'foo1'.


The type parameter 'a' can still be useful, but you have to use an
explicit type signature to constrain the type 'a':

ti1 :: Int - T1 Int
ti1 x = TI1 x

Now, 'ti1' will create values with the restricted type 'T1 Int', that you
can't use as arguments for your 'foo1'.


GADTs are perhaps more useful for what you seem to want. Try something
like this:

data T1 :: * - * where -- T1 has one type parameter
  TI1 :: Int - T1 Int
  TS1 :: String - T1 String

Now, the type systems guarantees that all values of the form 'TI1 x' have
type 'T1 Int'.


Greetings,

Arie


___
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] Newbie question: multi-methods in Haskell

2007-08-06 Thread peterv
In de book Modern C++ design, Andrei Alexandrescu writes that Haskell
supports “multi-methods”

http://books.google.com/books?id=aJ1av7UFBPwCpg=PA3ots=YPiJ_nWi6Ydq=moder
n+C%2B%2Bsig=FWO6SVfIrgtCWifj9yYHj3bnplQ#PPA263,M1

How is this actually done in Haskell? Maybe this is just a basic feature of
Haskell which I don't grasp yet because of my object-oriented background?

A good example is collision between pairs of objects of type (a,b). In
object oriented languages this cannot be handled in a nice way, because
neither a.Collide(b) or b.Collide(a) is the correct approach; one would like
to write (a,b).Collide()

A specific example might be better here. 

Assume the following class hierarchy:

Solid
|
+-- Asteroid
|
+-- Planet
|
+ -- Earth
|
+ -- Jupiter

Using multi-methods, I could write (in pseudo code)

collide (Asteroid, Planet) = an asteroid hit a planet
collide (Asteroid, Earth) = the end of the dinos
collide (Solid,Solid) =  solids collided
collide (Planet, Asteroid) = collide (Asteroid, Planet)
collide (Earth, Asteroid)  = collide (Earth, Asteroid)

So basically, the best collide function is picked, depending on the type
of the arguments.

How should I write Haskell code for something like this in general, in the
sense that this hierarchy is typically huge and the matrix (of collide
functions for each pair of types) is very sparse.

Thanks,
Peter




No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.476 / Virus Database: 269.11.6/938 - Release Date: 05/08/2007
16:16
 

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


Re: [Haskell-cafe] Newbie question: multi-methods in Haskell

2007-08-06 Thread Brian Hulley

peterv wrote:

In de book Modern C++ design, Andrei Alexandrescu writes that Haskell
supports “multi-methods”



Using multi-methods, I could write (in pseudo code)
collide (Asteroid, Planet) = an asteroid hit a planet
collide (Asteroid, Earth) = the end of the dinos
...
collide (Planet, Asteroid) = collide (Asteroid, Planet)
collide (Earth, Asteroid)  = collide (Earth, Asteroid)


Hi, In Haskell you can use multi parameter type classes to solve this 
problem:


{-# OPTIONS_GHC -fglasgow-exts
   -fallow-undecidable-instances
   -fallow-overlapping-instances #-}

module Collide where

class Collide a b where
   collide :: (a,b) - String

data Solid = Solid
data Asteroid = Asteroid
data Planet = Planet
data Jupiter = Jupiter
data Earth = Earth

instance Collide Asteroid Planet where
   collide (Asteroid, Planet) = an asteroid hit a planet

instance Collide Asteroid Earth where
   collide (Asteroid, Earth) = the end of the dinos

-- Needs overlapping and undecidable instances
instance Collide a b = Collide b a where
   collide (a,b) = collide (b, a)

-- ghci output
*Collide collide (Asteroid, Earth)
the end of the dinos
*Collide collide (Earth, Asteroid)
the end of the dinos

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


Re: [Haskell-cafe] Newbie question: multi-methods in Haskell

2007-08-06 Thread Dan Weston
Remember that type classes do not provide object-oriented functionality. 
The dispatch is static, not dynamic. Although OOP can be simulated in 
Haskell, it is not a natural idiom. If you need dynamic dispatch 
(including multiple dispatch), you may want to reconsider your solution.


Dan Weston

Brian Hulley wrote:

peterv wrote:

In de book Modern C++ design, Andrei Alexandrescu writes that Haskell
supports “multi-methods”



Using multi-methods, I could write (in pseudo code)
collide (Asteroid, Planet) = an asteroid hit a planet
collide (Asteroid, Earth) = the end of the dinos
...
collide (Planet, Asteroid) = collide (Asteroid, Planet)
collide (Earth, Asteroid)  = collide (Earth, Asteroid)


Hi, In Haskell you can use multi parameter type classes to solve this 
problem:


{-# OPTIONS_GHC -fglasgow-exts
   -fallow-undecidable-instances
   -fallow-overlapping-instances #-}

module Collide where

class Collide a b where
   collide :: (a,b) - String

data Solid = Solid
data Asteroid = Asteroid
data Planet = Planet
data Jupiter = Jupiter
data Earth = Earth

instance Collide Asteroid Planet where
   collide (Asteroid, Planet) = an asteroid hit a planet

instance Collide Asteroid Earth where
   collide (Asteroid, Earth) = the end of the dinos

-- Needs overlapping and undecidable instances
instance Collide a b = Collide b a where
   collide (a,b) = collide (b, a)

-- ghci output
*Collide collide (Asteroid, Earth)
the end of the dinos
*Collide collide (Earth, Asteroid)
the end of the dinos

Best regards, Brian.
___
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] Newbie question: multi-methods in Haskell

2007-08-06 Thread Tillmann Rendel

peterv schrieb:

In de book Modern C++ design, Andrei Alexandrescu writes that Haskell
supports “multi-methods”

http://books.google.com/books?id=aJ1av7UFBPwCpg=PA3ots=YPiJ_nWi6Ydq=moder
n+C%2B%2Bsig=FWO6SVfIrgtCWifj9yYHj3bnplQ#PPA263,M1


Chapter 11, Page 263 of this books:

The C++ virtual function mechanism allows dispatching of a call
depending on the dynamic type of one object. The multimethods feature
allows dispatching of a function call depending on the types of
multiple objects. A universally good implementation requires language
support, wich is the route that languages such as CLOS, ML, Haskell,
and Dylan have taken. C++ lacks such support, so it's emulation is
left to library writers.


I do not see why the author of this book included Haskell in this list. 
(But from what I know, CLOS is more like a combinator library then like 
a language, so I don't understand the point of this list at all).


Since Haskell has no language support for subtype polymorphism or 
dynamic dispatch of method calls, there are no dynamic multimethods 
either. But with multi-parameter typeclasses, we have statically 
dispatched multimethods, of course. (See Brian's answer). But the author 
speaks specifically about dynamic dispatch.


Sometimes, class hierarchies from an OO design are naturally represented 
by algebraic data types. Then OO methods become ordinary haskell 
function, and dynamic dispatch becomes pattern matching, wich is of 
course possible on all argument positions:


  data Solid = Asteroid
 | Planet Planet

  data Planet = Earth
  | Jupiter

  collide :: Solid - Solid - String
  collide Asteroid (Planet Earth) = the end of the dinos
  collide Asteroid (Planet _) = an asteroid hit a planet
  collide p@(Planet _) Asteroid  = collide Asteroid p
  collide _ _ = solids collided

But you have to sort the definitons for collide yourself, because there 
is no selection of the most specific automatically. While this is a 
sometimes sensible translation of an OO design into an FP design, it is 
not the same thing as having objects and subtypes and dynamic dispatch.


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


Re: [Haskell-cafe] Newbie question: multi-methods in Haskell

2007-08-06 Thread Brian Hulley

Dan Weston wrote:
Remember that type classes do not provide object-oriented 
functionality. The dispatch is static, not dynamic. Although OOP can 
be simulated in Haskell, it is not a natural idiom. If you need 
dynamic dispatch (including multiple dispatch), you may want to 
reconsider your solution.
Dynamic dispatch is easily added to Haskell code by using an existential 
to represent any collision:


{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances 
-fallow-overlapping-instances #-}


module Collide where

-- Changed to a single param to make life easier...
class Collide a where
   collide :: a - String

data Solid = Solid
data Asteroid = Asteroid
data Planet = Planet
data Jupiter = Jupiter
data Earth = Earth

instance Collide (Asteroid, Planet) where
   collide (Asteroid, Planet) = an asteroid hit a planet

instance Collide (Asteroid, Earth) where
   collide (Asteroid, Earth) = the end of the dinos

-- Needs overlapping and undecidable instances
instance Collide (a, b) = Collide (b, a) where
   collide (a,b) = collide (b, a)

-- This is how you get dynamic dispatch in Haskell
data Collision = forall a. Collide a = Collision a

instance Collide Collision where
   collide (Collision a) = collide a

-- ghci output
*Collide let ae = Collision (Asteroid, Earth)
*Collide let pa = Collision (Planet, Asteroid)
*Collide collide ae
the end of the dinos
*Collide collide pa
an asteroid hit a planet
*Collide map collide [ae, pa]
[the end of the dinos,an asteroid hit a planet]


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


RE: [Haskell-cafe] Newbie question: multi-methods in Haskell

2007-08-06 Thread peterv
This is very nice, but it does not really solve the original problem.

In your code, evaluating

collide (Jupiter, Asteroid)

will result in an endless loop. This is expected in your code, because no
inheritance relation is present between e.g Jupiter and Planet. With
multi-dispatch, it should pick the best matching collide function based on
inheritance, or raise an error when ambiguous types.

I could fix that be just keeping the leafs (Earth, Jupiter, Asteroid) as
datatypes, and adding type classes for the super classes (Planet, Solid),
like the code below, but I could not check Asteroid-Asteroid collision with
that, GHCi gives an error.

{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances
-fallow-overlapping-instances #-}

module Collide where

class Collide a where
collide :: a - String

data Asteroid = Asteroid
data Jupiter = Jupiter
data Earth = Earth

class IsSolid a
class IsSolid a = IsPlanet a

instance IsSolid Asteroid
instance IsSolid Jupiter
instance IsSolid Earth

instance IsPlanet Earth
instance IsPlanet Jupiter

instance (IsSolid a, IsSolid b) = Collide (a, b) where
collide (x,y) = generic collision

instance (IsPlanet a) = Collide (Asteroid, a) where
collide (x,y) = an asteroid hit a planet

instance (IsPlanet a) = Collide (a, Asteroid) where
collide (x, y) = an asteroid hit a planet

instance Collide (Asteroid, Earth) where
collide (_,_) = the end of the dinos

instance Collide (Earth, Asteroid) where
collide (_,_) = the end of the dinos

-- This is how you get dynamic dispatch in Haskell
data Collision = forall a. Collide a = Collision a

instance Collide Collision where
collide (Collision a) = collide a

ae = collide (Asteroid, Earth)
ea = collide (Earth, Asteroid)
ja = collide (Jupiter, Asteroid)
aj = collide (Asteroid, Jupiter)

-- However, this one gives an error?
--aa = collide (Asteroid, Asteroid)


-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Brian Hulley
Sent: Monday, August 06, 2007 9:15 PM
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question: multi-methods in Haskell

Dan Weston wrote:
 Remember that type classes do not provide object-oriented 
 functionality. The dispatch is static, not dynamic. Although OOP can 
 be simulated in Haskell, it is not a natural idiom. If you need 
 dynamic dispatch (including multiple dispatch), you may want to 
 reconsider your solution.
Dynamic dispatch is easily added to Haskell code by using an existential 
to represent any collision:

{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances 
-fallow-overlapping-instances #-}

module Collide where

-- Changed to a single param to make life easier...
class Collide a where
collide :: a - String

data Solid = Solid
data Asteroid = Asteroid
data Planet = Planet
data Jupiter = Jupiter
data Earth = Earth

instance Collide (Asteroid, Planet) where
collide (Asteroid, Planet) = an asteroid hit a planet

instance Collide (Asteroid, Earth) where
collide (Asteroid, Earth) = the end of the dinos

-- Needs overlapping and undecidable instances
instance Collide (a, b) = Collide (b, a) where
collide (a,b) = collide (b, a)

-- This is how you get dynamic dispatch in Haskell
data Collision = forall a. Collide a = Collision a

instance Collide Collision where
collide (Collision a) = collide a

-- ghci output
*Collide let ae = Collision (Asteroid, Earth)
*Collide let pa = Collision (Planet, Asteroid)
*Collide collide ae
the end of the dinos
*Collide collide pa
an asteroid hit a planet
*Collide map collide [ae, pa]
[the end of the dinos,an asteroid hit a planet]


Best regards, Brian.
___
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] Newbie question: multi-methods in Haskell

2007-08-06 Thread Brian Hulley

peterv wrote:

This is very nice, but it does not really solve the original problem.
  
To get Haskell to choose the best fit it's necessary to encode the 
location of each element in the hierarchy, so that elements deeper in 
the hierarchy are more instantiated than those at the top. Then instance 
selection chooses the best fit by just choosing the most instantiated match.


Encoding can be done using phantom types, so a generic solid has the path

IsSolid s

a planet has

IsSolid (IsPlanet p)

and a specific planet eg Earth has path

IsSolid (IsPlanet Earth)

A newtype can be used to associate the path with the actual object:

newtype InH path body = InH body

so Earth is represented by

InH Earth :: InH (IsSolid (IsPlanet Earth)) Earth

A class with a functional dependency gives us the mapping between 
concrete objects and the objects as viewed by the hierarchy:


class ToH body path | body - path where
toH :: body - InH path body
toH = InH

The functional dependency means that the path (location in the 
hierarchy) is uniquely determined by the body, and instance decls then 
define this relationship:



instance ToH Asteroid (IsSolid Asteroid)
instance ToH Jupiter (IsSolid (IsPlanet Jupiter))
instance ToH Earth (IsSolid (IsPlanet Earth))


The code is below but as you can see the OOP encoding in Haskell becomes 
quite heavy and clunky so this style is probably not ideal for a real 
program - Tillmann's suggestion to use algebraic datatypes instead is 
more idiomatic - but anyway here goes:


{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances
-fallow-overlapping-instances #-}

module Collide where

class Collide a where
collide :: a - String

data Asteroid = Asteroid
data Jupiter = Jupiter
data Earth = Earth


data IsSolid a
data IsPlanet a

newtype InH path body = InH body

class ToH body path | body - path where
toH :: body - InH path body
toH = InH

instance ToH Asteroid (IsSolid Asteroid)
instance ToH Jupiter (IsSolid (IsPlanet Jupiter))
instance ToH Earth (IsSolid (IsPlanet Earth))


data Collision = forall a. Collide a = Collision a

mkCollision
:: (ToH a pa, ToH b pb, Collide (InH pa a, InH pb b))
= a - b - Collision
mkCollision a b = Collision (toH a, toH b)


instance Collide (InH (IsSolid a) aa, InH (IsSolid b) bb) where
collide _ = generic collision

instance Collide (InH (IsSolid Asteroid) Asteroid, InH (IsSolid 
(IsPlanet bb)) cc) where

collide _ = an asteroid hit a planet

instance Collide (InH (IsSolid (IsPlanet a)) aa, InH (IsSolid Asteroid) 
Asteroid) where

collide _ = an asteroid hit a planet

instance Collide (InH (IsSolid Asteroid) Asteroid, InH (IsSolid 
(IsPlanet Earth)) Earth) where

collide _ = the end of the dinos

instance Collide (InH (IsSolid (IsPlanet Earth)) Earth, InH (IsSolid 
Asteroid) Asteroid) where

collide _ = the end of the dinos

instance Collide Collision where
collide (Collision a) = collide a

--- ghci output

*Collide mapM_ putStrLn (map collide
[ mkCollision Asteroid Earth
, mkCollision Earth Asteroid
, mkCollision Jupiter Asteroid
, mkCollision Asteroid Jupiter
, mkCollision Asteroid Asteroid
])
the end of the dinos
the end of the dinos
an asteroid hit a planet
an asteroid hit a planet
generic collision
*Collide

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


Re: [Haskell-cafe] Newbie question about automatic memoization

2007-07-31 Thread Jules Bean

Bryan Burgers wrote:

On 7/30/07, peterv [EMAIL PROTECTED] wrote:

Does Haskell support any form of automatic memorization?

For example, does the function

iterate f x

which expands to

[x, f(x), f(f(x)), f(f(f(x))), …

gets slower and slower each iteration, or can it take advantage of the fact
that f is referentially transparent and hence can be memoized / cached?

Thanks,
Peter


For 'iterate' the answer does not really need to be memoized.


Or, another way of phrasing that answer is 'yes'. The definition of 
iteration does memoize - although normally one would say 'share' - the 
intermediate results.




I imagine the definition of 'iterate' looks something like this:

iterate f x = x : iterate f (f x)



Haskell doesn't automatically memoize. But you are entitled to assume 
that named values are 'shared' rather than calculated twice. For 
example, in the above expression x, being a named value, is shared 
between (a) the head of the list and (b) the parameter of the function 
f inside the recursive call to iterate.


Of course sharing x may not seem very interesting, on the outermost 
call, but notice that on the next call the new x is the old f x, and 
on the call after that the new x is f (f x) w.r.t the original x.


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


[Haskell-cafe] Newbie question about Haskell skills progress

2007-07-31 Thread peterv
Having only a couple of days of practice programming Haskell (but having
read lots of books and docs), I find myself writing very explicit low level
code using inner aux functions (accumulators and loops). Then I force
myself  to revise the code, replacing these aux functions with suitable
higher-order functions from the library. However, I would like to use these
higher order functions right away, without using low-level aux constructs,
which is most likely caused by my very long history of imperative
programming.

 

Is this the normal way of progressing in Haskell, or should I consider a
different approach?

 

Thanks,

Peter

 

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


RE: [Haskell-cafe] Newbie question about automatic memoization

2007-07-31 Thread peterv
Thanks! Is this is also the case when using let and where, or is this just
syntactic sugar?

-Original Message-
From: Jules Bean [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, July 31, 2007 5:09 PM
To: Bryan Burgers
Cc: peterv; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Newbie question about automatic memoization

Bryan Burgers wrote:
 On 7/30/07, peterv [EMAIL PROTECTED] wrote:
 Does Haskell support any form of automatic memorization?

 For example, does the function

 iterate f x

 which expands to

 [x, f(x), f(f(x)), f(f(f(x))), .

 gets slower and slower each iteration, or can it take advantage of the
fact
 that f is referentially transparent and hence can be memoized / cached?

 Thanks,
 Peter
 
 For 'iterate' the answer does not really need to be memoized.

Or, another way of phrasing that answer is 'yes'. The definition of 
iteration does memoize - although normally one would say 'share' - the 
intermediate results.

 
 I imagine the definition of 'iterate' looks something like this:
 
 iterate f x = x : iterate f (f x)
 

Haskell doesn't automatically memoize. But you are entitled to assume 
that named values are 'shared' rather than calculated twice. For 
example, in the above expression x, being a named value, is shared 
between (a) the head of the list and (b) the parameter of the function 
f inside the recursive call to iterate.

Of course sharing x may not seem very interesting, on the outermost 
call, but notice that on the next call the new x is the old f x, and 
on the call after that the new x is f (f x) w.r.t the original x.

Jules

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


Re: [Haskell-cafe] Newbie question about Haskell skills progress

2007-07-31 Thread Dougal Stanton
On 31/07/07, peterv [EMAIL PROTECTED] wrote:




 Having only a couple of days of practice programming Haskell (but having
 read lots of books and docs), I find myself writing very explicit low level
 code using inner aux functions (accumulators and loops). Then I force
 myself  to revise the code, replacing these aux functions with suitable
 higher-order functions from the library. However, I would like to use these
 higher order functions right away, without using low-level aux constructs,
 which is most likely caused by my very long history of imperative
 programming…

Seems sensible to me! It'll come with time, I'm sure.

I often find it useful to think about general abstractions and then
choose an approach from there:

- many-to-one - fold
- many-to-many - map
- one-to-many - unfold

And so on in a similar fashion. This might mean you do something
stupid (as witnessed by my most recent visit to Haskell Cafe, where I
said some very silly things [1] but also got some enormously
clever/silly pointers [2]). But it's all part of life's rich pattern,
and I can't think of a nicer place to make a fool of one's self than
in this community.

[1]: http://www.haskell.org/pipermail/haskell-cafe/2007-July/029274.html
[2]: http://www.haskell.org/pipermail/haskell-cafe/2007-July/029285.html

 Is this the normal way of progressing in Haskell, or should I consider a
 different approach?

There are probably some people here who were imbibing type theory and
lambda calculus with their mammy's milk... but for the rest of us,
it's just one small step at a time.

Cheers

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


  1   2   3   >