Trouble with DataKinds - haskell

I have created a very simple example of a problem I'm having using GADTs and DataKinds. My real application is obviously more complicated but this captures the essence of my situation clearly. I'm trying to create a function that can return any of the values (T1, T2) of type Test. Is there a way to accomplish this or am I getting into the realm of dependent types? The questions here seem similar but I could not find (or comprehend) an answer to my question from them. I'm just starting to understand these GHC extensions. Thanks.
similar question 1
similar question 2
{-# LANGUAGE GADTs, DataKinds, FlexibleInstances, KindSignatures #-}
module Test where
data TIdx = TI | TD
data Test :: TIdx -> * where
T1 :: Int -> Test TI
T2 :: Double -> Test TD
type T1 = Test TI
type T2 = Test TD
prob :: T1 -> T2 -> Test TIdx
prob x y = undefined
----Here is the error----
Test.hs:14:26:
Kind mis-match
The first argument of `Test' should have kind `TIdx',
but `TIdx' has kind `*'
In the type signature for `prob': prob :: T1 -> T2 -> Test TIdx

The error message you get is because the type parameter to Test needs to
have the kind TIdx, but the only types that have that kind are TI and TD.
The type TIdx has the kind *.
If I understood correctly what you are trying to express is that the result
type of prob is either Test TI or Test TD, but the actual type is
determined at runtime. However, this won't work directly. The return type
generally has to be known at compile time.
What you can do, since the GADT constructors each map to specific phatom type of kind TIdx, is to return a result that erases the phantom type with an
existential or another GADT and then recover the type later using a pattern
match.
For example, if we define two functions that require a specific kind of Test:
fun1 :: T1 -> IO ()
fun1 (T1 i) = putStrLn $ "T1 " ++ show i
fun2 :: T2 -> IO ()
fun2 (T2 d) = putStrLn $ "T2 " ++ show d
This type-checks:
data UnknownTest where
UnknownTest :: Test t -> UnknownTest
prob :: T1 -> T2 -> UnknownTest
prob x y = undefined
main :: IO ()
main = do
let a = T1 5
b = T2 10.0
p = prob a b
case p of
UnknownTest t#(T1 _) -> fun1 t
UnknownTest t#(T2 _) -> fun2 t
The notable thing here is that in the case-expression, even though the
UnknownTest GADT has erased the phantom type, the T1 and T2 constructors give enough
type information to the compiler that t recovers its exact type Test TI or
Test TD within the branch of the case-expression, allowing us to e.g. call
functions that expect those specific types.

You have two options here. Either you can infer the type of the return value from the types of arguments or you can't.
In the former case, you refine the type:
data Which :: TIdx -> * where
Fst :: Which TI
Snd :: Which TD
prob :: Which i -> T1 -> T2 -> Test i
prob Fst x y = x
prob Snd x y = y
In the latter case, you have to erase the type information:
prob :: Bool -> T1 -> T2 -> Either Int Double
prob True (T1 x) y = Left x
prob False x (T2 y) = Right y
You can also erase the type information by using an existential type:
data SomeTest = forall i . SomeTest (Test i)
prob :: Bool -> T1 -> T2 -> SomeTest
prob True x y = SomeTest x
prob False x y = SomeTest y
In this case, you cannot do anything interesting with a value of SomeTest, but you might be able in your real example.

Related

Is there a way to bind the supressed type variable of an existential data type during pattern matching?

Using GADTs, I have defined a depth-indexed tree data type (2–3 tree). The depth is there to statically ensure that the trees are balanced.
-- Natural numbers
data Nat = Z | S Nat
-- Depth-indexed 2-3 tree
data DT :: Nat -> Type -> Type where
-- Pattern of node names: N{#subtrees}_{#containedValues}
N0_0 :: DT Z a
N2_1 :: DT n a -> a -> DT n a
-> DT (S n) a
N3_2 :: DT n a -> a -> DT n a -> a -> DT n a
-> DT (S n) a
deriving instance Eq a => Eq (DT n a)
Now, some operations (e.g. insertion) might or might not change the depth of the tree. So I want to hide it from the type signature. I do this using existential data types.
-- 2-3 tree
data T :: Type -> Type where
T :: {unT :: DT n a} -> T a
insert :: a -> T a -> T a
insert x (T dt) = case dt of
N0_0 -> T $ N2_1 N0_0 x N0_0
{- ... -}
So far so good. My problem is:
I don't see how I can now define Eq on T.
instance Eq a => Eq (T a) where
(T x) == (T y) = _what
Obviously, I would like to do something like this:
(T {n = nx} x) == (T {n = ny} y)
| nx == ny = x == y
| otherwise = False
I don't know how / whether I can bind the type variables in the patter match. And I am neither sure how to compare them once I get them.
(I suspect Data.Type.Equality is for this, but I haven't seen any example of it in use.)
So, is there a way to implement the Eq (T a) instance, or is there some other approach that is recommended in this case?
You should write a depth-independent equality operator, which is able to compare two trees even if they have different depths n and m.
dtEq :: Eq a => DT n a -> DT m a -> Bool
dtEq N0_0 N0_0 = True
dtEq (N2_1 l1 x1 r1) (N2_1 l2 x2 r2) =
dtEq l1 l2 && x1 == x2 && dtEq r1 r2
dtEq (N3_2 a1 x1 b1 y1 c1) (N3_2 a2 x2 b2 y2 c2) =
dtEq a1 a2 && x1 == x2 && dtEq b1 b2 && y1 == y2 && dtEq c1 c2
dtEq _ _ = False
Then, for your existential type:
instance Eq a => Eq (T a) where
(T x) == (T y) = dtEq x y
Even if in the last line the depths are unknown (because of the existential), it won't matter for dtEq since it can accept any depth.
Minor side note: dtEq exploits polymorphic recursion, in that recursive calls can use a different depth from the one in the original call. Haskell allows polymorphic recursion, as long as an explicit type signature is provided. (We need one anyway, since we are using GADTs.)
You could use Data.Coerce.coerce to compare the contents of the trees: as long as you label the depth parameter as phantom, it should be willing to give you coerce :: DT n a -> DT m a.
But this doesn't really solve the problem, of course: you want to know if their types are the same. Well, maybe there is some solution with Typeable, but it doesn't sound like much fun. Absent Typeable, it seems impossible to me, because you want two contradictory things.
First, you want that trees of different depths should be separate types, not intermixable at all. This means everyone who handles them has to know what type they are.
Second, you want that you can give such a tree to someone without telling them how deep it is, have them munge it around arbitrarily, and then give it back to you. How can they do that, if you require type knowledge to operate on them?
Existentials do not "suppress" type information: they throw it away. Like all type information, it is gone at runtime; and you've made it invisible at compile time too.
I'm also not sure your problem is just with Eq: how will you even implement functions like insert? It's easy for N0_0, because that is known to have type DT Z a, but for the other cases I don't see how you will construct a DT (S n) a to wrap in your T when you can't know what n was.

Unexpected caching behavior using polymorphic records in Haskell

I've run into some unexpected behavior using polymorphic records in Haskell, where some values are not cached when I expect them to be cached.
Here is a minimal example:
{-# LANGUAGE RankNTypes #-}
import Debug.Trace
-- Prints out two "hello"s
data Translation = Trans { m :: forall a . Floating a => a }
g :: Floating a => a -> a
g x = x + 1
f :: Floating a => a -> a
f x = trace "hello" $ x - 2.0
-- Only one "hello"
-- data Translation = Trans { m :: Float }
--
-- f :: Float -> Float
-- f x = trace "hello" $ x - 2.0
main :: IO ()
main = do
let trans = Trans { m = f 1.5 }
putStrLn $ show $ m trans
putStrLn $ show $ m trans
In the example, I thought if the value f 1.5 was computed and stored in the field m, on the next time it is accessed, it would not be computed again. However, it seems to be recomputed on every access to the record field, as shown by the fact that "hello" is printed twice.
On the other hand, if we remove the polymorphism from the field, the value is cached as expected, and "hello" is only printed once.
I suspect this is due to the interaction of typeclasses (being treated as records) preventing memoization. However, I don't fully understand why.
I realized that compiling with -O2 makes the problem go away, however, this behavior occurs in a much larger system where compiling with -O2 does not seem to have any effect, therefore I'd like to understand the root cause of the problem, so I can fix the performance issues in the larger system.
Hold my beer.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ConstraintKinds #-}
import Debug.Trace
data Dict c where Dict :: c => Dict c
-- An isomorphism between explicit dictionary-passing style (Dict c -> a)
-- and typeclass constraints (c => a) exists:
from :: (c => a) -> (Dict c -> a)
from v Dict = v
to :: (Dict c -> a) -> (c => a)
to f = f Dict
data Translation = Trans { m :: forall a . Floating a => a }
f1, f2 :: Dict (Floating a) -> a -> a
f1 = trace "hello" $ \Dict x -> x - 2.0
f2 = \Dict -> trace "hello" $ \x -> x - 2.0
main = do
let trans1 = Trans { m = to (flip f1 1.5) }
trans2 = Trans { m = to (flip f2 1.5) }
putStrLn "trans1"
print (m trans1)
print (m trans1)
putStrLn "trans2"
print (m trans2)
print (m trans2)
Take a second to predict what this will output before you run it. Then go ask your GHC if she agrees with your guess.
Clear as mud?
The basic distinction you need to draw here is right here in this significantly simplified example:
> g = trace "a" $ \() -> trace "b" ()
> g ()
a
b
()
> g ()
b
()
There is a separate notion of caching a function and caching its output. The latter is, simply, never done in GHC (though see discussion of what's going on with your optimized version below). The former may sound dumb, but it in fact is not so dumb as you might think; you could imagine writing a function which is, say, id if the collatz conjecture is true and not otherwise. In such a situation, it makes complete sense to only test the collatz conjecture once, and then cache whether we should behave as id or not forever afterwards.
Once you understand this basic fact, the next leap you must believe is that in GHC, typeclass constraints are compiled to functions. (The arguments to the function are typeclass dictionaries telling how each of the typeclass' methods behave.) GHC itself manages constructing and passing these dictionaries around for you, and in most cases it's quite transparent to the user.
But the upshot of this compilation strategy is this: a polymorphic but typeclass-constrained type is a function even if it doesn't appear to have function arrows in it. That is,
f 1.5 :: Floating a => a
looks like a plain old value; but in fact it is a function which takes a Floating a dictionary and produces a value of type a. So any computations that go into computing the value a are redone afresh each time this function is applied (read: used at a specific monomorphic type) because, after all, the precise value chosen depends critically on how the typeclass' methods behave.
This leaves only the question of why optimizations changed things in your situation. There I believe what happened is called "specialization", in which the compiler will try to notice when polymorphic things get used at a statically-known monomorphic type and make a binding for that. It goes something like this:
-- starting point
main = do
let trans = \dict -> trace "hello" $ minus dict (fromRational dict (3%2)) (fromRational dict (2%1))
print (trans dictForDouble)
print (trans dictForDouble)
-- specialization
main = do
let trans = \dict -> trace "hello" $ minus dict (fromRational dict (3%2)) (fromRational dict (2%1))
let transForDouble = trans dictForDouble
print transForDouble
print transForDouble
-- inlining
main = do
let transForDouble = trace "hello" $ minus dictForDouble (fromRational dict (3%2)) (fromRational dictForDouble (2%1))
print transForDouble
print transForDouble
In this last one the function-ness is gone; it is "as if" GHC has cached the output of trans when applied to the dictionary dictForDouble. (If you compile with optimizations and -ddump-simpl you will see it goes even further, doing constant-propagation to turn the minus ... stuff into just D# -0.5##. Whew!)
{-# LANGUAGE RankNTypes #-}
import Debug.Trace
--Does not get cached
data Translation = Trans { m :: forall a. Floating a => a }
f :: Floating a => a -> a
f x = trace "f" $ x - 2.0
Since a is a rigid type variable bound by a type expected by the context
forall a. Floating a => a you would have to cache the context as well
--Does get cached
data Translation' = Trans' { m' :: Float }
f' :: Float -> Float
f' x = trace "f'" $ x - 2.0
Since this is a value of type Float it can be computed once and cached afterwards.
main :: IO ()
main = do
let
trans = Trans { m = f 1.5 }
trans' = Trans' { m' = f' 1.5}
putStrLn $ show $ (m trans :: Double)
putStrLn $ show $ (m trans :: Float)
-- ^ you can evaluate it with 2 different contexts
putStrLn $ show $ (m' trans' :: Float)
putStrLn $ show $ (m' trans' :: Float)
-- ^ context fixed
Note that the former one does not get cached whether compiler optimization is turned on or off.
When they are both Float and you turn on optimization the problem is gone.
If you compile the larger system with optimization and it is to inefficient on some metric I would suspect that the problem lies somewhere else.

How to use the same record selector two ways within a function? Lenses?

I have some data that have different representations based on a type parameter, a la Sandy Maguire's Higher Kinded Data. Here are two examples:
wholeMyData :: MyData Z
wholeMyData = MyData 1 'w'
deltaMyData :: MyData Delta
deltaMyData = MyData Nothing (Just $ Left 'b')
I give some of the implementation details below, but first the actual question.
I often want to get a field of the data, usually via a local definition like:
let x = either (Just . Left . myDataChar) myDataChar -- myDataChar a record of MyData
It happens so often I would like to make a standard combinator,
getSubDelta :: ( _ -> _ ) -> Either a b -> Maybe (Either c d)
getSubDelta f = either (Just . Left . f) f
but filling in that signature is problematic. The easy solution is to just supply the record selector function twice,
getSubDelta :: (a->c) -> (b->d) -> Either a b -> Maybe (Either c d)
getSubDelta f g = either (Just . Left . f) g
but that is unseemly. So my question. Is there a way I can fill in the signature above? I'm assuming there is probably a lens based solution, what would that look like? Would it help with deeply nested data? I can't rely on the data types always being single constructor, so prisms? Traversals? My lens game is weak, so I was hoping to get some advice before I proceed.
Thanks!
Some background. I defined a generic method of performing "deltas", via a mix of GHC.Generics and type families. The gist is to use a type family in the definition of the data type. Then, depending how the type is parameterized, the records will either represent whole data or a change to existing data.
For instance, I define the business data using DeltaPoints.
MyData f = MyData { myDataInt :: DeltaPoint f Int
, myDataChar :: DeltaPoint f Char} deriving Generic
The DeltaPoints are implemented in the library, and have different forms for Delta and Z states.
data DeltaState = Z | Delta deriving (Show,Eq,Read)
type family DeltaPoint (st :: DeltaState) a where
DeltaPoint Z a = a
DeltaPoint Delta a = Maybe (Either a (DeltaOf a))
So a DeltaPoint Z a is just the original data, a, and a DeltaPoint Delta a, may or may not be present, and if it is present will either be a replacement of the original (Left) or an update (DeltaOf a).
The runtime delta functionality is encapsulated in a type class.
class HasDelta a where
type DeltaOf a
delta :: a -> a -> Maybe (Either a (DeltaOf a))
applyDeltaOf :: a -> DeltaOf a -> Maybe a
And with the use of Generics, I can usually get the delta capabilities with something like:
instance HasDelta (MyData Z) where
type (DeltaOf (MyData Z)) = MyData Delta
I think you probably want:
{-# LANGUAGE RankNTypes #-}
getSubDelta :: (forall f . (dat f -> DeltaPoint f fld))
-> Either (dat Z) (dat Delta)
-> Maybe (Either (DeltaPoint Z fld) (DeltaOf fld))
getSubDelta sel = either (Just . Left . sel) sel
giving:
x :: Either (MyData Z) (MyData Delta)
-> Maybe (Either (DeltaPoint Z Char) (DeltaOf Char))
x = getSubDelta myDataChar
-- same as: x = either (Just . Left . myDataChar) myDataChar

Composing Stateful functions in Haskell

What is the simplest Haskell library that allows composition of stateful functions?
We can use the State monad to compute a stock's exponentially-weighted moving average as follows:
import Control.Monad.State.Lazy
import Data.Functor.Identity
type StockPrice = Double
type EWMAState = Double
type EWMAResult = Double
computeEWMA :: Double -> StockPrice -> State EWMAState EWMAResult
computeEWMA α price = do oldEWMA <- get
let newEWMA = α * oldEWMA + (1.0 - α) * price
put newEWMA
return newEWMA
However, it's complicated to write a function that calls other stateful functions.
For example, to find all data points where the stock's short-term average crosses its long-term average, we could write:
computeShortTermEWMA = computeEWMA 0.2
computeLongTermEWMA = computeEWMA 0.8
type CrossingState = Bool
type GoldenCrossState = (CrossingState, EWMAState, EWMAState)
checkIfGoldenCross :: StockPrice -> State GoldenCrossState String
checkIfGoldenCross price = do (oldCrossingState, oldShortState, oldLongState) <- get
let (shortEWMA, newShortState) = runState (computeShortTermEWMA price) oldShortState
let (longEWMA, newLongState) = runState (computeLongTermEWMA price) oldLongState
let newCrossingState = (shortEWMA < longEWMA)
put (newCrossingState, newShortState, newLongState)
return (if newCrossingState == oldCrossingState then
"no cross"
else
"golden cross!")
Since checkIfGoldenCross calls computeShortTermEWMA and computeLongTermEWMA, we must manually wrap/unwrap their states.
Is there a more elegant way?
If I understood your code correctly, you don't share state between the call to computeShortTermEWMA and computeLongTermEWMA. They're just two entirely independent functions which happen to use state internally themselves. In this case, the elegant thing to do would be to encapsulate runState in the definitions of computeShortTermEWMA and computeLongTermEWMA, since they're separate self-contained entities:
computeShortTermEWMA start price = runState (computeEWMA 0.2 price) start
All this does is make the call site a bit neater though; I just moved the runState into the definition. This marks the state a local implementation detail of computing the EWMA, which is what it really is. This is underscored by the way GoldenCrossState is a different type from EWMAState.
In other words, you're not really composing stateful functions; rather, you're composing functions that happen to use state inside. You can just hide that detail.
More generally, I don't really see what you're using the state for at all. I suppose you would use it to iterate through the stock price, maintaining the EWMA. However, I don't think this is necessarily the best way to do it. Instead, I would consider writing your EWMA function over a list of stock prices, using something like a scan. This should make your other analysis functions easier to implement, since they'll just be list functions as well. (In the future, if you need to deal with IO, you can always switch over to something like Pipes which presents an interface really similar to lists.)
There is really no need to use any monad at all for these simple functions. You're (ab)using the State monad to calculate a one-off result in computeEWMA when there is no state involved. The only line that is actually important is the formula for EWMA, so let's pull that into it's own function.
ewma :: Double -> Double -> Double -> Double
ewma a price t = a * t + (1 - a) * price
If you inline the definition of State and ignore the String values, this next function has almost the exact same signature as your original checkIfGoldenCross!
type EWMAState = (Bool, Double, Double)
ewmaStep :: Double -> EWMAState -> EWMAState
ewmaStep price (crossing, short, long) =
(crossing == newCrossing, newShort, newLong)
where newCrossing = newShort < newLong
newShort = ewma 0.2 price short
newLong = ewma 0.8 price long
Although it doesn't use the State monad, we're certainly dealing with state here. ewmaStep takes a stock price, the old EWMAState and returns a new EWMAState.
Now putting it all together with scanr :: (a -> b -> b) -> b -> [a] -> [b]
-- a list of stock prices
prices = [1.2, 3.7, 2.8, 4.3]
_1 (a, _, _) = a
main = print . map _1 $ scanr ewmaStep (False, 0, 0) prices
-- [False, True, False, True, False]
Because fold* and scan* use the cumulative result of previous values to compute each successive one, they are "stateful" enough that they can often be used in cases like this.
In this particular case, you have a y -> (a, y) and a z -> (b, z) that you want to use to compose a (x, y, z) -> (c, (x, y, z)). Having never used lens before, this seems like a perfect opportunity.
In general, we can promote a stateful operations on a sub-state to operate on the whole state like this:
promote :: Lens' s s' -> StateT s' m a -> StateT s m a
promote lens act = do
big <- get
let little = view lens big
(res, little') = runState act little
big' = set lens little' big
put big'
return res
-- Feel free to golf and optimize, but this is pretty readable.
Our lens a witness that s' is a sub-state of s.
I don't know if "promote" is a good name, and I don't recall seeing this function defined elsewhere (but it's probably already in lens).
The witnesses you need are named _2 and _3 in lens so, you could change a couple of lines of code to look like:
shortEWMA <- promote _2 (computeShortTermEWMA price)
longEWMA <- promote _3 (computeLongTermEWMA price)
If a Lens allows you to focus on inner values, maybe this combinator should be called blurredBy (for prefix application) or obscures (for infix application).
With a little type class magic, monad transformers allow you to have nested transformers of the same type. First, you will need a new instance for MonadState:
{-# LANGUAGE
UndecidableInstances
, OverlappingInstances
#-}
instance (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) where
state f = lift (state f)
Then you must define your EWMAState as a newtype, tagged with the type of term (alternatively, it could be two different types - but using a phantom type as a tag has its advantages):
data Term = ShortTerm | LongTerm
type StockPrice = Double
newtype EWMAState (t :: Term) = EWMAState Double
type EWMAResult = Double
type CrossingState = Bool
Now, computeEWMA works on an EWMASTate which is polymorphic in term (the afformentioned example of tagging with phantom types), and in monad:
computeEWMA :: (MonadState (EWMAState t) m) => Double -> StockPrice -> m EWMAResult
computeEWMA a price = do
EWMAState old <- get
let new = a * old + (1.0 - a) * price
put $ EWMAState new
return new
For specific instances, you give them monomorphic type signatures:
computeShortTermEWMA :: (MonadState (EWMAState ShortTerm) m) => StockPrice -> m EWMAResult
computeShortTermEWMA = computeEWMA 0.2
computeLongTermEWMA :: (MonadState (EWMAState LongTerm) m) => StockPrice -> m EWMAResult
computeLongTermEWMA = computeEWMA 0.8
Finally, your function:
checkIfGoldenCross ::
( MonadState (EWMAState ShortTerm) m
, MonadState (EWMAState LongTerm) m
, MonadState CrossingState m) =>
StockPrice -> m String
checkIfGoldenCross price = do
oldCrossingState <- get
shortEWMA <- computeShortTermEWMA price
longEWMA <- computeLongTermEWMA price
let newCrossingState = shortEWMA < longEWMA
put newCrossingState
return (if newCrossingState == oldCrossingState then "no cross" else "golden cross!")
The only downside is you have to explicitly give a type signature - in fact, the instance we introduced at the beginning has ruined all hopes of good type errors and type inference for cases where you have multiple copies of the same transformer in a stack.
Then a small helper function:
runState3 :: StateT a (StateT b (State c)) x -> a -> b -> c -> ((a , b , c) , x)
runState3 sa a b c = ((a' , b', c'), x) where
(((x, a'), b'), c') = runState (runStateT (runStateT sa a) b) c
and:
>runState3 (checkIfGoldenCross 123) (shortTerm 123) (longTerm 123) True
((EWMAState 123.0,EWMAState 123.0,False),"golden cross!")
>runState3 (checkIfGoldenCross 123) (shortTerm 456) (longTerm 789) True
((EWMAState 189.60000000000002,EWMAState 655.8000000000001,True),"no cross")

GADTs or phantom types to type-check function calls but keep homogeneity of type

I assume the following problem can be solved using type arithmetic but haven't found the solution yet.
Problem
I have a finite map from strings to values (using Tries as implementation) that I parse from a binary/text file (json, xml, ...).
type Value = ...
type Attributes = Data.Trie Value
data Object = Object Attributes
Each map has the same type of values but not the same set of keys.
I group maps with the same set of keys together to be able to prevent having to type-switch all the time I have a specialised function that requires certain keys:
data T1
data T2
...
data Object a where
T1 :: Attributes -> Object T1
T2 :: Attributes -> Object T2
...
This allows me to write something like:
f1 :: Object T1 -> ...
instead of
f1 :: Object ->
f1 o | check_if_T1 o = ...
This works but has two disadvantages:
Homogeneous lists of Object now become heterogeneous, i.e. I cannot have a list [Object] anymore.
I need to write a lot of boilerplate to get/set attributes:
get :: Object a -> Attributes
get (T1 a) = a
get (T2 a) = a
...
Question
Is there a better way to specialise functions depending on the constructor of an ADT?
How could I regain the ability to have a list [Object]? Is there a specialized version of Dynamic that only allows certain types?
I thought about wrapping the Object again, but this would add a lot of boilerplate. For instance,
data TObject = TT1 T1 | TT2 T2 ...
What I need is:
get :: a -> TObject -> Object a
So that I can then derive:
collect :: a -> [TObject] -> [Object a]
I looked into HList but I don't think it fits my problem. Especially, since the order of types in [Object] is not known at compile time.
It sounds to me like this can be solved using functional dependency / type arithmetic but I simply haven't found a nice way yet.
If all the constructors return a monomorphic Object type and there's no recursion, you might want to think about just using separate types. Instead of
data T1
data T2
data Object a where
T1 :: Attributes -> Object T1
T2 :: Attributes -> Object T2
consider
data T1 = T1 Attributes
data T2 = T2 Attributes
Dynamic is one way, and using the above you could just add deriving Typeable and be done. Alternately, you can do it by hand:
data TSomething = It's1 T1 | It's2 T2
getT1s :: [TSomething] -> [T1]
getT2s :: [TSomething] -> [T2]
getT1s xs = [t1 | It's1 t1 <- xs]
getT2s xs = [t2 | It's2 t2 <- xs]
As you say, this involves a bit of boilerplate. The Typeable version looks a bit nicer:
deriving Typeable T1
deriving Typeable T2
-- can specialize at the call-site to
-- getTs :: [Dynamic] -> [T1] or
-- getTs :: [Dynamic] -> [T2]
getTs :: Typeable a => [Dynamic] -> [a]
getTs xs = [x | Just x <- map fromDynamic xs]

Resources