Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-05 Thread Andrew Coppin

On 04/10/2011 07:08 AM, Dominique Devriese wrote:

All,

In case anyone is interested, I just want to point out an interesting
article about the relation between Haskell type classes and C++
(overloading + concepts):

http://sms.cs.chalmers.se/publications/papers/2008-WGP.pdf

Dominique


Thanks for that. A very interesting read...


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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-05 Thread Alberto G. Corona
If a newbie considers this as something natural, this is another reason for
syntactic sugaring of HList:

http://www.haskell.org/pipermail/haskell-cafe/2011-April/090986.html

2011/10/2 Du Xi sdiy...@sjtu.edu.cn

 --I tried to write such polymorphic function:

 expand (x,y,z) = (x,y,z)
 expand (x,y) = (x,y,1)

 --And it didn't compile. Then I added a type signature:

 expand::a-b
 expand (x,y,z) = (x,y,z)
 expand (x,y) = (x,y,1)

 --It still didn't compile. I think the reason is that the following is
 disallowed:

 f::a-b
 f x = x

 --Is it possible to get around this and write the expand function? Of
 course, x and y may be of different types



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Is it possible to represent such polymorphism?

2011-10-05 Thread Felipe Almeida Lessa
On Wed, Oct 5, 2011 at 8:45 AM, Alberto G. Corona agocor...@gmail.com wrote:
 If a newbie considers this as something natural, this is another reason for
 syntactic sugaring of HList:
 http://www.haskell.org/pipermail/haskell-cafe/2011-April/090986.html

Exposing newbies to HList seems like a recipe for disaster for me =).

-- 
Felipe.

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-04 Thread Dominique Devriese
All,

In case anyone is interested, I just want to point out an interesting
article about the relation between Haskell type classes and C++
(overloading + concepts):

http://sms.cs.chalmers.se/publications/papers/2008-WGP.pdf

Dominique


2011/10/3 Ketil Malde ke...@malde.org:
 sdiy...@sjtu.edu.cn writes:

 This has nothing to do with OOP or being imperative. It's just about types.

 Of course, it's not necessarily linked to OOP, but OO languages - to the
 extent they have types - tend towards ad-hoc polymorphism instead of
 parametric polymorphism.  There are different trade-offs, one is the
 lack of return-type overloading in C++.

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants

 ___
 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] Is it possible to represent such polymorphism?

2011-10-04 Thread oleg

sdiyazg at sjtu.edu.cn wrote:

  generalizedFilterMap (\[x,y,z]- if(x==1z==1)then [y*10] else  
  [0]) (3,1) [1,2,3,4,1,2,1,3,1,4,1,5,2]
 [0,0,0,0,20,0,30,0,40,0,0]

 Of course, I could have simply used [Int] , (Num a)=[a] or
 (Int,Int,Int), but I'm trying to write code as generic as possible.

As I understand, the point of generalizedFilterMap is to permit the
filter function to examine several elements of the list within the
current window (rather than just the current element). The step argument
determines the step of sliding the window. Further, you wish to make
the step argument default (setting it to 1 if not given).

First of all, if you are interested in stencil computations, there are
several good packages and even the whole DSLs:

  http://research.microsoft.com/en-us/um/people/simonpj/papers/ndp/index.htm
  http://arxiv.org/abs/1109.0777
  http://people.csail.mit.edu/yuantang/

Second, the given code is not as generic as possible. In the above
example, the filter function examines values within the window of size
3. That fact has to be specified twice: in the pattern \ [x,y,z] - ...
and as the number 3. Having to specify the same information twice is
always less than satisfactory: if we expand the pattern to
\ [x,y,z,u] - we have to remember to update the other argument to the
function.

