Re: [Haskell-cafe] Overloading

2013-03-12 Thread Miguel Mitrofanov


12.03.2013, 02:53, Richard A. O'Keefe o...@cs.otago.ac.nz:
 On 12/03/2013, at 10:00 AM, MigMit wrote:

  On Mar 12, 2013, at 12:44 AM, Richard A. O'Keefe o...@cs.otago.ac.nz 
 wrote:
  Prelude :type (+)
  (+) :: Num a = a - a - a

  The predefined (+) in Haskell requires its arguments and its result
  to be precisely the same type.

  I think you had better justify the claim that Date+Period - Date and
  Date+Period - Period are possible at the same time by showing us
  actual code.
  Ehm...

  import Prelude hiding (Num)
  class SumDP a where (+) :: Date - Period - a
  instance SumDP Date where date + period = your_implementation_here
  instance SumDP Period where date + period = and_here

 Notice the difference?
 I said that THE PREDEFINED (+) in Haskell requires its arguments
 and its result to be precisely the same type.

 This example is not the predefined (+); it's another variable
 entirely that happens to have the same short name and cannot
 also add integers.

So? You've said:

 I think you had better justify the claim that Date+Period - Date and
 Date+Period - Period are possible at the same time by showing us
 actual code.

You didn't say THIS (+) should be the predefined one. And, since you were 
replying to what Carlos said, and he didn't say it either, my code is still a 
valid example.

Of course, you can refine your request so that it would mention the 
predefined (+), but that would be off-topic here.

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Carlos Camarao
On 12/03/2013, at 3:15 AM, Carlos Camarao wrote:

 Hi,

 I just started playing around a bit with Haskell, so sorry in
 advance for very basic (and maybe stupid) questions. Coming from
 the C++ world one thing I would like to do is overloading
 operators. For example I want to write (Date 6 6 1973) + (Period 2
 Months) for some self defined types Date and Period. Another
 example would be (Period 1 Years) + (Period 3 Months).

 Just defining the operator (+) does not work because it collides
 with Prelude.+. I assume using fully qualified names would work,
 but that is not what I want.

 Hi. To define (+) as an overloaded operator in Haskell, you have to
define
 and use a type class.

 Stop right there.  Overloading in the C++ sense is ad hoc
 polymorphism where the signatures of the various definitions need
 not resemble each other in any way.  Haskell just plain does not
 have anything like that.  (+) in Haskell is *not* overloaded; it has
 several implementations and allows you to define as many more as you
 want.  But they all conform to the *SAME* interface.  This is much
 more like OO inheritance.

Sorry, I think my sentence:
To define (+) as an overloaded operator in Haskell,
  you have to define and use a type class.
is not quite correct.  I meant that to define any operator in Haskell you
have to
have a type class defined with that operator as member.

Then, if there is already a type class defined, a programmer can
either use it (if that is suitable/adequate) or hide it and define
another one. Sorry, that's what I meant.

 In particular, C++ will let you define versions of + where the
 arguments are of two different types and the result is a third.  You
 cannot provide such an implementation for Haskell's predefined (+).

Yes, but the requirement of using the predefined (+) is an extra
requirement (I would call (+) in Haskell not a predefined operator,
but an operator whose type is defined in a class (Num) which is in the
Prelude). A Haskell programmer can still define versions of (+) where
the arguments are of two different types and the result is a third
(he cannot though use the two type classes, and thus neither instances
 of these two type classes, in a program).

The suitability/adequacy of the type defined in a class means that the
type of all names/operators in an instance of the class must be an
instance-type of the type specified in the class.

And unsuitability/inadequacy requires the definition and use of
another type class (sorry to repeat that, just reinforcing).

 Furthermore, Haskell supports a more powerful form of overloading than
 (any other language I know, including) C++: context-dependent
 overloading. This means that the type of an expression (f e), and thus
 of f, can be determined at compile-time (inferred) based on the
 context where (f e) occurs, not only on the type of the
 argument (e) of the function's call.

 Ada has had this since Ada 81.  The design goal that forced it was
 the wish to allow the same identifier to be used as an enumeral in
 more than one enumerated type, so that you could do
type Colour is (Red, Green, Blue);
type Fruit_State is (Green, Ripe, Rotten);
X : Colour := Green;
Y : Fruit_State := Green;

 and in particular, since character literals like 'X' are allowed as
 enumerals in Ada, they wished to be able to write
A: EBCDIC_Character := 'X';
B: ASCII_Character  := 'X';
 and have A and B be different bytes.  The difference is that Ada
 *does* do this sort of thing using overload resolution and Haskell
 *doesn't*.

Ok. I will have a look at Ada's overloading mechanism. Thanks! I am
trying to emphasize the constrained *polymorphism* that is possible in
Haskell, which allows overloading resolution not to be required in an
use of an operator or constant. I believe that this is a significant
new contribution of the language. (I think Green and 'X' are not
polymorphic, and any use of them required thus that overloading be
resolved).

 For example, you _could_ in principle use (d+p==d) and (d+p==p),
 with d::Date, p::Period, and instances of (+) with types
 Date-Period-Date and Date-Period-Period, if you wish…
 Prelude :type (+)
 (+) :: Num a = a - a - a
 The predefined (+) in Haskell requires its arguments and its result
 to be precisely the same type.

 I think you had better justify the claim that Date+Period - Date and
 Date+Period - Period are possible at the same time by showing us
 actual code.

I think I have shown it (see previous message): as Miguel Mitrofanov,
hiding and redefining Num.

Kind regards,

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Brandon Allbery
On Tue, Mar 12, 2013 at 1:52 PM, Carlos Camarao carlos.cama...@gmail.comwrote:

 Sorry, I think my sentence:
 To define (+) as an overloaded operator in Haskell,
   you have to define and use a type class.
 is not quite correct.  I meant that to define any operator in Haskell you
 have to
 have a type class defined with that operator as member.


What? An operator is just an infix function, taken from the set of symbols.
Any function can be an operator (and is, via `func` syntax). No typeclass
is required to define a random operator.

What did you really mean to say there?

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Carlos Camarao
On Tue, Mar 12, 2013 at 3:21 PM, Brandon Allbery allber...@gmail.comwrote:

 On Tue, Mar 12, 2013 at 1:52 PM, Carlos Camarao 
 carlos.cama...@gmail.comwrote:

 Sorry, I think my sentence:
 To define (+) as an overloaded operator in Haskell,
   you have to define and use a type class.
 is not quite correct.  I meant that to define any operator in Haskell you
 have to
 have a type class defined with that operator as member.


 What? An operator is just an infix function, taken from the set of
 symbols. Any function can be an operator (and is, via `func` syntax). No
 typeclass is required to define a random operator.

 What did you really mean to say there?


Sorry, I meant: To define any _overloaded_ name or operator (i.e. any
name/operator that can be overloaded) in Haskell you have to have a type
class defined with that name/operator as member.

Cheers,

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Richard A. O'Keefe
Carlos Camarao wrote:

 Sorry, I think my sentence: 
To define (+) as an overloaded operator in Haskell, 
  you have to define and use a type class. 
is not quite correct.  I meant that to define any operator in Haskell you have 
to
 have a type class defined with that operator as member. 

No.  Operators and type classes are entirely orthogonal in Haskell.
For example, the list concatenation operator (++) is not defined in
any type class.  It could be.  Either the `mplus` of
MonadPlus or the `mappend` of Monoid would make sense.  But it
happens not to be.

 Yes, but the requirement of using the predefined (+) is an extra
 requirement (I would call (+) in Haskell not a predefined operator,
 but an operator whose type is defined in a class (Num) which is in the
 Prelude). A Haskell programmer can still define versions of (+) where
 the arguments are of two different types and the result is a third
 (he cannot though use the two type classes, and thus neither instances
 of these two type classes, in a program).

I wish we could argue over semantics instead of vocabulary.
By calling the (+) of Num predefined I meant nothing other than
it is _defined_ in the Haskell report before (_pre_) you or I add
any code of our own.  We agree on the facts.

I don't call it an extra requirement.  The original context was
very clearly that in C++ where you have int+int, int+double,
double+int, double+double, char*+int, int+char* and so on all
predefined, you can *also* add your own date+period *without*
hiding the predefined versions.  And _that_ is overloading.  If the
question is whether Haskell can do overloading, _that_ is what has
to be achieved:  you can add a *new* interface date+period *without*
hiding the ones that were already defined before you started coding.

The interesting challenge here is that we should have

Date   + Period - Date  Date   - Period - Date
Period + Date   - Date  Period - Date   - ILLEGAL
Period + Period - DeriodPeriod - Period - Period
Date   + Date   - ILLEGAL   Date   - Date   - Date

and _also_ (remember we are trying to beat C++ here) Int +/- Int - Int.

I suspect that this can be done using type-level programming (so that
Date + Date and Period - Date _begin_ to type check but then violate
a type constraint) but that's where my Haskell skills are most risible.



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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread MigMit
On Mar 13, 2013, at 12:54 AM, Richard A. O'Keefe o...@cs.otago.ac.nz wrote:
 The interesting challenge here is that we should have
 
Date   + Period - Date  Date   - Period - Date
Period + Date   - Date  Period - Date   - ILLEGAL
Period + Period - DeriodPeriod - Period - Period
Date   + Date   - ILLEGAL   Date   - Date   - Date
 
 and _also_ (remember we are trying to beat C++ here) Int +/- Int - Int.

