[Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread s9gf4ult
Hello, haskellers. I am trying to write some generic subtyping issue. Here 
upcast is always safe operation because of subtype is always behaves like the 
parrent type. downcast is not the safe becase of not every parrent type value 
can be converted to children type. Rangeable here is the typeclass of values 
in some range, so downcasting to Rang1 or Range2 or any other type, having 
instance for Rangeable can be done by checking if value is in proper range. 
The same for MultipleTo, downcasting can be done with checking if value is 
multiple to some value.

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies, 
FlexibleContexts, UndecidableInstances, OverlappingInstances, 
IncoherentInstances #-}

class SubtypeOf a b | a - b where
  upcast :: a - b
  downcastSafe :: b - Maybe a
  downcast :: b - a
  downcast b = case downcastSafe b of
Nothing - error $ can not downcast the value
Just a - a

class (Ord a) = Rangable t a | t - a where
  lowLim :: t - a
  highLim :: t - a

class Packable t a | t - a where
  pack :: a - t
  unpack :: t - a

class MultipleTo t a | t - a where
  multiple :: t - a
  
instance (Num a, Ord a, Rangable range a, Packable range a) = SubtypeOf range 
a where
  upcast = unpack
  downcastSafe b | b = (lowLim $ pb)  b = (highLim $ pb) = Just $ pb
 | otherwise = Nothing
where
  pb = pack b

instance (Integral a, Packable range a, MultipleTo range a) = SubtypeOf range 
a where
  upcast = unpack
  downcastSafe b | b `mod` (multiple pb) == 0 = Just pb
 | otherwise = Nothing
where
  pb = pack b

newtype Range1 a = Range1 {unRange1 :: a}
 deriving Show

instance (Num a, Ord a) = Rangable (Range1 a) a where
  lowLim _ = 0
  highLim _ = 10

instance (Num a, Ord a) = Packable (Range1 a) a where
  pack = Range1
  unpack = unRange1

newtype Range2 a = Range2 {unRange2 :: a}
   deriving Show

instance (Num a, Ord a) = Rangable (Range2 a) a where
  lowLim _ = -10
  highLim _ = 200

instance (Num a, Ord a) = Packable (Range2 a) a where
  pack = Range2
  unpack = unRange2

but there is compilation error:

Duplicate instance declarations:
  instance [incoherent] (Num a, Ord a, Rangable range a,
 Packable range a) =
SubtypeOf range a
-- Defined at ...:22:10
  instance [incoherent] (Integral a, Packable range a,
 MultipleTo range a) =
SubtypeOf range a
-- Defined at ...:29:10
Failed, modules loaded: none.

If I remove one of instances of SubtypeOf the program is compiling. How to 
write this instances properly, or to write proper type casting ?

Thanks

PS. My english is not very good, but I hope this is understandable.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread Brandon Allbery
On Fri, Jan 25, 2013 at 3:18 PM, s9gf4...@gmail.com wrote:

 Duplicate instance declarations:

 instance [incoherent] (Num a, Ord a, Rangable range a,

 Packable range a) =

 SubtypeOf range a

 -- Defined at ...:22:10

 instance [incoherent] (Integral a, Packable range a,

 MultipleTo range a) =

 SubtypeOf range a

 -- Defined at ...:29:10


This would be correct.  Constraints on an instance are applied *after* the
instance is selected, so when Haskell is looking for an instance, these two
are identical.

This has the code smell of trying to use typeclasses for OOP.  That won't
work.  (Yes, really.)

-- 
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] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread s9gf4ult
 This has the code smell of trying to use typeclasses for OOP.  That won't 
work.  (Yes, really.)

I am not trying to use OOP, I am just writing some typecasting at all. 

 This would be correct.  Constraints on an instance are applied *after* the 
instance is selected, so when Haskell is looking for an instance, these two 
are identical.

I didn't understand why these two instances are identical ? The constraints 
are different and OverlappingInstances should permit overlapping typeclasses 
in constraints and select more specific instance clause.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread s9gf4ult
http://ideone.com/v2CrAm

I has posted to ideone to show what is wrong.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to escape from typecheck error: Duplicate instance declarations ?

2013-01-25 Thread Alexander Solla
On Fri, Jan 25, 2013 at 12:39 PM, s9gf4...@gmail.com wrote:

 **

  This has the code smell of trying to use typeclasses for OOP.  That
 won't work.  (Yes, really.)



 I am not trying to use OOP, I am just writing some typecasting at all.



  This would be correct.  Constraints on an instance are applied *after*
 the instance is selected, so when Haskell is looking for an instance, these
 two are identical.



 I didn't understand why these two instances are identical ? The
 constraints are different and OverlappingInstances should permit
 overlapping typeclasses in constraints and select more specific instance
 clause.


They are identical because constraints don't count for deciding that a
type is in a class.   For the purposes of deciding if a type is in a class,

instance Foo (Bar a)
instance Fizz a = Foo (Bar a)
instance Fuzz a = Foo (Bar a)

are exactly the same, and all three are therefore overlapping instances.
 None is more specific, because they all refer to the same type -- (Bar a).

Also, you can just use Typeable instead of that downcasting stuff.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe