Records in Haskell

2011-09-15 Thread Simon Peyton-Jones
Friends

Provoked the (very constructive) Yesod blog post on "Limitations of Haskell", 
and the follow up discussion, I've started a wiki page to collect whatever 
ideas we have about the name spacing issue for record fields.

http://hackage.haskell.org/trac/ghc/wiki/Records

As Simon M said on Reddit, this is something we'd like to fix; but we need a 
consensus on how to fix it.

Simon


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
I added my evaluation of the module-based approach to existing
records, but on second thoughts it's maybe inappropriate, so I'll post
it here. I saw that some people commented on the reddit discussion
that the solution is to put your types in separate modules but it
doesn't seem that anyone has tried to do this on a large scale. I
tried it (and some other record paradigms including Has), but I don't
think it scales. Here's why…

Suppose I have 112 hand-crafted data types in my
project (e.g. see attachment 51369.txt[1]), this creates a lot of
conflicts in field names and constructor names. For example:

{{{
data Comment = Comment {
  commentId   :: CommentId
, commentContent  :: Content
, commentReviewId :: ReviewId
, commentSubmissionId :: SubmissionId
, commentConferenceId :: ConferenceId
, commentDate :: ISODate
, commentReviewerNumber :: Int
  } deriving (Show)
}}}

This is a real type in my project. It has fields like “id”, “content”,
“reviewId”, “submissionId”, “date”. There are seven other data types
that have a field name “submissionId”. There are 15 with
“conferenceId”. There are 7 with “content”. And so on. This is just to
demonstrate that field clashes ''do'' occur ''a lot'' in a nontrivial
project.

It also demonstrates that if you propose to put each of these 112 types
into a separate module, you are having a laugh. I tried this around
the 20 type mark and it was, apart from being very slow at compiling,
''very'' tedious to work with. Creating and editing these modules was a
distracting and pointless chore.

It ''also'' demonstrated, to me, that qualified imports are horrible
when used on a large scale. It happened all the time, that'd I'd
import, say, 10 different data types all qualified.  Typing map
(Foo.id . BarMu.thisField) and foo Bar.Zot{x=1,y=2} becomes tedious
and distracting, especially having to add every type module when I
want to use a type. And when records use other types in other modules,
you have ''a lot'' of redundancy. With the prefixing paradigm I'd write
fooId and barMuThisField, which is about as tedious but there is at
least less . confusion and no need to make a load of modules and
import lines. Perhaps local modules would solve half of this
problem. Still have to write “Bar.mu bar” rather than “mu bar”, but
it'd be an improvement.

I also have 21 Enum types which often conflict. I end up having to
include the name of the type in the constructor, or rewording it
awkwardly. I guess I should put these all in separate modules and
import qualified,
too. Tedious, though. At least in this case languages like C# and
Java also require that you type EnumName.EnumValue, so c‘est la vie.

[1]: http://hackage.haskell.org/trac/ghc/attachment/wiki/Records/51369.txt

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Barney Hilken
As formulated on the wiki page, the "narrow issue" is a problem without a good 
solution. The reason the community rejected TDNR is because it's basically 
polymorphism done wrong. Since we already have polymorphism done right, why 
would we want it?

The right way to deal with records is first to agree a mechanism for writing a 
context which means

"a is a datatype with a field named n of type b"

then give the selector n the type

"a is a datatype with a field named n of type b" => n :: a -> b

There is no reason why this shouldn't be used with the current syntax (although 
it might clash with more advanced features like first-class labels).

Barney.


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread J. Garrett Morris
On Thu, Sep 15, 2011 at 6:03 AM, Barney Hilken  wrote:
> The right way to deal with records is first to agree a mechanism for
> writing a context which means
>
>        "a is a datatype with a field named n of type b"
>
> then give the selector n the type
>
>        "a is a datatype with a field named n of type b" => n :: a -> b
>
> There is no reason why this shouldn't be used with the current syntax
> (although it might clash with more advanced features like first-class
> labels).

Trex is one existing approach in the Haskell design space
http://web.cecs.pdx.edu/~mpj/pubs/polyrec.html
http://web.cecs.pdx.edu/~mpj/pubs/lightrec.html

 /g

-- 
"I’m surprised you haven’t got a little purple space dog, just to ram
home what an intergalactic wag you are."

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
TRex is already mentioned on the wiki as coming at a too high
implementation cost.

2011/9/15 J. Garrett Morris :
> On Thu, Sep 15, 2011 at 6:03 AM, Barney Hilken  wrote:
>> The right way to deal with records is first to agree a mechanism for
>> writing a context which means
>>
>>        "a is a datatype with a field named n of type b"
>>
>> then give the selector n the type
>>
>>        "a is a datatype with a field named n of type b" => n :: a -> b
>>
>> There is no reason why this shouldn't be used with the current syntax
>> (although it might clash with more advanced features like first-class
>> labels).
>
> Trex is one existing approach in the Haskell design space
> http://web.cecs.pdx.edu/~mpj/pubs/polyrec.html
> http://web.cecs.pdx.edu/~mpj/pubs/lightrec.html
>
>  /g
>
> --
> "I’m surprised you haven’t got a little purple space dog, just to ram
> home what an intergalactic wag you are."
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Windows build problems

