Re: [Haskell-cafe] Trouble with types

2009-06-02 Thread wren ng thornton

Vladimir Reshetnikov wrote:

Hi Daniel,

Could you please explain what does mean 'monomorphic' in this context?
I thought that all type variables in Haskell are implicitly
universally quantified, so (a - a) is the same type as (forall a. a
- a)


At the top level (i.e. definition level), yes. However, each use site 
this polymorphism may be restricted down (in particular, to the point of 
monomorphism).


In a syntax more like Core, the definition of the identity function is,

id :: forall a. a - a
id @a (x :: a) = x

Where the @ is syntax for reifying types or for capital-lambda 
application (whichever interpretation you prefer). In this syntax it's 
clear to see that |id| (of type forall a. a - a) is quite different 
than any particular |id @a| (of type a-a for the particular @a).



So in your example, there's a big difference between these definitions,

(f,g) = (id,id)

(f', g') @a = (id @a, id @a)

The latter one is polymorphic, but it has interesting type sharing going 
on which precludes giving universally quantified types to f' and g' (the 
universality is for the pair (f',g') and so the types of f' and g' must 
covary). Whereas the former has both fields of the tuple being 
polymorphic (independently).


Both interpretations of the original code are legitimate in theory, but 
the former is much easier to work with and reason about. It also allows 
for tupling definitions as a way of defining local name scope blocks, 
without side effects on types.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Trouble with types

2009-06-01 Thread Vladimir Reshetnikov
Hi,

I tried this code:

---
f, g :: a - a
(f, g) = (id, id)
---

Hugs: OK

GHC:
Couldn't match expected type `forall a. a - a'
   against inferred type `a - a'
In the expression: id
In the expression: (id, id)
In a pattern binding: (f, g) = (id, id)

What does mean this error message?
And what of them (Hugs, GHC) is correct?

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


Re: [Haskell-cafe] Trouble with types

2009-06-01 Thread Daniel Fischer
Am Montag 01 Juni 2009 14:44:37 schrieb Vladimir Reshetnikov:
 Hi,

 I tried this code:

 ---
 f, g :: a - a
 (f, g) = (id, id)
 ---

 Hugs: OK

 GHC:
 Couldn't match expected type `forall a. a - a'
against inferred type `a - a'
 In the expression: id
 In the expression: (id, id)
 In a pattern binding: (f, g) = (id, id)

 What does mean this error message?
 And what of them (Hugs, GHC) is correct?

http://www.haskell.org/ghc/docs/latest/html/users_guide/bugs-and-infelicities.html
Section 12.1.1.4, Declarations and bindings

GHC's typechecker makes all pattern bindings monomorphic by default; this 
behaviour can be 
disabled with -XNoMonoPatBinds. See Section 7.1, “Language options”.

Hugs is correct, it's a known infelicity in GHC which can be disabled.

 Thanks
 Vladimir


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


Re: [Haskell-cafe] Trouble with types

2009-06-01 Thread Vladimir Reshetnikov
Hi Daniel,

Could you please explain what does mean 'monomorphic' in this context?
I thought that all type variables in Haskell are implicitly
universally quantified, so (a - a) is the same type as (forall a. a
- a)

Thank you,
Vladimir

On 6/1/09, Daniel Fischer daniel.is.fisc...@web.de wrote:
 Am Montag 01 Juni 2009 14:44:37 schrieb Vladimir Reshetnikov:
 Hi,

 I tried this code:

 ---
 f, g :: a - a
 (f, g) = (id, id)
 ---

 Hugs: OK

 GHC:
 Couldn't match expected type `forall a. a - a'