Well, an obvious suggestion would be to use MultiParamTypeClasses and 
TypeFamilies:

{- LANGUAGE MultiParamTypeClasses, TypeFamilies -}
module Date where
import Prelude hiding (Num, (+))
data Date = Date
data Period = Period
class Plus a b where
type PlusResult a b
(+) :: a - b - PlusResult a b
instance Plus Date Period where
type PlusResult Date Period = Date
Date + Period = Date
instance Plus Period Date where
type PlusResult Period Date = Date
Period + Date = Date
instance Plus Period Period where
type PlusResult Period Period = Period
Period + Period = Period

But I suppose you've been thinking about Haskell98. That, I'm afraid, doesn't 
seem possible.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-12 Thread David Thomas
If you add NoImplicitPrelude, I think you should also be able to do:

import Prelude hiding (Num)
import qualified Prelude (Num)

instance Num a = Plus a a where
type PlusResult a a = a
a + b = a Prelude.+ b




On Tue, Mar 12, 2013 at 2:24 PM, MigMit miguelim...@yandex.ru wrote:

 On Mar 13, 2013, at 12:54 AM, Richard A. O'Keefe o...@cs.otago.ac.nz
 wrote:
  The interesting challenge here is that we should have
 
 Date   + Period - Date  Date   - Period - Date
 Period + Date   - Date  Period - Date   - ILLEGAL
 Period + Period - DeriodPeriod - Period - Period
 Date   + Date   - ILLEGAL   Date   - Date   - Date
 
  and _also_ (remember we are trying to beat C++ here) Int +/- Int - Int.

 Well, an obvious suggestion would be to use MultiParamTypeClasses and
 TypeFamilies:

 {- LANGUAGE MultiParamTypeClasses, TypeFamilies -}
 module Date where
 import Prelude hiding (Num, (+))
 data Date = Date
 data Period = Period
 class Plus a b where
 type PlusResult a b
 (+) :: a - b - PlusResult a b
 instance Plus Date Period where
 type PlusResult Date Period = Date
 Date + Period = Date
 instance Plus Period Date where
 type PlusResult Period Date = Date
 Period + Date = Date
 instance Plus Period Period where
 type PlusResult Period Period = Period
 Period + Period = Period

 But I suppose you've been thinking about Haskell98. That, I'm afraid,
 doesn't seem possible.
 ___
 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] Overloading

2013-03-12 Thread Donn Cave
On Mar 13, 2013, at 12:54 AM, Richard A. O'Keefe o...@cs.otago.ac.nz wrote:

 The interesting challenge here is that we should have
 
Date   + Period - Date  Date   - Period - Date
Period + Date   - Date  Period - Date   - ILLEGAL
Period + Period - DeriodPeriod - Period - Period
Date   + Date   - ILLEGAL   Date   - Date   - Date
 
 and _also_ (remember we are trying to beat C++ here) Int +/- Int - Int.

I think I would also want

Period * Int - Period
Period * Period - ILLEGAL


Donn

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


Re: [Haskell-cafe] Overloading

2013-03-12 Thread Carlos Camarao

 On Tue, Mar 12, 2013 at 5:54 PM, Richard A. O'Keefe o...@cs.otago.ac.nz
 wrote:

 Carlos Camarao wrote:

  Sorry, I think my sentence:
 To define (+) as an overloaded operator in Haskell,
   you have to define and use a type class.
 is not quite correct.  I meant that to define any operator in
 Haskell you have to
  have a type class defined with that operator as member.

  No.  Operators and type classes are entirely orthogonal in Haskell.
  For example, the list concatenation operator (++) is not defined in
  any type class.  It could be.  Either the `mplus` of
  MonadPlus or the `mappend` of Monoid would make sense.  But it
  happens not to be.

 I have already corrected myself (repeating, I meant:
To define an _overloaded_ name or operator in Haskell you have to
 have a type class defined with that name/operator as member).

  Yes, but the requirement of using the predefined (+) is an extra
  requirement (I would call (+) in Haskell not a predefined operator,
  but an operator whose type is defined in a class (Num) which is in
 the
  Prelude). A Haskell programmer can still define versions of (+)
 where
  the arguments are of two different types and the result is a third
  (he cannot though use the two type classes, and thus neither
 instances
  of these two type classes, in a program).

  I wish we could argue over semantics instead of vocabulary.
  By calling the (+) of Num predefined I meant nothing other than
  it is _defined_ in the Haskell report before (_pre_) you or I add
  any code of our own.  We agree on the facts.

 Ok. But the fact that (+) has type a-a-a is a matter (design
 decision) related to the definition of class Num in the Haskell
 Prelude. If (+) had type a-b-c, the fact that

A Haskell programmer can still define versions of (+) where the
 arguments are of two different types and the result is a third

 would _not_ depend on hiding and redefining a type class. The programmer
 could then just define the desired instances.

  I don't call it an extra requirement.  The original context
  was very clearly that in C++ where you have int+int, int+double,
  double+int, double+double, char*+int, int+char* and so on all
  predefined, you can *also* add your own date+period *without*
  hiding the predefined versions. And _that_ is overloading.
  If the question is whether Haskell can do overloading, _that_ is
  what has to be achieved: you can add a *new* interface
  date+period *without* hiding the ones that were already defined
  before you started coding.



 See above. In this view redefining the type of (+) in class Num

as a-b-c would be sufficient for Haskell to have overloading.

  The interesting challenge here is that we should have
 Date   + Period - Date  Date   - Period - Date
 Period + Date   - Date  Period - Date   - ILLEGAL
 Period + Period - DeriodPeriod - Period - Period
 Date   + Date   - ILLEGAL   Date   - Date   - Date
  and _also_ (remember we are trying to beat C++ here) Int +/- Int -
 Int.
 
   I suspect that this can be done using type-level programming (so
 that
  Date + Date and Period - Date _begin_ to type check but then violate
  a type constraint) but that's where my Haskell skills are most
 risible.


  Without redefining the type of (+) in the Prelude, the challenge can be
met by
  redefining (+) in another type class (and, yes, if Prelude.(+) is also
needed,
  hiding and importing it qualified).

  Note though that in this case _polymorphic_ uses of (+), whose
instantiation
  could be for instances of both classes (Prelude.Num and the other one)
  are not possible.

  Kind regards,

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


Re: [Haskell-cafe] Overloading

2013-03-11 Thread Carlos Camarao
On Sat, Mar 9, 2013 at 5:33 PM, Peter Caspers pcaspers1...@gmail.com
wrote:

Hi,

I just started playing around a bit with Haskell, so sorry in
advance for very basic (and maybe stupid) questions. Coming from
the C++ world one thing I would like to do is overloading
operators. For example I want to write (Date 6 6 1973) + (Period 2
Months) for some self defined types Date and Period. Another
example would be (Period 1 Years) + (Period 3 Months).

Just defining the operator (+) does not work because it collides
with Prelude.+. I assume using fully qualified names would work,
but that is not what I want.


Hi. To define (+) as an overloaded operator in Haskell, you have to define
and use a type class.  Since (+) is already a member of type class Num
in the Prelude, you would have to define instances of Num (i.e. define
instance Num Date and instance Num Period), but, since (+) has type
a-a-a in class Num, and you want to use (+) with type a-b-a (or
even a-b-c), you have to import the Prelude hiding class Num, and
define a new type class with (+) as member, like, say:

{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-}
module Date where

import Prelude hiding (Num)

type Day   = Int
type Year  = Int
data Month = Jan | Feb | Mar | Apr | Mai | Jun | Jul | Aug | Sep | Oct |
Nov | Dec
newtype Date  = Date Day Month Year

type NumDays= Int
type NumMonths = Int
newtype Period   = Period NumDays NumMonths

class Sum a b where
  (+):: a - b - a

instance Sum Day Period where
  (+) = ...
instance Sum Day Day where
  (+) = ...
instance Sum Period Period where
  (+) = ...


So maybe make the types instances of typeclasses?

Yes: overloading in Haskell is done with type classes.

This would be Num for (+) I guess.

(+) has type a-a-a in Num so that does not allow
Date-Period-... and Date-Date-...

For the first example above it will not work however, alone for it
is not of type a - a - a.

Yes. You have to define another type class that gives (+) type a-b-a
(even a-b-c, if you wish).

Also the second example does not fit, because I would have to make
Period an instance of Num, which does not make sense, because I
can not multiply Periods (for example).

Well, you could define multiplication as, say, an error: this is a
consequence
of using type classes: you have to give definitions for all class members.

Am I missing something or is that what I am trying here just
impossible by the language design (and then probably for a good
reason) ?

You have to use type classes to overload names (and operators). If the
type of a member in a type class is not general enough, you have to define
and use another type class.

A second question concerns the constructors in own datatypes like
Date above. Is it possible to restrict the construction of objects
to sensible inputs, i.e. reject something like Date 50 23 2013 ?
My workaround would be to provide a function say

date :: Int-Int-Int-Date

checking the input and returning a Date object or throw an error
if the input does not correspond to a real date. I could then hide
the Date constructor itself (by not exporting it). However this
seems not really elegant. Also again, taking this way I can not
provide several constructors taking inputs of different types, can
I ?

You can. The constructor has to be a member of a type class.

