Re: Newtype wrappers

2013-01-21 Thread wren ng thornton

On 1/21/13 1:40 AM, Shachaf Ben-Kiki wrote:

For example:

 {-# LANGUAGE TypeFamilies #-}
 import Unsafe.Coerce

 newtype Id a = MkId { unId :: a }

 {-# RULES "fmap unId" fmap unId = unsafeCoerce #-}

 data family Foo x y a
 data instance Foo x y (Id a) = FooI x
 data instance Foo x y Bool   = FooB { unB :: y }

 instance Functor (Foo x y) where fmap = undefined


You can define instances for type functions? Eek!

--
Live well,
~wren

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


Re: Error building ghc on raspberry pi.

2013-01-21 Thread Karel Gardas

On 01/21/13 04:43 PM, rocon...@theorem.ca wrote:

So the binary-dist has a settings.in file. It is the configure step in
the binary-dist that generates the corrupt settings file.


Perhaps you've forgotten to regenerate bin-dist configure as you did 
with build tree configure after applying my patch?



I'll try to poke around to see where and why the stage2 compiler and the
binary-dist compiler differ.


Please post your findings here, I'm really curious what is the culprit 
here...


Karel



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


Re: Error building ghc on raspberry pi.

2013-01-21 Thread roconnor

On Mon, 21 Jan 2013, Karel Gardas wrote:


On 01/21/13 12:49 AM, rocon...@theorem.ca wrote:

On Sun, 20 Jan 2013, Karel Gardas wrote:


Okay, I patched the settings filed generted by ./configure in the
binary-dist and rank make install which completed. However,

pi@raspberrypi /tmp/bindist $ bin/ghc --make Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )
Linking Main ...
pi@raspberrypi /tmp/bindist $ ./Main
Segmentation fault
pi@raspberrypi /tmp/bindist $ cat Main.hs
main = putStrLn "Hello World."

Damn it. So close. I don't know how make install succeded without
segfaulting.


Sigh! Go back to your build tree and try the same thing with
inplace/bin/ghc-stage2 and let us know if this works or not. BTW:
What's in Main.hs?


pi@raspberrypi /tmp $ ghc-7.6.1c/inplace/bin/ghc-stage2 Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )
Linking Main ...
pi@raspberrypi /tmp $ ./Main
Hello World.

The stage2 compiler works fine inplace.


OK, so binary-dist not only corrupted your settings file, but also somehow 
your compiler. Nice to see you are able to get working compiler on your RPi 
board. Congratulations! :-)


Thanks. :)

So the binary-dist has a settings.in file.  It is the configure step in 
the binary-dist that generates the corrupt settings file.


I'll try to poke around to see where and why the stage2 compiler 
and the binary-dist compiler differ.


--
Russell O'Connor  
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''

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


Re: any successfull ghc registerised builds on arm?

2013-01-21 Thread Simon Marlow

On 19/01/13 07:32, Stephen Paul Weber wrote:

Somebody claiming to be Stephen Paul Weber wrote:

Somebody claiming to be Nathan Hüsken wrote:

Was that an registerised or unregisterised build?
Did anyone succesfully build ghc on an arm system which produces non
crashing executables?


Just finally got a BB10 device set up so I can test my cross-compiler
on the ARM

I'm about to try a configuration with --enable-unregisterised to see
if that helps.


make -r --no-print-directory -f ghc.mk phase=final all
"inplace/bin/ghc-stage1" -static  -H64m -O0 -fasm-package-name
integer-simple-0.1.1.0 -hide-all-packages -i
-ilibraries/integer-simple/.
-ilibraries/integer-simple/dist-install/build
-ilibraries/integer-simple/dist-install/build/autogen
-Ilibraries/integer-simple/dist-install/build
-Ilibraries/integer-simple/dist-install/build/autogen
-Ilibraries/integer-simple/.-optP-include
-optPlibraries/integer-simple/dist-install/build/autogen/cabal_macros.h
-package ghc-prim-0.3.1.0  -package-name integer-simple -Wall
-XHaskell98 -XCPP -XMagicHash -XBangPatterns -XUnboxedTuples
-XForeignFunctionInterface -XUnliftedFFITypes -XNoImplicitPrelude -O
-fasm  -no-user-package-db -rtsopts  -odir
libraries/integer-simple/dist-install/build -hidir
libraries/integer-simple/dist-install/build -stubdir
libraries/integer-simple/dist-install/build -hisuf hi -osuf  o -hcsuf hc
-c libraries/integer-simple/./GHC/Integer/Type.hs -o
libraries/integer-simple/dist-install/build/GHC/Integer/Type.o

when making flags consistent: Warning:
 Compiler unregisterised, so compiling via C
/tmp/ghc25891_0/ghc25891_0.hc: In function 'c2pA_entry':

/tmp/ghc25891_0/ghc25891_0.hc:3691:1:
  warning: this decimal constant is unsigned only in ISO C90
[enabled by default]

/tmp/ghc25891_0/ghc25891_0.hc:3691:17:
  error: expected ')' before numeric constant
make[1]: ***
[libraries/integer-simple/dist-install/build/GHC/Integer/Type.o] Error 1
make: *** [all] Error 2


Strange, I didn't see this on my builds, which I think is the same as 
yours (GHC HEAD, cross-compiling for RPi with --enable-unregisterised).


If you make a ticket with full details, I can try to reproduce.

Cheers,
Simon



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


RE: Global constant propagation

2013-01-21 Thread Simon Peyton-Jones
Your example is complicated by the fact that k is overloaded (will work on any 
value in class Num), and in fact the numbers end up having type Integer, not 
Int.

But still, it is indeed like SpecConstr. Maybe we should generate a specialised 
version of 'k', specialised for k=0.   That might be a worthwhile thing to do, 
and would be a fairly straightforward modification of the SpecConstr code, to 
deal with literals as well as constructors.

Simon

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of C Rodrigues
|  Sent: 20 January 2013 21:18
|  To: glasgow-haskell-users@haskell.org
|  Subject: Global constant propagation
|  
|  
|  I'm curious about global constant propagation in GHC.  It's a fairly basic
|  optimization in the CFG-based compiler domain, and it's similar to 
constructor
|  specialization, but it doesn't seem to be in GHC's repertoire.  Perhaps it's 
usually
|  subsumed by other optimizations or it's more complicated than I am thinking. 
 Is
|  this optimization worth implementing?
|  
|  This optimization can help when a case expression returns a product, some 
fields
|  of which are the same in all branches.  The following program is a minimal
|  example of an optimizable situation that GHC doesn't exploit.
|  
|  
|  {-# OPTIONS_GHC -O3 -funbox-strict-fields #-}
|  
|  
|  data D = D !Int !Int
|  
|  
|  foo n = if n > 0
|  
|          then D 0 0
|  
|          else D 0 n
|  
|  
|  main =
|  
|    case foo $ read "7"
|  
|    of D x y -> if x == 0 then return () else print y >> putStrLn "A"
|  
|  
|  After inlining and case-of-case transformation, GHC produces
|  
|  
|  main = let n = read "7"
|  
|             k x y = case x of {0 -> return (); _ -> print y >> putStrLn "A"}
|  
|         in if n > 0
|  
|            then k 0 0
|  
|            else k 0 n
|  
|  
|  If the simplifier could discover that x is always 0, it could eliminate one 
parameter
|  of 'k' and the case expression.
|  
|  
|  ___
|  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