Unwanted eta-expansion

2011-10-04 Thread Roman Cheplyaka
Suppose I want a foldl which is evaluated many times on the same
list but with different folding functions.

I would write something like this, to perform pattern-matching on the
list only once:

module F where
myFoldl :: [a] - (b - a - b) - b - b
myFoldl [] = \f a - a
myFoldl (x:xs) = let y = myFoldl xs in \f a - y f (f a x)

However, for some reason GHC eta-expands it back. Here's what I see in
the core:

  % ghc -O2 -ddump-simpl -fforce-recomp -dsuppress-module-prefixes \
-dsuppress-uniques -dsuppress-coercions F.hs

 Tidy Core 
Rec {
myFoldl [Occ=LoopBreaker]
  :: forall a b. [a] - (b - a - b) - b - b
[GblId, Arity=3, Caf=NoCafRefs, Str=DmdType SLL]
myFoldl =
  \ (@ a) (@ b) (ds :: [a]) (eta :: b - a - b) (eta1 :: b) -
case ds of _ {
  [] - eta1; : x xs - myFoldl @ a @ b xs eta (eta eta1 x)
}
end Rec }

Why does it happen and can it be suppressed?

This is GHC 7.0.4.


-- 
Roman I. Cheplyaka :: http://ro-che.info/

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


RE: Unwanted eta-expansion

2011-10-04 Thread Simon Peyton-Jones
Combining lambdas makes a big difference in GHC. For example
f = \x. let y = E in \z. BODY
The function f takes one argument, and returns a heap-allocated lambda.  If E 
is cheap (say just a constructor) it might well be more efficient to transform 
to
f = \xz. let y = E in BODY

Pattern matching is another example, and GHC indeed eta expands through that by 
default, if it makes two lambdas into one.

To switch it off try -fno-do-lambda-eta-expansion.

Simon


| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Roman Cheplyaka
| Sent: 04 October 2011 07:40
| To: glasgow-haskell-users@haskell.org
| Subject: Unwanted eta-expansion
| 
| Suppose I want a foldl which is evaluated many times on the same
| list but with different folding functions.
| 
| I would write something like this, to perform pattern-matching on the
| list only once:
| 
| module F where
| myFoldl :: [a] - (b - a - b) - b - b
| myFoldl [] = \f a - a
| myFoldl (x:xs) = let y = myFoldl xs in \f a - y f (f a x)
| 
| However, for some reason GHC eta-expands it back. Here's what I see in
| the core:
| 
|   % ghc -O2 -ddump-simpl -fforce-recomp -dsuppress-module-prefixes \
| -dsuppress-uniques -dsuppress-coercions F.hs
| 
|  Tidy Core 
| Rec {
| myFoldl [Occ=LoopBreaker]
|   :: forall a b. [a] - (b - a - b) - b - b
| [GblId, Arity=3, Caf=NoCafRefs, Str=DmdType SLL]
| myFoldl =
|   \ (@ a) (@ b) (ds :: [a]) (eta :: b - a - b) (eta1 :: b) -
| case ds of _ {
|   [] - eta1; : x xs - myFoldl @ a @ b xs eta (eta eta1 x)
| }
| end Rec }
| 
| Why does it happen and can it be suppressed?
| 
| This is GHC 7.0.4.
| 
| 
| --
| Roman I. Cheplyaka :: http://ro-che.info/
| 
| ___
| 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: mkTopLevEnv: not interpreted main:Main

2011-10-04 Thread Simon Peyton-Jones
| I will work on building a smaller complete test case that reproduces the
| issue, and I could have done a better job of at least pointing out the
| relevant code for you.  Sorry about that.

I'm afraid I still can't guess what's happening. It'd be really helpful if you 
could build a smaller test case.  

Are you using GHC HEAD (or at least 7.2?). There have been changes in this 
area, and I'm looking at the HEAD code.  So it's worth trying the latest 
version, lest we end up debugging something that is already fixed.

If you build the HEAD from source you can also look at the call to mkTopLevEnv 
and print out a bit more trace info to help narrow things down.