2011-09-15 Thread Daniel Fischer
I'm trying to set up a build/test environment on Windows.

Building ghc (sh validate) fails after a while due to flex and bison 
crashing. Those two come with git and even
$ flex --version
(or bison) crashes, so they seem truly hosed.

Do I need flex/bison at all to build ghc?
It seems they're not used on linux for building ghc.
So, if not, how do I configure things that the build doesn't try to use 
bison/flex?
If yes, would installing flex and bison from gnuwin32 work?

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Ian Lynagh
On Thu, Sep 15, 2011 at 08:47:30AM +, Simon Peyton-Jones wrote:
> 
> Provoked the (very constructive) Yesod blog post on "Limitations of Haskell", 
> and the follow up discussion, I've started a wiki page to collect whatever 
> ideas we have about the name spacing issue for record fields.
> 
> http://hackage.haskell.org/trac/ghc/wiki/Records
> 
> As Simon M said on Reddit, this is something we'd like to fix; but we need a 
> consensus on how to fix it.

Re TypeDirectedNameResolution, I would actually prefer it if it were
less general. i.e. if you were to write
x.f
then f would be required to be a record selector.

Then there's no need for the "If there is exactly one f whose type
matches that of x" unpleasantness. Instead, the type of x must be
inferred first (without any knowledge about the type of f), and then we
know immediately which f is being referred to.


Thanks
Ian


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Records in Haskell

2011-09-15 Thread Simon Peyton-Jones
J Garrett Morris asked me

| I also rather like the TDNR proposal, as it's rather similar to the
| approach we're taking in Habit (our pet language at Portland State).
| However, I'm curious as to why you don't want to quantify over name
| resolution constraints.  For example, why shouldn't:
| 
| x f = f.x
| 
| be a reasonable function? 

Yes, it would, and of course any impl of TDNR would need an internal constraint 
similar to your Select.  In my original proposal I was hiding that, but it has 
to be there in the implementation.  But you are right that making it explicit 
might be a good thing.  Esp with Julien's new kind stuff (coming soon) we 
should be able to say

class Select (rec :: *) (fld :: String) where
  type ResTy rec fld:: *
  get :: rec -> ResTy rec fld

data T = MkT { x,y :: Int }
instance Select T "x" where
  get (MkT {x = v}) = v

And now we desugar   
f.x
as
get @T @"x" f

where the "@" stuff is type application, because get's type is ambiguous:
get :: forall rec fld. Select rec fld => rec -> ResTy rec fld

Just like what Hobbit does really.

You probably don't use the idea of extending to arbitrary other functions do 
you?  (Which Ian does not like anyway.)  Something like

getIndex :: T -> Int
getIndex (MkT x y) = x+y

Then I'd like to be able to say

t.getIndex

So there's an implicit instance
instance Select T "getIndex" where
 type ResTy T "getIndex" = Int
 get = getIndex


It's a little unclear what operations should be in class Select.  'get' 
certainly, but I propose *not* set, because it doesn't make sense for getIndex 
and friends.  So that would mean you could write a polymorphic update:

f v = f { x = v }

Restricting to record fields only would, I suppose, allow polymorphic update, 
by adding a 'set' method to Select.

Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
I personally really like the proposal here:
http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html

The wiki doesn't show any opposition to this system. If Haskell had
that record system now I would be very happy and would be fine with
leaving other record systems as purely research until this whole
research area comes to some decisions.

> I believe the way forward is to implement several of the possible systems, 
> and release them for feedback. To get users to actually try out the 
> libraries, I think we need some concrete syntax for constant records, so I 
> suggest we put in a feature request.

It would also be nice if one saintly person could spend the time
documenting the available record systems in one document, trying out
examples of codebases and collecting surveys on the various systems or
something. It's a project in itself.

Personally my vote for what it's worth is Worse is Better in this
case, and to implement Simon's proposal (not that I think this
proposal is Worse, but possibly worse than
X-other-really-nice-but-tough-to-decide-on-system). If we still have
nothing by this time in six months I'll implement the bloody thing in
GHC myself.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Greg Weber
Chris, Thank you for the real word experience report. I had assumed (because
everyone else told me) that importing qualified would be much, much better
than prefixing. I had thought that in your case since you are big on model
separation that you would have liked having a separate file for each model
to separate out all your model related code with. As a counter point, in all
of my (MVC) web application projects, we do have a separate file for each
model, and we like this approach. Each file usually contains a lot of
"business logic" related to the model- the only relatively empty model files
are ones that really represent embedded data. When I use MongoDB (which
actually supports embedded data instead of forcing you to create a separate
table), I will actually place the embedded models in the same file as the
model which includes them.

After my blog post complaining about records, I had a few people telling me
that I can just use existing polymorphism to avoid the name-spacing issue. I
collected the approaches here: http://www.yesodweb.com/wiki/record-hacks
I didn't think any of those telling me what i should do had actually tried
to do this themselves, particularly at any kind of larger scale. I am
interested to see if anyone has experience trying this approach, or if you
have considered it.

On Thu, Sep 15, 2011 at 3:00 AM, Christopher Done
wrote:

