[Haskell-cafe] DatatypeContexts / alternative
CASANOVA Juan
Juan.Casanova at ed.ac.uk
Tue Feb 23 18:14:59 UTC 2021
Hello again, Haskell Cafe,
Here again with another doubt on how am I supposed to. This one should be fairly easier, I believe.
In short, I would like to have a functor type that can only be applied to certain type parameters. Why? Well, something like this:
module DatatypeContextsExample where
import Data.Map
import Data.Bifunctor
data Foo t = Foo (Map t t)
instance Functor Foo where
fmap f (Foo m) = Foo (fromList (fmap (bimap f f) (toList m)))
This does not compile, because I am using toList and fromList, which require (Ord t). But I cannot really have Foo be a functor in this way without it. The thing is, every time I am going to use it, t is actually going to be Ord. But how do I tell Haskell to have this constraint?
DatatypeContexts seems to be the extension that allows this:
data Ord t => Foo t = Foo (Map t t)
But this has two issues. First, DatatypeContexts is deprecated. Second, more importantly, it still does not type check! It produces the exact same error, saying that Ord t could not be inferred. It should be inferred from the very fact that I am using the type Foo, but GHC does not seem to want to understand this.
I could also try with GADTs:
data Foo t where
Foo :: Ord t => Map t t -> Foo t
But this still gives the same error on the fmap definition, stating it cannot use Foo without Ord. But I am pattern-matching against it, shouldn't that be enough to know that (Ord t) is going to hold? I don't understand it.
Is there anything simple I am missing? Any other simple way to achieve this? Any fundamental problem with what I am trying to do?
Thanks as usual,
Juan.
The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336. Is e buidheann carthannais a th' ann an Oilthigh Dhùn Èideann, clàraichte an Alba, àireamh clàraidh SC005336.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20210223/caaa0b87/attachment.html>
More information about the Haskell-Cafe
mailing list