Re: alternative to loadWithLogge

2011-08-24 Thread 山本和彦
Judah,

 ghc-mod, IDE-like back-end for Emacs, uses warning related APIs
 including loadWithLogger and getWarnings in GHC 7.0.3 API. I found
 that they disappeared in GHC 7.2.1 API. What should I use to handle
 warnings in GHC 7.2.1 API?
 
 You can set the log_action field of the session's DynFlags to a custom
 handler.  Its value is
 
 type LogAction = Severity - SrcSpan - PprStyle - Message - IO ()
 
 The Severity parameter will let you tell whether a message is a
 warning or an error.

Thank you very much for this information.
Now ghc-mod can be complied with GHC 7.2.1!

--Kazu

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


Re: [Pkg-haskell-maintainers] libffi soname change upcoming

2011-08-24 Thread Joachim Breitner
Hi,

Am Mittwoch, den 24.08.2011, 12:44 +0200 schrieb Matthias Klose:
  The question that has to be answered first is: Assume the libraries do
  not depend on libffi themselves, and only ghc does. Now you update
  libffi and ghc gets rebuilds, what will happen:
  
   A) The haskell ABIs stay the same, the existing library packages can
  still be used. Great.
  
   B) The haskell ABIs change. We’ll have to binNMU all Haskell libraries,
  but oh well, not bad thanks to BD-Uninstallable-support in wanna-build
  and autosigning.
  
   C) The haskell ABIs do not change, but the old library builds are
  broken nevertheless. Big mess. Hard to recover from, because builds are
  not ordered automatically any more. Needs lots of NMUes and Dep-Waits.
 
 sorry, I don't get the `C' case. why should these be broken by a libffi or
 libgmp change?

Maybe it’s an unrealistic example, but I could imagine that ghc some
data type (size) defined by libffi is used when generating code for a
haskell library under the assumption that it has the same structure/size
in the run time system and/or other used haskell libraries.

But instead of making blind guesses, maybe GHC upstream can enlighten
us: Is it safe to build ghc and a Haskell library, then upgrade libffi
to a new version (with soname bump), rebuild ghc, but use the previous
library build?

  Removing the libffi dependencies from the haskell libraries makes C
  possible and only helps with A. So until someone investigates this, I’d
  rather err on the safe side, leave the dependencies in, and fix the
  issue by rebuilding all haskell libraries when you upload the new ffi
  soname to unstable.
 
 well, with binNMU orgies like this you'll pull in any new or tightened
 dependencies for shared libraries. Not depending on these unused libraries
 does avoid this.

True. I agree that it would be nice and worthwhile to remove the libffi
dependency from the libraries, but only if it is actually safe and
scenario C is guaranteed not to happen.

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: Cheap and cheerful partial evaluation

2011-08-24 Thread Ryan Newton
Ah, and there's no core-haskell facility presently?  Thanks.

On Wed, Aug 24, 2011 at 12:14 AM, Edward Z. Yang ezy...@mit.edu wrote:

 Since most of GHC's optimizations occur on core, not the user-friendly
 frontend language, doing so would be probably be nontrivial (e.g.
 we'd want some sort of core to Haskell decompiler.)

 Edward

 Excerpts from Ryan Newton's message of Tue Aug 23 13:46:45 -0400 2011:
  Edward,
 
  On first glance at your email I misunderstood you as asking about using
  GHC's optimizer as a source-to-source operation (using GHC as an
 optimizer,
  retrieving partially evaluated Haskell code).  That's not what you were
  asking for -- but is it possible?
 
