Re: [Haskell-cafe] Wondering if this could be done.

2010-12-04 Thread Henning Thielemann
 On 22 November 2010 07:48, Magicloud Magiclouds
 magicloud.magiclo...@gmail.com mailto:magicloud.magiclo...@gmail.com
 wrote:
 
 Hi,
  For example, I have a data A defined. Then I want to add (+) and (-)
 operators to it, as a sugar (compared to addA/minusA). But * or other
 stuff defined in class Num is meanless to A. So I just do:
 (+) :: A - A - A
 (+) a b =
  A (elem1 a + elem1 b) (elem2 a + elem2 b) -- I got errors here, for
 the (+) is ambiguous.
 
  So, just wondering, does this way work in Haskell?

(*) and (+) are in separate type classes in Numeric-Prelude.

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


Re: [Haskell-cafe] Wondering if this could be done.

2010-12-04 Thread Sebastian Fischer
On Mon, 2010-11-22 at 14:48 +0800, Magicloud Magiclouds wrote:
 (+) :: A - A - A
 (+) a b =
   A (elem1 a + elem1 b) (elem2 a + elem2 b) -- I got errors here, for
 the (+) is ambiguous. 

That's because (+) is implicitly imported from the Prelude. If you

import Prelude hiding ((+))

the error disappears.

Sebastian


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


Re: [Haskell-cafe] Wondering if this could be done.

2010-11-22 Thread Miguel Mitrofanov

 Sure, you can define your own type class like that:

import Prelude hiding ((+), (-)) -- usual (+) and (-) shouldn't be here...
import qualified Prelude as P -- but they still are accessible with a prefix
class Group a where
   (+) :: a - a - a
   (-) :: a - a - a
instance Group Integer where
   (+) = (P.+)
   (-) = (P.-)
instance Group A where
   (+) a b = A (elem1 a + elem1 b) (elem2 a + elem2 b) -- works for elem1 and 
elem2 being of class Group - say, Integer's
   (-) a b = ...

22.11.2010 9:48, Magicloud Magiclouds пишет:

Hi,
   For example, I have a data A defined. Then I want to add (+) and (-)
operators to it, as a sugar (compared to addA/minusA). But * or other
stuff defined in class Num is meanless to A. So I just do:
(+) :: A -  A -  A
(+) a b =
   A (elem1 a + elem1 b) (elem2 a + elem2 b) -- I got errors here, for
the (+) is ambiguous.

   So, just wondering, does this way work in Haskell?

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


Re: [Haskell-cafe] Wondering if this could be done.

2010-11-22 Thread Ling Yang
Haskell does not play as well with overloading as one would do it in C++;
every
name used must be fully qualified.  Indeed, if we try something like

Indeed, if we try something like

data A = A Int deriving (Show, Eq)

test = A 3 unA (A i) = i

class Group a where (+) :: a - a - a

instance Group A where (+) x y = A $ unA x + unA y

we will get

Ambiguous occurrence `+'

It could refer to either `Main.+', defined at .hs:7:1
or `Prelude.+', imported from Prelude

Failed, modules loaded: none.

Haskell has its own brand of 'overloading': type classes. Every (+) sign
used
assumes that the operands are of the Num typeclass in particular. In order
to
define (+) on something else you will need to instance the Num typeclass
over
your A type.

I am not sure what you mean by the stuff defined in class Num is meanless
to
A. Strictly speaking nothing needs to be defined in a typeclass declaration
other than the required type signatures.

To instance the Num typeclass with A, though, assuming that A constructors
take
something that works with Num, you would do something similar to what Miguel
posted:

data A = A Int deriving (Show, Eq)

test = A 3 unA (A i) = i

instance Num A where (+) x y = A $ (unA x) + (unA y) (-) x y = A $ (unA x) -
(unA y) (*) x y = A $ (unA x) * (unA y) abs x = A $ (unA $ abs x) signum y =
A
$ (unA $ signum y) fromInteger i = A (fromInteger i)

Look at fromInteger, which must take Integer as as argument. That may be
inconvenient for you. The Awesome Prelude, referenced in Chris's post, is a
way
of defining less specific version of basic types like Bool so that you have
more choices in defining things like fromInteger in the Num typeclass (which
must take an Integer; it is 'sad' if that Integer refers to a grounded,
specific type).

Still, if not every one of the Num operations make sense for your A type,
you
can leave them blank and get a warning.

On Sun, Nov 21, 2010 at 10:48 PM, Magicloud Magiclouds 
magicloud.magiclo...@gmail.com wrote:

 Hi,
  For example, I have a data A defined. Then I want to add (+) and (-)
 operators to it, as a sugar (compared to addA/minusA). But * or other
 stuff defined in class Num is meanless to A. So I just do:
 (+) :: A - A - A
 (+) a b =
  A (elem1 a + elem1 b) (elem2 a + elem2 b) -- I got errors here, for
 the (+) is ambiguous.

  So, just wondering, does this way work in Haskell?
 --
 竹密岂妨流水过
 山高哪阻野云飞
 ___
 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] Wondering if this could be done.

2010-11-21 Thread Magicloud Magiclouds
Hi,
  For example, I have a data A defined. Then I want to add (+) and (-)
operators to it, as a sugar (compared to addA/minusA). But * or other
stuff defined in class Num is meanless to A. So I just do:
(+) :: A - A - A
(+) a b =
  A (elem1 a + elem1 b) (elem2 a + elem2 b) -- I got errors here, for
the (+) is ambiguous.

  So, just wondering, does this way work in Haskell?
-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wondering if this could be done.

2010-11-21 Thread Gregory Crosswhite

On 11/21/10 10:48 PM, Magicloud Magiclouds wrote:

Hi,
   For example, I have a data A defined. Then I want to add (+) and (-)
operators to it, as a sugar (compared to addA/minusA). But * or other
stuff defined in class Num is meanless to A. So I just do:
(+) :: A -  A -  A
(+) a b =
   A (elem1 a + elem1 b) (elem2 a + elem2 b) -- I got errors here, for
the (+) is ambiguous.

   So, just wondering, does this way work in Haskell?


One solution to this problem is to use slightly modified operators, such 
as .+. and .-., or anything else that crosses your fancy and is 
accepted by the compiler.


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


Re: [Haskell-cafe] Wondering if this could be done.

2010-11-21 Thread Christopher Done
Check out the awesome prelude, used to define ESDLs:
http://tom.lokhorst.eu/2010/02/awesomeprelude-presentation-video

On 22 November 2010 07:48, Magicloud Magiclouds 
magicloud.magiclo...@gmail.com wrote:

 Hi,
  For example, I have a data A defined. Then I want to add (+) and (-)
 operators to it, as a sugar (compared to addA/minusA). But * or other
 stuff defined in class Num is meanless to A. So I just do:
 (+) :: A - A - A
 (+) a b =
  A (elem1 a + elem1 b) (elem2 a + elem2 b) -- I got errors here, for
 the (+) is ambiguous.

  So, just wondering, does this way work in Haskell?
 --
 竹密岂妨流水过
 山高哪阻野云飞
 ___
 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