RE: The role of INLINE and INLINABLE on recursive functions

2011-06-09 Thread Simon Peyton-Jones
INLINE:
- no effect for a recursive function
- for a non-recursive function, always inline a call that 
(a) is applied to as many args as the LHS of the defn
(b) has some interesting context.  Ie (\y x- f x y) doesn't
inline f

INLINEABLE
a) For type-class overloaded functions (including recursive ones)
- makes them auto-specialise at call sites in other modules
- allows SPECIALISE pragmas for them in other modules

b) For non-recursive functions, makes GHC willing, but not super-eager,
  to inline at call sites.  Ie just use GHC's usual inlining rules.
  The difference from not having the pragma is that the *original* 
  RHS is inlined (if GHC decides to) rather than the optimised RHS.
 
Does that help?  The dual role of INLINEABLE is a bit confusing.  And the 
utility of (b) isn't clear to me.


Simon

| -Original Message-
| From: Johan Tibell [mailto:johan.tib...@gmail.com]
| Sent: 09 June 2011 12:06
| To: Simon Peyton-Jones
| Subject: The role of INLINE and INLINABLE on recursive functions
| 
| Hi,
| 
| This comment on Trac got me curious:
| 
| Ok, we looked at this, and it turns out that 6.12.3 desugars `forever`
| differently: in 6.12, a local recursive `let` was introduced, which meant
| that `forever` could be inlined (and hence specialised) at every call
| site, whereas in 7.0 the desugarer leaves the function as a top-level
| recursive function which cannot be inlined.
| 
| The solution is to add an `INLINABLE` pragma for `forever`, which will
| allow it to be specialised at a call site.
| 
| What's the meaning of INLINE or INLINABLE on a recursive function?
| Normally we don't inline recursive functions (when would we stop
| inlining?) so it's unclear to me what the meaning of the pragmas would
| be in this cases. I know that INLINABLE on a recursive function that
| takes a type class dictionary leads to call site specialization of
| that function (but not inlining).
| 
| People often use this transformation to get recursive functions inlined:
| 
| f = ... f ...
| 
| f_transformed = go
|   where go = ... go ...
| {-# INLINE f_transformed #-}
| 
| Could we get the same result by just adding an INLINE pragma to the original 
f?
| 
| Cheers,
| Johan


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


Re: The role of INLINE and INLINABLE on recursive functions

2011-06-09 Thread Johan Tibell
On Thu, Jun 9, 2011 at 1:43 PM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 Does that help?

Definitely. Thanks!

Johan

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


Using CPP in Cmm

2011-06-09 Thread Johan Tibell
Hi,

I'm trying to write a test case to make sure memset gets unrolled
correctly by the backend. Unrolling only happens when the alignment
and size is statically known so writing a simple Cmm loop that calls
memset won't work as the sizes won't be statically known. I want to
test memset with a large (e.g. 10-20) different variations of
alignments and sizes and I don't want to cut-n-paste large chunks of
code so I tried the following (best viewed with a fixed-width font):


#define TEST_MEMSET(ALIGN,SIZE)\
W_ size, src, dst, off, alignV, set;   \
bits8 set8;\
   \
// Need two versions as memset takes a word for historical reasons \
// but really its a bits8. We check that setting has ben done  \
// correctly at the bits8 level, so need bits8 version for \
// checking.   \
set = 4;   \
set8 = 4::bits8;   \
   \
size = SIZE;   \
alignV = ALIGN;\
(ptr src) = foreign C malloc(size);\
(ptr dst) = foreign C malloc(size);\
prim %memset(src ptr, set, size, alignV) []; \
   \
// Check memset worked \
off = 0;   \
while1:\
if (off == size) { \
goto while1_end;   \
}  \
if (bits8[src + off] != set8) {\
foreign C printf(memsetErr ptr) [];\
goto while1_end;   \
}  \
off = off + 1; \
goto while1;   \
while1_end:\
foreign C free(src); \
foreign C free(dst);

unrollintrinTest
{
// Test many different combinations here.
TEST_MEMSET(8,8);
TEST_MEMSET(4,8);

jump %ENTRY_CODE(Sp(0));
}

This seems to work (i.e. the test passes) but it shouldn't! I'd expect
the fact that we generate several labels (and temp registers) with the
same name to lead to problems, but it doesn't seem to. I initially
tried to use the CPP ## string concatenation operator to create unique
names (tedious, but works) but GHC runs CPP in traditional mode so
that doesn't work. I also tried to introduce local {} blocks in the
Cmm to deal with the scoping of identifiers (like you would in C) but
that's not supported.

Any idea of how I can generate the same piece of Cmm code (that
contains labels and locally defined identifiers) multiple times
without name capturing?

Cheers,
Johan

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


RE: crash caused by generic visitor (?)

2011-06-09 Thread Simon Peyton-Jones
Great, thanks. I've added that link to the user-documentation page for the GHC 
API, here
http://haskell.org/haskellwiki/GHC/As_a_library#Links

Please do elaborate that page, which is a bit thin at the moment.  It should be 
easier to find supporting info about the GHC API.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Ranjit Jhala
| Sent: 14 May 2011 17:52
| To: ghc-users
| Subject: Re: crash caused by generic visitor (?)
| 
| Hi all,
| 
| my apologies. Looks like the issue (and a fix!) is described here
| 
|   http://mistuke.wordpress.com/category/vsx/
| 
| Thanks,
| 
| Ranjit.
| 
| On May 13, 2011, at 4:34 PM, Ranjit Jhala wrote:
| 
|  Hi all,
| 
|  I'm trying to extract the set of identifiers that are read in given
|  source file.  To this end, I wrote the following code (full source at end.)
| 
|  
|  main
|   = do fname   - (!! 0) `fmap` getArgs
|tcm - loadTypecheckedSource fname
|putStrLn $ showPpr tcm   -- this works fine
|putStrLn $ showPpr $ allIds tcm  -- this causes the crash
|return ()
| 
|  allIds ::  Data a = a - [Id]
|  allIds = listify (\x - case (x :: Id) of _ - True)
|  
| 
|  and where:
| 
|  loadTypecheckedSource ::  FilePath - IO TypecheckedSource
| 
|  unfortunately, when I compile and run it, I get the dreaded:
| 
|  Bug: Bug: panic! (the 'impossible' happened)
|  (GHC version 7.0.3 for i386-unknown-linux):
|  placeHolderNames
| 
|  Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
| 
|  Turns out that the problem is when the file contains a type annotation.
|  That is,
| 
|  ./Bug Test00.hs
| 
|  crashes, when Test00.hs is:
| 
|  module Test where
| 
|  x :: Int
|  x = 0
| 
|  but does not crash when the file is:
| 
|  module Test where
| 
|  x = 0
| 
|  Can anyone tell me why listify chokes in the latter case? (And how one might
|  get around the problem?) I include the full source below (compiled with: 
ghc --make
| Bug, using ghc 7.0.3)
| 
|  Thanks!
| 
|  Ranjit.
| 
|  
---
| ---
|  import GHC
|  import Outputable
|  import DynFlags (defaultDynFlags)
|  import GHC.Paths (libdir)
| 
|  import System.Environment (getArgs)
|  import Control.Monad
|  import qualified Data.List as L
|  import Data.Data
|  import Data.Generics.Schemes (listify)
| 
|  main
|   = do fname   - (!! 0) `fmap` getArgs
|tcm - loadTypecheckedSource fname
|putStrLn $ showPpr tcm   -- this works fine
|putStrLn $ showPpr $ allIds tcm  -- this causes the crash
|return ()
| 
|  allIds ::  Data a = a - [Id]
|  allIds = listify (\x - case (x :: Id) of _ - True)
| 
|  loadTypecheckedSource ::  FilePath - IO TypecheckedSource
|  loadTypecheckedSource fname
|   = defaultErrorHandler defaultDynFlags $
|   runGhc (Just libdir) $ do
| df  - getSessionDynFlags
| setSessionDynFlags df
| tgt - guessTarget fname Nothing
| setTargets [tgt]
| load LoadAllTargets
| res - load LoadAllTargets
| if failed res
|   then pprPanic Load Failed!! (text AAARGH!)
|   else tm_typechecked_source `fmap` getTypecheckedModule fname
| 
|  findModSummary ::  GhcMonad m = FilePath - m ModSummary
|  findModSummary fname
|   = do msums - depanal [] False
|case L.find ((fname ==) . ms_hspp_file) msums of
|  Just msum - return msum
|  Nothing   - pprPanic ModuleName Lookup Failed!! (text AARGHC!)
| 
|  getTypecheckedModule :: GhcMonad m = FilePath - m TypecheckedModule
|  getTypecheckedModule = findModSummary = parseModule = typecheckModule
| 
| 
| 
| 
| 
| ___
| 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: The role of INLINE and INLINABLE on recursive functions

2011-06-09 Thread Simon Marlow

On 09/06/2011 12:43, Simon Peyton-Jones wrote:

INLINE:
- no effect for a recursive function
- for a non-recursive function, always inline a call that
(a) is applied to as many args as the LHS of the defn
(b) has some interesting context.  Ie (\y x-  f x y) doesn't
inline f

INLINEABLE
a) For type-class overloaded functions (including recursive ones)
- makes them auto-specialise at call sites in other modules
- allows SPECIALISE pragmas for them in other modules

