
On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio
Dear all, I wrote the following types:
class Transformation t where (<+>) :: t -> SPLModel -> InstanceModel -> InstanceModel
data Configuration = forall t . Transformation t => Configuration (FeatureExpression, [t]) type ConfigurationKnowledge = [Configuration]
I tried to write a function that retrieves the list of transformations of a configuration. Bellow a code snip of such a function.
transformations ck fc = concat [snd c | (Configuration c) <- ck, eval fc (fst c)]
However, compiling this I got:
--- Inferred type is less polymorphic than expected Quantified type variable `t' escapes When checking an existential match that binds c :: (FeatureModel.Types.FeatureExpression, [t]) The pattern(s) have type(s): Configuration The body has type: [t] In a stmt of a list comprehension: (Configuration c) <- ck In the first argument of `concat', namely `[snd c | (Configuration c) <- ck, eval fc (fst c)]'
---
How can I fix this problem?
The problem is that transformations is creating a heterogenous list,
i.e., there is no guarantee that the contents of the list all have the
same type.
You can get around this by declaring a type representing any transformation,
data SomeTransformation = forall t. Transformation t => ST t
and having transformation return a list of those.
However, if Transformation really only has one member function, you'd
be better off eliminating the existential types entirely.
e.g.,
data Configuration = Configuration FeatureExpression (SPLModel ->
InstanceModel -> InstanceModel)
--
Dave Menendez

On Tue, Dec 1, 2009 at 11:21 AM, David Menendez
On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio
wrote: Dear all, I wrote the following types:
class Transformation t where (<+>) :: t -> SPLModel -> InstanceModel -> InstanceModel
data Configuration = forall t . Transformation t => Configuration (FeatureExpression, [t]) type ConfigurationKnowledge = [Configuration]
I would suggest doing away with the class in a case like this. data Transformation = Transformation { (<+>) :: SPLModel -> InstanceModel -> InstanceModel } data Configuration = Configuration FeatureExpression [Transformation] I suspect that it was OO heritage that led you to want a class here? Forget that! :-) Luke

newtype Transformation = Transformation {
(<+>) :: SPLModel -> InstanceModel -> InstanceModel
}
data SelectScenarios = SelectScenarios { scIds :: [Id] }
scenarioTransform scenario = Transformation $ \spl inst -> something
testScenario = SelectScenarios []
test = scenarioTransform testScenario <+> undefined
Don't use typeclasses unless you really need to. Higher-order
functions are usually what you want.
-- ryan
On Tue, Dec 1, 2009 at 3:21 PM, rodrigo.bonifacio
Thanks Luke.
In fact I, will have different implementations of the Transformation type. Something like:
data SelectScenarios = SelectScenarios {
scIds :: [Id]
}
And then I should be able to make SelectScenarios a kind of Transformation. So I think that I really need a class. What do you think about it?
instance Transformation SelectScenario where
(<+>) ....
Regards,
Rodrigo.
Em 01/12/2009 19:39, Luke Palmer < lrpalmer@gmail.com > escreveu:
On Tue, Dec 1, 2009 at 11:21 AM, David Menendez wrote:
On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio wrote:
Dear all, I wrote the following types:
class Transformation t where (<+>) :: t -> SPLModel -> InstanceModel -> InstanceModel
data Configuration = forall t . Transformation t => Configuration (FeatureExpression, [t]) type ConfigurationKnowledge = [Configuration]
I would suggest doing away with the class in a case like this.
data Transformation = Transformation { (<+>) :: SPLModel -> InstanceModel -> InstanceModel }
data Configuration = Configuration FeatureExpression [Transformation]
I suspect that it was OO heritage that l ed you to want a class here? Forget that! :-)
Luke
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Dec 1, 2009 at 4:21 PM, rodrigo.bonifacio
Thanks Luke.
In fact I, will have different implementations of the Transformation type. Something like:
data SelectScenarios = SelectScenarios {
scIds :: [Id]
}
What is this different type buying you? You can never "downcast" to it later.
And then I should be able to make SelectScenarios a kind of Transformation. So I think that I really need a class. What do you think about it?
instance Transformation SelectScenario where
(<+>) ....
So instead of making a type and an instance, just implement it directly as a Transformation: selectScenario :: [Id] -> Transformation selectScenario ids = Transformation { (<+>) = {- whatever implementation you gave for (<+>) above, using ids -} } If the only purpose of SelectScenario (your type) is to be used polymorphically as a Transformation, then this approach is isomorphic -- i.e. anything you can do with the existential type trick you can do with this approach. If SelectScecario is used for other purposes, then give an explicit cast function toTransformation :: SelectScenario -> Transformation toTransformation (SelectScenario ids) = Transformation { (<+>) = {- implementation of (<+>) just as if it were a class method -} } Existential types only buy you power when the quantified variable appears more than once on the right hand side, for example: forall a. Num a => (a,a). But even those can usually be factored out into more direct representations (I seem to recall Oleg has a proof that they always can, actually). Luke

On Tue, Dec 1, 2009 at 4:44 PM, Luke Palmer
Existential types only buy you power when the quantified variable appears more than once on the right hand side, for example: forall a. Num a => (a,a). But even those can usually be factored out into more direct representations (I seem to recall Oleg has a proof that they always can, actually).
You are probably right that there is an encoding that doesn't use existentials, but I've found they can be very useful in a few situations, such as: data Step s a = Done | Yield s a | Skip s data Stream a = forall s. Stream s (s -> Step s a) Here the type of the stream state is encapsulated and not accessible to the outside world, but it can still get some values of that type via the result of the Step function. data Expr a where ... App :: Expr (a -> b) -> Expr a -> Expr b Here we quantify over the type of the argument "a"; we just know that we have an expression of that type and an expression of the function type it wants. -- ryan
participants (4)
-
David Menendez
-
Luke Palmer
-
rodrigo.bonifacio
-
Ryan Ingram