Continuing the discussion from Why Data.Set (containers) doesn't have Functor and Monad instance?:
Is that a performance consideration? Why would Functor
– imagining we re-engineer Functor
to be able to cope with constraints – for an instance with no constraint (say List
) be less performant than what we have today? Of course if there is a constraint (say Ord
for Set
) that would impose an overhead, but I guess no worse than any of the myriads of work-rounds/specialist libraries we now have.
I suspect the real explanations are more like:
- The abstract computational theory [Moggi] lives in the pure world of unrestricted parametric typing; not the mucky world of programming languages.
- As at when constructor classes were developed in Haskell [Mark Jones 1994], Haskell’s class/instance/constraint/type mangling abilities were not up to the job. (IOW I think we could do better today – or even as of vintage ~2006.)
And the second Functor
law came up in RichardE’s talk, where I think he disposed of the objection convincingly. It’s your Eq
instance that’s not lawful. Don’t go blaming Functor
.
Sure if your function is monotonic. “The precondition is not checked.” say the docos – just as the lawfulness of your Eq/Ord
instances aren’t checked.
Yes it’s a very clear presentation. What worries me about that approach is a) the amount of machinery that’s needed, and machinery all over every type application (see below); b) that the machinery then gets hidden (because otherwise source code would be a forest of @
s), so
[a] challenge of our approach is that our elaboration step introduces numerous additional constraints in the types of polymorphic functions. For total type constructors, these additional arguments provide no value, but can still make optimization more difficult. In our current implementation, this causes significant performance loss in some test cases.
[from the … in Practice experience report]
And c) that the approach imposes a bunch of unnecessary constraints:
A bit of History: the type of Data.Set.map
- ~2002
Data.Set
hadmapSet :: Ord b => (a -> b) -> Set a -> Set b
. - ~2006 replaced by
Data.Set.map :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b
(mapSet
marked " Obsolete equivalent of map." – but those aren’t equivalent: they’re different signatures.) - ~2015 somebody came to their senses
Data.Set.map :: Ord b => (a -> b) -> Set a -> Set b
So I say (at least for Functor
) that the ‘Partial Type Constructors’ approach would impose a constraint on map
's Set a
application, where it’s not needed: carrying Ord a =>
is superfluous because Set a
is already built, we’d only throw away the dictionary. We do need the Ord b =>
in order (hah!) to (re)build Set b
with b
's ordering.
A bit more history: Datatype contexts
(RichardE mentions positively Haskell Report v1.0 1990, moving along …)
GHC as of 1999 had a sensible interpretation for Contexts – comparable to today’s Data.Set.map
. But the H98 report text was deemed ambiguous, and the ‘Haskell committee’ of the time (chiefly Wadler – see next message in the thread) voted down SPJ’s/GHC’s approach.
What if …
class Functorb (fb :: Type) where
fmapb :: fb ~ (f b) => (a -> b) -> f a -> f b
instance Ord b => Functorb (Set b) where -- with Ord b accepted
fmapb = mapSet -- Data.Set.map post-2015 version
-- and likewise for Applicative, Monad, and friends
- Firstly note those
class
andinstance
headers are H98 compliant with a single type parameter, so don’t need constructor classes nor MPTCs/FunDeps/type functions. - The
(~)
type equality constraint onfmapb
wasn’t a thing until ~2008 (?or earlier, arrived with GADTs/Type Families); the idea is long-standing in type theory. - The
(f b)
, lacking a concrete type constructor, needsFlexibleContexts
; which has been available since ~1998. -
data Ord b => Set b = ...
(under the GHC pre-1999 rules) wouldn’t ask for anOrd a
constraint, but onlyOrd b
– which theinstance
decl satisfies.
Question to the floor: are there examples where Functor
and friends needs constraints (actual methods/overloadings) on both the incoming and outgoing constructed type? (That is, on both f a
's a
and f b
's b
.) The constrained-monads paper seems to have one at 1.3 Vectors; OTOH the Vizzotto et al paper it comes from seems to decide they need a more general approach: Arrows rather than Monads.