There are many solutions to the problem, involving as much type
hacking as one may wish (some of the stencil packages above do track
the size of the stencil statically, in types). Perhaps one of the simplest
solution is the following


 generalizedFilterMap3 :: Int - ([a]-[a]) - [a] - [a]
 generalizedFilterMap3 step f = concatMap f . decimate step . tails

 -- pick every n-th
 decimate :: Int - [a] - [a]
 decimate 1 lst = lst
 decimate _ [] = []
 decimate n lst = head lst : decimate n (drop n lst)

 test1 = generalizedFilterMap3 1 f [1,2,3,4,1,2,1,3,1,4,1,5,2]
  where
  f (x:y:z:_) = if x==1z==1 then [y*10] else [0]
  f _ = []

Again there are many, many approaches to default arguments. Perhaps
the simplest, involving no typeclasses and no type computation is the
following

 data GMapArgs a = GMapDflt{step  :: Int,
gmapf :: [a] - [a]}

 dflt = GMapDflt{step = 1, gmapf = id}

 generalizedFilterMap dflt = generalizedFilterMap3 (step dflt) (gmapf dflt)

 test2 = generalizedFilterMap dflt{gmapf=f} [1,2,3,4,1,2,1,3,1,4,1,5,2]
  where
  f (x:y:z:_) = if x==1z==1 then [y*10] else [0]
  f _ = []

 test3 = generalizedFilterMap dflt{gmapf=f,step=2} [1,2,3,4,1,2,1,3,1,4,1,5,2]
  where
  f (x:y:z:_) = if x==1z==1 then [y*10] else [0]
  f _ = []

It requires no extensions. Record puns and other Record extensions
make the approach nicer.


 What I want is some thing like this in C++:

 float f(char x){ return 0.1f; }
 int f(double x){ return 1; }

One should point out the difficulties of comparing C++ with
Haskell. Haskell is designed to be higher-order, making it simple to
pass functions as arguments to other functions. Your code for generic
maps relies on that behavior. Try passing the overloaded C++ function
'f' defined above to some other function. That is, implement something
like the following
float g(??? f) { return f('x') + f(1.0); }
int main(void) {printf(%g,g(f)); return 0;}

One can certainly implement the above outline in C++, but it won't be
simple.


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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-03 Thread sdiyazg

Quoting Richard O'Keefe o...@cs.otago.ac.nz:



On 3/10/2011, at 7:15 AM, Du Xi wrote:


I guess this is what I want, thank you all. Although I still wonder  
 why something so simple in C++ is actually more verbose and   
requires less known features in Haskell...What was the design   
intent to disallow simple overloading?


It's not SIMPLE overloading you are asking for,
but AD HOC overloading, which may look simple, but really isn't.

Taking your C++ f() example, in what sense are the two functions   
_the same function_?






I understand that functions with the same name but different type  
signatures are not the same function, but are a family of  
functions,probably representing the same concept.


Also

identityInHaskell::a-a
identityInHaskell x = x
--I don't know if this is implemented as runtime polymorphism or  
compile-time polymorphism,

--but it is possible to implement this as compile-time polymorphism.

and

template typename T  T IdentityInCPP( T x ){ return x; }

are families of different functions.

I think the problem I have encountered can be broken down to 2 problems:

1. Haskell doesn't have a way to represent mapping from one type to  
another (consider metafunctions in C++), which is addressed by  
TypeFamilies.


2. Haskell disallows ad-hoc overloading. But I think implementing  
ad-hoc overloading itself should be no more complex than implementing  
type classes, perhaps it would tear a hole somewhere else?




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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-03 Thread Malcolm Wallace
 Although I still wonder why something so simple in C++ is actually more 
 verbose and requires less known features in Haskell...What was the design 
 intent to disallow simple overloading?

The simple C++ overloading you want to add to Haskell, is in fact rather 
semantically complex, and it leads to undecidability of the type system.  The 
inherent formal complexity here suggests that this form of overloading is 
highly unlikely to be the correct solution in practice to the problem you are 
trying to solve.  And even if it were a technically correct solution, it is 
likely to be unmaintainable and fragile to code changes.  There is a high 
probability that a more-formally-tractable solution exists, and that using it 
will improve your understanding of the problem at hand, and make your code more 
regular and robust to change.

Regards,
Malcolm

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-03 Thread sdiyazg

Quoting Felipe Almeida Lessa felipe.le...@gmail.com:


On Sun, Oct 2, 2011 at 4:26 PM, Edward Z. Yang ezy...@mit.edu wrote:

What are you actually trying to do?  This seems like a rather
unusual function.


If you're new to the language, most likely you're doing something
wrong if you need this kind of function.  =)

--
Felipe.



{-# LANGUAGE TypeFamilies,FlexibleInstances #-}

module RicherListOp ( generalizedFilter,generalizedMap,generalizedFilterMap )
where
import Data.List

generalizedFilter pred = impl.expand3 where
impl (dL,dR,step) = generalizedFilterMap tf (dL+dR+1,step) where
tf s = if pred s then [s !! dL] else []

generalizedMap tf = generalizedFilterMap $ \x-[tf x]

generalizedFilterMap tf ns ls = impl {-$ expand2-} ns where
impl (len,step) = f ls where
		f xs | length xs =len = (tf $ genericTake len xs) ++ (f $  
genericDrop step xs)

f _ = []

class Expand3 t where
type Result3 t
expand3 :: t-Result3 t

instance (Integral a,Integral b)=Expand3 (a,b) where
type Result3 (a,b) = (a,b,Int)
expand3 (l,r) = (l,r,1)

instance (Integral a,Integral b,Integral c)=Expand3 (a,b,c) where
type Result3 (a,b,c) = (a,b,c)
expand3 = id

--instance (Integral a)=Expand3 a where
--  type Result3 a = (a,a,a)
--  expand3 r = (0,r,1)

--class Expand2 t where
--  type Result2 t
--  expand2 :: t-Result2 t

--instance (Integral a)=Expand2 (a,a) where
--  type Result2 (a,a) = (a,a)
--  expand2 = id

--instance (Integral a)=Expand2 a where
--  type Result2 a = (a,a)
--  expand2 a = (a,1)

examples:
generalizedFilterMap (\[x,y,z]- if(x==1z==1)then [y*10] else  
[0]) (3,1) [1,2,3,4,1,2,1,3,1,4,1,5,2]

[0,0,0,0,20,0,30,0,40,0,0]
it :: [Integer]

generalizedFilter (\[x,y,z] - x==1z==1) (1,1) [1,2,3,4,1,2,1,3,1,4,1,5,2]

[2,3,4]
it :: [Integer]

The code commented out is what I still can't get working. (I'm no  
longer trying to finish them. They are included just to illustrate my  
idea). Of course, I could have simply used [Int] , (Num a)=[a] or  
(Int,Int,Int), but I'm trying to write code as generic as possible.



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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-03 Thread sdiyazg

Quoting Andrew Coppin andrewcop...@btinternet.com:


On 02/10/2011 07:15 PM, Du Xi wrote:

In C++, the code is inferred from the types. (I.e., if a function is
overloaded, the correct implementation is selected depending on the
types of the arguments.)

In Haskell, the types are inferred from the code. (Which is why type
signatures are optional.)

Really, it's just approaching the same problem from a different direction.

Also, as others have said, you're probably just approaching the problem
from the wrong angle. You don't design an object-oriented program the
same way you'd design a procedural program; if you do, you end up with a
horrible design. Similarly, you don't design a functional program the
same way you would design an object-oriented one. It takes time (and
experience) to figure out how to approach FP - or any other radically
different paradigm, I suppose...

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




Quoting Brandon Allbery allber...@gmail.com:


On Sun, Oct 2, 2011 at 15:17, sdiy...@sjtu.edu.cn wrote:

Not for your meaning of clean.

C++ is an object-oriented programming language; given a method call, it
tries really hard to shoehorn the arguments to the call into some declared
method somewhere along the inheritance chain.  Haskell is a functional
programming language; it is strongly typed, and typeclasses are a mechanism
to allow that typing to be weakened in a strictly controlled fashion.  In
some sense, it's not *supposed* to be convenient, because the whole point is
you're not supposed to throw arbitrarily-typed expressions at arbitrary
functions.  Instead, a properly designed program is characterized by its
types; if the types are well designed for the problem being solved, they
very nearly write the program by themselves.

This doesn't mean that use of typeclasses / ad-hoc polymorphism is
automatically a sign of a poor design, but it *does* mean you should think
about what you're trying to do whenever you find yourself considering them.

Nor does it mean that C++ is in some sense wrong; it means the languages
are fundamentally different, and the appropriate design of a program is
therefore also usually different between the two.

--
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms



This has nothing to do with OOP or being imperative.It's just about types.


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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-03 Thread Ketil Malde
sdiy...@sjtu.edu.cn writes:

 This has nothing to do with OOP or being imperative. It's just about types.

Of course, it's not necessarily linked to OOP, but OO languages - to the
extent they have types - tend towards ad-hoc polymorphism instead of
parametric polymorphism.  There are different trade-offs, one is the
lack of return-type overloading in C++.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


[Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Du Xi

--I tried to write such polymorphic function:

expand (x,y,z) = (x,y,z)
expand (x,y) = (x,y,1)

--And it didn't compile. Then I added a type signature:

expand::a-b
expand (x,y,z) = (x,y,z)
expand (x,y) = (x,y,1)

--It still didn't compile. I think the reason is that the following is  
disallowed:


f::a-b
f x = x

--Is it possible to get around this and write the expand function?  
Of course, x and y may be of different types




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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Yves Parès
2-tuple and 3-tuple *are not the same type*.
So to do this you must use typeclasses.
Plus you have to deal with the type parameters

class To3Tuple a where
   expand :: a - (Int, Int, Int)

instance To3Tuple (Int, Int, Int) where
   expand = id

instance To3Tuple (Int, Int) where
   expand (x,y) = (x,y,1)


Here I had to force my tuples to be tuples of integers.
It's more complicated if you want polymorphism.


2011/10/2 Du Xi sdiy...@sjtu.edu.cn

 --I tried to write such polymorphic function:

 expand (x,y,z) = (x,y,z)
 expand (x,y) = (x,y,1)

 --And it didn't compile. Then I added a type signature:

 expand::a-b
 expand (x,y,z) = (x,y,z)
 expand (x,y) = (x,y,1)

 --It still didn't compile. I think the reason is that the following is
 disallowed:

 f::a-b
 f x = x

 --Is it possible to get around this and write the expand function? Of
 course, x and y may be of different types



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Is it possible to represent such polymorphism?

2011-10-02 Thread Andrew Coppin

On 02/10/2011 02:04 PM, Du Xi wrote:


--It still didn't compile. I think the reason is that the following is
disallowed:

f::a-b
f x = x


The type a - b doesn't mean what you think it does.

It does /not/ mean that f is allowed to return any type it wants to. It 
means that f must be prepaired to return any type that /the caller/ 
wants it to. So, given ANY POSSIBLE INPUT, the function must be able to 
construct a value of ANY POSSIBLE TYPE.


This is, of course, impossible. The only way you can implement a 
function with this type signature is to cheat.




Also, you can't just take x, which has type a, and then pretend that it 
has type b instead. Haskell doesn't work like that. Your type signature 
says that the result type can be different than the input type, but your 
function definition forces the result to always be /the same/ type as 
the input. Hence, it is rejected.




That aside, the fundamental problem here is that each tuple type is a 
different, completely unrelated type, as far as the type system is 
concerned. (x,y) and (x,y,z) might look similar to you, but to the type 
system they're as similar as, say, Either x y and StateT x y z.


In Haskell, the only way to get a function to work for several unrelated 
types (but not /every/ possible type) is to use classes. Depending on 
exactly what you're trying to do, you might be better using lists, or 
perhaps some custom data type. It depends what you want to do.


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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread David Barbour
On Sun, Oct 2, 2011 at 6:04 AM, Du Xi sdiy...@sjtu.edu.cn wrote:

 --Is it possible to get around this and write the expand function? Of
 course, x and y may be of different types


Not as written, but try HList.
http://hackage.haskell.org/package/HList
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Du Xi

Quoting Andrew Coppin andrewcop...@btinternet.com:


On 02/10/2011 02:04 PM, Du Xi wrote:


--It still didn't compile. I think the reason is that the following is
disallowed:

f::a-b
f x = x


The type a - b doesn't mean what you think it does.

It does /not/ mean that f is allowed to return any type it wants to. It
means that f must be prepaired to return any type that /the caller/
wants it to. So, given ANY POSSIBLE INPUT, the function must be able to
construct a value of ANY POSSIBLE TYPE.

This is, of course, impossible. The only way you can implement a
function with this type signature is to cheat.



Also, you can't just take x, which has type a, and then pretend that it
has type b instead. Haskell doesn't work like that. Your type signature
says that the result type can be different than the input type, but
your function definition forces the result to always be /the same/ type
as the input. Hence, it is rejected.



That aside, the fundamental problem here is that each tuple type is a
different, completely unrelated type, as far as the type system is
concerned. (x,y) and (x,y,z) might look similar to you, but to the type
system they're as similar as, say, Either x y and StateT x y z.

In Haskell, the only way to get a function to work for several
unrelated types (but not /every/ possible type) is to use classes.
Depending on exactly what you're trying to do, you might be better
using lists, or perhaps some custom data type. It depends what you want
to do.

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



Then again , in typeclass definition how can I express the type a-b  
where a is the type parameter of the class and b is a type deduced  
from the rules defined in each instance of the class, which varies on  
a per-instance basis? e.g.


instance ExampleClass a where
f :: a-SomeTypeWhichIsDifferentInEachInstance

What I want is some thing like this in C++:

float f(char x){ return 0.1f; }
int f(double x){ return 1; }




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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread David Barbour
On Sun, Oct 2, 2011 at 8:45 AM, Du Xi sdiy...@sjtu.edu.cn wrote:

 Then again , in typeclass definition how can I express the type a-b
 where a is the type parameter of the class and b is a type deduced from
 the rules defined in each instance of the class, which varies on a
 per-instance basis? e.g.

 instance ExampleClass a where
f :: a-**SomeTypeWhichIsDifferentInEach**Instance

 What I want is some thing like this in C++:

 float f(char x){ return 0.1f; }
 int f(double x){ return 1; }


Use TypeFamilies.


{-# LANGUAGE TypeFamilies #}
...
type family FType a :: *
type instance FType Char = Float
type instance FType Double = Int

class ExampleClass a where
  f :: a - FType a
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Victor Gorokgov

02.10.2011 19:55, David Barbour пишет:

Use TypeFamilies.


{-# LANGUAGE TypeFamilies #}
...
type family FType a :: *
type instance FType Char = Float
type instance FType Double = Int

class ExampleClass a where
f :: a - FType a



Better to include type in class.

class ExampleClass a where
type FType a
f :: a - FType a

instance ExampleClass Char where
type FType Char = Float
f char = ...

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Du Xi

Quoting Victor Gorokgov m...@rkit.pp.ru:


02.10.2011 19:55, David Barbour пишет:

Use TypeFamilies.


{-# LANGUAGE TypeFamilies #}
...
type family FType a :: *
type instance FType Char = Float
type instance FType Double = Int

class ExampleClass a where
f :: a - FType a



Better to include type in class.

class ExampleClass a where
type FType a
f :: a - FType a

instance ExampleClass Char where
type FType Char = Float
f char = ...

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


I guess this is what I want, thank you all. Although I still wonder  
why something so simple in C++ is actually more verbose and requires  
less known features in Haskell...What was the design intent to  
disallow simple overloading?



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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread sdiyazg

Finally I got what I meant:


class ExpandTuple t where
type Result t
expand :: t-Result t

instance (Integral a)=ExpandTuple (a,a) where
type Result (a,a) = (a,a,a)
expand (x,y) = (x,y,1)

instance (Integral a)=ExpandTuple (a,a,a) where
type Result (a,a,a) = (a,a,a)
expand = id

But it's so verbose (even more so than similar C++ template code I  
guess), introduces an additional name (the typeclass) into the current  
scope, and requires 2 extensions: TypeFamilies and  
FlexibleInstances.Is there a cleaner way to do this?



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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Edward Z. Yang
What are you actually trying to do?  This seems like a rather
unusual function.

Edward

Excerpts from sdiyazg's message of Sun Oct 02 15:17:07 -0400 2011:
 Finally I got what I meant:
 
 
 class ExpandTuple t where
 type Result t
 expand :: t-Result t
 
 instance (Integral a)=ExpandTuple (a,a) where
 type Result (a,a) = (a,a,a)
 expand (x,y) = (x,y,1)
 
 instance (Integral a)=ExpandTuple (a,a,a) where
 type Result (a,a,a) = (a,a,a)
 expand = id
 
 But it's so verbose (even more so than similar C++ template code I  
 guess), introduces an additional name (the typeclass) into the current  
 scope, and requires 2 extensions: TypeFamilies and  
 FlexibleInstances.Is there a cleaner way to do this?
 

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Felipe Almeida Lessa
On Sun, Oct 2, 2011 at 4:26 PM, Edward Z. Yang ezy...@mit.edu wrote:
 What are you actually trying to do?  This seems like a rather
 unusual function.

If you're new to the language, most likely you're doing something
wrong if you need this kind of function.  =)

-- 
Felipe.

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Brandon Allbery
On Sun, Oct 2, 2011 at 15:17, sdiy...@sjtu.edu.cn wrote:

 But it's so verbose (even more so than similar C++ template code I guess),
 introduces an additional name (the typeclass) into the current scope, and
 requires 2 extensions: TypeFamilies and FlexibleInstances.Is there a cleaner
 way to do this?


Not for your meaning of clean.

C++ is an object-oriented programming language; given a method call, it
tries really hard to shoehorn the arguments to the call into some declared
method somewhere along the inheritance chain.  Haskell is a functional
programming language; it is strongly typed, and typeclasses are a mechanism
to allow that typing to be weakened in a strictly controlled fashion.  In
some sense, it's not *supposed* to be convenient, because the whole point is
you're not supposed to throw arbitrarily-typed expressions at arbitrary
functions.  Instead, a properly designed program is characterized by its
types; if the types are well designed for the problem being solved, they
very nearly write the program by themselves.

This doesn't mean that use of typeclasses / ad-hoc polymorphism is
automatically a sign of a poor design, but it *does* mean you should think
about what you're trying to do whenever you find yourself considering them.

Nor does it mean that C++ is in some sense wrong; it means the languages
are fundamentally different, and the appropriate design of a program is
therefore also usually different between the two.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Antoine Latter
On Sun, Oct 2, 2011 at 2:17 PM,  sdiy...@sjtu.edu.cn wrote:
 Finally I got what I meant:


 class ExpandTuple t where
        type Result t
        expand :: t-Result t

 instance (Integral a)=ExpandTuple (a,a) where
        type Result (a,a) = (a,a,a)
        expand (x,y) = (x,y,1)

 instance (Integral a)=ExpandTuple (a,a,a) where
        type Result (a,a,a) = (a,a,a)
        expand = id


If I were writing this sort of function, I would simply write:

 expand (x, y) = (x, y, 1)

and I would leave it at that. Since your 'expand' doesn't do anything
the three-tuples, I don't see why I would want to call the function
with a three-tuple argument.

But I don't know your full use case.

Antoine

 But it's so verbose (even more so than similar C++ template code I guess),
 introduces an additional name (the typeclass) into the current scope, and
 requires 2 extensions: TypeFamilies and FlexibleInstances.Is there a cleaner
 way to do this?


 ___
 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] Is it possible to represent such polymorphism?