Furthermore, Haskell supports a more powerful form of overloading than
(any other language I know, including) C++: context-dependent
overloading. This means that the type of an expression (f e), and thus
of f, can be determined at compile-time (inferred) based on the
context where (f e) occurs, not only on the type of the
argument (e) of the function's call.

For example, you _could_ in principle use (d+p==d) and (d+p==p),
with d::Date, p::Period, and instances of (+) with types
Date-Period-Date and Date-Period-Period, if you wish...

Cheers,

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


Re: [Haskell-cafe] Overloading

2013-03-11 Thread Richard A. O'Keefe

On 12/03/2013, at 3:15 AM, Carlos Camarao wrote:

 On Sat, Mar 9, 2013 at 5:33 PM, Peter Caspers pcaspers1...@gmail.com wrote:
 
 Hi,
 
 I just started playing around a bit with Haskell, so sorry in
 advance for very basic (and maybe stupid) questions. Coming from
 the C++ world one thing I would like to do is overloading
 operators. For example I want to write (Date 6 6 1973) + (Period 2
 Months) for some self defined types Date and Period. Another
 example would be (Period 1 Years) + (Period 3 Months).
 
 Just defining the operator (+) does not work because it collides
 with Prelude.+. I assume using fully qualified names would work,
 but that is not what I want.
 
 
 Hi. To define (+) as an overloaded operator in Haskell, you have to define
 and use a type class.

Stop right there.  Overloading in the C++ sense is ad hoc polymorphism
where the signatures of the various definitions need not resemble each
other in any way.  Haskell just plain does not have anything like that.
(+) in Haskell is *not* overloaded; it has several implementations and
allows you to define as many more as you want.  But they all conform to
the *SAME* interface.  This is much more like OO inheritance.

In particular, C++ will let you define versions of + where the arguments
are of two different types and the result is a third.  You cannot provide
such an implementation for Haskell's predefined (+).
 
 Furthermore, Haskell supports a more powerful form of overloading than
 (any other language I know, including) C++: context-dependent
 overloading. This means that the type of an expression (f e), and thus
 of f, can be determined at compile-time (inferred) based on the
 context where (f e) occurs, not only on the type of the
 argument (e) of the function's call.

Ada has had this since Ada 81.  The design goal that forced it was
the wish to allow the same identifier to be used as an enumeral in
more than one enumerated type, so that you could do

   type Colour is (Red, Green, Blue);
   type Fruit_State is (Green, Ripe, Rotten);
   X : Colour := Green;
   Y : Fruit_State := Green;

and in particular, since character literals like 'X' are allowed as
enumerals in Ada, they wished to be able to write

A: EBCDIC_Character := 'X';
B: ASCII_Character  := 'X';

and have A and B be different bytes.  The difference is that Ada
*does* do this sort of thing using overload resolution and Haskell
*doesn't*.

 
 For example, you _could_ in principle use (d+p==d) and (d+p==p), 
 with d::Date, p::Period, and instances of (+) with types 
 Date-Period-Date and Date-Period-Period, if you wish…

Prelude :type (+)
(+) :: Num a = a - a - a

The predefined (+) in Haskell requires its arguments and its result
to be precisely the same type.

I think you had better justify the claim that Date+Period - Date and
Date+Period - Period are possible at the same time by showing us
actual code.


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


Re: [Haskell-cafe] Overloading

2013-03-11 Thread MigMit

On Mar 12, 2013, at 12:44 AM, Richard A. O'Keefe o...@cs.otago.ac.nz wrote:
 
 Prelude :type (+)
 (+) :: Num a = a - a - a
 
 The predefined (+) in Haskell requires its arguments and its result
 to be precisely the same type.
 
 I think you had better justify the claim that Date+Period - Date and
 Date+Period - Period are possible at the same time by showing us
 actual code.

Ehm...

import Prelude hiding (Num)
class SumDP a where (+) :: Date - Period - a
instance SumDP Date where date + period = your_implementation_here
instance SumDP Period where date + period = and_here

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


Re: [Haskell-cafe] Overloading

2013-03-11 Thread Richard A. O'Keefe

On 12/03/2013, at 10:00 AM, MigMit wrote:

 
 On Mar 12, 2013, at 12:44 AM, Richard A. O'Keefe o...@cs.otago.ac.nz 
 wrote:
 
 Prelude :type (+)
 (+) :: Num a = a - a - a
 
 The predefined (+) in Haskell requires its arguments and its result
 to be precisely the same type.
 
 I think you had better justify the claim that Date+Period - Date and
 Date+Period - Period are possible at the same time by showing us
 actual code.
 
 Ehm...
 
 import Prelude hiding (Num)
 class SumDP a where (+) :: Date - Period - a
 instance SumDP Date where date + period = your_implementation_here
 instance SumDP Period where date + period = and_here

Notice the difference?
I said that THE PREDEFINED (+) in Haskell requires its arguments
and its result to be precisely the same type.

This example is not the predefined (+); it's another variable
entirely that happens to have the same short name and cannot
also add integers.



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


Re: [Haskell-cafe] Overloading

2013-03-10 Thread MigMit

On Mar 10, 2013, at 11:47 AM, Peter Caspers pcaspers1...@gmail.com wrote:

 Thank you all for your answers, this helps a lot. To clarify my last point ...
 
 Also again, taking this way I can not provide several constructors taking 
 inputs of different types, can I ?
 Sorry, didn't get what you mean here.
 
 In C++ it is perfectly normal to have overloaded functions like
 
 f : Int - Int - Int
 f : Int - Char - Int
 
 in coexistence, because the compiler can infer (at compile time) what 
 function to call by looking at the arguments types.
 
 In Haskell I think this is not possible simply due to the flexibility given 
 by partial function application, i.e.
 
 f 5
 
 would not be well defined any more, it could be Int - Int or Char - Int.

Well, that's what typeclasses are for.

class F a where f :: Int - a - Int

instance F Int where f = ...
instance F Char where f = ...

ghci :t f 5
ghci f 5 :: (F a) = a - Int
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-10 Thread ok


 In C++ it is perfectly normal to have overloaded functions like

 f : Int - Int - Int
 f : Int - Char - Int

Something that may not be obvious about Haskell is that
Haskell does NOT have overloaded functions/operators at all.

More precisely, for any identifier and any point in a
Haskell module, there is at most ONE definition of that
identifier that is in scope at that point.

More precisely, we can think of a function has having
two parts: an *interface* which specifies its type and zero
or more *implementations* which specify its behaviour, all
of which must have types that match or are special cases
of that interface.
For any identfier and any point in a Haskell module,
there is at most one INTERFACE for that identifier that
is in scope at that point, so there is no possible doubt
about the type of that identifier.

As an example, the standard Prelude has *one* interface
for +, namely
(+) :: Num t = t - t - t
and it offers a number of implementations of + (in
'instance' declarations) for various types.
There are additional implementations in other modules,
but they all must have types that are instances of this one.

I don't believe that partial (Curried) application has
anything to do with it.  Torsors would need multiparameter
type classes so that
 g + t :: t
 t - t :: g
and so on, but Haskell originally didn't have multiparameter
type classes.



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


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Peter Caspers



In C++ it is perfectly normal to have overloaded functions like

f : Int - Int - Int
f : Int - Char - Int

Something that may not be obvious about Haskell is that
Haskell does NOT have overloaded functions/operators at all.


thanks, this was the core of my question. So by example, if I define a 
Date type as


data Date = Date Int deriving Show

representing a date by its serial number and want two constructors 
(conditions are only examples here)


-- smart constructor with serialNumber
date serialNumber
 | serialNumber  0 = Date serialNumber
 | otherwise = error (invalid serialNumber  ++ show serialNumber)

-- smart constructor with day month year
date2 day month year
| month = 1  month =12 = undefined
| otherwise = error (invalid month  ++ show month)

there is no way of naming both functions date (instead of date2 above, 
which compiles), right ? I still think the basic reason is that


date 5

would then either refer to the first constructor (i.e. representing a 
date with serial number 5) or a partial application of the second
constructor (i.e. representing a function taking month and year and 
returning the date 5th month, year).


If this is the case, what would be the natural Haskell way of organizing 
the smart constructors ? Just number them as above ? Or naming them

dateFromSerialNumber, dateFromDayMonthYear ?

Or would you do it differently from the start ?

Thank you
Peter

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


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Daniel Trstenjak

Hi Peter,

 -- smart constructor with serialNumber
 date serialNumber
  | serialNumber  0 = Date serialNumber
  | otherwise = error (invalid serialNumber  ++ show serialNumber)

Instead of raising an error it's more secure to return a Maybe value.

date :: Int - Maybe Date
date serialNumber
   | serialNumber  0 = Just $ Date serialNumber
   | otherwise= Nothing

 -- smart constructor with day month year
 date2 day month year
 | month = 1  month =12 = undefined
 | otherwise = error (invalid month  ++ show month)

To increase type safety it's a good idea to use as much explicit data
types instead of Int values as possible:

data Month = January | ...

 If this is the case, what would be the natural Haskell way of
 organizing the smart constructors ? Just number them as above ? Or
 naming them
 dateFromSerialNumber, dateFromDayMonthYear ?

I would use the descriptive names but leave out the 'date', because you could 
still have:

import qualified Date

Date.fromSerialNumber



Greetings,
Daniel

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


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Peter Caspers

Hi Daniel,


Instead of raising an error it's more secure to return a Maybe value.

