Cons of -XUndecidableInstances

According to the haskell-prime wiki[1], -XUndecidableInstances removes checks on the form of instance declaration, and just impose a depth limit to ensure termination (of compilation, I assume?). The listed Con is that this removes the clear boundary between legal and illegal programs, and behaviour may be implementation-dependent as the edge of that boundary is reached. How can I tell when I'm nearing that boundary? (And where are the sorts of things GHC does with types documented? I can't seem to find any good explanation of these things.) More specifically, I have class Model m a | m -> a where ... class Entropy d where ... instance (Model m a) => Entropy m where ... The first line requires MultiParamTypeClasses and FunctionalDependencies (the two seem to go together) - the third requires UndecidableInstances (since the type variable 'a' appears on the left but not the right). Is this likely to cause a problem? My guess is it shouldn't, since it's equivalent to class Model m a | m -> a where ... class Entropy d a where ... instance (Model m a) => Entropy m a where ... without bothering to actually use 'a' in Entropy - but one never knows... (Actually, a third type variable has to be introduced to Entropy to remove the UndecidableInstances dependency - "Constraint is no smaller than the instance head". This only increases the illogic in my humble eyes. These examples seem simple enough for GHC to handle nicely...) [1] http://hackage.haskell.org/trac/haskell-prime/wiki/UndecidableInstances -- Scott Lawrence

On Mon, Jun 6, 2011 at 00:26, Scott Lawrence
According to the haskell-prime wiki[1], -XUndecidableInstances removes checks on the form of instance declaration, and just impose a depth limit to ensure termination (of compilation, I assume?). The listed Con is that this removes the clear boundary between legal and illegal programs, and behaviour may be implementation-dependent as the edge of that boundary is reached. How can I tell when I'm nearing that boundary? (And where are the sorts of things GHC does with types
You can't; that's more or less the definition of that limit. The informal definition of -XUndecidableInstances is "allow things which could lead to the typechecker trying to solve the Halting Problem". So yes, it's fairly conservative without that option because the only types allowed are those that it can prove ahead of time will terminate (a much smaller set than that of types that will terminate).

Scott Lawrence wrote:
More specifically, I have
class Model m a | m -> a where ... class Entropy d where ... instance (Model m a) => Entropy m where ...
The first line requires MultiParamTypeClasses and FunctionalDependencies... the third requires UndecidableInstances... Is this likely to cause a problem?
Yes. You almost never want to use UndecidableInstances when writing practical programs in Haskell. When GHC tells you that you need them, it almost always means that your types are poorly designed, usually due to influence from previous experience with OOP. Your best bet is to step back and think again about the problem you are trying to solve. What is the best way to formulate the problem functionally? That will lead you in the right direction. Please feel free to share more details about what you are trying to do. We would be happy to help you work out some good directions. Regards, Yitz

On Mon, Jun 6, 2011 at 01:52, Yitzchak Gale
Scott Lawrence wrote: You almost never want to use UndecidableInstances when writing practical programs in Haskell.
Ah. That's what I wanted to know :P (Although it does seem to me - from looking around docs and the source - that GHC's rules for allowing certain combinations might be a bit too conservative - but then, I have next to no idea what I'm doing, so hey.)
When GHC tells you that you need them, it almost always means that your types are poorly designed, usually due to influence from previous experience with OOP.
* hides behind book
Your best bet is to step back and think again about the problem you are trying to solve. What is the best way to formulate the problem functionally? That will lead you in the right direction. Please feel free to share more details about what you are trying to do. We would be happy to help you work out some good directions.
I'm modelling text in a markov-model-like way. I have an actual markov model (albeit one in which X_n depends on a fixed range X_n-1 .. X-n-k). I'm vaguely anticipating the presence of other models: class Model m a | m -> a where lexemes :: m -> Set a genFunc :: m -> [a] -> ProbDist a Having that working, I'm trying to estimate the information entropy of a model entropy :: (Model m) => m -> Double (This is a slight simplification, since entropy needs a second argument "precision" to know when to terminate.) Which works well and fine - this function is pretty trivial to implement, on the assumption that Markov (the instance of Model described above) implements genFunc properly. But it happens not to - the array argument to genFunc must be the right size, otherwise an even probability distribution is used. So my OOP-infected mind wants to specialize 'entropy' for Markov: class Entropy d where entropy :: d -> Double -- again, simplified Note that it's not (Entropy d a) because the type of the lexeme doesn't matter. Now, the problem code instance (Model m a) => Entropy m where entropy = undefined As you might have picked up, I suspect the part where I want to specialize entropy for Markov is where I mess up - but I'm not sure what to do. (To be clear, I expect to want to specialize entropy for other models too - the general function I have in mind would be horribly slow for many reasonable models.) Thanks.
Regards, Yitz
-- Scott Lawrence