against inferred type `a - a'
 In the expression: id
 In the expression: (id, id)
 In a pattern binding: (f, g) = (id, id)

 What does mean this error message?
 And what of them (Hugs, GHC) is correct?

 http://www.haskell.org/ghc/docs/latest/html/users_guide/bugs-and-infelicities.html
 Section 12.1.1.4, Declarations and bindings

 GHC's typechecker makes all pattern bindings monomorphic by default; this
 behaviour can be
 disabled with -XNoMonoPatBinds. See Section 7.1, “Language options”.

 Hugs is correct, it's a known infelicity in GHC which can be disabled.

 Thanks
 Vladimir


 ___
 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] Trouble with types

2007-12-25 Thread Yitzchak Gale
Hi Konstantin,

Here is yet another possible approach:

Perhaps you really meant what you wrote in your definition
of firstFunction - namely, that it needs to be polymorphic,
so that it can convert to _any_ type that is an instance
of SecondClass.

In that case, you might want to add another method to
SecondClass:

class SecondClass a where
   secondConstructor :: Double - a
   secondFunction :: a - Double
instance SecondClass SecondData where
   secondConstructor = SecondData
   secondFunction (SecondData d) = d

Now you can say:

instance FirstClass FirstData where
   firstFunction (FirstData d) = secondConstructor d

In short, it all depends on what exactly you are trying
to do.

Hope this helps,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with types

2007-12-25 Thread Bulat Ziganshin
Hello Konstantin,

Tuesday, December 25, 2007, 8:11:34 AM, you wrote:

 class FirstClass a where
 firstFunction :: (SecondClass b) = a - b

this looks like one more attempt to use OOP thinking in Haskell. look
at http://haskell.org/haskellwiki/OOP_vs_type_classes and especially
papers referenced there

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Trouble with types

2007-12-24 Thread Konstantin Vladimirov
Colleagues!

The essence of trouble may be given by code:

[haskell]
module TypeTrouble where

class FirstClass a where
firstFunction :: (SecondClass b) = a - b

class SecondClass a where
secondFunction :: a - Double

data FirstData = FirstData Double

data SecondData = SecondData Double

instance SecondClass SecondData where
secondFunction (SecondData d) = d

instance FirstClass FirstData where
firstFunction (FirstData d) = SecondData d
[/haskell]

I need, the firstFunction of FirstClass types to return a value of a
SecondClass type. For example SecondData for FirstData, but for some
FirstClass ThirdData, some SecondClass FourthData, etc.

GHC 6.8.1 produces an error:

[quote]
typetrouble.hs:17:31:
Couldn't match expected type `b' against inferred type `SecondData'
`b' is a rigid type variable bound by
the type signature for `firstFunction' at typetrouble.hs:4:31
In the expression: SecondData d
In the definition of `firstFunction':
firstFunction (FirstData d) = SecondData d
In the definition for method `firstFunction'
[/quote]

How can I make this idea work?

-- 
With best regards, Konstantin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with types

2007-12-24 Thread Stefan O'Rear
On Tue, Dec 25, 2007 at 08:11:34AM +0300, Konstantin Vladimirov wrote:
 [haskell]
 module TypeTrouble where
 
 class FirstClass a where
 firstFunction :: (SecondClass b) = a - b
 
 class SecondClass a where
 secondFunction :: a - Double
 [/haskell]
 
 I need, the firstFunction of FirstClass types to return a value of a
 SecondClass type. For example SecondData for FirstData, but for some
 FirstClass ThirdData, some SecondClass FourthData, etc.

The problem, as is often the case, is that that which is unwritten does
not resolve in the way you expect and require it to.

FirstClass' true signature is

class FirstClass a where
firstFunction :: a - forall b. SecondClass b = b

That is to say, any implementation of firstFunction must work for ANY
instance of SecondClass.  But you want SOME, not ANY.  And SOME
(normally notated exists tvar. tspec) is not supported in any known
dialect of Haskell.  It's possible to get fairly close with GHC
Haskell's fundeps / type families:

-- fundep version
class SecondClass b = FirstClass a b where
firstFunction :: a - b
-- type family version
class SecondClass (Cod a) = FirstClass a where
type Cod a :: *
firstFunction :: a - Cod a

It is almost certainly possible to accomplish your goals within
standard Haskell, but the best approach is not obvious at the current
level of detail.

Stefan


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


Re: [Haskell-cafe] Trouble with types

2007-12-24 Thread Antoine Latter
On Dec 25, 2007 12:11 AM, Konstantin Vladimirov
[EMAIL PROTECTED] wrote:

 class FirstClass a where