date :: Int - Maybe Date
date serialNumber
| serialNumber  0 = Just $ Date serialNumber
| otherwise= Nothing


yes, I understand (Maybe seems the equivalent of c++'s boost::optionalT).


-- smart constructor with day month year
date2 day month year
 | month = 1  month =12 = undefined
 | otherwise = error (invalid month  ++ show month)

To increase type safety it's a good idea to use as much explicit data
types instead of Int values as possible:

data Month = January | ...


ok, I will try to change my code in that direction. The idea is clear.


I would use the descriptive names but leave out the 'date', because you could 
still have:

import qualified Date

Date.fromSerialNumber



also clear, yes. I think I have a better starting point now. Not 
impossible that I will come back later with further questions :-)


Thank you for your help
Peter


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


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Donn Cave
Peter Caspers pcaspers1...@gmail.com,

 data Month = January | ...
 
 ok, I will try to change my code in that direction. The idea is clear.

To whatever extent these algebraic data types do map to integer
values for your purposes, you can implement that by making Month an
instance of Enum.

Donn

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


Re: [Haskell-cafe] Overloading

2013-03-10 Thread Richard A. O'Keefe

On 11/03/2013, at 12:10 AM, Peter Caspers wrote:

 thanks, this was the core of my question. So by example, if I define a Date 
 type as
 
 data Date = Date Int deriving Show
 
 representing a date by its serial number and want two constructors 
 (conditions are only examples here)
 
 -- smart constructor with serialNumber
 date serialNumber
 | serialNumber  0 = Date serialNumber
 | otherwise = error (invalid serialNumber  ++ show serialNumber)
 
 -- smart constructor with day month year
 date2 day month year
| month = 1  month =12 = undefined
| otherwise = error (invalid month  ++ show month)
 
 there is no way of naming both functions date (instead of date2 above, which 
 compiles), right ?

Right.
 I still think the basic reason is that
 
 date 5
 
 would then either refer to the first constructor (i.e. representing a date 
 with serial number 5) or a partial application of the second
 constructor (i.e. representing a function taking month and year and returning 
 the date 5th month, year).

I am having real trouble understanding why you think this.
Yes, for an *untyped* language, date 27 would not know whether
to return a date or a closure.  But Haskell is *not* an untyped
language.  The one-identifier-one-visible-interface rule is about
making a practical type inference algorithm.

I'm also having some trouble understanding why negative serial
numbers would be illegal.  Dates are a Z-torsor; to convert
integers to dates you have to choose an arbitrary origin.
My Dershowitz-and-Reingold-inspired Smalltalk calendar library
lets you use Julian day number (shifted by 0.5), modified Julian
day number, rata die, and ahargana.  I've been thinking of allowing
a fifth origin: COBOL's 0=31-Dec-1600.  serialNumber is a bad
name because the origin is arbitrary and the name does not reveal
what the origin is.

You can easily write

date :: Either Int (Int Int Int) - Date

date (Left days_since_epoch) = Date days_since_epoch
date (Right (year,month,day))
  | 1 = month  month = 12  1 = day 
day = days_in_month year month
= …
  | otherwise = error (bad date)

Or even set up your own interface type:

import System.Time  -- to get Month; pity Data.Time doesn't offer that.

data Date_Presentation
   = Julian_Day_Number Int
   | Modified_Julian_Day_Number Int
   | Rata_Die Int
   | Ahargana Int
   | Days_Since_COBOL_Epoch Int
   | Gregorian Int Month Int
   | Julian Int Month Int
   | Revised_Julian Int Month Int -- more accurate than Gregorian 

date :: Date_Presentation - Date

date (Julian_Day_Number j) = …
…
date (Revised_Julian y m d) = …

You will notice that this list offers 5 date presentations that
use a single number and three that use two numbers and a month name.
Overloading is no help with that!

 If this is the case, what would be the natural Haskell way of organizing the 
 smart constructors ? Just number them as above ? Or naming them
 dateFromSerialNumber, dateFromDayMonthYear ?

As noted above, there is NO unique serial number for a date
and NO unique day/month/year representation either.

Smalltalk-80 introduced baStudlyCaps namesThatIsNamesWithInternalCapitals
because it was implemented on a machine that used the ASCII 63
left arrow and up arrow instead of the ASCII 67 underscore and caret.
So it used the codepoint we associate with underscore for the assignment
symbol.  In C and C++ and SML and Haskell, we are allowed to use
underscores.  ThereisnoneedtorunyourwordstogetherOrUseInternalCaps.
Nobody_will_shoot_you_for_writing_readably.

You should probably take advantage of the module name and call your
functions
Date.from_julian_day_number :: Int - Date
Date.from_gregorian :: Int - Month - Int - Date

 Or would you do it differently from the start ?

One question is support for different calendars.

I would probably have a My_Date module that just offers
julian day number, modified julian day number, ahagarna,
rata die, and maybe a couple of other epochs.  I would
create nested modules My_Date.Gregorian, My_Date.Julian,
My_Date.Revised_Julian, My_Date.Mayan, and so on, so that
a new calendar could be supported by just plugging in a
new module, not by changing anything.

For something without so many alternatives, I might make a different choice.



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


[Haskell-cafe] Overloading

2013-03-09 Thread Peter Caspers

Hi,

I just started playing around a bit with Haskell, so sorry in advance 
for very basic (and maybe stupid) questions. Coming from the C++ world 
one thing I would like to do is overloading operators. For example I 
want to write (Date 6 6 1973) + (Period 2 Months) for some self defined 
types Date and Period. Another example would be (Period 1 Years) + 
(Period 3 Months).


Just defining the operator (+) does not work because it collides with 
Prelude.+. I assume using fully qualified names would work, but that is 
not what I want.


So maybe make the types instances of typeclasses? This would be Num for 
(+) I guess. For the first example above it will not work however, alone 
for it is not of type a - a - a. Also the second example does not fit, 
because I would have to make Period an instance of Num, which does not 
make sense, because I can not multiply Periods (for example).


Am I missing something or is that what I am trying here just impossible 
by the language design (and then probably for a good reason) ?


A second question concerns the constructors in own datatypes like Date 
above. Is it possible to restrict the construction of objects to 
sensible inputs, i.e. reject something like Date 50 23 2013 ? My 
workaround would be to provide a function say


date :: Int-Int-Int-Date

checking the input and returning a Date object or throw an error if the 
input does not correspond to a real date. I could then hide the Date 
constructor itself (by not exporting it). However this seems not really 
elegant. Also again, taking this way I can not provide several 
constructors taking inputs of different types, can I ?


Thanks a lot
Peter


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


Re: [Haskell-cafe] Overloading

2013-03-09 Thread MigMit

On Mar 10, 2013, at 12:33 AM, Peter Caspers pcaspers1...@gmail.com wrote:

 Hi,
 
 I just started playing around a bit with Haskell, so sorry in advance for 
 very basic (and maybe stupid) questions. Coming from the C++ world one thing 
 I would like to do is overloading operators. For example I want to write 
 (Date 6 6 1973) + (Period 2 Months) for some self defined types Date and 
 Period. Another example would be (Period 1 Years) + (Period 3 Months).
 
 Just defining the operator (+) does not work because it collides with 
 Prelude.+. I assume using fully qualified names would work, but that is not 
 what I want.
 
 So maybe make the types instances of typeclasses? This would be Num for (+) I 
 guess. For the first example above it will not work however, alone for it is 
 not of type a - a - a. Also the second example does not fit, because I 
 would have to make Period an instance of Num, which does not make sense, 
 because I can not multiply Periods (for example).

If you really want that, you can stop ghc from importing Prelude. I haven't 
tested it yet, but I think

import Prelude hiding (Num)

should work. Of course, in this case you would lose all predefined instances of 
Num, including the ability to add integers, but you can get them back through 
another module.



But I would strongly suggest that you define another operator instead. Unlike 
C++, Haskell allows you to define as many operators as you like.


 Am I missing something or is that what I am trying here just impossible by 
 the language design (and then probably for a good reason) ?
 
 A second question concerns the constructors in own datatypes like Date above. 
 Is it possible to restrict the construction of objects to sensible inputs, 
 i.e. reject something like Date 50 23 2013 ? My workaround would be to 
 provide a function say
 
 date :: Int-Int-Int-Date
 
 checking the input and returning a Date object or throw an error if the input 
 does not correspond to a real date. I could then hide the Date constructor 
 itself (by not exporting it). However this seems not really elegant.

Well, it's the way it is usually done. This is called a smart constructor 
pattern.

 Also again, taking this way I can not provide several constructors taking 
 inputs of different types, can I ?

Sorry, didn't get what you mean here.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overloading

2013-03-09 Thread Anthony Cowley
On Mar 9, 2013, at 3:33 PM, Peter Caspers pcaspers1...@gmail.com wrote:

 Hi,
 
 I just started playing around a bit with Haskell, so sorry in advance for 
 very basic (and maybe stupid) questions. Coming from the C++ world one thing 
 I would like to do is overloading operators. For example I want to write 
 (Date 6 6 1973) + (Period 2 Months) for some self defined types Date and 
 Period. Another example would be (Period 1 Years) + (Period 3 Months).
 
 So maybe make the types instances of typeclasses? This would be Num for (+) I 
 guess. For the first example above it will not work however, alone for it is 
 not of type a - a - a. Also the second example does not fit, because I 
 would have to make Period an instance of Num, which does not make sense, 
 because I can not multiply Periods (for example).
 
 Am I missing something or is that what I am trying here just impossible by 
 the language design (and then probably for a good reason) ?