Sorry not to be more helpful.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Chris Smith
| Sent: 03 October 2011 14:43
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users@haskell.org
| Subject: RE: mkTopLevEnv: not interpreted main:Main
| 
| Thanks, Simon.
| 
| I will work on building a smaller complete test case that reproduces the
| issue, and I could have done a better job of at least pointing out the
| relevant code for you.  Sorry about that.
| 
| I'm definitely not building my own IIModule.  The use of the GHC API is
| as follows.  (I'm fairly sure you can ignore doWithErrors, so I haven't
| included it; it just sets up some log actions and exception and signal
| handlers, runs its argument in the Ghc monad, and converts the result
| from a Maybe to an Either that reports errors).
| 
| doWithErrors :: GHC.Ghc (Maybe a) - IO (Either [String] a)
| 
| compile :: String - String - FilePath - IO (Either [String] t)
| compile vname tname fn = doWithErrors $ do
| dflags - GHC.getSessionDynFlags
| let dflags' = dflags {
| GHC.ghcMode = GHC.CompManager,
| GHC.ghcLink = GHC.LinkInMemory,
| GHC.hscTarget = GHC.HscAsm,
| GHC.optLevel = 2,
| GHC.safeHaskell = GHC.Sf_Safe,
| GHC.packageFlags = [GHC.TrustPackage gloss,
| GHC.ExposePackage gloss-web-adapters ]
| }
| GHC.setSessionDynFlags dflags'
| target - GHC.guessTarget fn Nothing
| GHC.setTargets [target]
| r - fmap GHC.succeeded (GHC.load GHC.LoadAllTargets)
| case r of
| True - do
| mods - GHC.getModuleGraph
| let mainMod = GHC.ms_mod (head mods)
| GHC.setContext [ mainMod ]
|[ GHC.simpleImportDecl
|(GHC.mkModuleName Graphics.Gloss),
|  GHC.simpleImportDecl
|(GHC.mkModuleName GlossAdapters) ]
| v - GHC.compileExpr $ vname ++  ::  ++ tname
| return (Just (unsafeCoerce# v))
| False - return Nothing
| 
| --
| Chris
| 
| 
| ___
| 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: Two Proposals

2011-10-04 Thread Simon Peyton-Jones
I like both George's proposals.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of George Giorgidze
| Sent: 30 September 2011 18:28
| To: glasgow-haskell-users@haskell.org
| Subject: Two Proposals
| 
| GHC Users,
| 
| I would like to make to the following two proposals:
|   * Eliminate the default grouping close from SQL-like comprehensions
|   * Introduce a GHC extension for list literal overloading
| 
| OK, let me start with the first proposal.
| 
| Currently, the SQL-like comprehension notation (both in its list 
comprehension and
| monad comprehension variants) features the following five clauses:
| 
| then f
| then f by e
| then group by e
| then group using f
| then group by e using f
| 
| The first two clauses are used for specifying transformations of type [a] - 
[a] (or
| Monad m = m a- m a for monad comprehensions). The following three clauses 
are used
| for specifying transformations of type [a] - [[a]] (or Monad m, Functor f = 
m a -
| m (f a) for monad comprehensions). See [1] for further details.
| 
| Note that the third clause does not mention which function is used for 
grouping. In
| this case GHC.Exts.groupWith function is used as a default for list 
comprehensions
| and the mgroupWith function from the MonadGroup class is used as a default 
for monad
| comprehensions.
| 
| I would like to suggest to remove the third clause for the following reasons:
| * Currently the syntax is asymmetrical. Note that there is the default case 
for the
| 'then group' clause and not for the 'then' clause.
| * In the current notation it is not clear which grouping function is used in 
the
| default case
| * For many monads including lists it is not clear which function should be 
selected
| as a default (e.g., the groupWith function also does sorting and it is not 
clear to
| me why this should be the default)
| * Gets rid of the MonadGroup class. Currently the sole purpose of this class 
is to
| introduce a default grouping function for monad comprehensions.
| * Explicit mention of the grouping function would make  monad/list 
comprehensions
| much easier to read by making it immediately apparent which function is used 
for
| grouping.
| 
| My second proposal is to introduce the OverloadedLists extension that 
overloads list
| literals. See Section 5.2 in [1] for details.
| 
| Basically the idea is to treat list literals like:
| 
| [1,2,3]
| 
| as
| 
| fromList [1,2,3]
| 
| where
| 
| class IsList l where
|   type Item l
|   fromList :: [Item l] - l
| 
| In the following I give useful instances of the IsList class.
| 
| instance IsList [a] where
|   type Item [a] = a
|   fromList = id
| 
| instance (Ord a) = IsList (Set a) where
|   type Item (Set a) = a
|   fromList = Set.fromList
| 
| instance (Ord k) = IsList (Map k v) where
|   type Item (Map k v) = (k,v)
|   fromList = Map.fromList
| 
| instance IsList (IntMap v) where
|   type Item (IntMap v) = (Int,v)
|   fromList = IntMap.fromList
| 
| instance IsList Text where
|   type Item Text = Char
|   fromList = Text.pack
| 
| As you can see the extension would allow list literals to be used for sets, 
maps and
| integer maps. In addition the suggested OverloadedLists extension would 
subsume
| OverloadedStrings extension (see the instance for Text, for example). Having 
said
| that, for now, I am not suggesting to remove the OverloadedStrings extension 
as it
| appears to be widely used.
| 
| This extension could also be used for giving data-parallel array literals 
instead of
| the special syntax used currently.
| 
| Unless there is a vocal opposition to the aforementioned two proposals, I 
would like
| to implement them in GHC. Both changes appear to be straightforward to 
implement.
| 
| Thanks in advance for your feedback.
| 
| Cheers, George
| 
| [1] http://www-db.informatik.uni-tuebingen.de/files/giorgidze/haskell2011.pdf
| ___
| 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: Two Proposals

2011-10-04 Thread Yitzchak Gale
George Giorgidze wrote:
 My second proposal is to introduce the
 OverloadedLists extension that overloads
 list literals...

I am opposed to this proposal as stated.

But I think that with a modification,
it can not only be improved, but also solve
the problems with the current OverloadedStrings
extension.

OverloadedStrings - and George's unmodified
proposal - change compile time errors into run
time errors. Literals with hard-to-find problems
are accepted by the compiler and become
_|_ at run time.

An example of the problem: the xml-types
package has an IsString instance for
Name. The fromString method parses
XML namespaces from XML names and
calls error if the parse fails. Without the
extension, one would specify the parts using
constructors; that is wordy and awkward but
checked at compile time. A quasi-quoter
could be defined, but that syntax would still
be far less convenient in practice than
string literals.

I agree that we need a way of allowing literals
to have some flexibility in their types. But there
should be a way for overloading to work
at compile time, i.e. more like a quasi-quoter,
when needed.

Of course, quasi-quoter overloading can also
just create an expression that applies a coercion function
at run time. So in that sense, quasi-quoter overloading
is more general than ad-hoc-polymorphism overloading.

In all of George's examples fromList happens to be total,
so there isn't an issue having it happen at run time. But if we
make this generally available, you can be certain that
it will cause problems later on. Just as with IsString,
people will not be able to resist the nice syntax, and
they will define fromList implementations that are partial.

Here is a tentative modification of George's proposal:

class IsList l where
  type Item l
  fromList :: [Item l] - l
  listExpQ :: [ExpQ] - ExpQ

  -- Minimal complete definition: fromList
  listExpQ = appE (varE (mkName fromList)) . listE

If the type of a list literal determines a specific instance
of IsList at compile time, use the listExpQ from that
instance to interpret the list literal. Otherwise, use the
default listExpQ, which is just George's original proposal.

An alternative would be to put listExpQ in a separate type
class with an IsList constraint.

IsString can similarly be extended in a backward compatible
way to allow syntax checking at compile time. Here the
type could be stringExpQ :: String - ExpQ

Numeric literals with Num and Integral can also be extended,
though I think the problem is less common for those.

Thanks,
Yitz

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


Re: Bug#639015: libffi soname change upcoming

2011-10-04 Thread Joachim Breitner
Hi,

Am Donnerstag, den 29.09.2011, 11:39 +0100 schrieb Simon Marlow:
  I’m not sure if I got your conclusion: Do you expect problems if the RTS
  and libraries were built against different versions of libffi, or not?

 To answer your question: yes I would expect problems. 

Thanks for your assessment.

Matthias, I hope you understand why I would not drop the libffi
dependencies from the Haskell packages; better safe than sorry. I can
supervise the resulting binNMU-orgy, if you prefer.

  My question was: 
 how do other (non-Haskell) packages on Debian that contain static 
 libraries deal with this problem?  We should follow whatever approach is 
 used by others.

I’m actually not sure if we have this situation (various interdepending
static libraries dynamically linking libffi).

OCAML might be in a similar situation, but it seems that they don’t use
libffi. Their packages do, however, all seem to have a dependency on
libc6 which corresponds to our situation. Only that a so-name bump of
libc is probably less frequent than one in libffi...

Greetings,
Joachim

-- 
Joachim nomeata Breitner
Debian Developer
  nome...@debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C
  JID: nome...@joachim-breitner.de | http://people.debian.org/~nomeata


signature.asc
Description: This is a digitally signed message part
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Two Proposals

2011-10-04 Thread Roman Leshchinskiy
George Giorgidze wrote:

 This extension could also be used for giving data-parallel array literals
 instead of the special syntax used currently.

Unfortunately, it couldn't. DPH array literals don't (and can't really) go
through lists.

In general, if we are going to overload list literals then forcing the
desugaring to always go through lists seems wrong to me. There are plenty
of data structures where that might result in a significant performance
hit.

Roman




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


Re: Two Proposals

2011-10-04 Thread Yitzchak Gale
Roman Leshchinskiy wrote:
 In general, if we are going to overload list literals then forcing the
 desugaring to always go through lists seems wrong to me. There are plenty
 of data structures where that might result in a significant performance
 hit.

These are literals. So the lists will almost always be quite short,
and they will be evaluated only once. So I don't think there will
be that much of a performance hit normally.

That said, my extension that allows them to be desugared
at compile time would solve that issue if it arises.

Regards,
Yitz

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


Re: Two Proposals

2011-10-04 Thread Ryan Newton
Just anecdotally I remember we had this problem with Accelerate.

Back when we were using it last Spring for some reason we were forced by the
API to at least nominally go through lists on our way to the GPU -- which we
sorely hoped were deforested!  At times (and somewhat unpredictably), we'd
be faced enormous execution times and memory footprints as the runtime tried
to create gigantic lists for feeding to Accelerate.

Other than that -- I like having a nice literal syntax for other types.  But
I'm not sure that I construct literals for Sets and IntMaps often enough to
profit much...

  -Ryan


On Tue, Oct 4, 2011 at 9:38 AM, Roman Leshchinskiy r...@cse.unsw.edu.auwrote:

 George Giorgidze wrote:
 
  This extension could also be used for giving data-parallel array literals
  instead of the special syntax used currently.

 Unfortunately, it couldn't. DPH array literals don't (and can't really) go
 through lists.

 In general, if we are going to overload list literals then forcing the
 desugaring to always go through lists seems wrong to me. There are plenty
 of data structures where that might result in a significant performance
 hit.

 Roman




 ___
 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: Two Proposals

2011-10-04 Thread Gábor Lehel
On Tue, Oct 4, 2011 at 3:25 PM, Yitzchak Gale g...@sefer.org wrote:
 George Giorgidze wrote:
 My second proposal is to introduce the
 OverloadedLists extension that overloads
 list literals...

 I am opposed to this proposal as stated.

 But I think that with a modification,
 it can not only be improved, but also solve
 the problems with the current OverloadedStrings
 extension.

 OverloadedStrings - and George's unmodified
 proposal - change compile time errors into run
 time errors. Literals with hard-to-find problems
 are accepted by the compiler and become
 _|_ at run time.

 An example of the problem: the xml-types
 package has an IsString instance for
 Name. The fromString method parses
 XML namespaces from XML names and
 calls error if the parse fails. Without the
 extension, one would specify the parts using
 constructors; that is wordy and awkward but
 checked at compile time. A quasi-quoter
 could be defined, but that syntax would still
 be far less convenient in practice than
 string literals.

 I agree that we need a way of allowing literals
 to have some flexibility in their types. But there
 should be a way for overloading to work
 at compile time, i.e. more like a quasi-quoter,
 when needed.

 Of course, quasi-quoter overloading can also
 just create an expression that applies a coercion function
 at run time. So in that sense, quasi-quoter overloading
 is more general than ad-hoc-polymorphism overloading.

 In all of George's examples fromList happens to be total,
 so there isn't an issue having it happen at run time. But if we
 make this generally available, you can be certain that
 it will cause problems later on. Just as with IsString,
 people will not be able to resist the nice syntax, and
 they will define fromList implementations that are partial.

 Here is a tentative modification of George's proposal:

 class IsList l where
  type Item l
  fromList :: [Item l] - l
  listExpQ :: [ExpQ] - ExpQ

  -- Minimal complete definition: fromList
  listExpQ = appE (varE (mkName fromList)) . listE

listExpQ doesn't actually use the class's type variable here. You'd
have to add a dummy parameter ('l' or preferably 'Proxy l').

That said, this seems like what the Lift class[1] was made for. Maybe:

class Lift l = IsList l where
fromList :: [Item l] - l

and then have GHC apply the function at compile time, during the
Template Haskell phase, and then lift and splice the result. That
would resolve both your complaint about partial instances (an
exception at compile time is a compile error) and Roman's about
performance (if it results in a performance hit with some data
structures, it'll only be at compile time). I don't know if it would
work out mechanically (i.e. whether GHC's internals allow this kind of
thing).

In the spirit of don't let the perfect be the enemy of the good
though, I'm solidly in favor of the original proposal as it is. My
only quibble is whether it might not be better called FromList (or
FromListLiteral or ...), given that a Map Is not really a List. Since
IsString is named the same way, the question is whether consistency or
accuracy is more important.

[1] 
http://hackage.haskell.org/packages/archive/template-haskell/2.4.0.0/doc/html/Language-Haskell-TH-Syntax.html


 If the type of a list literal determines a specific instance
 of IsList at compile time, use the listExpQ from that
 instance to interpret the list literal. Otherwise, use the
 default listExpQ, which is just George's original proposal.

 An alternative would be to put listExpQ in a separate type
 class with an IsList constraint.

 IsString can similarly be extended in a backward compatible
 way to allow syntax checking at compile time. Here the
 type could be stringExpQ :: String - ExpQ

 Numeric literals with Num and Integral can also be extended,
 though I think the problem is less common for those.

 Thanks,
 Yitz

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




-- 
Work is punishment for failing to procrastinate effectively.

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


Re: Two Proposals

2011-10-04 Thread Gábor Lehel
2011/10/4 Gábor Lehel illiss...@gmail.com:
 On Tue, Oct 4, 2011 at 3:25 PM, Yitzchak Gale g...@sefer.org wrote:
 George Giorgidze wrote:
 My second proposal is to introduce the
 OverloadedLists extension that overloads
 list literals...

 I am opposed to this proposal as stated.

 But I think that with a modification,
 it can not only be improved, but also solve
 the problems with the current OverloadedStrings
 extension.

 OverloadedStrings - and George's unmodified
 proposal - change compile time errors into run
 time errors. Literals with hard-to-find problems
 are accepted by the compiler and become
 _|_ at run time.

 An example of the problem: the xml-types
 package has an IsString instance for
 Name. The fromString method parses
 XML namespaces from XML names and
 calls error if the parse fails. Without the
 extension, one would specify the parts using
 constructors; that is wordy and awkward but
 checked at compile time. A quasi-quoter
 could be defined, but that syntax would still
 be far less convenient in practice than
 string literals.

 I agree that we need a way of allowing literals
 to have some flexibility in their types. But there
 should be a way for overloading to work
 at compile time, i.e. more like a quasi-quoter,
 when needed.

 Of course, quasi-quoter overloading can also
 just create an expression that applies a coercion function
 at run time. So in that sense, quasi-quoter overloading
 is more general than ad-hoc-polymorphism overloading.

 In all of George's examples fromList happens to be total,
 so there isn't an issue having it happen at run time. But if we
 make this generally available, you can be certain that
 it will cause problems later on. Just as with IsString,
 people will not be able to resist the nice syntax, and
 they will define fromList implementations that are partial.

 Here is a tentative modification of George's proposal:

 class IsList l where
  type Item l
  fromList :: [Item l] - l
  listExpQ :: [ExpQ] - ExpQ

  -- Minimal complete definition: fromList
  listExpQ = appE (varE (mkName fromList)) . listE

 listExpQ doesn't actually use the class's type variable here. You'd
 have to add a dummy parameter ('l' or preferably 'Proxy l').

 That said, this seems like what the Lift class[1] was made for. Maybe:

 class Lift l = IsList l where
    fromList :: [Item l] - l

 and then have GHC apply the function at compile time, during the
 Template Haskell phase, and then lift and splice the result. That
 would resolve both your complaint about partial instances (an
 exception at compile time is a compile error) and Roman's about
 performance (if it results in a performance hit with some data
 structures, it'll only be at compile time). I don't know if it would
 work out mechanically (i.e. whether GHC's internals allow this kind of
 thing).

 In the spirit of don't let the perfect be the enemy of the good
 though, I'm solidly in favor of the original proposal as it is. My
 only quibble is whether it might not be better called FromList (or
 FromListLiteral or ...), given that a Map Is not really a List. Since
 IsString is named the same way, the question is whether consistency or
 accuracy is more important.

(Of course I mean that if we can get something better, great, but the
original proposal is a lot better than nothing - not that I would
actually prefer the original to something better than it.)


 [1] 
 http://hackage.haskell.org/packages/archive/template-haskell/2.4.0.0/doc/html/Language-Haskell-TH-Syntax.html


 If the type of a list literal determines a specific instance
 of IsList at compile time, use the listExpQ from that
 instance to interpret the list literal. Otherwise, use the
 default listExpQ, which is just George's original proposal.

 An alternative would be to put listExpQ in a separate type
 class with an IsList constraint.

 IsString can similarly be extended in a backward compatible
 way to allow syntax checking at compile time. Here the
 type could be stringExpQ :: String - ExpQ

 Numeric literals with Num and Integral can also be extended,
 though I think the problem is less common for those.

 Thanks,
 Yitz

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




 --
 Work is punishment for failing to procrastinate effectively.




-- 
Work is punishment for failing to procrastinate effectively.

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


Re: Two Proposals

2011-10-04 Thread Gábor Lehel
On Fri, Sep 30, 2011 at 7:28 PM, George Giorgidze giorgi...@gmail.com wrote:
 GHC Users,

 I would like to make to the following two proposals:
  * Eliminate the default grouping close from SQL-like comprehensions
  * Introduce a GHC extension for list literal overloading

 OK, let me start with the first proposal.

 Currently, the SQL-like comprehension notation (both in its list 
 comprehension and monad comprehension variants) features the following five 
 clauses:

 then f
 then f by e
 then group by e
 then group using f
 then group by e using f

 The first two clauses are used for specifying transformations of type [a] - 
 [a] (or Monad m = m a- m a for monad comprehensions). The following three 
 clauses are used for specifying transformations of type [a] - [[a]] (or 
 Monad m, Functor f = m a - m (f a) for monad comprehensions). See [1] for 
 further details.

 Note that the third clause does not mention which function is used for 
 grouping. In this case GHC.Exts.groupWith function is used as a default for 
 list comprehensions and the mgroupWith function from the MonadGroup class is 
 used as a default for monad comprehensions.

 I would like to suggest to remove the third clause for the following reasons:
 * Currently the syntax is asymmetrical. Note that there is the default case 
 for the 'then group' clause and not for the 'then' clause.
 * In the current notation it is not clear which grouping function is used in 
 the default case
 * For many monads including lists it is not clear which function should be 
 selected as a default (e.g., the groupWith function also does sorting and it 
 is not clear to me why this should be the default)
 * Gets rid of the MonadGroup class. Currently the sole purpose of this class 
 is to introduce a default grouping function for monad comprehensions.
 * Explicit mention of the grouping function would make  monad/list 
 comprehensions much easier to read by making it immediately apparent which 
 function is used for grouping.

 My second proposal is to introduce the OverloadedLists extension that 
 overloads list literals. See Section 5.2 in [1] for details.

 Basically the idea is to treat list literals like:

 [1,2,3]

 as

 fromList [1,2,3]

 where

 class IsList l where
  type Item l
  fromList :: [Item l] - l

 In the following I give useful instances of the IsList class.

 instance IsList [a] where
  type Item [a] = a
  fromList = id

 instance (Ord a) = IsList (Set a) where
  type Item (Set a) = a
  fromList = Set.fromList

 instance (Ord k) = IsList (Map k v) where
  type Item (Map k v) = (k,v)
  fromList = Map.fromList

 instance IsList (IntMap v) where
  type Item (IntMap v) = (Int,v)
  fromList = IntMap.fromList

 instance IsList Text where
  type Item Text = Char
  fromList = Text.pack

...one more thought: would this work together with instances of Enum?

Could you write:

letters :: Text
letters = ['a'..'z']


 As you can see the extension would allow list literals to be used for sets, 
 maps and integer maps. In addition the suggested OverloadedLists extension 
 would subsume OverloadedStrings extension (see the instance for Text, for 
 example). Having said that, for now, I am not suggesting to remove the 
 OverloadedStrings extension as it appears to be widely used.

 This extension could also be used for giving data-parallel array literals 
 instead of the special syntax used currently.

 Unless there is a vocal opposition to the aforementioned two proposals, I 
 would like to implement them in GHC. Both changes appear to be 
 straightforward to implement.

 Thanks in advance for your feedback.

 Cheers, George

 [1] http://www-db.informatik.uni-tuebingen.de/files/giorgidze/haskell2011.pdf
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




-- 
Work is punishment for failing to procrastinate effectively.

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


Re: Two Proposals

2011-10-04 Thread Roman Leshchinskiy
Yitzchak Gale wrote:
 Roman Leshchinskiy wrote:
 In general, if we are going to overload list literals then forcing the
 desugaring to always go through lists seems wrong to me. There are
 plenty
 of data structures where that might result in a significant performance
 hit.

 These are literals. So the lists will almost always be quite short,
 and they will be evaluated only once. So I don't think there will
 be that much of a performance hit normally.

Calling them literals is misleading, IMO. They won't necessarily be only
evaluated once:

f x = [x]

In DPH, it wasn't uncommon for certain benchmarks to spend 90% of the time
constructing arrays from [:x,y,z:] terms until we made a significant
effort to ensure that this doesn't happen. This is the only real data
point related to this that I have but it does indicate that making the
desugaring efficient is quite important.

 That said, my extension that allows them to be desugared
 at compile time would solve that issue if it arises.

Personally, I don't like having desugaring depend on TH at all. I'm not
sure think there is a real need for it. This would, IMO, already be better
than fromList wrt efficiency:

class Cons a where
  type Elem a
  empty :: a
  cons  :: Elem a - a - a

Roman




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


RE: mkTopLevEnv: not interpreted main:Main

2011-10-04 Thread Chris Smith
Here's a test case: the complete source code is in the following.  I
compile it with:

ghc -package ghc --make Test.hs

The GHC version is

cdsmith@godel:~$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.2.1

Then run the application several times in a row.  If you count to 3
between runs, it's fine.  If you run it multiple times in a row rapidly,
you get intermittent errors, as so:

cdsmith@godel:~$ ./Test
Just 42
cdsmith@godel:~$ ./Test
Just 42
cdsmith@godel:~$ ./Test
Test: mkTopLevEnv: not interpreted main:Main
cdsmith@godel:~$ ./Test
Just 42
cdsmith@godel:~$ ./Test
Test: mkTopLevEnv: not interpreted main:Main
cdsmith@godel:~$ ./Test
Just 42
cdsmith@godel:~$ ./Test
Test: mkTopLevEnv: not interpreted main:Main

Note this isn't even in the same process!  But it's definitely caused by
running the test multiple times in a quick sequence.

Here's the complete source code for Test.hs

{-# LANGUAGE MagicHash #-}

import System.IO.Unsafe
import GHC.Exts  (unsafeCoerce#)
import GHC.Paths (libdir)

import qualified GHC  as GHC
import qualified DynFlags as GHC

compile :: IO (Maybe Int)
compile = GHC.runGhc (Just libdir) $ do
dflags - GHC.getSessionDynFlags
let dflags' = dflags {
GHC.ghcMode = GHC.CompManager,
GHC.ghcLink = GHC.LinkInMemory,
GHC.hscTarget = GHC.HscAsm,
GHC.optLevel = 2,
GHC.safeHaskell = GHC.Sf_Safe
}
GHC.setSessionDynFlags dflags'
target - GHC.guessTarget A.hs Nothing
GHC.setTargets [target]
r - fmap GHC.succeeded (GHC.load GHC.LoadAllTargets)
case r of
True - do
mods - GHC.getModuleGraph
let mainMod = GHC.ms_mod (head mods)
GHC.setContext [ mainMod ] [ ]
v - GHC.compileExpr a :: Integer
return (Just (unsafeCoerce# v))
False - return Nothing

main = do
writeFile A.hs a = 42
print = compile



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


Re: mkTopLevEnv: not interpreted main:Main

2011-10-04 Thread Felipe Almeida Lessa
This may have something to do with timestamps on the files.  I cannot
reproduce the error with

  $ while ./T; do sleep 1; done
  ...

However, I *am* able to reproduce the error with

  $ while ./T ; do sleep 0.9; done
  Just 42
  Just 42
  Just 42
  Just 42
  Just 42
  T: mkTopLevEnv: not interpreted main:Main

Note that this is on GHC 7.0.4 after removing the Safe Haskell line.

Cheers,

-- 
Felipe.

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


RE: mkTopLevEnv: not interpreted main:Main

2011-10-04 Thread Chris Smith
Here's a version with fewer flags/features, that acts the same.

I tried removing the loading of an external module, and that did *not*
exhibit the problem.  It also does *not* fail when the file name is
different each time, so the fact that it's the same file, A.hs, each
time is somehow part of the issue.

I'm getting to the point where I can't imagine what this could possibly
be about.


{-# LANGUAGE MagicHash #-}

import System.IO.Unsafe
import GHC.Exts  (unsafeCoerce#)
import GHC.Paths (libdir)

import qualified GHC  as GHC
import qualified DynFlags as GHC

compile :: IO (Maybe Int)
compile = GHC.runGhc (Just libdir) $ do
dflags - GHC.getSessionDynFlags
let dflags' = dflags { GHC.ghcLink = GHC.LinkInMemory }
GHC.setSessionDynFlags dflags'
target - GHC.guessTarget A.hs Nothing
GHC.setTargets [target]
r - fmap GHC.succeeded (GHC.load GHC.LoadAllTargets)
case r of
True - do
mods - GHC.getModuleGraph
let mainMod = GHC.ms_mod (head mods)
GHC.setContext [ mainMod ] [ ]
v - GHC.compileExpr a :: Integer
return (Just (unsafeCoerce# v))
False - return Nothing

main = do
writeFile A.hs a = 42
print = compile



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


Re: mkTopLevEnv: not interpreted main:Main

2011-10-04 Thread Chris Smith
Thanks everyone for the help!

I'm working now on reproducing this with HEAD, and if I do, I'll write a
ticket.  On the other hand, it only seems to be an issue when one is
recompiling a file within one second of the first attempt, and Felipe's
workaround of deleting the .hi and .o files fixes it even then.  I can't
imagine recompiling a file multiple times per second is a common use
case, so this is probably low priority!

-- 
Chris



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