2011-10-02 Thread Tom Murphy
Assuming that z :: Int, you can declare an algebraic datatype
data TwoOrThree a b = Three (a, b, Int)
| Two (a, b)
   deriving(Show, Eq) -- so you can experiment

And then define expand as

expand :: TwoOrThree a b - (a, b, Int)
expand (Three tuple) = tuple
expand (Two (a, b)) = (a, b, 1)

Tom (amindfv)
On Oct 2, 2011 6:04 AM, Du Xi sdiy...@sjtu.edu.cn wrote:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Andrew Coppin
On 02/10/2011 07:15 PM, Du Xi wrote:

 I guess this is what I want, thank you all. Although I still wonder why 
 something so simple in C++ is actually more verbose and requires less 
 known features in Haskell...What was the design intent to disallow 
 simple overloading?

In C++, the code is inferred from the types. (I.e., if a function is
overloaded, the correct implementation is selected depending on the
types of the arguments.)

In Haskell, the types are inferred from the code. (Which is why type
signatures are optional.)

Really, it's just approaching the same problem from a different direction.

Also, as others have said, you're probably just approaching the problem
from the wrong angle. You don't design an object-oriented program the
same way you'd design a procedural program; if you do, you end up with a
horrible design. Similarly, you don't design a functional program the
same way you would design an object-oriented one. It takes time (and
experience) to figure out how to approach FP - or any other radically
different paradigm, I suppose...

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Scott Turner
On 2011-10-02 14:15, Du Xi wrote:
 I guess this is what I want, thank you all. Although I still wonder why
 something so simple in C++ is actually more verbose and requires less
 known features in Haskell...What was the design intent to disallow
 simple overloading?