> I added my evaluation of the module-based approach to existing
> records, but on second thoughts it's maybe inappropriate, so I'll post
> it here. I saw that some people commented on the reddit discussion
> that the solution is to put your types in separate modules but it
> doesn't seem that anyone has tried to do this on a large scale. I
> tried it (and some other record paradigms including Has), but I don't
> think it scales. Here's why…
>
> Suppose I have 112 hand-crafted data types in my
> project (e.g. see attachment 51369.txt[1]), this creates a lot of
> conflicts in field names and constructor names. For example:
>
> {{{
> data Comment = Comment {
>  commentId   :: CommentId
>, commentContent  :: Content
>, commentReviewId :: ReviewId
>, commentSubmissionId :: SubmissionId
>, commentConferenceId :: ConferenceId
>, commentDate :: ISODate
>, commentReviewerNumber :: Int
>  } deriving (Show)
> }}}
>
> This is a real type in my project. It has fields like “id”, “content”,
> “reviewId”, “submissionId”, “date”. There are seven other data types
> that have a field name “submissionId”. There are 15 with
> “conferenceId”. There are 7 with “content”. And so on. This is just to
> demonstrate that field clashes ''do'' occur ''a lot'' in a nontrivial
> project.
>
> It also demonstrates that if you propose to put each of these 112 types
> into a separate module, you are having a laugh. I tried this around
> the 20 type mark and it was, apart from being very slow at compiling,
> ''very'' tedious to work with. Creating and editing these modules was a
> distracting and pointless chore.
>
> It ''also'' demonstrated, to me, that qualified imports are horrible
> when used on a large scale. It happened all the time, that'd I'd
> import, say, 10 different data types all qualified.  Typing map
> (Foo.id . BarMu.thisField) and foo Bar.Zot{x=1,y=2} becomes tedious
> and distracting, especially having to add every type module when I
> want to use a type. And when records use other types in other modules,
> you have ''a lot'' of redundancy. With the prefixing paradigm I'd write
> fooId and barMuThisField, which is about as tedious but there is at
> least less . confusion and no need to make a load of modules and
> import lines. Perhaps local modules would solve half of this
> problem. Still have to write “Bar.mu bar” rather than “mu bar”, but
> it'd be an improvement.
>
> I also have 21 Enum types which often conflict. I end up having to
> include the name of the type in the constructor, or rewording it
> awkwardly. I guess I should put these all in separate modules and
> import qualified,
> too. Tedious, though. At least in this case languages like C# and
> Java also require that you type EnumName.EnumValue, so c‘est la vie.
>
> [1]: http://hackage.haskell.org/trac/ghc/attachment/wiki/Records/51369.txt
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread J. Garrett Morris
On Thu, Sep 15, 2011 at 7:51 AM, Simon Peyton-Jones
 wrote:

> class Select (rec :: *) (fld :: String) where
>  type ResTy rec fld:: *
>  get :: rec -> ResTy rec fld
>
> data T = MkT { x,y :: Int }
> instance Select T "x" where
>  get (MkT {x = v}) = v
>
> And now we desugar
>    f.x
> as
>    get @T @"x" f

That's close to our approach, yes.  To avoid the ambiguity in the type
of 'get' (which we call 'select'), we introduce a type constructor

< Lab :: lab -> *

to build singleton types out of type-level lables.  Then the Select
class is defined by:

< class Select (t :: *) (f :: lab) = (r :: *)
 Lab f -> r

and 'f.x' is desugared to 'select f #x' (again, using '#x' as syntax for
the label thingy).  The potential advantage to this approach is that it
allows select to behave normally, without the need to insert type
applications (before type inference); on the other hand, it requires
syntax for the singleton label types.  Take your pick, I suppose. :)

> You probably don't use the idea of extending to arbitrary other
> functions do you?  (Which Ian does not like anyway.)  Something like
>
>    getIndex :: T -> Int
>    getIndex (MkT x y) = x+y
>
> Then I'd like to be able to say
>
>        t.getIndex
>
> So there's an implicit instance
>        instance Select T "getIndex" where
>         type ResTy T "getIndex" = Int
>         get = getIndex

We don't support that for arbitrary functions, no.  On the other hand,
our Select class is exposed, so the user can potentially add new
instances; for a silly example in Habit:

< newtype Temperature = Temp Signed
<
< instance Temperature.celsius = Signed where
<   (Temp c).celsius = c
<
< instance Temperature.fahrenheit = Signed where
<   (Temp c).fahrenheit = 32 + (c*9)/5

> It's a little unclear what operations should be in class
> Select.  'get' certainly, but I propose *not* set, because it doesn't
> make sense for getIndex and friends.  So that would mean you could
> write a polymorphic update:

We treat update as a separate class,

< class Update (t :: *) (f :: lab)
 Lab f -> t.f -> t

and desugar update syntax, something like:

