question on typeclasses and applicatives

I came up with some code when trying to understand applicatives: import Control.Applicative import qualified Data.Map as M instance Applicative (M.Map String) where pure x = M.fromList [("",x)] fs <*> xs = M.fromList [(k1 ++ " " ++ k2,v1 v2) | k1 <- M.keys fs, k2 <- M.keys xs, v1 <- M.elems fs, v2 <- M.elems xs] 1. When I :load this in ghci it gives me some error about using (M.Map String) here, and tells me it'll work if I use the -XFlexibleInstances flag. Why is this type of behavior disabled by default? Is it potentially dangerous in some way? 2. When running the following: fromList [("double",(*2))] <*> fromList[("two",2),("seven",7)] I get: fromList [("double seven",4),("double two",4)] instead of what I'd expect: fromList [("double seven",14),("double two",4)] Although this: (*2) <$> fromList[("two",2),("seven",7)] gives what I'd expect: fromList [("seven",14),("two",4)] Why is this happening? I can't seem to figure it out.

On Thursday 02 September 2010 21:02:33, Alec Benzer wrote:
I came up with some code when trying to understand applicatives:
import Control.Applicative import qualified Data.Map as M
instance Applicative (M.Map String) where pure x = M.fromList [("",x)] fs <*> xs = M.fromList [(k1 ++ " " ++ k2,v1 v2) | k1 <- M.keys fs, k2 <- M.keys xs, v1 <- M.elems fs, v2 <- M.elems xs]
1. When I :load this in ghci it gives me some error about using (M.Map String) here, and tells me it'll work if I use the -XFlexibleInstances flag. Why is this type of behavior disabled by default?
Because the language specification imposed that instance declarations must have the form instance Class (T a1 a2 ... an) where ... where T is a type constructor, 0 <= n and a1, a2, ..., an are *distinct* type variables.
Is it potentially dangerous in some way?
I know of no dangers off the top of my head.
2. When running the following:
fromList [("double",(*2))] <*> fromList[("two",2),("seven",7)]
I get:
fromList [("double seven",4),("double two",4)]
instead of what I'd expect:
fromList [("double seven",14),("double two",4)]
That's because you really get fromList [("double seven", (*2) 7),("double seven", (*2) 2), ("double two", (*2) 7), ("double two", (*2) 2)] and later values for the same key overwrite earlier. You probably wanted fs <*> xs = M.fromList [(k1 ++ " " ++ k2, v1 v2) | (k1,v1) <- M.assocs fs, (k2,v2) <- M.assocs xs]
Although this:
(*2) <$> fromList[("two",2),("seven",7)]
gives what I'd expect:
fromList [("seven",14),("two",4)]
Why is this happening? I can't seem to figure it out.

On Thu, Sep 2, 2010 at 3:19 PM, Daniel Fischer
On Thursday 02 September 2010 21:02:33, Alec Benzer wrote:
I came up with some code when trying to understand applicatives:
import Control.Applicative import qualified Data.Map as M
instance Applicative (M.Map String) where pure x = M.fromList [("",x)] fs <*> xs = M.fromList [(k1 ++ " " ++ k2,v1 v2) | k1 <- M.keys fs, k2 <- M.keys xs, v1 <- M.elems fs, v2 <- M.elems xs]
1. When I :load this in ghci it gives me some error about using (M.Map String) here, and tells me it'll work if I use the -XFlexibleInstances flag. Why is this type of behavior disabled by default?
Because the language specification imposed that instance declarations must have the form
I guess I meant why does the language specification impose this?
instance Class (T a1 a2 ... an) where ...
where T is a type constructor, 0 <= n and a1, a2, ..., an are *distinct* type variables.
I don't understand, what you you mean by distinct? Like how is String not a distinct type variable by itself?
Is it potentially dangerous in some way?
I know of no dangers off the top of my head.
2. When running the following:
fromList [("double",(*2))] <*> fromList[("two",2),("seven",7)]
I get:
fromList [("double seven",4),("double two",4)]
instead of what I'd expect:
fromList [("double seven",14),("double two",4)]
That's because you really get
fromList [("double seven", (*2) 7),("double seven", (*2) 2), ("double two", (*2) 7), ("double two", (*2) 2)]
and later values for the same key overwrite earlier.
You probably wanted
fs <*> xs = M.fromList [(k1 ++ " " ++ k2, v1 v2) | (k1,v1) <- M.assocs fs, (k2,v2) <- M.assocs xs]
Oh, ya, that's what I meant. Didn't think that list comprehension through.
Although this:
(*2) <$> fromList[("two",2),("seven",7)]
gives what I'd expect:
fromList [("seven",14),("two",4)]
Why is this happening? I can't seem to figure it out.

On Thursday 02 September 2010 22:06:45, Alec Benzer wrote:
Because the language specification imposed that instance declarations must have the form
I guess I meant why does the language specification impose this?
Historical accident, probably. Perhaps it's easier to implement.
instance Class (T a1 a2 ... an) where ...
where T is a type constructor, 0 <= n and a1, a2, ..., an are *distinct* type variables.
I don't understand, what you you mean by distinct? Like how is String not a distinct type variable by itself?
distinct = different, however, String is not a type variable, it's a type (more specifically, a type synonym). Type variables start with a lowercase letter, things starting with an uppercase letter are type constructors (in this context), same as for values f True = whatever -- True is a data constructor f true = whatever -- true is a variable, matches anything So in Haskell98 (and Haskell2010), instance Class (Either a b) where ... is a legal instance declaration, the instance head is a type constructor (Either) applied to two distinct type variables. Not legal are instance Class (Either a a) where ... (type variables not distinct), instance Class (Either Char a) where ... (Char is not a type variable). It's an inconvenient restriction, so you can turn on FlexibleInstances to allow the latter two instances (not both in the same programme, though, that would need the dreaded OverlappingInstances).

Ah, ok, so the reason what I trying didn't work is because I used an
actual type instead of a type variable? I got confused because of the
emphasis you put on * distinct *.
And so, if I want to make Maps applicative functors without dealing
with FlexibleInstances, I'd have to do something like this?
import Control.Applicative
import qualified Data.Map as M
import Data.Monoid
instance (Monoid k, Ord k) => Applicative (M.Map k) where
pure x = M.fromList [(mempty,x)]
fs <*> xs = M.fromList [(k1 `mappend` k2,v1 v2) | (k1,v1) <-
M.assocs fs, (k2,v2) <- M.assocs xs]
(sacrificing some functionality, since spaces won't get intercalated
between keys if i use strings)
On Thu, Sep 2, 2010 at 4:31 PM, Daniel Fischer
On Thursday 02 September 2010 22:06:45, Alec Benzer wrote:
Because the language specification imposed that instance declarations must have the form
I guess I meant why does the language specification impose this?
Historical accident, probably. Perhaps it's easier to implement.
instance Class (T a1 a2 ... an) where ...
where T is a type constructor, 0 <= n and a1, a2, ..., an are *distinct* type variables.
I don't understand, what you you mean by distinct? Like how is String not a distinct type variable by itself?
distinct = different, however, String is not a type variable, it's a type (more specifically, a type synonym). Type variables start with a lowercase letter, things starting with an uppercase letter are type constructors (in this context), same as for values
f True = whatever -- True is a data constructor f true = whatever -- true is a variable, matches anything
So in Haskell98 (and Haskell2010),
instance Class (Either a b) where ...
is a legal instance declaration, the instance head is a type constructor (Either) applied to two distinct type variables.
Not legal are
instance Class (Either a a) where ...
(type variables not distinct),
instance Class (Either Char a) where ...
(Char is not a type variable).
It's an inconvenient restriction, so you can turn on FlexibleInstances to allow the latter two instances (not both in the same programme, though, that would need the dreaded OverlappingInstances).