b) For non-recursive functions, makes GHC willing, but not super-eager,
   to inline at call sites.  Ie just use GHC's usual inlining rules.
   The difference from not having the pragma is that the *original*
   RHS is inlined (if GHC decides to) rather than the optimised RHS.

Does that help?  The dual role of INLINEABLE is a bit confusing.  And the 
utility of (b) isn't clear to me.


So there are a couple of reasons to want (b).  First, it shifts the 
decision about whether to inline to the call site, where the user has 
more control (e.g. with -funfolding-use-threshold300).  This came up 
during the work on the containers package, where there was a concern 
that overuse of INLINE was causing code bloat in clients.


Second, (b) is useful in cases like this:

g x = ... large ...

f x = ... g x ...

and you want f to be inlined (but not necessarily everywhere, only if 
it's useful).  If you don't say INLINABLE, then g gets inlined into f's 
rhs (let's assume g is only used once), and f never gets inlined because 
it's too big.  If you say INLINE, then f gets inlined everywhere, which 
might be overkill.  INLINABLE is just right.


Cheers,
Simon






Simon

| -Original Message-
| From: Johan Tibell [mailto:johan.tib...@gmail.com]
| Sent: 09 June 2011 12:06
| To: Simon Peyton-Jones
| Subject: The role of INLINE and INLINABLE on recursive functions
|
| Hi,
|
| This comment on Trac got me curious:
|
| Ok, we looked at this, and it turns out that 6.12.3 desugars `forever`
| differently: in 6.12, a local recursive `let` was introduced, which meant
| that `forever` could be inlined (and hence specialised) at every call
| site, whereas in 7.0 the desugarer leaves the function as a top-level
| recursive function which cannot be inlined.
|
| The solution is to add an `INLINABLE` pragma for `forever`, which will
| allow it to be specialised at a call site.
|
| What's the meaning of INLINE or INLINABLE on a recursive function?
| Normally we don't inline recursive functions (when would we stop
| inlining?) so it's unclear to me what the meaning of the pragmas would
| be in this cases. I know that INLINABLE on a recursive function that
| takes a type class dictionary leads to call site specialization of
| that function (but not inlining).
|
| People often use this transformation to get recursive functions inlined:
|
| f = ... f ...
|
| f_transformed = go
|   where go = ... go ...
| {-# INLINE f_transformed #-}
|
| Could we get the same result by just adding an INLINE pragma to the original 
f?
|
| Cheers,
| Johan


___
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: Using CPP in Cmm

2011-06-09 Thread Thorkil Naur
Hello,

On Thu, Jun 09, 2011 at 03:44:43PM +0200, Johan Tibell wrote:
 ...
 I initially
 tried to use the CPP ## string concatenation operator to create unique
 names (tedious, but works) but GHC runs CPP in traditional mode so
 that doesn't work.

One -traditional way that I have used to concatenate pieces of C code is
demonstrated by:

 $ cat t.c
 #define s(z) z
 s(a)s(b)
 $ gcc t.c -E
 # 1 t.c
 # 1 built-in
 # 1 command-line
 # 1 t.c

 a b
 $ gcc t.c -E -traditional
 # 1 t.c
 # 1 built-in
 # 1 command-line
 # 1 t.c

 ab
 $

 ...

Best regards
Thorkil

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


Re: How to install GhC on a Mac without registering?

2011-06-09 Thread Manuel M T Chakravarty
[Ian, sorry for the duplicate — wrong sender email at first.]

Ian Lynagh:
 On Mon, Jun 06, 2011 at 03:47:57PM +0100, Malcolm Wallace wrote:
 
 On 6 Jun 2011, at 13:49, Lyndon Maydwell wrote:
 
 I would be fantastic if XCode wasn't a dependency.  ...
 
 Not to detract at all from the work of the wonderful GHC and Haskell
 Platform contributors in any way. For me it would just make it that
 much easier to convince mac-using friends to give Haskell a try.
 
 The ghc team already bundle a copy of gcc in their Windows distribution, 
 precisely because it can be fiddly to get a working copy of gcc for that 
 platform otherwise.  I wonder if they would consider the possibility of 
 shipping gcc on Mac too?  (There may be good reasons not to do that, but 
 let's have the discussion.)
 
 I'm pretty sure we aren't allowed to redistribute XCode.
 
 As well as gcc and friends, I think XCode also includes various headers
 and/or libraries that we need.
 
 If there is an alternative - especially one that allows us to support
 multiple versions of OS X more easily - then using it may make sense.

You are right, the Xcode install includes many tools as well as headers etc.

What would be the advantage of including gcc and all these other things in GHC? 
 Anybody who is halfway serious about developing software on a Mac will have 
Xcode installed anyway.  Besides, as Xcode updates are now available from the 
Mac App Store, you don't even need to register as a developer with Apple 
anymore — yes, you need to pay the nominal $5 for the 4GB download.  If you 
don't want to do that, install the (probably older) version of Xcode that came 
with the install DVDs of your Mac.

I don't think you can compare this with the situation on Windows.  Microsoft 
does not distribute a canonical set of Unix tools that all developers use.

Manuel


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