< e { x = e' }

to calls to the update function

< update e #x e'

As with Select, this should allow polymorphic update functions:

< updX :: Update f #x => f -> f.x -> f
< updX f e = f { x = e }

 /g

-- 
"I’m surprised you haven’t got a little purple space dog, just to ram
home what an intergalactic wag you are."

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Use -V0 causes space to leak?

2011-09-15 Thread Neil Davies

Hi

I have some long running (multi-gigabit, multi-cpu hour) programs and  
as part of trying to speed up I thought I would set the -V0 flag -  
when I did this there was a slow space leak that caused it to blow the  
heap.


Anyone out there have an explanation? Is there some garbage collection  
thing associated with something that -V0 suppresses?


Cheers

Neil

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
2011/9/15 Greg Weber :
> Chris, Thank you for the real word experience report. I had assumed (because
> everyone else told me) that importing qualified would be much, much better
> than prefixing. I had thought that in your case since you are big on model
> separation that you would have liked having a separate file for each model
> to separate out all your model related code with. As a counter point, in all
> of my (MVC) web application projects, we do have a separate file for each
> model, and we like this approach. Each file usually contains a lot of
> "business logic" related to the model- the only relatively empty model files
> are ones that really represent embedded data. When I use MongoDB (which
> actually supports embedded data instead of forcing you to create a separate
> table), I will actually place the embedded models in the same file as the
> model which includes them.

Ah, this is because my approach to types is to put them in a
ProjectName.Types.X module. I /do/ have separate modules for all my
models, e.g.

$ ls Confy/Model/*.hs
Confy/Model/Actions.hs Confy/Model/Driver.hs
Confy/Model/Manuscript.hsConfy/Model/Proceedings.hs 
Confy/Model/SubmissionAuthor.hs  Confy/Model/Token.hs
Confy/Model/Activity.hsConfy/Model/Fields.hs
Confy/Model/Message.hs   Confy/Model/ReviewComment.hs   
Confy/Model/Submission.hsConfy/Model/Track.hs
Confy/Model/Author.hs  Confy/Model/FormField.hs
Confy/Model/Papertype.hs Confy/Model/ReviewerPreference.hs
Confy/Model/Tables.hsConfy/Model/User.hs
Confy/Model/Conference.hs  Confy/Model/Form.hs  
Confy/Model/Participant.hs  Confy/Model/Review.hs   
Confy/Model/Template.hs  Confy/Model/UserMeta.hs
Confy/Model/Deadline.hsConfy/Model/LogEntry.hs
Confy/Model/Period.hsConfy/Model/Role.hsConfy/Model/TH.hs   

 Confy/Model/Utils.hs

I have my HaskellDB types and then I have my normal Haskell types
which contain different fields to the database model.

But to put the /type/ in the model file itself causes cyclic import
problems when I have to start caring about what imports what and then
having modules that just contain types, etc. I find this to be quite
laborious, I did it at first but it became a hindrance to development
practice for me. Have you not found that you have this problem if you
put types in the same modules as code in a large project? Examples
welcome, too.

> After my blog post complaining about records, I had a few people telling me
> that I can just use existing polymorphism to avoid the name-spacing issue. I
> collected the approaches here: http://www.yesodweb.com/wiki/record-hacks
> I didn't think any of those telling me what i should do had actually tried
> to do this themselves, particularly at any kind of larger scale. I am
> interested to see if anyone has experience trying this approach, or if you
> have considered it.

I considered that approach but never tried it, one would probably
enlist the help of TemplateHaskell to do that approach properly. Maybe
it's not so bad? I suppose I could try making a few branches in my
project and try out this approach.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Greg Weber
I should be clear that in my counter point I am using Ruby, not Haskell on
those projects. In Ruby one can use a string for the name of a class (which
will be evaluated later) and other general dynamic typing tricks to avoid
cyclical dependencies.

I have worked on one large Yesod project. I felt they were creating
artificially shortened field names in some cases (that I found difficult to
understand/remember) to try and ease the pain of large prefixed record
selectors. However, Yesod does create all the records with prefixes in one
module/file- so all the types are in there. They create a new model file for
each model (conceptually, but not for a model representing simple embedded
data). The model file can import all the record types.

Personally I would prefer to define my type in the model file so I can
quickly see my type with the related code if it were possible, but it seems
that it isn't.

On Thu, Sep 15, 2011 at 8:15 AM, Christopher Done
wrote:

> 2011/9/15 Greg Weber :
> > Chris, Thank you for the real word experience report. I had assumed
> (because
> > everyone else told me) that importing qualified would be much, much
> better
> > than prefixing. I had thought that in your case since you are big on
> model
> > separation that you would have liked having a separate file for each
> model
> > to separate out all your model related code with. As a counter point, in
> all
> > of my (MVC) web application projects, we do have a separate file for each
> > model, and we like this approach. Each file usually contains a lot of
> > "business logic" related to the model- the only relatively empty model
> files
> > are ones that really represent embedded data. When I use MongoDB (which
> > actually supports embedded data instead of forcing you to create a
> separate
> > table), I will actually place the embedded models in the same file as the
> > model which includes them.
>
> Ah, this is because my approach to types is to put them in a
> ProjectName.Types.X module. I /do/ have separate modules for all my
> models, e.g.
>
> $ ls Confy/Model/*.hs
> Confy/Model/Actions.hs Confy/Model/Driver.hs
> Confy/Model/Manuscript.hsConfy/Model/Proceedings.hs
> Confy/Model/SubmissionAuthor.hs  Confy/Model/Token.hs
> Confy/Model/Activity.hsConfy/Model/Fields.hs
> Confy/Model/Message.hs   Confy/Model/ReviewComment.hs
> Confy/Model/Submission.hsConfy/Model/Track.hs
> Confy/Model/Author.hs  Confy/Model/FormField.hs
> Confy/Model/Papertype.hs Confy/Model/ReviewerPreference.hs
> Confy/Model/Tables.hsConfy/Model/User.hs
> Confy/Model/Conference.hs  Confy/Model/Form.hs
> Confy/Model/Participant.hs  Confy/Model/Review.hs
> Confy/Model/Template.hs  Confy/Model/UserMeta.hs
> Confy/Model/Deadline.hsConfy/Model/LogEntry.hs
> Confy/Model/Period.hsConfy/Model/Role.hs
>  Confy/Model/TH.hs
>  Confy/Model/Utils.hs
>
> I have my HaskellDB types and then I have my normal Haskell types
> which contain different fields to the database model.
>
> But to put the /type/ in the model file itself causes cyclic import
> problems when I have to start caring about what imports what and then
> having modules that just contain types, etc. I find this to be quite
> laborious, I did it at first but it became a hindrance to development
> practice for me. Have you not found that you have this problem if you
> put types in the same modules as code in a large project? Examples
> welcome, too.
>
> > After my blog post complaining about records, I had a few people telling
> me
> > that I can just use existing polymorphism to avoid the name-spacing
> issue. I
> > collected the approaches here: http://www.yesodweb.com/wiki/record-hacks
> > I didn't think any of those telling me what i should do had actually
> tried
> > to do this themselves, particularly at any kind of larger scale. I am
> > interested to see if anyone has experience trying this approach, or if
> you
> > have considered it.
>
> I considered that approach but never tried it, one would probably
> enlist the help of TemplateHaskell to do that approach properly. Maybe
> it's not so bad? I suppose I could try making a few branches in my
> project and try out this approach.
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Christopher Done
2011/9/15 Greg Weber :
> I should be clear that in my counter point I am using Ruby, not Haskell on
> those projects. In Ruby one can use a string for the name of a class (which
> will be evaluated later) and other general dynamic typing tricks to avoid
> cyclical dependencies.

Ah, okay. Sure, late binding (that's what it's called) makes it convenient.

> I have worked on one large Yesod project. I felt they were creating
> artificially shortened field names in some cases (that I found difficult to
> understand/remember) to try and ease the pain of large prefixed record
> selectors.

I can understand that. Accessors like reviewAssignSubmissionId for a
ReviewAssign record are pretty tedious but at least I don't have
trouble remembering them.

> However, Yesod does create all the records with prefixes in one
> module/file- so all the types are in there. They create a new model file for
> each model (conceptually, but not for a model representing simple embedded
> data). The model file can import all the record types.

Right, that's what I do. Types in one big types file, and then the
functions for the model in Project.Model.X which imports the types
file. This is an internal project, but it will be released as open
source in a few months so showing you the haddock output isn't a big
deal: http://chrisdone.com/confy-doc/ My militantness regarding adding
haddock docs is scant due to deadline pressures as you'd expect, but
it's not so bad.

E.g. checkout http://chrisdone.com/confy-doc/Confy-Model-Conference.html
and it's blatant I'm using a lot of other types.

All entities or entity-like things are in:
http://chrisdone.com/confy-doc/Confy-Types-Entities.html and enums in
http://chrisdone.com/confy-doc/Confy-Types-Enums.html

And do not look at
http://chrisdone.com/confy-doc/Confy-Model-Tables.html because it is
frightening and will make you go bald. If you're already bald, feel
free! HaskellDB and its HList-like record system.

> Personally I would prefer to define my type in the model file so I can
> quickly see my type with the related code if it were possible, but it seems
> that it isn't.

I guess it can be possible with a lot of discipline and patience.
Maybe others have done this in large projects and found it not so bad?

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Barney Hilken
Here is a simple concrete proposal:

Nonextensible records with polymorphic selectors.
=

1. Introduce a built-in class Label, whose members are strings at the type 
level. We need a notation for them; I will use double single quotes, so 
''string'' is automatically an instance of Label, and you can't define other 
instances.

2. Define a class (in a library somewhere)

class Label n => Contains r n where
type field r n :: *
select :: r -> n -> field r n
update :: r -> n -> field r n -> r

3. Declarations with field labels such as

data C = F {l1 :: t1, l2 :: t2} | G {l2 :: t2}

are syntactic sugar for

data C = F t1 t2 | G t2

instance Contains C ''l1'' where
field C ''l1'' = t1
select (F x y) _ = x
update (F x y) _ x' = F x' y

instance Contains C ''l2'' where
field C ''l2'' = t2
select (F x y) _ = y
select (G y) _ = y
update (F x y) _ y' = F x y'
update (G y) _ y' = G y'

4. Selector functions only need to be defined once, however many types they are 
used in

l1 :: Contains r ''l1'' => r -> field r ''l1''
l1 = select r (undef ::''l1'')

l2 :: Contains r ''l2'' => r -> field r ''l2''
l2 = select r (undef ::''l2'')

5. Constructors are exactly as before

6. Updates such as

r {l1 = x}

are syntactic sugar for

update r (undef::''l1'') x

=

This has the advantage that the extension to Haskell is fairly small, and it's 
compatible with existing user code, but if we later decide we want extensible 
records, we need only add a type function to order Label lexicographically.

Barney.


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Windows build problems

2011-09-15 Thread Bill Tutt
>From Daniel Fischer:

> I'm trying to set up a build/test environment on Windows.

> Building ghc (sh validate) fails after a while due to flex and bison
> crashing. Those two come with git and even
> $ flex --version
> (or bison) crashes, so they seem truly hosed.

> Do I need flex/bison at all to build ghc?
> It seems they're not used on linux for building ghc.
> So, if not, how do I configure things that the build doesn't try to use
> bison/flex?
> If yes, would installing flex and bison from gnuwin32 work?

I ran into this issue last night as well. See
http://hackage.haskell.org/trac/ghc/ticket/5489

flex appears to be required from integer-gmp's ./configure for one of
GMP's demo programs. (a calculator demo I think)

I'm trying to see if a slightly newer msys installation process as
listed in the Trac bug will take care of it.

However, last night I got a stage 1 ghc seg fault while compiling some
Haskell code further along in the build.

I currently have a devel1 build in progress to see what I come up with next.

I also ran into: http://hackage.haskell.org/trac/ghc/ticket/5488 about
bootstrapping using the Windows 7.2.1 standalone bits to bootstrap
ghc-HEAD.
If the devel1 build doesn't give any useful symptoms to pass along
I'll probably retry the build using the Haskell Platform compiler.

Fyi,
Bill

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Barney Hilken
Typos in my last message: the identifier "field" should be "Field" throughout, 
and "undef" should be "undefined". Here is the corrected version:

Nonextensible records with polymorphic selectors.
=

1. Introduce a built-in class Label, whose members are strings at the type 
level. We need a notation for them; I will use double single quotes, so 
''string'' is automatically an instance of Label, and you can't define other 
instances.

2. Define a class (in a library somewhere)

class Label n => Contains r n where
type Field r n :: *
select :: r -> n -> Field r n
update :: r -> n -> Field r n -> r

3. Declarations with field labels such as

data C = F {l1 :: t1, l2 :: t2} | G {l2 :: t2}

are syntactic sugar for

data C = F t1 t2 | G t2

instance Contains C ''l1'' where
Field C ''l1'' = t1
select (F x y) _ = x
update (F x y) _ x' = F x' y

instance Contains C ''l2'' where
Field C ''l2'' = t2
select (F x y) _ = y
select (G y) _ = y
update (F x y) _ y' = F x y'
update (G y) _ y' = G y'

4. Selector functions only need to be defined once, however many types they are 
used in

l1 :: Contains r ''l1'' => r -> Field r ''l1''
l1 = select r (undefined ::''l1'')

l2 :: Contains r ''l2'' => r -> Field r ''l2''
l2 = select r (undefined ::''l2'')

5. Constructors are exactly as before

6. Updates such as

r {l1 = x}

are syntactic sugar for

update r (undefined::''l1'') x

=

Sorry about that.

Barney.


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Windows build problems

2011-09-15 Thread Daniel Fischer
On Thursday 15 September 2011, 21:41:10, Bill Tutt wrote:
> From Daniel Fischer:
> > I'm trying to set up a build/test environment on Windows.
> > 
> > Building ghc (sh validate) fails after a while due to flex and bison
> > crashing. Those two come with git and even
> > $ flex --version
> > (or bison) crashes, so they seem truly hosed.
> > 
> > Do I need flex/bison at all to build ghc?
> > It seems they're not used on linux for building ghc.
> > So, if not, how do I configure things that the build doesn't try to
> > use bison/flex?
> > If yes, would installing flex and bison from gnuwin32 work?
> 
> I ran into this issue last night as well. See
> http://hackage.haskell.org/trac/ghc/ticket/5489

Ugh. I'd like to avoid uninstalling msys and installing something new if 
possible.

> 
> flex appears to be required from integer-gmp's ./configure for one of
> GMP's demo programs. (a calculator demo I think)

I can't find anything indicating that on linux, so it'd be probably be due 
to using the in-tree gmp on Windows? But the only mention of flex that 
seems possibly relevant is

# These flags make flex 8-bit
SRC_FLEX_OPTS   += -8

in mk/config.mk.in, and bison is only mentioned in two word lists in 
libraries/bytestring/tests at all (as the animal of course).
So I'm still mystified.

> 
> I'm trying to see if a slightly newer msys installation process as
> listed in the Trac bug will take care of it.

If you get it to work, I'd appreciate detailed (Windows is so far utterly 
incomprehensible to me, so they'd better be very explicit) instructions.

> 
> However, last night I got a stage 1 ghc seg fault while compiling some
> Haskell code further along in the build.

Perhaps compiling GHC.Debug.hs? That's where I get a stage1 segfault on 
linux when bootstrapping with 7.2.1, cf 
http://hackage.haskell.org/trac/ghc/ticket/5484

However, I'm bootstrapping with 7.0.4 (switched on Windows due to the ar 
location problem mentioned in #5488, that gets me to the bison/flex 
problem, builds fine on linux).

> 
> I currently have a devel1 build in progress to see what I come up with
> next.
> 
> I also ran into: http://hackage.haskell.org/trac/ghc/ticket/5488 about
> bootstrapping using the Windows 7.2.1 standalone bits to bootstrap
> ghc-HEAD.
> If the devel1 build doesn't give any useful symptoms to pass along
> I'll probably retry the build using the Haskell Platform compiler.

If your stage1 segfault is the same as mine, switching to 7.0.x should get 
you around it.

> 
> Fyi,
> Bill

Thx,
Daniel

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Windows build problems

2011-09-15 Thread Bill Tutt
On Thu, Sep 15, 2011 at 6:00 PM, Daniel Fischer
 wrote:
>>
>> flex appears to be required from integer-gmp's ./configure for one of
>> GMP's demo programs. (a calculator demo I think)
>
> I can't find anything indicating that on linux, so it'd be probably be due
> to using the in-tree gmp on Windows? But the only mention of flex that
> seems possibly relevant is

integer-gmp/gmp/gmpbuild/configure.in has AM_PROG_LEX which requires (f)lex.
it also has AC_PROG_YACC which I'd guess requires yacc/bison.

>>
>> I'm trying to see if a slightly newer msys installation process as
>> listed in the Trac bug will take care of it.
>
> If you get it to work, I'd appreciate detailed (Windows is so far utterly
> incomprehensible to me, so they'd better be very explicit) instructions.
>

I feel your pain. The Windows instructions could definately use some
updating. :)

I ended up getting an error during stage 2 about the iconv.dll not
being findable. (I'm guessing the new msys/mingw autosmarted GHC
boot/configure or cabal configure process somehow )

ghc-stage2 was trying to build vector-0.8 and failed during Loading
package base ... (due to not finding iconv.dll)

>>
>> However, last night I got a stage 1 ghc seg fault while compiling some
>> Haskell code further along in the build.
>
> Perhaps compiling GHC.Debug.hs? That's where I get a stage1 segfault on
> linux when bootstrapping with 7.2.1, cf
> http://hackage.haskell.org/trac/ghc/ticket/5484

That sounds like it. I'll go back and look at that after I see how bad
the iconv issue is to chase down.
That msys install the wiki points everybody at really is ancient. :)

Bill

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Windows build problems

2011-09-15 Thread Bill Tutt
On Thu, Sep 15, 2011 at 9:01 PM, Bill Tutt  wrote:
>
> I ended up getting an error during stage 2 about the iconv.dll not
> being findable. (I'm guessing the new msys/mingw autosmarted GHC
> boot/configure or cabal configure process somehow )
>

Yep. This is most likely the problem. -liconv wasn't found during
Simon's 8/23 ghc-HEAD build on Windows:
http://darcs.haskell.org/ghcBuilder/builders/simonmar-win32-head/377/8.html

cabal configure of libraries\base found a working -liconv
from one of:
/bin/libiconv-2.dll
/msys/1.0/bin/msys-libiconv-2.dll
/lib/libiconv.a
/lib/libiconv.dll.a
/lib/libiconv.la

The in tree mingw is picking up /lib/libiconv.a but apparently
libraries\base\configure doesn't require it to be a shared library.

Fyi,
Bill

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Evan Laforge
> It ''also'' demonstrated, to me, that qualified imports are horrible
> when used on a large scale. It happened all the time, that'd I'd
> import, say, 10 different data types all qualified.  Typing map
> (Foo.id . BarMu.thisField) and foo Bar.Zot{x=1,y=2} becomes tedious
> and distracting, especially having to add every type module when I
> want to use a type. And when records use other types in other modules,
> you have ''a lot'' of redundancy. With the prefixing paradigm I'd write
> fooId and barMuThisField, which is about as tedious but there is at
> least less . confusion and no need to make a load of modules and
> import lines. Perhaps local modules would solve half of this
> problem. Still have to write “Bar.mu bar” rather than “mu bar”, but
> it'd be an improvement.

I disagree about qualified imports, in my experience they're even more
useful as the scale increases, because there are many more modules
each symbol could come from, and many more name conflicts, and of
course there starts to be module name conflicts.  I don't find it much
of an imposition because I have an automatic tool to add and remove
imports when needed, and once the import is already there keyword
completion works on it.  Grepping for '^data .. =', I have 199 types,
of which 97 are probably records, spread over 296 modules.  The 97
records are spread over 50 modules, but in practice there are a number
with 5-10 and then a long tail with just 1 or 2 each.

However I entirely agree a better syntax for records would make
programming clearer, more concise, and more fun.  I also agree that
one module per record is annoying, so I wind up with many records per
module, so I have record prefixes anyway.  Access is annoying, but not
so bad, I think.  It's true '(ModuleB.recField2 . ModuleA.recField1)
val' is inferior to val.field1.field2, but at least the functions
compose and if you make a habit of reducing the dots by defining a few
precomposed functions you can cut out a lot of the work of moving a
field, or more likely, grouping several fields into a nested record.
But the really annoying thing is that modification doesn't compose.
Record updates also don't mix well with other update functions.  So,
just to put give another data point, here's an extreme case:

set_track_width view_id tracknum width = do
views <- gets views
view <- maybe (throw "...") return $ Map.lookup view views
track_views <- modify_at "set_track_width"
(Block.view_tracks view) tracknum $ \tview ->
tview { Block.track_view_width = width }
let view' = view { Block.view_tracks = track_views }
modify $ \st ->
st { state_views = Map.insert view_id view' (state_views st) }

I inlined the 'modify_view' function, so this looks even nastier than
the real code, but it would be nice to not have to define those helper
functions!  In an imperative language, this would look something like

state.views[view_id].tracks[tracknum].width = width

Of course, there's also monadic vs. non-monadic getting its claws in
there (and the lack of stack traces, note the explicit passing of the
function name).  So if I hypothesize a .x syntax that is a
modification function, some handwavy two arg forward composition, and
remove the monadic part (could get it back in with some fancy
combinator footwork), theoretically haskell could get pretty close to
the imperative version:

let Map.modify k m f = Data.Map.adjust f k m
(.views .> Map.modify view_id .> .tracks .> modify_at tracknum .>
.width) state width
-- or, let set = (...) in state `set` width

It's also nice if the field names can be in their own namespace, since
it's common to say 'x.y = y'.  I'm not saying I think the above would
be a good record syntax, just that I think composing with other modify
functions is important.  Passing to State.modify is another obvious
thing to want to do.

The above is an extreme case, but I've lost count of the number of
times I've typed 'modify $ \st -> st { field = f (field st) }'.  I
don't even have to think about it anymore.

I know that these are the problems that lenses / first class labels
libraries aim to solve, so if we're talking only about non-extensible
records, I'm curious about what a language extension could provide
that a library can't.  Simply not being standard and built-in is a big
one, but presumably the platform is an answer to that.

It would be nice if record updates and access to come with no
performance penalty over the existing system, since updating records
forms a large part of the runtime of some programs, I'm not sure if
the libraries can provide that?

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Windows build problems

2011-09-15 Thread B. Scott Michel
Bill:

It might also be the case that you're seeing the same issue as ghci not finding 
the stdc++ library. The solution may be as simple as hacking the Makefile is 
nail a specific PATH to where iconv.dll is located. But, I'm not in front of a 
development box, so I can't be of much help.


-scooter
Sent from my Verizon Wireless BlackBerry

-Original Message-
From: Bill Tutt 
Sender: glasgow-haskell-users-boun...@haskell.org
Date: Thu, 15 Sep 2011 21:22:34 
To: 
Subject: Re: Windows build problems

On Thu, Sep 15, 2011 at 9:01 PM, Bill Tutt  wrote:
>
> I ended up getting an error during stage 2 about the iconv.dll not
> being findable. (I'm guessing the new msys/mingw autosmarted GHC
> boot/configure or cabal configure process somehow )
>

Yep. This is most likely the problem. -liconv wasn't found during
Simon's 8/23 ghc-HEAD build on Windows:
http://darcs.haskell.org/ghcBuilder/builders/simonmar-win32-head/377/8.html

cabal configure of libraries\base found a working -liconv
from one of:
/bin/libiconv-2.dll
/msys/1.0/bin/msys-libiconv-2.dll
/lib/libiconv.a
/lib/libiconv.dll.a
/lib/libiconv.la

The in tree mingw is picking up /lib/libiconv.a but apparently
libraries\base\configure doesn't require it to be a shared library.

Fyi,
Bill

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


accessing compilation parameters from template haskell

2011-09-15 Thread Ganesh Sittampalam
Hi,

It would be useful to access the current compilation parameters or even
an entire RunGhc monad from inside a Template Haskell splice. Is there
any way to do this?

The reason I want to do this is I'm using the ghc API at runtime to
dynamically execute code, and I want both the dynamically loaded code
and static code to use a shared runtime module that defines some types
used for communication across the boundary. To guarantee the internal
representations etc are the same, I store the object file of the runtime
during compilation then load it dynamically at runtime - but to make
this work I need to know where the object file is (-odir and -hidir) and
I also need to know or be able to deduce the GHC DynFlags so I can
replicate them at runtime.

I could also achieve this goal by putting my runtime in a separate
package and installing it first, but that's less self-contained and
would be a pain during development.

Cheers,

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2011-09-15 Thread Ganesh Sittampalam
On 15/09/2011 15:43, Ian Lynagh wrote:
> On Thu, Sep 15, 2011 at 08:47:30AM +, Simon Peyton-Jones wrote:
>>
>> Provoked the (very constructive) Yesod blog post on "Limitations of 
>> Haskell", and the follow up discussion, I've started a wiki page to collect 
>> whatever ideas we have about the name spacing issue for record fields.
>>
>> http://hackage.haskell.org/trac/ghc/wiki/Records
>>
>> As Simon M said on Reddit, this is something we'd like to fix; but we need a 
>> consensus on how to fix it.
> 
> Re TypeDirectedNameResolution, I would actually prefer it if it were
> less general. i.e. if you were to write
> x.f
> then f would be required to be a record selector.
> 
> Then there's no need for the "If there is exactly one f whose type
> matches that of x" unpleasantness. Instead, the type of x must be
> inferred first (without any knowledge about the type of f), and then we
> know immediately which f is being referred to.

One benefit of TDNR is to replicate the discoverability of APIs that OO
programming has - if x :: Foo then typing "x." in an IDE gives you a
list of things you can do with a Foo. (Obviously it's not a complete lis
for various reasons, but it does allow the author of Foo and others to
design discoverable APIs.)

So I think we'd be losing quite a bit to force f to be a record selector.

Ganesh

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users