Simple overloading is known as ad-hoc polymorphism, while Haskell's
type system is based on parametric polymorphism.  As Wikipedia says,
Parametric polymorphism is a way to make a language more expressive,
while still maintaining full static type-safety.

For example, functional programming gets a lot of power out of passing
functions as arguments. Compare what this gives you in C++ versus
Haskell.  In C++ an overloaded function has multiple types, and when a
function appears as an argument one of those types is selected.  In
Haskell, a polymorphic function can be passed as an argument, and it
still can be used polymorphically within the function that receives it.

When each name in the program has just one type, as in Haskell, type
inference can be much more effective. Type declarations are not
required. Most of the type declarations in my own Haskell code are there
either for documentation, or to ensure that the compiler will catch type
errors within a function definition.

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-02 Thread Yves Parès
Yes, do you have a Python background?
Because I've often see misunderstanding about the utility of tuples with
persons who were used to Python, because Python tutorials usually induce *
BAD* practices in this respect (considering tuples and lists equivalent, for
instance).
Add to this the dynamic typing which allows you to have whatever type you
want in your tuples' cells, and when coming to Haskell, it's somewhat uneasy
to see that there is not a tuple type, but *an infinity*.

My advice (which is only my opinion) is that you should restrict you use of
tuples. For instance do not use them to make vectors (is it what you were
trying to do? Because it looked like you were trying to handle 2D and 3D
vectors), do something more type-explicit, by making a new datatype Vector,
or 2 new datatypes Vector2 and Vector3.
You shouldn't use tuples as a way to structure data (i.e. in replacement of
real types), only for convenience when a function has to return several
values.


2011/10/2 Felipe Almeida Lessa felipe.le...@gmail.com

 On Sun, Oct 2, 2011 at 4:26 PM, Edward Z. Yang ezy...@mit.edu wrote:
  What are you actually trying to do?  This seems like a rather
  unusual function.

 If you're new to the language, most likely you're doing something
 wrong if you need this kind of function.  =)

 --
 Felipe.

 ___
 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] Is it possible to represent such polymorphism?

2011-10-02 Thread Richard O'Keefe

On 3/10/2011, at 7:15 AM, Du Xi wrote:
 
 I guess this is what I want, thank you all. Although I still wonder why 
 something so simple in C++ is actually more verbose and requires less known 
 features in Haskell...What was the design intent to disallow simple 
 overloading?

It's not SIMPLE overloading you are asking for,
but AD HOC overloading, which may look simple, but really isn't.

Taking your C++ f() example, in what sense are the two functions _the same 
function_?



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