firstFunction :: (SecondClass b) = a - b


snip!


 instance FirstClass FirstData where
firstFunction (FirstData d) = SecondData d

The problem is that the type of firstFunction as producing a result of
type 'b', where 'b' is *any* type inahbiting the typeclass
SecondClass.

Your definition of firstFunction can produce only *one* of the
inhabitants of SecondClass.  You'd think this would be okay, seeing
as there is only one member of the typeclass, but because anyone can
come along and add a new typeclass instance, you're definition of
firstFunction needs to account for that.

If you're type-classes only ever have one instance, maybe it's easier
to not use them, and go with:

 convert :: FirstData - SecondData
 convert (FirstData d) = SecondData d

But I'm not sure if that suggestion is at all helpful.

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


[Haskell-cafe] Trouble with types

2004-07-23 Thread Kari Pahula
I'm new to Haskell, as you can probably tell...

I have the following data types:

data Real a = Energy a = Energy a deriving (Eq, Ord, Show)

data Real a = HeatC a = HeatC a deriving (Eq, Ord, Show)

data Object h c = Object {energy :: (Energy h), heatc :: (HeatC c)} deriving (Eq, Show)

data Real a = Temp a = Temp a deriving (Eq, Ord, Show)

I'd like to make a function to calculate the temperature of an object.
Physically this is the total heat times the heat capacity.

I tried this with the following:

temp :: (Real a) = Object (Energy a) (HeatC a) - Temp a
temp Object (Energy e) (HeatC c) = Temp e*c

But this fails in hugs with:
ERROR temp.hs:22 - Constructor Object must have exactly 2 arguments in pattern

What's the syntax to use here?  Should I do this in some other way?
Should I use newtype here instead of data?
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with types

2004-07-23 Thread Tomasz Zielonka
On Fri, Jul 23, 2004 at 07:18:28PM +0300, Kari Pahula wrote:
 
 temp :: (Real a) = Object (Energy a) (HeatC a) - Temp a
 temp Object (Energy e) (HeatC c) = Temp e*c

Probably this, but I didn't check:

  temp (Object (Energy e) (HeatC c)) = Temp e*c

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with types

2004-07-23 Thread Jon Fairbairn
On 2004-07-23 at 19:18+0300 Kari Pahula wrote:
 temp :: (Real a) = Object (Energy a) (HeatC a) - Temp a
 temp Object (Energy e) (HeatC c) = Temp e*c
 
 But this fails in hugs with:
 ERROR temp.hs:22 - Constructor Object must have exactly 2 arguments in pattern

You've given temp three arguments: Object, (Energy e) and (HeatC c).

You meant:

 temp (Object (Energy e) (HeatC c)) = Temp e*c

HTH

-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with types

2004-07-23 Thread Tomasz Zielonka
On Fri, Jul 23, 2004 at 06:22:57PM +0200, Tomasz Zielonka wrote:
   temp (Object (Energy e) (HeatC c)) = Temp e*c

temp (Object (Energy e) (HeatC c)) = Temp (e*c)

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Trouble with types

2004-07-23 Thread Stefan Holdermans
Kari,

Others have not mentioned the change required in the type signature yet.

 temp :: (Real a) = Object (Energy a) (HeatC a) - Temp a
 temp Object (Energy e) (HeatC c) = Temp e*c

 temp :: forall a . (Real a) = Object a a - Temp a
 temp (Object (Energy e) (HeatC c)) =  Temp (e * c) 

HTH,

Stefan

 data (Real a) = Energy a = Energy a deriving (Eq, Ord, Show)
 data (Real a) = HeatC a  = HeatC a  deriving (Eq, Ord, Show)
 data (Real a) = Temp a   = Temp a   deriving (Eq, Ord, Show)

 data Object h c   = Object { energy :: Energy h,
  heatc  :: HeatC c
} deriving (Eq, Show)

 main =  let obj = Object { energy = Energy 2.5 
  , heatc  = HeatC 12.0
  }
 in  print (temp obj) -- prints Temp 30.0


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe