Re: ghc-cabal-Random

2012-01-02 Thread Serge D. Mechveliani
On Sun, Jan 01, 2012 at 07:51:39AM -0500, Ryan Newton wrote:
> I haven't entirely followed this and I see that it's been split over
> multiple threads.
> 
> Did "cabal install random" actually fail for you under
> ghc-7.4.0.20111219?  If so I'd love to know about it as the maintainer
> of the "random" package.  (It seems to work for me for
> random-1.0.1.1.)

"cabal install random" 
cannot run in my situation, because I have not  cabal  usable in the 
command line (I only have the Cabal library in the place where the   
ghc-7.4.0.20111219 libraries are installed).
My idea is that having installed GHC, I use the GHC packages and, probably, 
do not need to install Cabal (why complicate things?, why force a DoCon 
user to install extra software?). 

> That said, I'm sure AC-random is a fine alternative, and there are
> many other packages on Hackage as well, including cryptographic
> strength ones (crypto-api, intel-aes, etc).

I tried AC-Random, and see that it suggests just different classes, 
with different operations. So that all the Random instances in my 
application must be re-programmed. So is the consequence of being out of 
Standard, and out of GHC !

--
Sergei
mech...@botik.ru


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


RE: Records in Haskell

2012-01-02 Thread Simon Peyton-Jones
It seems to me that there's only one essential missing language feature, which 
is appropriately-kinded type-level strings (and, ideally, the ability to 
reflect these strings back down to the value level). Given that, template 
haskell, and the HList bag of tricks, I'm confident that  a fair number of 
elegant records packages can be crafted. Based on that experience, we can then 
decide what syntactic sugar would be useful to elide the TH layer altogether.

I think we can do this part without much trouble, once the dust has settled on 
-XPolyKinds.  It certainly fits with all the work we've been doing recently on 
the kind system. I agree that it's a fairly basic requirement; for example, 
it's also assumed by 
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields

Specifically

*Allow String as a new kind


*Now you can define classes or types with kinds like

MyCls :: String -> a -> Constraint

T :: String -> *


*Provide type-level string literals, so that "foo" :: String

Open questions:

*Is String (at the kind level) a synonym for [Char]?  I'm inclined 
*not* to do this initially, because it would require us to have promoted 
character literals too -- and the implementation of record labels as strings of 
type-level cons-cells is not going to be efficient.

*If String is not a kind level synonym for [Char], maybe it should have 
a different name.  For example,   "foo" :: Label?  Or Atom?   After all, if it 
doesn't behave like a Haskell string it probably should not have the same name.

*Are there any operations over Labels?

*I don't know exactly what you have in mean by "the ability to reflect 
the type-level string at the value level".

Simon

From: Gershom Bazerman [mailto:gersh...@gmail.com]
Sent: 31 December 2011 19:12
To: Simon Peyton-Jones
Cc: Greg Weber; glasgow-haskell-users@haskell.org
Subject: Re: Records in Haskell

On Dec 31, 2011, at 1:28 PM, Simon Peyton-Jones wrote:
The trouble is that I just don't have the bandwidth (or, if I'm honest, the 
motivation) to drive this through to a conclusion. And if no one else does 
either, perhaps it isn't *that* important to anyone.  That said, it clearly is 
*somewhat* important to a lot of people, so doing nothing isn't very 
satisfactory either.

Usually I feel I know how to move forward, but here I don't.

Simon
It seems to me that there's only one essential missing language feature, which 
is appropriately-kinded type-level strings (and, ideally, the ability to 
reflect these strings back down to the value level). Given that, template 
haskell, and the HList bag of tricks, I'm confident that  a fair number of 
elegant records packages can be crafted. Based on that experience, we can then 
decide what syntactic sugar would be useful to elide the TH layer altogether.

Beyond that, it would really help namespacing in general to appropriately 
extend the module system to allow multiple modules to be declared within a 
single file -- or, better yet, "submodules". I know that this introduces a few 
corner cases that need to be thought through -- what happens with overlapping 
declarations, for example. But I tend to think the path here is relatively 
straightforward and obvious, and the added expressive power should make 
namespacing issues much more tractable. Like the type-level strings proposal, 
this isn't about implementing records as such -- rather, it's about generally 
extending the expressive power of the language so that record systems--among 
other things--are easier to write.

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


Re: ghc-cabal-Random

2012-01-02 Thread Brent Yorgey
On Mon, Jan 02, 2012 at 04:35:25PM +0400, Serge D. Mechveliani wrote:
> On Sun, Jan 01, 2012 at 07:51:39AM -0500, Ryan Newton wrote:
> > I haven't entirely followed this and I see that it's been split over
> > multiple threads.
> > 
> > Did "cabal install random" actually fail for you under
> > ghc-7.4.0.20111219?  If so I'd love to know about it as the maintainer
> > of the "random" package.  (It seems to work for me for
> > random-1.0.1.1.)
> 
> "cabal install random" 
> cannot run in my situation, because I have not  cabal  usable in the 
> command line (I only have the Cabal library in the place where the   
> ghc-7.4.0.20111219 libraries are installed).
> My idea is that having installed GHC, I use the GHC packages and, probably, 
> do not need to install Cabal (why complicate things?, why force a DoCon 
> user to install extra software?). 

It is not really "forcing them to install extra software".  Pretty
much everyone these days will already have the Haskell Platform, which
comes with cabal-install anyway.

-Brent

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


Re: ghc-cabal-Random

2012-01-02 Thread Ryan Newton
Just FYI it is possible to use OLD "cabal" binaries with the new GHC 7.4.
 No need to necessarily rebuild cabal-install with GHC 7.4.

I do this all the time.  Perhaps it's a bad practice ;-).

  -Ryan

On Mon, Jan 2, 2012 at 8:07 AM, Brent Yorgey  wrote:

> On Mon, Jan 02, 2012 at 04:35:25PM +0400, Serge D. Mechveliani wrote:
> > On Sun, Jan 01, 2012 at 07:51:39AM -0500, Ryan Newton wrote:
> > > I haven't entirely followed this and I see that it's been split over
> > > multiple threads.
> > >
> > > Did "cabal install random" actually fail for you under
> > > ghc-7.4.0.20111219?  If so I'd love to know about it as the maintainer
> > > of the "random" package.  (It seems to work for me for
> > > random-1.0.1.1.)
> >
> > "cabal install random"
> > cannot run in my situation, because I have not  cabal  usable in the
> > command line (I only have the Cabal library in the place where the
> > ghc-7.4.0.20111219 libraries are installed).
> > My idea is that having installed GHC, I use the GHC packages and,
> probably,
> > do not need to install Cabal (why complicate things?, why force a DoCon
> > user to install extra software?).
>
> It is not really "forcing them to install extra software".  Pretty
> much everyone these days will already have the Haskell Platform, which
> comes with cabal-install anyway.
>
> -Brent
>
> ___
> 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


testing 7.4.1-candidate

2012-01-02 Thread Serge D. Mechveliani
Dear GHC team,

I have tested  ghc-7.4.0.20111219  on  Debian Linux  by
1) making it from source, 
2) making it by itself,
3) making DoCon-2.12 and running its test.

It looks all right. 

In installing DoCon, there appears a new point of installing the package 
Random,  because  Random  has separated from GHC.
So, I write in the DoCon-2.12 announce: 
 
**
Used extra libraries (beyond Haskell-2010)

Set.Set, Map.Map-- of GHC,
System.Random version 1.0.1.1
   -- a separate from GHC library (written in Haskell) residing on
   http://hackage.haskell.org/package/random
   (first, install GHC, then use ghc to install Random).
**

Thanks to people who helped me with installing Random.
I have downloaded  System.Random-1.0.1.1  from  
http://hackage.haskell.org/package/random,
unzipped it to a separate from ghc place -- call it  $R, 
and installed it to a  $R/inst  by 

  ghc --make Setup
  ./Setup configure --prefix=$R/inst -p
  ./Setup build -v
  ./Setup haddock
  ./Setup install -v

After this,   ghc-pkg list   shows  random-1.0.1.1  in the list, and now
DoCon finds it.

Regards,

--
Sergei
mech...@botik.ru


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


Re: Records in Haskell

2012-01-02 Thread Nicolas Frisby
I'm interested in type-level strings myself. I'm using an
approximation in order to enrich the instant-generics-style reflection
of data type declarations with a sensitivity to constructor names. For
example, this lets me automatically convert between many the
similarly-named constructors of related data types (e.g. pipeline of
ASTs in a compiler).
Is there any existing developments regarding type-level strings? I
have (arbitrarily) taken the approach of promoting the cereal library
to the type-level, encoding strings that way, and working from there
(ultimately inspired by Kiselyov and Chan's implicit configurations
paper). It's certainly not perfect, but it's all I need for the
functionality I've been chasing so far.
In regard to Labels versus Atom, etc., in my use case of converting
between similar datatypes, it would be very reasonable to eventually
add/remove prefixes/suffixes from these type-level reifications of
constructor names. If type-level strings are not implemented as lists
of characters, I would still like access to a comparable API. Perhaps
an isomorphism?
Thanks for your time,Nick
PS — I suspect the "reflect to value-level" idea was something along
the lines of automatically providing a function @stringVal :: forall
(a :: Label). a -> String@.
On Mon, Jan 2, 2012 at 6:38 AM, Simon Peyton-Jones
 wrote:
> It seems to me that there's only one essential missing language feature,
> which is appropriately-kinded type-level strings (and, ideally, the ability
> to reflect these strings back down to the value level). Given that, template
> haskell, and the HList bag of tricks, I'm confident that  a fair number of
> elegant records packages can be crafted. Based on that experience, we can
> then decide what syntactic sugar would be useful to elide the TH layer
> altogether.
>
>
>
> I think we can do this part without much trouble, once the dust has settled
> on -XPolyKinds.  It certainly fits with all the work we’ve been doing
> recently on the kind system. I agree that it’s a fairly basic requirement;
> for example, it’s also assumed by
> http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields
>
>
>
> Specifically
>
> ·    Allow String as a new kind
>
> ·    Now you can define classes or types with kinds like
>
> MyCls :: String -> a -> Constraint
>
> T :: String -> *
>
> ·    Provide type-level string literals, so that “foo” :: String
>
>
>
> Open questions:
>
> ·    Is String (at the kind level) a synonym for [Char]?  I’m inclined
> *not* to do this initially, because it would require us to have promoted
> character literals too -- and the implementation of record labels as strings
> of type-level cons-cells is not going to be efficient.
>
> ·    If String is not a kind level synonym for [Char], maybe it should
> have a different name.  For example,   “foo” :: Label?  Or Atom?   After
> all, if it doesn’t behave like a Haskell string it probably should not have
> the same name.
>
> ·    Are there any operations over Labels?
>
> ·    I don’t know exactly what you have in mean by “the ability to
> reflect the type-level string at the value level”.
>
>
>
> Simon
>
>
>
> From: Gershom Bazerman [mailto:gersh...@gmail.com]
> Sent: 31 December 2011 19:12
> To: Simon Peyton-Jones
> Cc: Greg Weber; glasgow-haskell-users@haskell.org
>
>
> Subject: Re: Records in Haskell
>
>
>
> On Dec 31, 2011, at 1:28 PM, Simon Peyton-Jones wrote:
>
> The trouble is that I just don't have the bandwidth (or, if I'm honest, the
> motivation) to drive this through to a conclusion. And if no one else does
> either, perhaps it isn't *that* important to anyone.  That said, it clearly
> is *somewhat* important to a lot of people, so doing nothing isn't very
> satisfactory either.
>
> Usually I feel I know how to move forward, but here I don't.
>
> Simon
>
> It seems to me that there's only one essential missing language feature,
> which is appropriately-kinded type-level strings (and, ideally, the ability
> to reflect these strings back down to the value level). Given that, template
> haskell, and the HList bag of tricks, I'm confident that  a fair number of
> elegant records packages can be crafted. Based on that experience, we can
> then decide what syntactic sugar would be useful to elide the TH layer
> altogether.
>
>
>
> Beyond that, it would really help namespacing in general to appropriately
> extend the module system to allow multiple modules to be declared within a
> single file -- or, better yet, "submodules". I know that this introduces a
> few corner cases that need to be thought through -- what happens with
> overlapping declarations, for example. But I tend to think the path here is
> relatively straightforward and obvious, and the added expressive power
> should make namespacing issues much more tractable. Like the type-level
> strings proposal, this isn't about implementing records as such -- rather,
> it's about generally extending the expressive power of the language 

Re: Records in Haskell

2012-01-02 Thread Johan Tibell
On Mon, Jan 2, 2012 at 4:38 AM, Simon Peyton-Jones
 wrote:
> Open questions:
>
> ·    Is String (at the kind level) a synonym for [Char]?  I’m inclined 
> *not* to do this initially, because it would require us to have promoted 
> character literals too -- and the implementation of record labels as strings 
> of type-level cons-cells is not going to be efficient.

I'd say no, for the simple reason that we have regretted that the
value level String type wasn't opaque, preventing us from replacing it
with a more efficient implementation. I say make it opaque.

-- Johan

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


Re: Records in Haskell

2012-01-02 Thread Sebastian Fischer
On Mon, Jan 2, 2012 at 1:38 PM, Simon Peyton-Jones wrote:

>  ·**If String is not a kind level synonym for [Char], maybe it
> should have a different name.  For example,   “foo” :: Label?  Or Atom?
>

Or Symbol?

The name is inspired by Ruby's :symbol notation. We could even use the same
notation (seems unambiguous on the type level, no?). Even if we don't use
the notation we could use the name.

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


Re: Records in Haskell

2012-01-02 Thread Iavor Diatchki
Hello,

On Mon, Jan 2, 2012 at 4:38 AM, Simon Peyton-Jones
 wrote:
>
> ·    I don’t know exactly what you have in mean by “the ability to
> reflect the type-level string at the value level”.
>

This can be done using singleton types in exactly the same way that it
is done on the type-nats branch.  It is useful if we want to allow
users to define interesting polymorphic functions for values of types
with type-level string literals (e.g., in the context of records, this
would allow a user to define a custom showing function that can
display the record labels).  Here is what the type-nat singletons
approach might look like for string literals:

newtype StringS (s :: String) = StringS String  -- Abstract type
for singletons (constructor not exported)

fromStringS :: StringS s -> String
fromStringS (StringS s) = s

class StringI s where
  stringS :: StringS s-- "smart" constructor for StringS values.

Users cannot define instances for class "StingI", they are built into
GHC.  When GHC sees a constraint of the from "StringI X", for a
concrete string "X", it discharges it by making  a string evidence
value containing "X".  So, for example, the following would happen on
the GHCi prompt:

> fromStringS (stringS :: StringS "Hello")
"Hello"

The common pattern for using types in this way is something like this:

data CustomType (s :: String) = ...

tyParamString :: StringI s => CustomType s -> StringS s
tyParamString _ = stringS

showCustomType :: StringI s => CustomType s -> String
showCustomType x = "the type param is " ++ fromStringS (tyParamString
x) ++ moreStuff x

I hope this helps,
-Iavor

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


Re: Records in Haskell

2012-01-02 Thread Gershom Bazerman
On Jan 2, 2012, at 8:05 PM, Iavor Diatchki wrote:

> Hello,
> 
> On Mon, Jan 2, 2012 at 4:38 AM, Simon Peyton-Jones
>  wrote:
>> 
>> ·I don’t know exactly what you have in mean by “the ability to
>> reflect the type-level string at the value level”.
> 
> This can be done using singleton types in exactly the same way that it
> is done on the type-nats branch.  It is useful if we want to allow
> users to define interesting polymorphic functions for values of types
> with type-level string literals (e.g., in the context of records, this
> would allow a user to define a custom showing function that can
> display the record labels).  Here is what the type-nat singletons
> approach might look like for string literals:
> 
> newtype StringS (s :: String) = StringS String  -- Abstract type
> for singletons (constructor not exported)
> 
> fromStringS :: StringS s -> String
> fromStringS (StringS s) = s
> 
> class StringI s where
>  stringS :: StringS s-- "smart" constructor for StringS values.

Thanks for the clear exposition! This is nearly exactly what I had in mind, and 
describes precisely one of the use cases I'd imagine.

The other tool I could imagine using, although for less common purposes, would 
be:

newtype StringC a = StringC (forall (s :: String). StringS s -> a)

runStringC :: String -> StringC a -> a
runStringC = compiler magic

With type level nats and the like, it's easy enough to write this by hand, and 
not terribly inefficient. But with type level strings, I'd imagine that it 
would be nicer to push the work to the compiler.

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


Re: Records in Haskell

2012-01-02 Thread Matthew Farkas-Dyck
On 02/01/2012, Simon Peyton-Jones  wrote:
> It seems to me that there's only one essential missing language feature,
> which is appropriately-kinded type-level strings (and, ideally, the ability
> to reflect these strings back down to the value level). Given that, template
> haskell, and the HList bag of tricks, I'm confident that  a fair number of
> elegant records packages can be crafted. Based on that experience, we can
> then decide what syntactic sugar would be useful to elide the TH layer
> altogether.
>
> I think we can do this part without much trouble, once the dust has settled
> on -XPolyKinds.  It certainly fits with all the work we've been doing
> recently on the kind system. I agree that it's a fairly basic requirement;
> for example, it's also assumed by
> http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields
>
> Specifically
>
> *Allow String as a new kind
>
>
> *Now you can define classes or types with kinds like
>
> MyCls :: String -> a -> Constraint
>
> T :: String -> *
>
>
> *Provide type-level string literals, so that "foo" :: String
>
> Open questions:
>
> *Is String (at the kind level) a synonym for [Char]?  I'm inclined
> *not* to do this initially, because it would require us to have promoted
> character literals too -- and the implementation of record labels as strings
> of type-level cons-cells is not going to be efficient.
>
> *If String is not a kind level synonym for [Char], maybe it should
> have a different name.  For example,   "foo" :: Label?  Or Atom?   After
> all, if it doesn't behave like a Haskell string it probably should not have
> the same name.

I agree. In this case, though, I think we ought to allow
kind-polymorphic quoted type-level literals, thus:
"foobar" :: Label
or
"foobar" :: String
at least.

> *Are there any operations over Labels?
>
> *I don't know exactly what you have in mean by "the ability to
> reflect the type-level string at the value level".
>
> Simon
>
> From: Gershom Bazerman [mailto:gersh...@gmail.com]
> Sent: 31 December 2011 19:12
> To: Simon Peyton-Jones
> Cc: Greg Weber; glasgow-haskell-users@haskell.org
> Subject: Re: Records in Haskell
>
> On Dec 31, 2011, at 1:28 PM, Simon Peyton-Jones wrote:
> The trouble is that I just don't have the bandwidth (or, if I'm honest, the
> motivation) to drive this through to a conclusion. And if no one else does
> either, perhaps it isn't *that* important to anyone.  That said, it clearly
> is *somewhat* important to a lot of people, so doing nothing isn't very
> satisfactory either.
>
> Usually I feel I know how to move forward, but here I don't.
>
> Simon
> It seems to me that there's only one essential missing language feature,
> which is appropriately-kinded type-level strings (and, ideally, the ability
> to reflect these strings back down to the value level). Given that, template
> haskell, and the HList bag of tricks, I'm confident that  a fair number of
> elegant records packages can be crafted. Based on that experience, we can
> then decide what syntactic sugar would be useful to elide the TH layer
> altogether.
>
> Beyond that, it would really help namespacing in general to appropriately
> extend the module system to allow multiple modules to be declared within a
> single file -- or, better yet, "submodules". I know that this introduces a
> few corner cases that need to be thought through -- what happens with
> overlapping declarations, for example. But I tend to think the path here is
> relatively straightforward and obvious, and the added expressive power
> should make namespacing issues much more tractable. Like the type-level
> strings proposal, this isn't about implementing records as such -- rather,
> it's about generally extending the expressive power of the language so that
> record systems--among other things--are easier to write.
>
> Cheers,
> Gershom
>

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


Re: Records in Haskell

2012-01-02 Thread Ryan Newton
On Thu, Dec 29, 2011 at 12:00 PM, Simon Peyton-Jones
wrote:

> | The lack of response, I believe, is just a lack of anyone who
> | can cut through all the noise and come up with some
> | practical way to move forward in one of the many possible
> | directions.
>
> You're right.


There are a few tens of thousands of Haskell programmers now, right?

I think a significant fraction of them would in fact appreciate the basic
dot syntax and namespace-fixes that TDNR proposed.

I fear that record-packages-as-libraries are unlikely to be used by a large
number of people.  Are they now?  I love do-it-in-the-language as a
principle, but I've watched it really impair the Scheme community with
respect to many language features.  (Recall your experiences, if you've had
them, with homebrew Scheme OOP systems.)  It seems hard for non-standard
language extensions to gain wide use.  Though, to be fair, Haskell's basic
types have a history of being replaced by widely accepted alternatives
(Vector, ByteString).

In spite of its limitations, was there that much of a negative response to
Simon's more recent proposal?
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields

"+1"!

This is a great bang-for-the-buck proposal; it leverages the existing
multiparameter type classes in a sensible way.

I admit I'm a big fan of polymorphic extension.  But I don't love it enough
for it to impede progress!

Regarding extension:  In trying to read through all this material I don't
see a lot of love for "lacks" constraints a la TRex.  As one anecdote, I've
been very pleased using Daan Leijen's scoped labels approach.  I
implemented it for my embedded stream processing DSL (WaveScript) and wrote
>10K lines of application code with it.  I never once ran into a bug
resulting from shadowed/duplicate fields!

Cheers,
  -Ryan





> But it is very telling that the vast majority of responses on
>
> http://www.reddit.com/r/haskell/comments/nph9l/records_stalled_again_leadership_needed/
> were not about the subject (leadership) but rather on suggesting yet more,
> incompletely-specified solutions to the original problem.  My modest
> attempt to build a consensus by articulating the simplest solution I could
> think of, manifestly failed.
>
> The trouble is that I just don't have the bandwidth (or, if I'm honest,
> the motivation) to drive this through to a conclusion. And if no one else
> does either, perhaps it isn't *that* important to anyone.  That said, it
> clearly is *somewhat* important to a lot of people, so doing nothing isn't
> very satisfactory either.
>
> Usually I feel I know how to move forward, but here I don't.
>
> Simon
>
>
>
> ___
> 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