Take a look at affine spaces and additive groups in the vector-space package. 
There may be other treatments of torsors on hackage, but vector-space has a 
fairly straightforward approach.

 A second question concerns the constructors in own datatypes like Date above. 
 Is it possible to restrict the construction of objects to sensible inputs, 
 i.e. reject something like Date 50 23 2013 ? My workaround would be to 
 provide a function say
 
 date :: Int-Int-Int-Date
 
 checking the input and returning a Date object or throw an error if the input 
 does not correspond to a real date. I could then hide the Date constructor 
 itself (by not exporting it). However this seems not really elegant. Also 
 again, taking this way I can not provide several constructors taking inputs 
 of different types, can I ?

This approach -- hiding data constructors and exporting functions that perform 
validation -- is called smart constructors, and is accepted practice. It 
isn't entirely satisfying due to interfering with pattern matching in client 
code, so you either need to work with projection functions for your data type, 
or use ViewPatterns to provide a more transparent record type at use sites.

Anthony


 
 Thanks a lot
 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] Overloading

2013-03-09 Thread Amy de Buitléir
 Also again, taking this way I can not provide several constructors taking
inputs of different types, can I ?

You can have multiple constructors, taking different numbers and types of input
parameters, yes.




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


Re: [Haskell-cafe] Overloading

2013-03-09 Thread Peter Caspers
Thank you all for your answers, this helps a lot. To clarify my last 
point ...



Also again, taking this way I can not provide several constructors taking 
inputs of different types, can I ?

Sorry, didn't get what you mean here.


In C++ it is perfectly normal to have overloaded functions like

f : Int - Int - Int
f : Int - Char - Int

in coexistence, because the compiler can infer (at compile time) what 
function to call by looking at the arguments types.


In Haskell I think this is not possible simply due to the flexibility 
given by partial function application, i.e.


f 5

would not be well defined any more, it could be Int - Int or Char - Int.

Thanks again and kind regards
Peter







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


[Haskell-cafe] overloading integer literals

2012-08-14 Thread Евгений Пермяков
During development some toy base library I found impossible to use 
Numeric literals. Quick search showed, that one need both fromInteger in 
scope (reasonable) and, as I understand, access to Integer type from 
'base' package ('base' for clarity later). It is perfectly reasonable if 
we assume that every module must depend on 'base'. However, with 
ghc-prim and NoIplicitPrelude it is not necessary this way. One may wish 
to drop 'base' dependency entirely. Currently, the only workaround I 
found is to use cast from string literals (that works perfectly okay) or 
use unboxed literals like 0xBB## (of unboxed type). Both solutions look 
dirty, especially in pattern guards.


Is there any better solution or movement to improve RebindableSyntax 
facilities ? for example, moving out classes for RebindableSyntax into 
ghc-prim package and tuning them so all syntax facilities in base could 
be defined in terms of RebindableSyntax  would be great.


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


[Haskell-cafe] overloading

2012-07-12 Thread Patrick Browne
Hi,I am comparing Haskell's class/instance techniques for overloading with those available Order Sorted Algebra (OSA in CafeOBJ) Using just the basic class/instance mechanism is there any way to avoid the type annotations in the evaluations below?Patclass Location a b where move::a-binstance Location Int Int where move e = e + 3instance Location  Float Int where move e = floor(e + 3.1) instance Location  [Float] [Int] where  move [] = []  move (e:l) = (move e):(move l)instance Location [Int] [Int] where move [] = [] move (e:l) = (move e):(move l)-- evaluations-- testing float-- (move ((7.6::Float))::Int)-- ((move ([21.8,7.4,9.1]::[Float]))::[Int])--  testing integers--  move ((3::Int))::Int-- ((move ([21,7,9]::[Int]))::[Int])
 Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán.  http://www.dit.ie
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean.  http://www.dit.ie



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


[Haskell-cafe] Overloading in a sub-class

2011-08-17 Thread Patrick Browne
Hi,
Below are two questions concerning overloading in a sub-class.
Thanks,
Pat

class Numb0 a where
 (+) :: a - a - a
 negate :: a - a


instance Numb0 Int where
 x + y = y
 negate x = x

-- Are  + and negate part of the signature of Numb1?
class Numb0 a  = Numb1 a where


-- Is it possible to override these operations in instances of Numb1?
-- Something like:
-- instance Numb1 Float where
--x + y = y
--negate x =  x
-- Or even using Int as in the super class instance:
-- instance Numb1 Int where
--x + y = y
--negate x =  x




This message has been scanned for content and viruses by the DIT Information 
Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie

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


Re: [Haskell-cafe] Overloading in a sub-class

2011-08-17 Thread Albert Y. C. Lai

On 11-08-17 12:10 PM, Patrick Browne wrote:

-- Are  + and negate part of the signature of Numb1?
class Numb0 a  =  Numb1 a where


No.


-- Is it possible to override these operations in instances of Numb1?
-- Something like:
-- instance Numb1 Float where
--x + y = y
--negate x =  x


No.

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


Re: [Haskell-cafe] overloading show function

2011-06-30 Thread Holger Siegel

Am 29.06.2011 um 23:50 schrieb Philipp Schneider:

 Hi cafe,
 
 in my program i use a monad of the following type
 
 newtype M a = M (State - (a, State))
 
 i use the monad in two different ways. The type variable a can be a
 pair as in
 
 interp :: Term - Environment - M (Value,Environment)
 
 and it can be just a value as in
 
 type Environment = [(Name, Either Value (M Value))]

Simple rule: Never return an environment!

An environment contains local variable bindings, so no subcomputation will ever 
need to return its environment. I don't know anything about the language your 
program interprets, but I'm sure that you can rewrite function interp as

  interp :: Term - Environment - M Value