-Ryan
 
  P.S.   One compiler that comes to mind that exposes this kind of thing
  nicely is Chez Scheme ( http://scheme.com/ ).  In Chez you can get your
  hands on cp0 which does a source to source transform (aka compiler pass
  zero, after macro expansion), and could use cp0 to preprocess the source
 and
  then print it back out.
 
  On Mon, Aug 22, 2011 at 8:48 AM, Edward Z. Yang ezy...@mit.edu wrote:
 
   I think this ticket sums it up very nicely!
  
   Cheers,
   Edward
  
   Excerpts from Max Bolingbroke's message of Mon Aug 22 04:07:59 -0400
 2011:
On 21 August 2011 19:20, Edward Z. Yang ezy...@mit.edu wrote:
 And no sooner do I send this email do I realize we have 'inline'
   built-in,
 so I can probably experiment with this right now...
   
You may be interested in my related ticket #5029:
http://hackage.haskell.org/trac/ghc/ticket/5059
   
I don't think this is totally implausible but you have to be very
careful with recursive functions.
   
Max
  
   ___
   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: Cheap and cheerful partial evaluation

2011-08-24 Thread Edward Z. Yang
I think it would be a pretty interesting project. :^)

Edward

Excerpts from Ryan Newton's message of Wed Aug 24 15:18:48 -0400 2011:
 Ah, and there's no core-haskell facility presently?  Thanks.
 
 On Wed, Aug 24, 2011 at 12:14 AM, Edward Z. Yang ezy...@mit.edu wrote:
 
  Since most of GHC's optimizations occur on core, not the user-friendly
  frontend language, doing so would be probably be nontrivial (e.g.
  we'd want some sort of core to Haskell decompiler.)
 
  Edward
 
  Excerpts from Ryan Newton's message of Tue Aug 23 13:46:45 -0400 2011:
   Edward,
  
   On first glance at your email I misunderstood you as asking about using
   GHC's optimizer as a source-to-source operation (using GHC as an
  optimizer,
   retrieving partially evaluated Haskell code).  That's not what you were
   asking for -- but is it possible?
  
 -Ryan
  
   P.S.   One compiler that comes to mind that exposes this kind of thing
   nicely is Chez Scheme ( http://scheme.com/ ).  In Chez you can get your
   hands on cp0 which does a source to source transform (aka compiler pass
   zero, after macro expansion), and could use cp0 to preprocess the source
  and
   then print it back out.
  
   On Mon, Aug 22, 2011 at 8:48 AM, Edward Z. Yang ezy...@mit.edu wrote:
  
I think this ticket sums it up very nicely!
   
Cheers,
Edward
   
Excerpts from Max Bolingbroke's message of Mon Aug 22 04:07:59 -0400
  2011:
 On 21 August 2011 19:20, Edward Z. Yang ezy...@mit.edu wrote:
  And no sooner do I send this email do I realize we have 'inline'
built-in,
  so I can probably experiment with this right now...

 You may be interested in my related ticket #5029:
 http://hackage.haskell.org/trac/ghc/ticket/5059

 I don't think this is totally implausible but you have to be very
 careful with recursive functions.

 Max
   
___
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


Panic when using syb with GHC API

2011-08-24 Thread Simon Hengel
Hello,
I'm trying to query a type-checked module with syb, this works for a
plain binding.  But as soon as I add a type signature for that binding,
I get an panic!

I experienced similar problems with a renamed module.

Are those data structures meant to be used with syb?  And if yes, what
did I miss?

Bellow is some code to reproduce my issue.  Any help is very much
appreciated.

-- A.hs
module Main where

import GHC
import Outputable
import Data.Generics
import GHC.Paths (libdir)

import Bag

main :: IO ()
main = do
  m - parse
  putStrLn $ showSDoc $ ppr $ m
  putStrLn \n---\n
  putStrLn $ showSDoc $ ppr $ selectAbsBinds m

parse = runGhc (Just libdir) $ do
  _ - getSessionDynFlags = setSessionDynFlags
  target - guessTarget B.hs Nothing
  setTargets [target]
  Succeeded - load LoadAllTargets
  modSum - getModSummary $ mkModuleName B
  m - parseModule modSum = typecheckModule
  return $ typecheckedSource m

selectAbsBinds :: GenericQ [HsBindLR Id Id]
selectAbsBinds = everything (++) ([] `mkQ` f)
  where
f x@(AbsBinds _ _ _ _ _) = [x]
f _ = []


-- B.hs
module B where

foo :: Char
foo = 'f'

Cheers,
Simon

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