Oops. I can just abandon the Entropy typeclass and put the function
directly into Model, eh? Yeah, I think I'll do that...
Supposing I didn't want to - any alternatives? Other instances of
Entropy I might consider:
instance (Eq a) => Entropy [a]
instance (Eq a) => Entropy (Tree a)
On Mon, Jun 6, 2011 at 02:13, Scott Lawrence
On Mon, Jun 6, 2011 at 01:52, Yitzchak Gale
wrote: Scott Lawrence wrote: You almost never want to use UndecidableInstances when writing practical programs in Haskell.
Ah. That's what I wanted to know :P
(Although it does seem to me - from looking around docs and the source - that GHC's rules for allowing certain combinations might be a bit too conservative - but then, I have next to no idea what I'm doing, so hey.)
When GHC tells you that you need them, it almost always means that your types are poorly designed, usually due to influence from previous experience with OOP.
* hides behind book
Your best bet is to step back and think again about the problem you are trying to solve. What is the best way to formulate the problem functionally? That will lead you in the right direction. Please feel free to share more details about what you are trying to do. We would be happy to help you work out some good directions.
I'm modelling text in a markov-model-like way. I have an actual markov model (albeit one in which X_n depends on a fixed range X_n-1 .. X-n-k). I'm vaguely anticipating the presence of other models:
class Model m a | m -> a where lexemes :: m -> Set a genFunc :: m -> [a] -> ProbDist a
Having that working, I'm trying to estimate the information entropy of a model
entropy :: (Model m) => m -> Double
(This is a slight simplification, since entropy needs a second argument "precision" to know when to terminate.)
Which works well and fine - this function is pretty trivial to implement, on the assumption that Markov (the instance of Model described above) implements genFunc properly. But it happens not to - the array argument to genFunc must be the right size, otherwise an even probability distribution is used. So my OOP-infected mind wants to specialize 'entropy' for Markov:
class Entropy d where entropy :: d -> Double -- again, simplified
Note that it's not (Entropy d a) because the type of the lexeme doesn't matter. Now, the problem code
instance (Model m a) => Entropy m where entropy = undefined
As you might have picked up, I suspect the part where I want to specialize entropy for Markov is where I mess up - but I'm not sure what to do. (To be clear, I expect to want to specialize entropy for other models too - the general function I have in mind would be horribly slow for many reasonable models.)
Thanks.
Regards, Yitz
-- Scott Lawrence
-- Scott Lawrence

Scott Lawrence wrote:
I'm modelling text in a markov-model-like way. I have an actual markov model (albeit one in which X_n depends on a fixed range X_n-1 .. X-n-k). I'm vaguely anticipating the presence of other models:
class Model m a | m -> a where lexemes :: m -> Set a genFunc :: m -> [a] -> ProbDist a
Generally, we don't start out with a type class. Type classes are great for the special situations in which they are needed (although you can do pretty well without them even then), but first let's get the basic concepts. Perhaps a model is just a function: type Model a = Ord a => Set a -> [a] -> ProbDist a or something like that.
Having that working, I'm trying to estimate the information entropy of a model
entropy :: (Model m) => m -> Double
Perhaps just a function: entropy :: Model a -> Double I still don't know enough details about what you're doing, so my types are probably off. But I hope you get the idea. If that's not general enough, you may introduce more functions, or some data types. Those give you a huge amount of power - remember that data types can take multiple type parameters (without any GHC extension), they can have functions as their parameters, etc. Or, perhaps you'll even get to the point where you'll need a type class, but that's pretty far down the road, and what you would need it for is very different than what a class is in OOP - they are different concepts. Hope this helps, Yitz

On 06/06/2011 02:57 AM, Yitzchak Gale wrote:
Generally, we don't start out with a type class. Type classes are great for the special situations in which they are needed (although you can do pretty well without them even then), but first let's get the basic concepts.
Perhaps a model is just a function:
type Model a = Ord a => Set a -> [a] -> ProbDist a
or something like that.
Erm... yeah, actually. But... this prevents me from storing more information in a Model in the future. While I don't really anticipate needing too (I can see this function covering all likely use cases), it does seem sorta restrictive.
Having that working, I'm trying to estimate the information entropy of a model
entropy :: (Model m) => m -> Double Perhaps just a function:
entropy :: Model a -> Double
I still don't know enough details about what you're doing, so my types are probably off. But I hope you get the idea.
No, your types are right.
If that's not general enough, you may introduce more functions, or some data types. Those give you a huge amount of power - remember that data types can take multiple type parameters (without any GHC extension), they can have functions as their parameters, etc.
Or, perhaps you'll even get to the point where you'll need a type class, but that's pretty far down the road, and what you would need it for is very different than what a class is in OOP - they are different concepts.
Oh, I understand the difference between a class and a typeclass. It's the difference between an interface and a typeclass that I apparently haven't grasped. Thanks.
Hope this helps, Yitz

On 06/06/2011 03:13 AM, Scott Lawrence wrote:
I still don't know enough details about what you're doing,
so my types are probably off. But I hope you get the idea. No, your types are right.
Or not. type Model a = (Ord a) => Set a -- the set of lexemes -> [a] -- the original text to model -> [a] -- list of previous lexemes -> ProbDist a -- the next lexeme and then entropy :: Model a -> Set a -> [a] -> Double or perhaps more simply entropy :: [a] -> ProbDist a -> Double (Let me know if I'm doing something insane again - thanks.) But this doesn't allow me to specialize for markov models. Seems to me that to do that, I'd have to store data - and once I'm using a datatype for markov models: data Markov a = Markov { lexemeSet :: Set a , matrix :: Map [a] (ProbDist a) } Then in order to get a consistent interface to various models, I'm going to need a typeclass. (Which is required to use a single function name on multiple datatypes, yes?) I suppose the alternative is something like data Model a = Markov {...} | OtherModel Is that the functional solution? It seems to preclude the possibility of separating the markov-specialized code and the other specialized code.

Scott Lawrence wrote:
type Model a = (Ord a) => Set a -- the set of lexemes -> [a] -- the original text to model -> [a] -- list of previous lexemes -> ProbDist a -- the next lexeme
and then
entropy :: Model a -> Set a -> [a] -> Double
or perhaps more simply
entropy :: [a] -> ProbDist a -> Double
Those all look reasonable.
Then in order to get a consistent interface to various models, I'm going to need a typeclass. (Which is required to use a single function name on multiple datatypes, yes?)
Why is it important to use the same function name? If you have two different functions that do two different things, they can have two different names. If further down the line you need to write a function that is independent of the model, the types of its arguments will show you what you need to do.
I suppose the alternative is something like
data Model a = Markov {...} | OtherModel
Is that the functional solution? It seems to preclude the possibility of separating the markov-specialized code and the other specialized code.
Right, it doesn't sound like that's the way to go here. Regards, YItz

I wrote:
type Model a = (Ord a) => Set a -- the set of lexemes -> [a] -- the original text to model -> [a] -- list of previous lexemes -> ProbDist a -- the next lexeme
and then
entropy :: Model a -> Set a -> [a] -> Double
On Mon, Jun 6, 2011 at 03:56, Yitzchak Gale
If further down the line you need to write a function that is independent of the model, the types of its arguments will show you what you need to do.
Is there a trick that I'm missing? If I want (as a horribly constructed hypothetical example) to write a function later on with type (Model a -> Model b) that calls 'entropy' (no idea why), but I want to use the specialized version of 'entropy' for 'Markov' (which requires data that isn't even contained in the first argument, which is really just a function), I don't see any way to do it, without having two entirely different code paths for 'Markov' and other models, starting from the point of decision (user input or some other factor) - an unwieldy solution in case of more than 2 different models (each, presumably, with their own subset of specializations). -- Scott Lawrence

Scott Lawrence wrote:
But... this prevents me from storing more information in a Model in the future. While I don't really anticipate needing too (I can see this function covering all likely use cases), it does seem sorta restrictive.
I tend not to think about "storing information inside of things". I just write functions that do the computations I need - their types describe the desired inputs and outputs. Data types group them together into logical structures that reflect what I want to do. Where the information is coming from and where it is going then remains a totally independent issue. It is a different part of the program. That is actually more flexible, not restrictive. Kind of like the MVC design pattern. The IO monad, which keeps the parts of the program that interact with outside world separate, helps us think in this way. Regards, Yitz

On Mon, Jun 6, 2011 at 7:52 AM, Yitzchak Gale
Scott Lawrence wrote:
More specifically, I have
class Model m a | m -> a where ... class Entropy d where ... instance (Model m a) => Entropy m where ...
The first line requires MultiParamTypeClasses and FunctionalDependencies... the third requires UndecidableInstances... Is this likely to cause a problem?
Yes.
You almost never want to use UndecidableInstances when writing practical programs in Haskell. When GHC tells you that you need them, it almost always means that your types are poorly designed, usually due to influence from previous experience with OOP.
Your best bet is to step back and think again about the problem you are trying to solve. What is the best way to formulate the problem functionally? That will lead you in the right direction. Please feel free to share more details about what you are trying to do. We would be happy to help you work out some good directions.
Are you sure you weren't thinking of OverlappingInstances here? I haven't seen as much scorn heaped upon Undecidable.
Regards, Yitz
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.

I wrote:
You almost never want to use UndecidableInstances when writing practical programs in Haskell. When GHC tells you that you need them, it almost always means that your types are poorly designed, usually due to influence from previous experience with OOP.
Gábor Lehel wrote:
Are you sure you weren't thinking of OverlappingInstances here? I haven't seen as much scorn heaped upon Undecidable.
Sorry, I didn't mean to come across as heaping scorn on anything. :) Having come from OOP myself, I know that at first you don't realize the power and beauty of functional programming. The vast majority of programming problems have a beautiful solution without stepping outside of Haskell 98. One of the symptoms of thinking about a problem in OOP style rather than functionally is that you immediately find yourself needing all of those kinds of type system extensions, which just end up adding a huge amount of unneeded complexity. Once you are fluent and comfortable with functional thinking, you can learn about the many other tools and techniques that are available and when it is best to apply them. I must admit that even while designing and implementing large systems, I haven't found myself needing anything involving either UndecidableInstances or OverlappingInstances for several years. Regards, Yitz

On Mon, Jun 6, 2011 at 7:52 AM, Yitzchak Gale
You almost never want to use UndecidableInstances when writing practical programs in Haskell.
Surprisingly enough, mtl uses UndecidableInstances, so almost every
practical Haskell program uses it in one way or another.
G
--
Gregory Collins

Gregory Collins wrote:
Surprisingly enough, mtl uses UndecidableInstances, so almost every practical Haskell program uses it in one way or another.
The library uses it, you don't use it directly in your program. Anyway, transformers does the job when you need to build on the basic monad transformers. You only need the UndecidableInstances stuff when you need to write functions that work for multiple different monad stacks and you are using type classes to define common interfaces. I find that to be a messy approach. There's almost always a better way. Regards, Yitz

On 6/6/11 1:52 AM, Yitzchak Gale wrote:
You almost never want to use UndecidableInstances when writing practical programs in Haskell. When GHC tells you that you need them, it almost always means that your types are poorly designed, usually due to influence from previous experience with OOP.
That's a bit unfair. There are many kinds of type-level hackery which require UndecidableInstances but are (a) perfectly safe for practical use, and (b) have nothing to do with OOP. One particularly trivial example that comes to mind is: newtype Mu f = Mu (f (Mu f)) instance Show (f (Mu f)) => Show (Mu f) where show (Mu x) = "Mu (" ++ show x ++ ")" -- Or however you'd like to show it This can be solved for any f=F by, instance Show a => Show (F a) where... -- Live well, ~wren

One particularly trivial example that comes to mind is:
newtype Mu f = Mu (f (Mu f))
instance Show (f (Mu f)) => Show (Mu f) where show (Mu x) = "Mu (" ++ show x ++ ")" -- Or however you'd like to show it
Ehm, that does look like poor design. Sure you don't mean "Mu f can be printed if and only if f (Mu f) can be printed". What you probably mean is "if f transforms printable things to printable things, then Mu f is a printable thing". And you CAN express just that: type ShowD a = forall p. (forall x. Show x => p x) -> p a showD :: Show a => ShowD a showD px = px class ShowF f where showF :: Show a => ShowD (f a) instance Show a => Show (F a) where... -- here goes your "f" instance ShowF F where showF = showD -- and that is the only line of boilerplate instance ShowF f => Show (Mu f) where show (Mu fm) = "Mu (" ++ runShowHelper (showF (ShowHelper show)) fm ++ ")" newtype ShowHelper x = ShowHelper {runShowHelper :: x -> String} Sorry for possible bugs — I don't have ghc anywhere near me at the moment, but the idea is clear, I guess. Отправлено с iPhone