The structure of the interpreter will become clearer and your problem will 
vanish.


 
 now in any case when i print the monad, i just want to print the value
 and never the environment.
 
 More specific i want to use somthing like the following
 
 instance (Show a,Show b) = Show (M (a,b)) where
   show (M f) = let ((v,_), s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s
 
 instance Show a = Show (M a) where
   show (M f) = let (v, s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s
 
 however this gives me the following error message:
 
Overlapping instances for Show (M (Value, Environment))
  arising from a use of `print'
Matching instances:
  instance (Show a, Show b) = Show (M (a, b))
-- Defined at
 /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:78:10-42
  instance Show a = Show (M a)
-- Defined at
 /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:82:10-29
In a stmt of an interactive GHCi command: print it
 
 Any ideas how to fix it? Thanks!
 Philipp
 
 ___
 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] overloading show function

2011-06-30 Thread Wolfgang Braun
An environment contains local variable bindings, so no subcomputation will 
ever need to return its environment.
  - That is not true.  A subcomputation can possible modify an environment 
except the language forbids such a case.


On 06/30/2011 02:36 PM, Holger Siegel wrote:
 Am 29.06.2011 um 23:50 schrieb Philipp Schneider:

 Hi cafe,

 in my program i use a monad of the following type

 newtype M a = M (State - (a, State))

 i use the monad in two different ways. The type variable a can be a
 pair as in

 interp :: Term - Environment - M (Value,Environment)

 and it can be just a value as in

 type Environment = [(Name, Either Value (M Value))]
 Simple rule: Never return an environment!

 An environment contains local variable bindings, so no subcomputation will 
 ever need to return its environment. I don't know anything about the language 
 your program interprets, but I'm sure that you can rewrite function interp as

   interp :: Term - Environment - M Value

 The structure of the interpreter will become clearer and your problem will 
 vanish.


 now in any case when i print the monad, i just want to print the value
 and never the environment.

 More specific i want to use somthing like the following

 instance (Show a,Show b) = Show (M (a,b)) where
   show (M f) = let ((v,_), s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s

 instance Show a = Show (M a) where
   show (M f) = let (v, s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s

 however this gives me the following error message:

Overlapping instances for Show (M (Value, Environment))
  arising from a use of `print'
Matching instances:
  instance (Show a, Show b) = Show (M (a, b))
-- Defined at
 /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:78:10-42
  instance Show a = Show (M a)
-- Defined at
 /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:82:10-29
In a stmt of an interactive GHCi command: print it

 Any ideas how to fix it? Thanks!
 Philipp

 ___
 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


Re: [Haskell-cafe] overloading show function

2011-06-30 Thread Philipp Schneider
On 06/30/2011 02:36 PM, Holger Siegel wrote:
 Am 29.06.2011 um 23:50 schrieb Philipp Schneider:

 Hi cafe,

 in my program i use a monad of the following type

 newtype M a = M (State - (a, State))

 i use the monad in two different ways. The type variable a can be a
 pair as in

 interp :: Term - Environment - M (Value,Environment)

 and it can be just a value as in

 type Environment = [(Name, Either Value (M Value))]
 Simple rule: Never return an environment!

 An environment contains local variable bindings, so no subcomputation will 
 ever need to return its environment. I don't know anything about the language 
 your program interprets, but I'm sure that you can rewrite function interp as

   interp :: Term - Environment - M Value

 The structure of the interpreter will become clearer and your problem will 
 vanish.

Hello Holger,

I'm giving two lambda interpreters. The first one is a call by value
interpreter, the second one a call by name interpreter which are
described in Philip Wadler's paper The essence of functional
programming page 4 and 12. Now my task is to write a lazy lambda
interpreter. The exercise is more playful than serious since Wadler's
call by value interpreter is, since written in lazy Haskell, already a
lazy lambda interpreter. (To get true call by value one would need to
force evaluations of the arguments with the seq function.)
For both of Wadler's interpreters the type of the interpertation
function is:
interp :: Term - Environment - M Value

Now to simulate lazy interpretation i need to do the following: Decide
is the value I need already evaluated or is it still a computation. In
the later case I need to evaluate it and save its value in the
environment. This is the reason I changed the type of the interpretation
function to:
interp :: Term - Environment - M (Value,Environment)

I appened my full interpreter. If you can find a more elegant way to
save the newly interpreted values, you are more than welcome to show my
how to do it.

Cheers,
Philipp


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


Re: [Haskell-cafe] overloading show function

2011-06-30 Thread Philipp Schneider
On 06/30/2011 08:25 PM, Philipp Schneider wrote:
 On 06/30/2011 02:36 PM, Holger Siegel wrote:
 Am 29.06.2011 um 23:50 schrieb Philipp Schneider:

 Hi cafe,

 in my program i use a monad of the following type

 newtype M a = M (State - (a, State))

 i use the monad in two different ways. The type variable a can be a
 pair as in

 interp :: Term - Environment - M (Value,Environment)

 and it can be just a value as in

 type Environment = [(Name, Either Value (M Value))]
 Simple rule: Never return an environment!

 An environment contains local variable bindings, so no subcomputation will 
 ever need to return its environment. I don't know anything about the 
 language your program interprets, but I'm sure that you can rewrite function 
 interp as

   interp :: Term - Environment - M Value

 The structure of the interpreter will become clearer and your problem will 
 vanish.

 Hello Holger,

 I'm giving two lambda interpreters. The first one is a call by value
 interpreter, the second one a call by name interpreter which are
 described in Philip Wadler's paper The essence of functional
 programming page 4 and 12. Now my task is to write a lazy lambda
 interpreter. The exercise is more playful than serious since Wadler's
 call by value interpreter is, since written in lazy Haskell, already a
 lazy lambda interpreter. (To get true call by value one would need to
 force evaluations of the arguments with the seq function.)
 For both of Wadler's interpreters the type of the interpertation
 function is:
 interp :: Term - Environment - M Value

 Now to simulate lazy interpretation i need to do the following: Decide
 is the value I need already evaluated or is it still a computation. In
 the later case I need to evaluate it and save its value in the
 environment. This is the reason I changed the type of the interpretation
 function to:
 interp :: Term - Environment - M (Value,Environment)

 I appened my full interpreter. If you can find a more elegant way to
 save the newly interpreted values, you are more than welcome to show my
 how to do it.

 Cheers,
 Philipp
I forgot to add the interpreter.
{-# LANGUAGE OverlappingInstances #-}

import Prelude hiding (lookup, fail)

import Control.Monad
   
-- Basiswerte

data Value= WrongAd
  | WrongAp
  | WrongL
  | Num Int
  | Fun (Either Value (M Value) - M Value)

instance Show Value where
   show WrongAd= wrong add  
   show WrongAp= wrong app 
   show WrongL= wrong lookup   
   show (Num i)  = show i
   show (Fun f)  = function

-- Terme 

data Term = Var Name
  | Con Int
  | Add Term Term
  | Lam Name Term
  | App Term Term deriving Show

-- Interpretation der Terme (Lazy evaluation)

interp :: Term - Environment - M (Value,Environment)
interp (Var x) e   = lookup x e
interp (Con i) e   = return (Num i,e)
interp (Add u v) e =  do
  (a,e) - interp u e
  (b,e) - interp v e
  s - add a b
  return (s,e)
interp (Lam x v) e  = return (Fun (\m - (interp v ((x, m):e)) = return . fst) , e)
interp (App t u) e  = do
  (f,e) - interp t e
  a - (apply f (Right ((interp u e) = return . fst)))
  return (a,e)


add :: Value - Value - M Value
add (Num i) (Num j) = tick = (\() - return (Num (i+j)))
add a b = return WrongAd

apply :: Value - Either Value (M Value) - M Value
apply (Fun k) a= tick = (\() - k a)
apply notFun a = return WrongAp

-- Umgebung

type Environment = [(Name, Either Value (M Value))]
type Name = String

lookup :: Name - Environment - M (Value,Environment)
lookup x eComplete = lookup_h x eComplete
  where
lookup_h x []= return (WrongL,[])
lookup_h x e@((y,b):etl) = 
  if x==y then case b of 
-- schon ausgewertet
Left a - return (a,e) 
-- noch nicht ausgewertet (speichere den ausgewerteten Wert)
Right a - (a = (\x- return (x, (y,Left x):eComplete)))
  else lookup_h x etl

-- Lazy-Interpreter zaehlt die Reduktionen (Wadler: Beispiel 9)

type State = Int

newtype M a = M (State - (a, State))

tick = M (\s - ((), s+1))


instance (Show a,Show b) = Show (M (a,b)) where
   show (M f) = let ((v,_), s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s

instance Show a = Show (M a) where
   show (M f) = let (v, s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s


instance Monad M where
   return a = M (\s - (a, s))
   (M m) = k = M (\s0 - let (a, s1) = m s0
   (M m')  = k a
   in m' s1
  ) 
   fail s = error s -- wird nicht aufgerufen
   
-- Beispiele:

-- test :: Term - String
test t = (interp t [])

term0 = (Con 10)
term0' = (Var x)
term1 = (Add (Con 10) (Con 11))
term2 = (Lam x (Add (Var x) (Con 10)))
term3 = (App term2 (Con 11))
term4 = (Lam x (Add (Var x) (Var x)))
term5 = (App term4 term1)
term6 = (Lam x (Lam y (Add (Var x) (Var y
term7 = (App term6 (Con 10))
term8 = 

Re: [Haskell-cafe] overloading show function

2011-06-30 Thread Holger Siegel

Am 30.06.2011 um 20:23 schrieb Philipp Schneider:

 On 06/30/2011 02:36 PM, Holger Siegel wrote:
 Am 29.06.2011 um 23:50 schrieb Philipp Schneider:
 
 Hi cafe,
 
 in my program i use a monad of the following type
 
 newtype M a = M (State - (a, State))
 
 i use the monad in two different ways. The type variable a can be a
 pair as in
 
 interp :: Term - Environment - M (Value,Environment)
 
 and it can be just a value as in
 
 type Environment = [(Name, Either Value (M Value))]
 Simple rule: Never return an environment!
 
 An environment contains local variable bindings, so no subcomputation will 
 ever need to return its environment. I don't know anything about the 
 language your program interprets, but I'm sure that you can rewrite function 
 interp as
 
  interp :: Term - Environment - M Value
 
 The structure of the interpreter will become clearer and your problem will 
 vanish.
 
 Hello Holger,
 
 I'm giving two lambda interpreters. The first one is a call by value
 interpreter, the second one a call by name interpreter which are
 described in Philip Wadler's paper The essence of functional
 programming page 4 and 12. Now my task is to write a lazy lambda
 interpreter. The exercise is more playful than serious since Wadler's
 call by value interpreter is, since written in lazy Haskell, already a
 lazy lambda interpreter. (To get true call by value one would need to
 force evaluations of the arguments with the seq function.)

Hello Philipp,

that's a nice exercise.

 For both of Wadler's interpreters the type of the interpertation
 function is:
 interp :: Term - Environment - M Value
 
 Now to simulate lazy interpretation i need to do the following: Decide
 is the value I need already evaluated or is it still a computation. In
 the later case I need to evaluate it and save its value in the
 environment. This is the reason I changed the type of the interpretation
 function to:
 interp :: Term - Environment - M (Value,Environment)

But that won't work: After you have evaluated an entry of the environment, you 
store the resulting value but you throw away its updated environment. That 
means, you lose the results of all subcomputations instead of propagating them 
to all other copies of the environment. Consider the following expression:

let x = big_computation in let y = x in y + x

First, big_computation is bound to the name x, resulting in an environment 
[(x, big_computation)]. Then a closure consisting of this environment 
together with the right hand side 'x' is bound to the name y. Now y+x is 
evaluated: The closure is entered, and from its environment the content of x - 
a call to big_computation - is looked up. Now big_computation is evaluated and 
the result is bound to x in this environment. After that, this result is also 
returned as the value of y. But when returning from the evaluation of y, the 
environment with the updated value of x is lost and you have to re-evaluate it 
in order to calculate x+y!

And that is why I say never return an environment. It is either wrong or 
unnecessary or the resulting semantics of the interpreter is hard to comprehend.

In order to implement lazy evaluation correctly, you have to maintain some 
global state in which the thunks are updated. For example, your environment 
could bind IORefs that contain unevaluated thunks to variable names and update 
them when the thunk is evaluated. But then your interpreter has to run in the 
IO monad.

By the way, do you already know Peter Sestoft's paper Deriving a lazy abstract 
machine?

Cheers, Holger


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


Re: [Haskell-cafe] overloading show function

2011-06-30 Thread Philipp Schneider
On 06/30/2011 09:49 PM, Holger Siegel wrote:
 Am 30.06.2011 um 20:23 schrieb Philipp Schneider:

 On 06/30/2011 02:36 PM, Holger Siegel wrote:
 Am 29.06.2011 um 23:50 schrieb Philipp Schneider:

 Hi cafe,

 in my program i use a monad of the following type

 newtype M a = M (State - (a, State))

 i use the monad in two different ways. The type variable a can be a
 pair as in

 interp :: Term - Environment - M (Value,Environment)

 and it can be just a value as in

 type Environment = [(Name, Either Value (M Value))]
 Simple rule: Never return an environment!

 An environment contains local variable bindings, so no subcomputation will 
 ever need to return its environment. I don't know anything about the 
 language your program interprets, but I'm sure that you can rewrite 
 function interp as

  interp :: Term - Environment - M Value

 The structure of the interpreter will become clearer and your problem will 
 vanish.

 Hello Holger,

 I'm giving two lambda interpreters. The first one is a call by value
 interpreter, the second one a call by name interpreter which are
 described in Philip Wadler's paper The essence of functional
 programming page 4 and 12. Now my task is to write a lazy lambda
 interpreter. The exercise is more playful than serious since Wadler's
 call by value interpreter is, since written in lazy Haskell, already a
 lazy lambda interpreter. (To get true call by value one would need to
 force evaluations of the arguments with the seq function.)
 Hello Philipp,

 that's a nice exercise.

 For both of Wadler's interpreters the type of the interpertation
 function is:
 interp :: Term - Environment - M Value

 Now to simulate lazy interpretation i need to do the following: Decide
 is the value I need already evaluated or is it still a computation. In
 the later case I need to evaluate it and save its value in the
 environment. This is the reason I changed the type of the interpretation
 function to:
 interp :: Term - Environment - M (Value,Environment)
 But that won't work: After you have evaluated an entry of the environment, 
 you store the resulting value but you throw away its updated environment. 
 That means, you lose the results of all subcomputations instead of 
 propagating them to all other copies of the environment. Consider the 
 following expression:

 let x = big_computation in let y = x in y + x

 First, big_computation is bound to the name x, resulting in an environment 
 [(x, big_computation)]. Then a closure consisting of this environment 
 together with the right hand side 'x' is bound to the name y. Now y+x is 
 evaluated: The closure is entered, and from its environment the content of x 
 - a call to big_computation - is looked up. Now big_computation is evaluated 
 and the result is bound to x in this environment. After that, this result is 
 also returned as the value of y. But when returning from the evaluation of y, 
 the environment with the updated value of x is lost and you have to 
 re-evaluate it in order to calculate x+y!
Hello Holger,

Can you give me an example of a lambda term in which this would be an issue?
Evaluating the following works just fine in my implementation.
interp (App (Lam x (Add (Var x) (Var x))) big_computation) []
When the first variable x is evaluated my interp function returns the
value and the updated environment. Then to evaluate the second variable
the value is just looked up from this environment.
Of course in the following big_computation would be evaluated twice
(App (Lam x (App (Lam y (Add (Var x) (Var y))) big_computation))
big_computation)
But i simply don't have a concept like let x=y.
 And that is why I say never return an environment. It is either wrong or 
 unnecessary or the resulting semantics of the interpreter is hard to 
 comprehend.

 In order to implement lazy evaluation correctly, you have to maintain some 
 global state in which the thunks are updated. For example, your environment 
 could bind IORefs that contain unevaluated thunks to variable names and 
 update them when the thunk is evaluated. But then your interpreter has to run 
 in the IO monad.
I agree that this would  be the proper way to do it, but I was trying
to minimize the use of monads since they have just been introduced in
the course.
 By the way, do you already know Peter Sestoft's paper Deriving a lazy 
 abstract machine?
I haven't read is so far, but thanks for pointing it out.
 Cheers, Holger

Cheers,
Philipp

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


Re: [Haskell-cafe] overloading show function

2011-06-30 Thread Holger Siegel

Am 30.06.2011 um 22:57 schrieb Philipp Schneider:

 On 06/30/2011 09:49 PM, Holger Siegel wrote:
 (...) But that won't work: After you have evaluated an entry of the 
 environment, you store the resulting value but you throw away its updated 
 environment. That means, you lose the results of all subcomputations instead 
 of propagating them to all other copies of the environment. Consider the 
 following expression:
 
 let x = big_computation in let y = x in y + x
 
 First, big_computation is bound to the name x, resulting in an environment 
 [(x, big_computation)]. Then a closure consisting of this environment 
 together with the right hand side 'x' is bound to the name y. Now y+x is 
 evaluated: The closure is entered, and from its environment the content of x 
 - a call to big_computation - is looked up. Now big_computation is evaluated 
 and the result is bound to x in this environment. After that, this result is 
 also returned as the value of y. But when returning from the evaluation of 
 y, the environment with the updated value of x is lost and you have to 
 re-evaluate it in order to calculate x+y!
 Hello Holger,
 
 Can you give me an example of a lambda term in which this would be an issue?
 Evaluating the following works just fine in my implementation.
 interp (App (Lam x (Add (Var x) (Var x))) big_computation) []
 When the first variable x is evaluated my interp function returns the
 value and the updated environment. Then to evaluate the second variable
 the value is just looked up from this environment.
 Of course in the following big_computation would be evaluated twice
 (App (Lam x (App (Lam y (Add (Var x) (Var y))) big_computation))
 big_computation)
 But i simply don't have a concept like let x=y.


 App (Lam x (App (Lam y (Add (Var y) (Var x))) (Var x ))) (Con 2)

takes three reduction steps, which is correct, but

 App (Lam x (App (Lam y (Add (Var y) (Var x))) (Var x ))) (Add (Con 
1)(Con 1))

takes five reduction steps although it should take only four.


 And that is why I say never return an environment. It is either wrong or 
 unnecessary or the resulting semantics of the interpreter is hard to 
 comprehend.
 
 In order to implement lazy evaluation correctly, you have to maintain some 
 global state in which the thunks are updated. For example, your environment 
 could bind IORefs that contain unevaluated thunks to variable names and 
 update them when the thunk is evaluated. But then your interpreter has to 
 run in the IO monad.
 I agree that this would  be the proper way to do it, but I was trying
 to minimize the use of monads since they have just been introduced in
 the course.

That shouldn't be too hard. Just change your definition of monad M to

 newtype M a = M (State - IO (a, State))

and define the corresponding monad instance as an exercise :) (or ask me by 
private mail if you like).


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


Re: [Haskell-cafe] overloading show function

2011-06-30 Thread Philipp Schneider
On 06/30/2011 11:46 PM, Holger Siegel wrote:
 Am 30.06.2011 um 22:57 schrieb Philipp Schneider:

 On 06/30/2011 09:49 PM, Holger Siegel wrote:
 (...) But that won't work: After you have evaluated an entry of the 
 environment, you store the resulting value but you throw away its updated 
 environment. That means, you lose the results of all subcomputations 
 instead of propagating them to all other copies of the environment. 
 Consider the following expression:

 let x = big_computation in let y = x in y + x

 First, big_computation is bound to the name x, resulting in an environment 
 [(x, big_computation)]. Then a closure consisting of this environment 
 together with the right hand side 'x' is bound to the name y. Now y+x is 
 evaluated: The closure is entered, and from its environment the content of 
 x - a call to big_computation - is looked up. Now big_computation is 
 evaluated and the result is bound to x in this environment. After that, 
 this result is also returned as the value of y. But when returning from the 
 evaluation of y, the environment with the updated value of x is lost and 
 you have to re-evaluate it in order to calculate x+y!
 Hello Holger,

 Can you give me an example of a lambda term in which this would be an issue?
 Evaluating the following works just fine in my implementation.
 interp (App (Lam x (Add (Var x) (Var x))) big_computation) []
 When the first variable x is evaluated my interp function returns the
 value and the updated environment. Then to evaluate the second variable
 the value is just looked up from this environment.
 Of course in the following big_computation would be evaluated twice
 (App (Lam x (App (Lam y (Add (Var x) (Var y))) big_computation))
 big_computation)
 But i simply don't have a concept like let x=y.

  App (Lam x (App (Lam y (Add (Var y) (Var x))) (Var x ))) (Con 2)

 takes three reduction steps, which is correct, but

  App (Lam x (App (Lam y (Add (Var y) (Var x))) (Var x ))) (Add (Con 
 1)(Con 1))

 takes five reduction steps although it should take only four.
Ok, I now see the problem. Thanks for pointing it out to me.

 And that is why I say never return an environment. It is either wrong or 
 unnecessary or the resulting semantics of the interpreter is hard to 
 comprehend.

 In order to implement lazy evaluation correctly, you have to maintain some 
 global state in which the thunks are updated. For example, your environment 
 could bind IORefs that contain unevaluated thunks to variable names and 
 update them when the thunk is evaluated. But then your interpreter has to 
 run in the IO monad.
 I agree that this would  be the proper way to do it, but I was trying
 to minimize the use of monads since they have just been introduced in
 the course.
 That shouldn't be too hard. Just change your definition of monad M to

  newtype M a = M (State - IO (a, State))

 and define the corresponding monad instance as an exercise :) (or ask me by 
 private mail if you like).
I'll try to implement it tomorrow. Hopefully I'll succeed without your
help. ;)


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


[Haskell-cafe] overloading show function

2011-06-29 Thread Philipp Schneider
Hi cafe,

in my program i use a monad of the following type

newtype M a = M (State - (a, State))

i use the monad in two different ways. The type variable a can be a
pair as in

interp :: Term - Environment - M (Value,Environment)

and it can be just a value as in

type Environment = [(Name, Either Value (M Value))]

now in any case when i print the monad, i just want to print the value
and never the environment.

More specific i want to use somthing like the following

instance (Show a,Show b) = Show (M (a,b)) where
   show (M f) = let ((v,_), s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s

instance Show a = Show (M a) where
   show (M f) = let (v, s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s

however this gives me the following error message:

Overlapping instances for Show (M (Value, Environment))
  arising from a use of `print'
Matching instances:
  instance (Show a, Show b) = Show (M (a, b))
-- Defined at
/home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:78:10-42
  instance Show a = Show (M a)
-- Defined at
/home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:82:10-29
In a stmt of an interactive GHCi command: print it

Any ideas how to fix it? Thanks!
Philipp

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


Re: [Haskell-cafe] overloading show function

2011-06-29 Thread aditya siram
Try enabling OverlappingInstances extension by adding this to the top
of the file:
{-# LANGUAGE OverlappingInstances #-}

-deech

On Wed, Jun 29, 2011 at 4:50 PM, Philipp Schneider
philipp.schneid...@gmx.net wrote:
 Hi cafe,

 in my program i use a monad of the following type

 newtype M a = M (State - (a, State))

 i use the monad in two different ways. The type variable a can be a
 pair as in

 interp :: Term - Environment - M (Value,Environment)

 and it can be just a value as in

 type Environment = [(Name, Either Value (M Value))]

 now in any case when i print the monad, i just want to print the value
 and never the environment.

 More specific i want to use somthing like the following

 instance (Show a,Show b) = Show (M (a,b)) where
   show (M f) = let ((v,_), s) = f 0 in
     Value:  ++ show v ++   Count:  ++ show s

 instance Show a = Show (M a) where
   show (M f) = let (v, s) = f 0 in
     Value:  ++ show v ++   Count:  ++ show s

 however this gives me the following error message:

    Overlapping instances for Show (M (Value, Environment))
      arising from a use of `print'
    Matching instances:
      instance (Show a, Show b) = Show (M (a, b))
        -- Defined at
 /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:78:10-42
      instance Show a = Show (M a)
        -- Defined at
 /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:82:10-29
    In a stmt of an interactive GHCi command: print it

 Any ideas how to fix it? Thanks!
 Philipp

 ___
 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] overloading show function

2011-06-29 Thread Steffen Schuldenzucker


Hi Philipp,

On 06/29/2011 11:50 PM, Philipp Schneider wrote:

Hi cafe,

in my program i use a monad of the following type

newtype M a = M (State -  (a, State))


btw., it looks like you just rebuilt the State monad.



...

instance (Show a,Show b) =  Show (M (a,b)) where
show (M f) = let ((v,_), s) = f 0 in
  Value:  ++ show v ++   Count:  ++ show s

instance Show a =  Show (M a) where
show (M f) = let (v, s) = f 0 in
  Value:  ++ show v ++   Count:  ++ show s

however this gives me the following error message:

 Overlapping instances for Show (M (Value, Environment))
   arising from a use of `print'
 Matching instances:
   instance (Show a, Show b) =  Show (M (a, b))
 -- Defined at
/home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:78:10-42
   instance Show a =  Show (M a)
 -- Defined at
/home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:82:10-29
 In a stmt of an interactive GHCi command: print it


This is a well-known issue. The problem is as follows: Your second 
instance declares an instance Show (M a) for any type a. If a is of the 
Form (b, c), we can derive a tuple instance from that. This however 
conflicts with the tuple instance declared above.


If you want GHC to choose the most specific instance (which would be 
your first one for tuples), use the


{-# LANGUAGE OverlappingInstances #-}

pragma. Be careful with this however, as it might lead to unexpected 
results. For a similar problem, you may want to consult the haskell wiki[1].


-- Steffen

[1] http://haskell.org/haskellwiki/GHC/AdvancedOverlap

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


Re: [Haskell-cafe] overloading show function

2011-06-29 Thread Philipp Schneider
Thank you very much, this worked.

On 06/30/2011 12:03 AM, aditya siram wrote:
 Try enabling OverlappingInstances extension by adding this to the top
 of the file:
 {-# LANGUAGE OverlappingInstances #-}

 -deech

 On Wed, Jun 29, 2011 at 4:50 PM, Philipp Schneider
 philipp.schneid...@gmx.net wrote:
 Hi cafe,

 in my program i use a monad of the following type

 newtype M a = M (State - (a, State))

 i use the monad in two different ways. The type variable a can be a
 pair as in

 interp :: Term - Environment - M (Value,Environment)

 and it can be just a value as in

 type Environment = [(Name, Either Value (M Value))]

 now in any case when i print the monad, i just want to print the value
 and never the environment.

 More specific i want to use somthing like the following

 instance (Show a,Show b) = Show (M (a,b)) where
   show (M f) = let ((v,_), s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s

 instance Show a = Show (M a) where
   show (M f) = let (v, s) = f 0 in
 Value:  ++ show v ++   Count:  ++ show s

 however this gives me the following error message:

Overlapping instances for Show (M (Value, Environment))
  arising from a use of `print'
Matching instances:
  instance (Show a, Show b) = Show (M (a, b))
-- Defined at
 /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:78:10-42
  instance Show a = Show (M a)
-- Defined at
 /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:82:10-29
In a stmt of an interactive GHCi command: print it

 Any ideas how to fix it? Thanks!
 Philipp

 ___
 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] Overloading functions based on arguments?

2009-02-13 Thread Eugene Kirpichov
class Foobar a b where
  foobar :: a - b - Int

instance Foobar String Int where ...
instance Foobar Int String where ...

2009/2/13 Daniel Kraft d...@domob.eu:
 Hi,

 I just came across a problem like this:  Suppose I've got two related
 functions that do similar things, and I want to call them the same... Like
 in:

 foobar :: String - Int - Int
 foobar :: Int - String - Int

 (Bad example, but I hope you got the point.)

 Is this kind of overloading (instead of the polymorphism based overloading)
 possible in Haskell?  Namely to have two functions with the same name but
 different signatures so they could be distinguished by a call's parameters?
  I fear not...  So I guess I have to name the functions differently, right?

 Thanks,
 Daniel

 ___
 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] Overloading functions based on arguments?

2009-02-13 Thread Colin Adams
If you have two functions that do two different things, then they
certainly OUGHT to have different names.

You can of course put the two functions in different modules. Then
they do have different (qualified) names.

2009/2/13 Daniel Kraft d...@domob.eu:
 Hi,

 I just came across a problem like this:  Suppose I've got two related
 functions that do similar things, and I want to call them the same... Like
 in:

 foobar :: String - Int - Int
 foobar :: Int - String - Int

 (Bad example, but I hope you got the point.)

 Is this kind of overloading (instead of the polymorphism based overloading)
 possible in Haskell?  Namely to have two functions with the same name but
 different signatures so they could be distinguished by a call's parameters?
  I fear not...  So I guess I have to name the functions differently, right?

 Thanks,
 Daniel

 ___
 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] Overloading functions based on arguments?

2009-02-13 Thread Duncan Coutts
On Fri, 2009-02-13 at 13:25 +0300, Eugene Kirpichov wrote:
 class Foobar a b where
   foobar :: a - b - Int
 
 instance Foobar String Int where ...
 instance Foobar Int String where ...

But we typically do not to this. It's ugly. Classes work nicely when
there is some kind of parametrisation going on, where a function can
work with any instance of some interface. Ad-hoc overloading in the
style of Java/C++ just isn't done, even though it can be encoded by the
above trick.

In the simple case just us a different name. If you would have lots of
variations then consider other approaches like passing a data type
containing some of the arguments (since that can encode alternatives).

Duncan

 2009/2/13 Daniel Kraft d...@domob.eu:
  Hi,
 
  I just came across a problem like this:  Suppose I've got two related
  functions that do similar things, and I want to call them the same... Like
  in:
 
  foobar :: String - Int - Int
  foobar :: Int - String - Int
 
  (Bad example, but I hope you got the point.)
 
  Is this kind of overloading (instead of the polymorphism based overloading)
  possible in Haskell?  Namely to have two functions with the same name but
  different signatures so they could be distinguished by a call's parameters?
   I fear not...  So I guess I have to name the functions differently, right?
 
  Thanks,
  Daniel


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


[Haskell-cafe] Overloading functions based on arguments?

2009-02-13 Thread Daniel Kraft

Hi,

I just came across a problem like this:  Suppose I've got two related 
functions that do similar things, and I want to call them the same... 
Like in:


foobar :: String - Int - Int
foobar :: Int - String - Int

(Bad example, but I hope you got the point.)

Is this kind of overloading (instead of the polymorphism based 
overloading) possible in Haskell?  Namely to have two functions with the 
same name but different signatures so they could be distinguished by a 
call's parameters?  I fear not...  So I guess I have to name the 
functions differently, right?


Thanks,
Daniel

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


Re: [Haskell-cafe] Overloading functions based on arguments?

2009-02-13 Thread Henning Thielemann

Daniel Kraft wrote:

Hi,

I just came across a problem like this:  Suppose I've got two related 
functions that do similar things, and I want to call them the same... 
Like in:


foobar :: String - Int - Int
foobar :: Int - String - Int

(Bad example, but I hope you got the point.)


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