Nice! Moreover the "real implementation" can use standalone deriving:
```
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
import Data.Function
data IsNormalized = Normalized | NotNormalized
data Sum (e :: IsNormalized)
= Value Int
| Sum (Sum e) (Sum e)
deriving (Show)
normalize :: Sum a -> Sum Normalized
normalize (Value i) = Value i
normalize (Sum (Value i) b) = Sum (Value i) (normalize b)
normalize (Sum (Sum x y) b) = normalize (Sum x (Sum y b))
instance Eq (Sum NotNormalized) where
(==) = (==) `on` normalize
deriving instance Eq (Sum Normalized)
sample1 :: Sum NotNormalized
sample1 = Value 10 `Sum` (Value 11 `Sum` Value 12)
sample2 :: Sum NotNormalized
sample2 = (Value 10 `Sum` Value 11) `Sum` Value 12
test = sample1 == sample2
-- True
```
What about phantom types?
{-# LANGUAGE KindSignatures, DataKinds #-} data IsNormalized = Normalized | NotNormalized data Sum (n :: IsNormalized) = Value Int | Sum (Sum n) (Sum n)You could still say
instance MyClass (Sum n) where…but you could also write
normalizeSum :: Sum NotNormalized -> Sum Normalized -- or even create a class with two inhabitants for this instance Eq (Sum NotNormalized) where (==) = (==) `on` normalizeSum instance Eq (Sum Normalized) where … -- real implementationIt's not ideal. For example if you want to sort a list, it would still be better to normalize the whole list before sorting, but at least you could still use the other operators afterwards without a "denormalization" step. So maybe it would help reduce some boilerplate?
Cheers,
MarLinn
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.