On Jun 7, 2011, at 12:43 PM, MigMit wrote:
One particularly trivial example that comes to mind is:
newtype Mu f = Mu (f (Mu f))
instance Show (f (Mu f)) => Show (Mu f) where show (Mu x) = "Mu (" ++ show x ++ ")" -- Or however you'd like to show it
Ehm, that does look like poor design.
Sure you don't mean "Mu f can be printed if and only if f (Mu f) can be printed". What you probably mean is "if f transforms printable things to printable things, then Mu f is a printable thing". And you CAN express just that:
Actually, I would argue that the former _is_ what is meant. It's a weaker condition than the latter and it is the necessary and sufficient condition to define the instance - one of the steps involved in formatting a value of type "Mu f" is to format a value of type "f (Mu f)". It doesn't actually matter whether "forall x. Show x => Show (f x)" holds in general.
type ShowD a = forall p. (forall x. Show x => p x) -> p a
showD :: Show a => ShowD a showD px = px
class ShowF f where showF :: Show a => ShowD (f a)
instance Show a => Show (F a) where... -- here goes your "f"
instance ShowF F where showF = showD -- and that is the only line of boilerplate
instance ShowF f => Show (Mu f) where show (Mu fm) = "Mu (" ++ runShowHelper (showF (ShowHelper show)) fm ++ ")"
newtype ShowHelper x = ShowHelper {runShowHelper :: x -> String}
Sorry for possible bugs — I don't have ghc anywhere near me at the moment, but the idea is clear, I guess.
I don't really see how this is preferable when the compiler can solve the equation automatically. All that is needed is to tell it to try. If portability is a concern then I could see going through the gymnastics (and also eliminating the use of higher-rank types), but that's the only case in which I would consider it the preferred option. -- James

On 6/7/11 1:01 PM, James Cook wrote:
On Jun 7, 2011, at 12:43 PM, MigMit wrote:
wren ng thornton wrote:
One particularly trivial example that comes to mind is:
newtype Mu f = Mu (f (Mu f))
instance Show (f (Mu f)) => Show (Mu f) where show (Mu x) = "Mu (" ++ show x ++ ")" -- Or however you'd like to show it
Ehm, that does look like poor design.
Sure you don't mean "Mu f can be printed if and only if f (Mu f) can be printed". What you probably mean is "if f transforms printable things to printable things, then Mu f is a printable thing". And you CAN express just that:
Actually, I would argue that the former _is_ what is meant. It's a weaker condition than the latter and it is the necessary and sufficient condition to define the instance - one of the steps involved in formatting a value of type "Mu f" is to format a value of type "f (Mu f)". It doesn't actually matter whether "forall x. Show x => Show (f x)" holds in general.
Indeed. Often the fact that (forall x. Show x => Show (f x)) holds will serve to prove that Show (f (Mu f)), but there's no reason why the more stringent proof is a requirement. The necessary and sufficient condition is: instance forall f. ( Show (Mu f) => Show (f (Mu f)) ) => Show (Mu f) where... Which isn't directly expressible in Haskell. And even if we could write it, it wouldn't mean what it ought to mean; because the typeclass resolution system commits to an instance once the head matches, rather than viewing the context as preconditions for matching the head. Thus, there's no way to pass in an implication like that; it's equivalent to requiring both Show (Mu f) and Show (f (Mu f)). And since the former is trivially satisfied, we only need to specify the need for Show (f (Mu f)).
type ShowD a = forall p. (forall x. Show x => p x) -> p a
While I don't shy away from RankNTypes, I don't see that this really buys us anything. UndecidableInstances is easily supportable, higher rank polymorphism takes a bit of work and therefore reduces portability. -- Live well, ~wren
participants (8)
-
Brandon Allbery
-
Gregory Collins
-
Gábor Lehel
-
James Cook
-
MigMit
-
Scott Lawrence
-
wren ng thornton
-
Yitzchak Gale