Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Ranges and List Comprehensions in SQL (Tom Murphy)
   2. Re:  question on typeclasses and applicatives (Alec Benzer)
   3. Re:  question on typeclasses and applicatives (Daniel Fischer)
   4. Re:  question on typeclasses and applicatives (Alec Benzer)
   5. Re:  question on typeclasses and applicatives (Brent Yorgey)
   6. Re:  question on typeclasses and applicatives (Daniel Fischer)
   7. Re:  Ranges and List Comprehensions in SQL (Brent Yorgey)
   8. Re:  question on typeclasses and applicatives (Alec Benzer)


----------------------------------------------------------------------

Message: 1
Date: Thu, 2 Sep 2010 15:54:12 -0400
From: Tom Murphy <amin...@gmail.com>
Subject: [Haskell-beginners] Ranges and List Comprehensions in SQL
To: beginners@haskell.org
Message-ID:
        <aanlktineg+pzrz-g_x7vpqwyaodv==cdmp60bx1x9...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi Everyone,

     Is there a "From SQL"-type function that "restores" a range or list
comprehension?

Example:
Let's say I want to keep track of which episodes of a TV show I've seen. I
have an SQL table, in which is a record:
   id (INTEGER): 30
   title (VARCHAR): "The Simpsons"
   episodes_watched (Some data format): [1..4], [14], [18..21], [23..25]

Then, when I pull the record, in Haskell, the "Episodes Watched" is already
one list:
[1,2,3,4,14,18,19,21,23,24,25]

, or a series of lists that I can append together:
[1,2,3,4], [14], [18,19,20,21], [23,24,25]


Note in the example that I would like to be able to store multiple ranges
within a single record.


Thanks so much for any help!
Tom
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100902/1a043af5/attachment-0001.html

------------------------------

Message: 2
Date: Thu, 2 Sep 2010 16:06:45 -0400
From: Alec Benzer <alecben...@gmail.com>
Subject: Re: [Haskell-beginners] question on typeclasses and
        applicatives
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <aanlktimxdyb=jvohgxdxurpojbp5oj+cmdv4gls7m...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Thu, Sep 2, 2010 at 3:19 PM, Daniel Fischer <daniel.is.fisc...@web.de> wrote:
>
> 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.
>


------------------------------

Message: 3
Date: Thu, 2 Sep 2010 22:31:47 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] question on typeclasses and
        applicatives
To: Alec Benzer <alecben...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <201009022231.47793.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

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).



------------------------------

Message: 4
Date: Thu, 2 Sep 2010 17:10:29 -0400
From: Alec Benzer <alecben...@gmail.com>
Subject: Re: [Haskell-beginners] question on typeclasses and
        applicatives
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <aanlktinrfzjg9boctt0sd7tifhk=xczg=gaequwj+...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

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 <daniel.is.fisc...@web.de> wrote:
> 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).
>
>


------------------------------

Message: 5
Date: Thu, 2 Sep 2010 17:48:04 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] question on typeclasses and
        applicatives
To: beginners@haskell.org
Message-ID: <20100902214804.ga15...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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


------------------------------

Message: 6
Date: Thu, 2 Sep 2010 23:50:39 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] question on typeclasses and
        applicatives
To: Alec Benzer <alecben...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <201009022350.40179.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

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?



------------------------------

Message: 7
Date: Thu, 2 Sep 2010 17:52:32 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Ranges and List Comprehensions in SQL
To: beginners@haskell.org
Message-ID: <20100902215232.gb15...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Thu, Sep 02, 2010 at 03:54:12PM -0400, Tom Murphy wrote:
> Hi Everyone,
> 
>      Is there a "From SQL"-type function that "restores" a range or list
> comprehension?
> 
> Example:
> Let's say I want to keep track of which episodes of a TV show I've seen. I
> have an SQL table, in which is a record:
>    id (INTEGER): 30
>    title (VARCHAR): "The Simpsons"
>    episodes_watched (Some data format): [1..4], [14], [18..21], [23..25]
> 
> Then, when I pull the record, in Haskell, the "Episodes Watched" is already
> one list:
> [1,2,3,4,14,18,19,21,23,24,25]
> 
> , or a series of lists that I can append together:
> [1,2,3,4], [14], [18,19,20,21], [23,24,25]
> 
> 
> Note in the example that I would like to be able to store multiple ranges
> within a single record.

I am not sure I understand what you are asking.  Do you want something
like this?

  data Range = Range Integer Integer

  toRanges :: [Integer] -> [Range]
  toRanges = ...

toRanges should not be too hard to write but nothing like that exists
as far as I know.

But I'm pretty sure I haven't understood your question, because I
don't see what SQL has to do with it.  Are you actually using a
database?  Or are you just using SQL as inspiration?

-Brent


------------------------------

Message: 8
Date: Thu, 2 Sep 2010 18:17:22 -0400
From: Alec Benzer <alecben...@gmail.com>
Subject: Re: [Haskell-beginners] question on typeclasses and
        applicatives
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <aanlktim_=gogyofmh5x_fjw2qcjiqokgh3bc2abfq...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

> 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 <daniel.is.fisc...@web.de> wrote:
> 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?
>
>


------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 27, Issue 6
****************************************

Reply via email to