On Thu, Sep 02, 2010 at 05:10:29PM -0400, Alec Benzer wrote:
Ah, ok, so the reason what I trying didn't work is because I used an actual type instead of a type variable? I got confused because of the emphasis you put on * distinct *.
I think the emphasis is from the error message that GHC spits out, not from Daniel. This is a particularly confusing error message though.
And so, if I want to make Maps applicative functors without dealing with FlexibleInstances, I'd have to do something like this?
import Control.Applicative import qualified Data.Map as M import Data.Monoid
instance (Monoid k, Ord k) => Applicative (M.Map k) where pure x = M.fromList [(mempty,x)] fs <*> xs = M.fromList [(k1 `mappend` k2,v1 v2) | (k1,v1) <- M.assocs fs, (k2,v2) <- M.assocs xs]
Sure. Although there's really no reason to avoid FlexibleInstances.
(sacrificing some functionality, since spaces won't get intercalated between keys if i use strings)
Technically, the version with the intercalated spaces didn't satisfy the Applicative laws anyway. For example, if <*> inserts a space it is not the case that pure f <*> x = f <$> x since there would be an extra space introduced on the left-hand side. I like your more general Monoid-based version much better (and I think it's not too hard to show it satisfies the Applicative laws, although I haven't thought about it too hard). -Brent

On Thursday 02 September 2010 23:10:29, Alec Benzer wrote:
Ah, ok, so the reason what I trying didn't work is because I used an actual type instead of a type variable?
Basically yes. There's a small additional problem because String is a type synonym (and type synonyms are forbidden in H98 instance declarations). Apparently, FlexibleInstances allows them in type variable positions, but if you want to put a type synonym in the type constructor position, you need TypeSynonymInstances. So for import Control.Monad.State type STI = StateT Int instance Foo (STI [] a) where you need FlexibleInstances ([] is not a type variable) and TypeSynonymInstances.
I got confused because of the emphasis you put on * distinct *.
Sorry for that. I wanted to prevent "Why can't I have instance Foo (Bar a a) where ... ?".
And so, if I want to make Maps applicative functors without dealing with FlexibleInstances, I'd have to do something like this?
import Control.Applicative import qualified Data.Map as M import Data.Monoid
instance (Monoid k, Ord k) => Applicative (M.Map k) where pure x = M.fromList [(mempty,x)] fs <*> xs = M.fromList [(k1 `mappend` k2,v1 v2) | (k1,v1) <- M.assocs fs, (k2,v2) <- M.assocs xs]
(sacrificing some functionality, since spaces won't get intercalated between keys if i use strings)
Yes, but why avoid FlexibleInstances?

Technically, the version with the intercalated spaces didn't satisfy the Applicative laws anyway. For example, if <*> inserts a space it is not the case that
pure f <*> x = f <$> x
since there would be an extra space introduced on the left-hand side.
That could be fixed by replacing k1 ++ " " ++ k2 with k1 ++ (if null k1 then "" else " ") ++ k2, or something though, couldn't it?
Sure. Although there's really no reason to avoid FlexibleInstances.
Yes, but why avoid FlexibleInstances?
I guess I'm still sort of confused or perturbed with why it's disabled
by default. If the compiler has the ability to do it and there are no
problems with doing it, why not just allow it without requiring you to
pass a flag to the compiler?
On Thu, Sep 2, 2010 at 5:50 PM, Daniel Fischer
On Thursday 02 September 2010 23:10:29, Alec Benzer wrote:
Ah, ok, so the reason what I trying didn't work is because I used an actual type instead of a type variable?
Basically yes. There's a small additional problem because String is a type synonym (and type synonyms are forbidden in H98 instance declarations). Apparently, FlexibleInstances allows them in type variable positions, but if you want to put a type synonym in the type constructor position, you need TypeSynonymInstances.
So for
import Control.Monad.State
type STI = StateT Int
instance Foo (STI [] a) where
you need FlexibleInstances ([] is not a type variable) and TypeSynonymInstances.
I got confused because of the emphasis you put on * distinct *.
Sorry for that. I wanted to prevent "Why can't I have instance Foo (Bar a a) where ... ?".
And so, if I want to make Maps applicative functors without dealing with FlexibleInstances, I'd have to do something like this?
import Control.Applicative import qualified Data.Map as M import Data.Monoid
instance (Monoid k, Ord k) => Applicative (M.Map k) where pure x = M.fromList [(mempty,x)] fs <*> xs = M.fromList [(k1 `mappend` k2,v1 v2) | (k1,v1) <- M.assocs fs, (k2,v2) <- M.assocs xs]
(sacrificing some functionality, since spaces won't get intercalated between keys if i use strings)
Yes, but why avoid FlexibleInstances?

On Friday 03 September 2010 00:17:22, Alec Benzer wrote:
I guess I'm still sort of confused or perturbed with why it's disabled by default. If the compiler has the ability to do it and there are no problems with doing it, why not just allow it without requiring you to pass a flag to the compiler?
It's disabled by default because the language standard laid down different rules. Generally, compiler writers tend to avoid enabling too much non- standard behaviour by default (though chapter 12 of the GHC user's guide lists a couple of deviations). However, often there's useful stuff that goes against the standard (well, it seemed to be a good idea at the time), so many compilers offer extensions to go beyond the standard.

On Thu, Sep 2, 2010 at 6:49 PM, Daniel Fischer
On Friday 03 September 2010 00:17:22, Alec Benzer wrote:
I guess I'm still sort of confused or perturbed with why it's disabled by default. If the compiler has the ability to do it and there are no problems with doing it, why not just allow it without requiring you to pass a flag to the compiler?
It's disabled by default because the language standard laid down different rules. Generally, compiler writers tend to avoid enabling too much non- standard behaviour by default (though chapter 12 of the GHC user's guide lists a couple of deviations). However, often there's useful stuff that goes against the standard (well, it seemed to be a good idea at the time), so many compilers offer extensions to go beyond the standard.
I guess I would then be concerned with why they didn't allow it in the standard (though I guess "well, it seemed to be a good idea at the time" answers that). I think I also would want to avoid doing things not in the language standard on principle, since my instinct would tell me that if only a particular compiler implements, I shouldn't use it because it'll produce non-standard code. Though this sort of comes comes from C/C++ where there are different compilers on different platforms, but I guess with haskell people pretty much use ghc everywhere?

On Friday 03 September 2010 02:11:22, Alec Benzer wrote:
I guess I would then be concerned with why they didn't allow it in the standard (though I guess "well, it seemed to be a good idea at the time" answers that).
Well, you should ask why. For halfway sane languages like Haskell or C (C89 or C99, not the mad pre-ANSI stuff), most things in the standard are there for good reasons. But some are there because it wasn't noticed early enough that it is in fact a bad idea. And of course lots of really good stuff isn't in the standard because at the time, nobody even thought of it (or had an idea how to implement it). For completely insane languages like Perl or C++, one cannot assume good reasons of course.
I think I also would want to avoid doing things not in the language standard on principle, since my instinct would tell me that if only a particular compiler implements, I shouldn't use it because it'll produce non-standard code. Though this sort of comes comes from C/C++ where there are different compilers on different platforms, but I guess with haskell people pretty much use ghc everywhere?
Pretty much. For a long time, GHC has been the only usable implementation, so real world Haskell is de facto Glasgow Haskell. John Meacham's JHC is now close to being generally usable, I think. And UHC, the Utrecht Haskell Compiler, sounds like a promising project too.

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 9/2/10 20:11 , Alec Benzer wrote:
I guess I would then be concerned with why they didn't allow it in the standard (though I guess "well, it seemed to be a good idea at the time" answers that).
Keep in mind that type theory has advanced a *lot* since Haskell '98 was frozen. Quite a few things that are commonplace in modern GHC were considered prohibitively difficult or expensive to implement back then; others were adjudged "too confusing" (which got monad comprehensions removed and the monomorphism restriction added; the latter is almost universally considered a mistake).
I think I also would want to avoid doing things not in the language standard on principle, since my instinct would tell me that if only a particular compiler implements, I shouldn't use it because it'll produce non-standard code. Though this sort of comes comes from C/C++ where there are different compilers on different platforms, but I guess with haskell people pretty much use ghc everywhere?
More to the point, ghc is the language developers' playground, so other compilers (the few that there are) generally follow ghc's lead. - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.10 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAkyATt0ACgkQIn7hlCsL25UFWACcDYjiefvBZl1tH96XR5iOuWt3 Y9gAnjAYZt1UjfOgthSxG72Norny//ng =8tc2 -----END PGP SIGNATURE-----
participants (4)
-
Alec Benzer
-
Brandon S Allbery KF8NH
-
Brent Yorgey
-
Daniel Fischer