Trouble with overlapping instances - haskell

I'm currently working in a project where I derive some instances for a class. Since the class has only one method with will have the same definition save for a few specific cases, I tried defining an overlappable general instance and then defining the ones I need to be overlapping.
This doesn't work because I get an overlapping instances error. Doing some testing, we came accross this reduced example that's pretty much equivalent to my original problem:
{-# LANGUAGE FlexibleInstances, UndecidableInstances, MultiParamTypeClasses #-}
module Instance where
data Id a = Id a String
data C a = C a
class Bad a b where
bad :: a -> String
instance {-# OVERLAPPABLE #-} Bad a b where
bad = \_ -> "Default case"
instance {-# OVERLAPPING #-} Bad (Id a) (C a) where
bad = \_ -> "Id"
class Good a b where
good :: a -> String
instance {-# OVERLAPPABLE #-} Good a b where
good = \_ -> "Default case"
instance {-# OVERLAPPING #-} Good (Id a) b where
good = \_ -> "Id"
test = let a = Id () "a"
in putStrLn (good a) >> putStrLn (bad a)
(Note that this won't compile unless you comment the second Bad instance.)
Class Good works without any problem (test outputs "Id"). If I don't remove the second instance for Bad, I get:
Overlapping instances for Bad (Id ()) b0
arising from a use of ‘bad’
Matching instances:
instance [overlappable] Bad a b -- Defined at Instance.hs:12:31
instance [overlapping] Bad (Id a) (C a)
-- Defined at Instance.hs:15:30
(The choice depends on the instantiation of ‘b0’
To pick the first instance above, use IncoherentInstances
when compiling the other instance declarations)
In the first argument of ‘putStrLn’, namely ‘(bad a)’
In the second argument of ‘(>>)’, namely ‘putStrLn (bad a)’
In the expression: putStrLn (good a) >> putStrLn (bad a)
What I don't understand is why does this happen, when the only difference between them is an aditional restriction in the second class parameter.
Also, isn't the point of overlappable instances to avoid overlapping errors?
Regards

As per my comment above, I think your pragmas should have AllowAmbiguousTypes instead of UndecidableInstances,
else you get a different error (at least I do on GHC 8.0.1) pertaining to b being ambiguous in the function signature
bad :: Bad a b => a -> String.
AmbiguousTypes allows you to write signatures for functions that will be ambiguous when they are used.
Instead, the ambiguity check is moved to the call-site. This works really well with something like TypeApplications
to specify those ambiguous variables. In this case, bad is always ambiguous, so we need this pragma to move to the
error message at the call-site. Now, I have the same message as you.
The reason that even with OVERLAPPABLE and OVERLAPPING Haskell complains is that depending on how b is instantiated (which hasn't been
specified), it will choose one of the two instances of Bad. In other words, you could want b to unify with C a,
just as well as you could not, so Haskell throws up its hands and says "you haven't told me enough about b for me to be
able to pick a most specific instance of Bad".
On the other hand, even without knowing b, Haskell knows which of the instances Good a b and Good (Id a) b are more
specific - it is always the second one (even without knowing what b is that is the case).
I really recommend you read the documentation about overlapping instances
as it explains the whole algorithm.
You can usually get around these problems using things like TypeApplications (to specify b), or translating your type class to a type family.

Related

Typeclass resolution in Haskell reporting ambiguity even if there is only one instance

I am experimenting with transitive typeclass instances in Haskell. It is well-known that one cannot declare a transitive instance in the original typeclass (i.e. (C a b, C b c) => C a c). Therefore I tried to define another class representing the transitive closure of the original class instead. Minimal code is as below:
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Ambig where
class Coe a b where
from :: a -> b
class CoeTrans a b where
from' :: a -> b
instance CoeTrans a a where
from' = id
instance (Coe a b, CoeTrans b c) => CoeTrans a c where
from' = from' . from #a #b
instance Coe Bool Int where
from False = 0
from True = 1
instance Coe Int Integer where
from x = toInteger x
where CoeTrans is the transitive closure of Coe. When I'm trying to use from' in CoeTrans, however, it always reports ambiguity:
-- >>> from' True :: Integer
-- Ambiguous type variable ‘b0’ arising from a use of ‘from'’
-- prevents the constraint ‘(Coe Bool b0)’ from being solved.
-- Probable fix: use a type annotation to specify what ‘b0’ should be.
-- These potential instance exist:
-- instance Coe Bool Int
-- -- Defined at /Users/t/Desktop/aqn/src/Ambig.hs:21:10
Even if there is virtually only one instance. But according to GHC docs a typeclass resolution will succeed iff there is one applicable instance.
Why would this happen and is there any way to solve the transitive instance problem?
I think you misunderstood the docs a bit. They really say that a typeclass resolution for a given type will succeed iff one instance is present. But in your case, no type is given. b0 is ambiguous.
The compiler needs to know b0 before it can pick an instance of Coe Bool b0, even though there is only one in the current scope. And this is done this way on purpose. And the key words there are "current scope". You see, if the compiler could just pick whatever is available in scope, your program would be vulnerable to subtle changes in scope: you may change your imports, or some of your imported modules may change their internal structure. This may result in different instances appearing or disappearing in your current scope, which may result in different behaviour of your program without any kind of warning.
If you really intend for there to always be at most one unambiguous path between any two types, you can solve it by adding a functional dependency to Coe:
class Coe a b | a -> b where
from :: a -> b
This will have two effects:
The compiler will know that it can always deduce b just by knowing a.
And to facilitate that, the compiler will prohibit multiple instances with same a, but different bs from being defined.
Now the compiler can see that, since the argument of from' is Bool, it must search for an instance of Coe Bool b for some b, and from there it will know for sure what b has to be, and from there it can search for the next instance, and so on.
If, on the other hand, you really intended for there to be multiple possible paths between two given types, and for the compiler to just pick one - you're out of luck. The compiler refuses on principle` to randomly pick one of multiple possibilities - see explanation above.

Haskell: Define Show function for a user defined type, which is defined by "type" key word

Let's say I have the type StrInt defined as below
type StrInt = (String, Int)
toStrInt:: Str -> Int -> StrInt
toStrInt str int = (str, int)
I want the Show function to work as below:
Input: show (toStrInt "Hello", 123)
Output: "Hello123"
I have tried to define show as below:
instance Show StrInt where
show (str, int) = (show str) ++ (show int)
But that gives me error:
Illegal instance declaration for ‘Show StrInt’
(All instance types must be of the form (T t1 ... tn)
where T is not a synonym.
Use TypeSynonymInstances if you want to disable this.)
In the instance declaration for ‘Show StrInt’
Any ideas on how to solve this issue?
Appreciate your help!
What you're trying to do is 1. not a good idea to start with, 2. conflicts with the already-existing Show instance and is therefore not possible without OverlappingInstances hackery (which is almost never a good idea), and 3. the error message you're getting is not related to these problems; other class-instances with the same message may be perfectly fine but of course require the extension that GHC asks about.
The Show class is not for generating arbitrary string output in whatever format you feel looks nice right now. That's the purpose of pretty-printing. Show instead is supposed to yield syntactically valid Haskell, like the standard instance does:
Prelude> putStrLn $ show (("Hello,"++" World!", 7+3) :: (String,Int))
("Hello, World!",10)
Prelude> ("Hello, World!",10) -- pasted back the previous output
("Hello, World!",10)
If you write any Show instance yourself, it should also have this property.
Again because (String, Int) already has a Show instance, albeit just one arising from more generic instances namely
instance (Show a, Show b) => Show (a,b)
instance Show a => Show [a]
instance Show Int
declaring a new instance for the same type results in a conflict. Technically speaking this could be circumvented by using an {-# OVERLAPPING #-} pragma, but I would strongly advise against this because doing that kind of thing can lead to very confusing behaviour down the line when instance resolution inexplicably changes based on how the types are presented.
Instead, when you really have a good reason to give two different instances to a type containing given data, the right thing to do is generally to make it a separate type (so it's clear that there will be different behaviour) which just happens to have the same components.
data StrInt' = StrInt String Int
instance Show StrInt' where
...
That actually compiles without any further issues or need for extensions. (Alternatively you can also use newtype StrInt = StrInt (String, Int), but that doesn't really buy you anything and just means you can't bring in record labels.)
Instances of the form instance ClassName TypeSynonym are possible too, and can sometimes make sense, but as GHC already informed you they require the TypeSynonymInstances extension or one that supersedes it. In fact TypeSynonymInstances is not enough if the synonym points to a composite type like a tuple, in that case you need FlexibleInstances (which includes TypeSynonymInstances), an extension I enable all of the time.
{-# LANGUAGE FlexibleInstances #-}
class C
type StrInt = (String, Int)
instance C StrInt

Overlapping multi-parameter instances and instance specificity

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
module OverlappingSpecificsError where
class EqM a b where
(===) :: a -> b -> Bool
instance {-# OVERLAPPABLE #-} Eq a => EqM a a where
a === b = a == b
instance {-# OVERLAPPABLE #-} EqM a b where
a === b = False
aretheyreallyeq :: (Eq a, Eq b) => Either a b -> Either a b -> Bool
aretheyreallyeq (Left a1) (Right b2) = a1 == b2
aretheyeq :: (Eq a, Eq b) => Either a b -> Either a b -> Bool
aretheyeq (Left a1) (Right b2) = a1 === b2
Neither aretheyreallyeq or aretheyeq compile, but the error for aretheyreallyeq makes sense to me, and also tells me that aretheyeq should not give an error: One of the instances that GHCi suggests are possible for EqM in aretheyeq should be impossible due to the same error on aretheyreallyeq. What's going on?
The point is, GHCi insists that both of the instances of EqM are applicable in aretheyeq. But a1 is of type a and b2 is of type b, so in order for the first instance to be applicable, it would have to have the types a and b unify.
But this should not be possible, since they are declared as type variables at the function signature (that is, using the first EqM instance would give rise to the function being of type Either a a -> Either a a -> Bool, and the error in aretheyreallyeq tells me that GHCi will not allow that (which is what I expected anyway).
Am I missing something, or is this a bug in how overlapping instances with multi-parameter type classes are checked?
I am thinking maybe it has to do with the fact that a and b could be further instantiated later on to the point where they are equal, outside aretheyeq, and then the first instance would be valid? But the same is true for aretheyreallyeq. The only difference is that if they do not ever unify we have an option for aretheyeq, but we do not for aretheyreallyeq. In any case, Haskell does not have dynamic dispatch for plenty of good and obvious reasons, so what is the fear in committing to the instance that will always work regardless of whether later on a and b are unifiable? Maybe there is some way to present this that would make choosing the instance when calling the function possible in some way?
It is worth noting that if I remove the second instance, then the function obviously still does not compile, stating that no instance EqM a b can be found. So if I do not have that instance, then none works, but when that one works, suddenly the other does too and I have an overlap? Smells like bug to me miles away.
Instance matching on generic variables works this way in order to prevent some potentially confusing (and dangerous) scenarios.
If the compiler gave in to your intuition and chose the EqM a b instance when compiling aretheyeq (because a and b do not necessarily unify, as you're saying), then the following call:
x = aretheyeq (Left 'z') (Right 'z')
would return False, contrary to intuition.
Q: wait a second! But in this case, a ~ Char and b ~ Char, and we also have Eq a and Eq b, which means Eq Char, which should make it possible to choose the EqM a a instance, shouldn't it?
Well, yes, I suppose this could be happening in theory, but Haskell just doesn't work this way. Class instances are merely extra parameters passed to functions (as method dictionaries), so in order for there to be an instance, it must either be unambiguously choosable within the function itself, or it must be passed in from the consumer.
The former (unambiguously choosable instance) necessarily requires that there is just one instance. And indeed, if you remove the EqM a a instance, your function compiles and always returns False.
The latter (passing an instance from the consumer) means a constraint on the function, like this:
aretheyeq :: EqM a b => Either a b -> Either a b -> Bool
What you are asking is that Haskell essentially has two different versions of this function: one requiring that a ~ b and picking the EqM a a instance, and the other not requiring that, and picking the EqM a b instance.
And then the compiler would cleverly pick the "right" version. So that if I call aretheyeq (Left 'z') (Right 'z'), the first version gets called, but if I call aretheyeq (Left 'z') (Right 42) - the second.
But now think further: if there are two versions of aretheyeq, and which one to pick depends on whether the types are equal, then consider this:
dummy :: a -> b -> Bool
dummy a b = aretheyeq (Left a) (Right b)
How does dummy know which version of aretheyeq to pick? So now there has to be two versions of dummy as well: one for when a ~ b and another for other cases.
And so on. The ripple effect continues until there are concrete types.
Q: wait a second! Why two versions? Can't there be just one version, which then decides what to do based on what arguments are passed in?
Ah, but it can't! This is because types are erased at compile time. By the time the function starts to run, it's already compiled, and there is no more type information. So everything has to be decided at compile time: which instance to pick, and the ripple effect from it.
It isn't a bug in sense of working exactly as documented. Starting with
Now suppose that, in some client module, we are searching for an instance of the target constraint (C ty1 .. tyn). The search works like this:
The first stage of finding candidate instances works as you expect; EqM a b is the only candidate and so the prime candidate. But the last step is
Now find all instances, or in-scope given constraints, that unify with the target constraint, but do not match it. Such non-candidate instances might match when the target constraint is further instantiated. If all of them are incoherent top-level instances, the search succeeds, returning the prime candidate. Otherwise the search fails.
The EqM a a instance falls into this category, and isn't incoherent, so the search fails. And you can achieve the behavior you want by marking it as {-# INCOHERENT #-} instead of overlappable.
To further complete Alexey's answer, which really gave me the hint at what I should do to achieve the behaviour I wanted, I compiled the following minimum working example of a slightly different situation more alike my real use case (which has to do with ExistentialQuantification):
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ExistentialQuantification #-}
module ExistentialTest where
class Class1 a b where
foo :: a -> b
instance {-# INCOHERENT #-} Monoid a => Class1 a (Either b a) where
foo x = Right (x <> x)
instance {-# INCOHERENT #-} Monoid a => Class1 a (Either a b) where
foo x = Left x
data Bar a = Dir a | forall b. Class1 b a => FromB b
getA :: Bar a -> a
getA (Dir a) = a
getA (FromB b) = foo b
createBar :: Bar (Either String t)
createBar = FromB "abc"
createBar2 :: Bar (Either t String)
createBar2 = FromB "def"
If you remove the {-# INCOHERENT #-} annotations, you get exactly the same compile errors as in my original example on both createBar and createBar2, and the point is the same: in createBar it is clear that the only suitable instance is the second one, whereas in createBar2 the only suitable one is the first one, but Haskell refuses to compile because of this apparent confusion it might create when using it, until you annotate them with INCOHERENT.
And then, the code works exactly as you'd expect it to: getA createBar returns Left "abc" whereas getA createBar2 returns Right "defdef", which is exactly the only thing that could happen in a sensible type system.
So, my conclusion is: the INCOHERENT annotation is precisely to allow what I wanted to do since the beginning without Haskell complaining about potentially confusing instances and indeed taking the only one that makes sense. A doubt remains as to whether INCOHERENT may make it so that instances that indeed remain overlapping even after taking into account everything compile, using an arbitrary one (which is obviously bad and dangerous). So, a corollary to my conclusion is: only use INCOHERENT when you absolutely need to and are absolutely convinced that there is indeed only one valid instance.
I still think it is a bit absurd that Haskell has no more natural and safe way to tell the compiler to stop worrying about me being potentially being confused and doing what is obviously the only type checking answer to the problem...
aretheyreallyeq fails because there are two different type variables in scope. In
aretheyreallyeq :: (Eq a, Eq b) => Either a b -> Either a b -> Bool
aretheyreallyeq (Left a1) (Right b2) = a1 == b2
a1 :: a, and b2 :: b, there's no method for comparing values of potentially different types (as this is how they're declared), so this fails. This has nothing to do with any of the enabled extensions or pragmas of course.
aretheyeq fails because there are two instances that could match, not that they definitely do. I'm not sure what version of GHC you're using but here's the exception message I see and it seems to be fairly clear to me:
• Overlapping instances for EqM a b arising from a use of ‘===’
Matching instances:
instance [overlappable] EqM a b -- Defined at /home/tmp.hs:12:31
instance [overlappable] Eq a => EqM a a
-- Defined at /home/tmp.hs:9:31
(The choice depends on the instantiation of ‘a, b’
To pick the first instance above, use IncoherentInstances
when compiling the other instance declarations)
• In the expression: a1 === b2
In an equation for ‘aretheyeq’:
aretheyeq (Left a1) (Right b2) = a1 === b2
In this case, my interpretation is that it's saying that given certain choices for a and b, there are potentially multiple different matching instances.

Could you write a type function to invert a constraint?

Is it possible to write a type function that would take a constraint like Show and return one that constrains the RHS to types that are not an instance of Show?
The signature would be something like
type family Invert (c :: * -> Constraint) :: * -> Constraint
No. It is a design principle of the language that you are never allowed to do this. The rule is if a program is valid, adding more instances should not break it. This is the open-world assumption. Your desired constraint is a pretty direct violation:
data A = A
f :: Invert Show a => a -> [a]
f x = [x]
test :: [A]
test = f A
Would work, but adding
instance Show A
would break it. Therefore, the original program should never have been valid in the first place, and therefore Invert cannot exist.
As HTNW answered, it is in general not supposed to be possible to assert that a type is not an instance of a class. However, it is certainly possible to assert for a concrete type that it's never supposed to be possible to have an instance of some class for it. An ad-hoc way would be this:
{-# LANGUAGE ConstraintKinds, KindSignatures, AllowAmbiguousTypes
, MultiParamTypeClasses, FlexibleInstances #-}
import GHC.Exts (Constraint)
class Non (c :: * -> Constraint) (t :: *) where
nonAbsurd :: c t => r
But this is unsafe – the only way to write an instance is, like,
instance Non Show (String->Bool) where
nonAbsurd = undefined
but then somebody else could come up with a bogus instance Show (String->Bool) and would then be able to use your nonAbsurd for proving the moon is made out of green cheese.
A better option to make an instance impossible is to “block” it: write that instance yourself “pre-emptively”, but in such a way that it's a type error to actually invoke it.
import Data.Constraint.Trivial -- from trivial-constraint
instance Impossible0 => Show (String->Bool) where
show = nope
Now if anybody tries to add that instance, or tries to use it, they'll get a clear compiler error.

Associated Parameter Restriction using Functional Dependency

The function f below, for a given type 'a', takes a parameter of type 'c'. For different types 'a', 'c' is restricted in different ways. Concretely, when 'a' is any Integral type, 'c' should be allowed to be any 'Real' type. When 'a' is Float, 'c' can ONLY be Float.
One attempt is:
{-# LANGUAGE
MultiParamTypeClasses,
FlexibleInstances,
FunctionalDependencies,
UndecidableInstances #-}
class AllowedParamType a c | a -> c
class Foo a where
f :: (AllowedParamType a c) => c -> a
fIntegral :: (Integral a, Real c) => c -> a
fIntegral = error "implementation elided"
instance (Integral i, AllowedParamType i d, Real d) => Foo i where
f = fIntegral
For some reason, GHC 7.4.1 complains that it "could not deduce (Real c) arising from a use of fIntegral". It seems to me that the functional dependency should allow this deduction. In the instance, a is unified with i, so by the functional dependency, d should be unified with c, which in the instance is declared to be 'Real'. What am I missing here?
Functional dependencies aside, will this approach be expressive enough to enforce the restrictions above, or is there a better way? We are only working with a few different values for 'a', so there will be instances like:
instance (Integral i, Real c) => AllowedParamType i c
instance AllowedParamType Float Float
Thanks
A possibly better way, is to use constraint kinds and type families (GHC extensions, requires GHC 7.4, I think). This allows you to specify the constraint as part of the class instance.
{-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances, UndecidableInstances #-}
import GHC.Exts (Constraint)
class Foo a where
type ParamConstraint a b :: Constraint
f :: ParamConstraint a b => b -> a
instance Integral i => Foo i where
type ParamConstraint i b = Real b
f = fIntegral
EDIT: Upon further experimentation, there are some subtleties that mean that this doesn't work as expected, specifically, type ParamConstraint i b = Real b is too general. I don't know a solution (or if one exists) right now.
OK, this one's been nagging at me. given the wide variety of instances,
let's go the whole hog and get rid of any relationship between the
source and target type other than the presence of an instance:
{-# LANGUAGE OverlappingInstances, FlexibleInstances,TypeSynonymInstances,MultiParamTypeClasses #-}
class Foo a b where f :: a -> b
Now we can match up pairs of types with an f between them however we like, for example:
instance Foo Int Int where f = (+1)
instance Foo Int Integer where f = toInteger.((7::Int) -)
instance Foo Integer Int where f = fromInteger.(^ (2::Integer))
instance Foo Integer Integer where f = (*100)
instance Foo Char Char where f = id
instance Foo Char String where f = (:[]) -- requires TypeSynonymInstances
instance (Foo a b,Functor f) => Foo (f a) (f b) where f = fmap f -- requires FlexibleInstances
instance Foo Float Int where f = round
instance Foo Integer Char where f n = head $ show n
This does mean a lot of explicit type annotation to avoid No instance for... and Ambiguous type error messages.
For example, you can't do main = print (f 6), but you can do main = print (f (6::Int)::Int)
You could list all of the instances with the standard types that you want,
which could lead to an awful lot of repetition, our you could light the blue touchpaper and do:
instance Integral i => Foo Double i where f = round -- requires FlexibleInstances
instance Real r => Foo Integer r where f = fromInteger -- requires FlexibleInstances
Beware: this does not mean "Hey, if you've got an integral type i,
you can have an instance Foo Double i for free using this handy round function",
it means: "every time you have any type i, it's definitely an instance
Foo Double i. By the way, I'm using round for this, so unless your type i is Integral,
we're going to fall out." That's a big issue for the Foo Integer Char instance, for example.
This can easily break your other instances, so if you now type f (5::Integer) :: Integer you get
Overlapping instances for Foo Integer Integer
arising from a use of `f'
Matching instances:
instance Foo Integer Integer
instance Real r => Foo Integer r
You can change your pragmas to include OverlappingInstances:
{-# LANGUAGE OverlappingInstances, FlexibleInstances,TypeSynonymInstances,MultiParamTypeClasses #-}
So now f (5::Integer) :: Integer returns 500, so clearly it's using the more specific Foo Integer Integer instance.
I think this sort of approach might work for you, defining many instances by hand, carefully considering when to go completely wild
making instances out of standard type classes. (Alternatively, there aren't all that many standard types, and as we all know, notMany choose 2 = notIntractablyMany, so you could just list them all.)
Here's a suggestion to solve a more general problem, not yours specifically (I need more detail yet first - I promise to check later). I'm writing it in case other people are searching for a solution to a similar problem to you, I certainly was in the past, before I discovered SO. SO is especially great when it helps you try a radically new approach.
I used to have the work habit:
Introduce a multi-parameter type class (Types hanging out all over the place, so...)
Introduce functional dependencies (Should tidy it up but then I end up needing...)
Add FlexibleInstances (Alarm bells start ringing. There's a reason the compiler has this off by default...)
Add UndecidableInstances (GHC is telling you you're on your own, because it's not convinced it's up to the challenge you're setting it.)
Everything blows up. Refactor somehow.
Then I discovered the joys of type families (functional programming for types (hooray) - multi-parameter type classes are (a bit like) logic programming for types). My workflow changed to:
Introduce a type class including an associated type, i.e. replace
class MyProblematicClass a b | a -> b where
thing :: a -> b
thang :: b -> a -> b
with
class MyJustWorksClass a where
type Thing a :: * -- Thing a is a type (*), not a type constructor (* -> *)
thing :: a -> Thing a
thang :: Thing a -> a -> Thing a
Nervously add FlexibleInstances. Nothing goes wrong at all.
Sometimes fix things by using constraints like (MyJustWorksClass j,j~a)=> instead of (MyJustWorksClass a)=> or (Show t,t ~ Thing a,...)=> instead of (Show (Thing a),...) => to help ghc out. (~ essentially means 'is the same type as')
Nervously add FlexibleContexts. Nothing goes wrong at all.
Everything works.
The reason "Nothing goes wrong at all" is that ghc calculates the type Thing a using my type function Thang rather than trying to deduce it using a merely a bunch of assertions that there's a function there and it ought to be able to work it out.
Give it a go! Read Fun with Type Functions before reading the manual!

Resources