On Wed, Oct 5, 2011 at 8:45 AM, Alberto G. Corona 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 f
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
> --I tried to write such polymorphic function:
>
> expand (x,y,z) = (x,y,z)
> expand (x,y) = (x,y,1)
>
>
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 f
sdiyazg at sjtu.edu.cn wrote:
> >> generalizedFilterMap (\[x,y,z]-> if(x==1&&z==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
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 :
> sdiy...@sjtu.edu.cn writes:
>
>> T
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 tra
Quoting Andrew Coppin :
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
si
Quoting Felipe Almeida Lessa :
On Sun, Oct 2, 2011 at 4:26 PM, Edward Z. Yang 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.
{
> 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
Quoting 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 ove
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 "SIMPL
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 t
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 kno
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
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))
On Sun, Oct 2, 2011 at 2:17 PM, 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
On Sun, Oct 2, 2011 at 15:17, 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
On Sun, Oct 2, 2011 at 4:26 PM, Edward Z. Yang 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.
__
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)=>Exp
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,
Quoting 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.
cla
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
On Sun, Oct 2, 2011 at 8:45 AM, Du Xi 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.
>
> i
Quoting 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
mea
On Sun, Oct 2, 2011 at 6:04 AM, Du Xi 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-Caf
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 prepair
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) =
--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
28 matches
Mail list logo