Re: porting to uClibc-based 686 Linux

2013-04-03 Thread Dubiousjim
I've gotten somewhat further cross-compiling 7.6.2 sources, though
still not all the way.

I also tried following the instructions at
http://hackage.haskell.org/trac/ghc/wiki/Building/Porting
with these sources, but couldn't get them to work either.

This continues to log my efforts to follow the instructions at
http://hackage.haskell.org/trac/ghc/wiki/Building/CrossCompiling

One thing I notice by comparing the 7.6.2 sources and the pre-release
sources available at 
http://www.haskell.org/ghc/dist/current/dist/ghc-7.7-src.tar.bz2
is that the instructions at the wiki webpage just cited are tailored
to the post-7.6.2 sources. Some of the configure settings should be
different for 7.6.2.

In particular, I had been using this:

is that the instructions at the wiki webpage just cited are tailored
to the post-7.6.2 sources. Some of the configure settings should be
different for 7.6.2.

In particular, I had been using this:

./configure --target=i686-buildroot-linux-uclibc --disable-largefile

as the wiki pages seem to suggest. But now I see that I should also be
setting --host for 7.6.2, and also supplying an --alien=script option.

The latter is a script you need to write which will run on the host and
take arguments of the form run cmd more arguments It should
then copy cmd to the target machine and execute cmd more
arguments... there, passing through its stdout.

Here is the alien script I'm using:

#!/bin/sh -x

TARGET=its.ip.address
CMD=$2
shift 2
scp $CMD ${USER}@${TARGET}:alien.cache/
ssh ${USER}@${TARGET} alien.cache/${CMD##*/} $@


That relies on the presence of a folder alien.cache in ${USER}'s home
directory on the target machine. It also relies on your being able to
ssh from host to target without requiring a password.

This script seems to be invoked twice during my builds, for
mkGHCConstants
mkDerivedConstants
There's a third time I think it should be invoked but isn't, and then I
have to invoke it manually. (This is explained below.)

So here are the steps I'm following now. Most everything described in my
preceding email still seems to be necessary; I'm including those steps
here as well.

 To refresh, I'm trying to bootstrap from a working ghc (now I have 7.6.2
 installed on the host) on a typical Linux 686 host system, glibc-based,
 to get a ghc that can be installed on a similar target system, differing
 in that it uses uclibc instead of glibc.
 
 I have a working cross-compiler, and seem to have everything else I need
 to have installed on my host. I did have to make sure that my
 cross-compiler tree had gmp and libiconv and ncurses installed in it.
 
 I also had to edit the file /usr/lib/ghc-7.6.2/include/ghcautoconf.h
 on my host system. This was #defining _FILE_OFFSET_BITS to 64, but the
 uclibc on my target system wasn't compiled with large file support,
 hence I thought the uclibc in my cross-compiler toolchain shouldn't be
 either. But then that #define in the host's ghcautoconf.h was
 conflicting. So I just commented it out for the time being.
 
 
 Here's what I've done, on the host, from a clean detar of the ghc 7.6.2
 sources.
 
 I made this change at three locations in ghc's topmost
 configure script, to get it to recognize my cross-compiler tag 
 i686-buildroot-linux-uclibc:
 
case $build_vendor in
 -  pc|gentoo) # like i686-pc-linux-gnu and i686-gentoo-freebsd8
 +  pc|gentoo|buildroot) # like i686-pc-linux-gnu and
 i686-gentoo-freebsd8
  BuildVendor=unknown
  ;;
 
 (The other two locations are for $host_vendor and $target_vendor. Maybe
 it's only necessary to do this for $target_vendor.)
 
 Next, here is my mk/build.mk file:
 
 # Fast build with optimised libraries, no profiling (RECOMMENDED):
 BuildFlavour = quick
 ...
 # An unregisterised, optimised build of ghc, for porting:
 # BuildFlavour = unreg
 ...
 
 The rest as in mk/build.mk.sample



 Next, the configure scripts for
 libraries/{base,directory,integer-gmp,old-time,process,terminfo,time,unix}
 would stall, complaining that the C compiler didn't generate
 binaries they could execute. I fixed that by patching those configure
 scripts like this---I don't know if this is correct, it may be the
 source of my later troubles. On the other hand, I don't know how else
 to get past the configure scripts failing. Adding switches like --host
 and --host= to my original configure, as an error message suggests,
 seems to have no effect.
 
 @@ -2833,7 +2833,7 @@
test $ac_status = 0; }; }; then
  cross_compiling=no
else
 -if test $cross_compiling = maybe; then
 +if true || test $cross_compiling = maybe; then
   cross_compiling=yes
  else
   { { $as_echo $as_me:${as_lineno-$LINENO}: error: in
   \`$ac_pwd': 5



 Next, I had to make this patch to libraries/haskeline/cbits/h_wcwidth.c,
 else I would get errors about types like size_t not being recognized. (I
 forget the exact 

Re: porting to uClibc-based 686 Linux

2013-04-03 Thread Dubiousjim
On Wed, Apr 03, 2013 at 09:56:58AM -0400, Dubiousjim wrote:

 Ok, with all of that, the build completes. And the build ghc-stage2
 (which I temporarily named inplace/lib/ghc-stage2.exe, but now let's
 restore it to its original name) does in fact execute on the target
 machine:
 
 $ inplace/lib/ghc-stage2 --version
 The Glorious Glasgow Haskell Compilation System, version 7.6.2
 $ inplace/lib/ghc-stage2 --interactive
 ghc-stage2: missing -Bdir option
 $ cat ~/hello.hs
 main = putStrLn Hello World!\n
 $ inplace/lib/ghc-stage2 -B./inplace/lib ~/hello.hs -o hello
 $ ./hello
 Can't modify application's text section; use the GCC option -fPIE
 for
 position-independent executables.
 
 That's as far as I've got for now. Hopefully someone will have
 bothered to read this far and have some suggestions for what I should be
 doing differently, or how to proceed from here, to get the compiled
 ghc-stage2 really working on the target machine, so that I can use it to
 compile ghc on the target machine directly.

Oh, in fact I'm closer than I thought. The error I reported as:

 $ inplace/lib/ghc-stage2 -B./inplace/lib --interactive
 GHCi, version 7.6.2: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... ghc-stage2: mmap 442368 bytes at (nil):
 Operation not permitted
 ghc-stage2: Try specifying an address with +RTS -xmaddr -RTS

is in fact due to my forgetfulness. My target system uses PaX kernel
security, and so
compilers like ghc have to be tweaked before they can be used:

$ paxctl -c inplace/lib/ghc-stage2
$ paxctl -m inplace/lib/ghc-stage2
$ inplace/bin/ghc-stage2  -B./inplace/lib --interactive
GHCi, version 7.6.2: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude 

Yay, the interpreter works!

But there's still something funny with the binaries generated by the
compiler. That means I can't yet use this ghc to directly recompile ghc
on my target system.

$ cat ~/hello.hs
main = putStrLn Hello World!\n
$ rm -f hello
$ inplace/bin/ghc-stage2 -B./inplace/lib ~/hello.hs -o hello
[1 of 1] Compiling Main ( /home/jim/hello.hs,
/home/jim/hello.o ) [flags changed]
Linking hello ...
$ ./hello
Can't modify application's text section; use the GCC option -fPIE
for
position-independent executables.

Seems like I'm close, but not quite there yet.

Supplying the flag -fPIE to ghc when building hello says:

ghc-stage2: unrecognised flags: -fPIE

The flag -fPIC on the other hand is accepted, but then the generated
binary hello still fails with the same error.

-- 
dubious...@gmail.com


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


RE: ImplicitParams and MonoLocalBinds

2013-04-03 Thread Simon Peyton-Jones
Correct.  Maybe the flag should be called “MonoOpenBinds”!

Really, the simplest solution is to write a type signature.  Then all is clear.

I’m very open to adding something to the documentation to explain about this. 
The current section is below... concrete suggestions for improvement would be 
welcome.

Simon



7.12.10. Let-generalisation
An ML-style language usually generalises the type of any let-bound or 
where-bound variable, so that it is as polymorphic as possible. With the flag 
-XMonoLocalBinds GHC implements a slightly more conservative policy: it 
generalises only closed bindings. A binding is considered closed if either

  *   It is one of the top-level bindings of a module, or
  *   Its free variables are all themselves closed
For example, consider
f x = x + 1
g x = let h y = f y * 2
  k z = z+x
  in  h x + k x
Here f and g are closed because they are bound at top level. Also h is closed 
because its only free variable f is closed. But k is not closed because it 
mentions x which is locally bound. Another way to think of it is this: all 
closed bindings could be defined at top level. (In the example, we could move h 
to top level.)
All of this applies only to bindings that lack an explicit type signature, so 
that GHC has to infer its type. If you supply a type signature, then that fixes 
type of the binding, end of story.
The rationale for this more conservative strategy is given in the 
papershttp://research.microsoft.com/%7Esimonpj/papers/constraints/index.htm 
Let should not be generalised and Modular type inference with local 
assumptions, and a related blog 
posthttp://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7.
The flag -XMonoLocalBinds is implied by -XTypeFamilies and -XGADTs. You can 
switch it off again with -XNoMonoLocalBinds but type inference becomes less 
predicatable if you do so. (Read the papers!)



From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Iavor Diatchki
Sent: 29 March 2013 00:07
To: Roman Cheplyaka
Cc: GHC Users Mailing List
Subject: Re: ImplicitParams and MonoLocalBinds

Hi,

Aha! This page explains what is going on: 
http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7

The summary is that the definition of what is local is not what one might 
expect:  only things that depend
on variables in scope are considered to be locals, other bindings, that could 
be lifted out (e.g., like `p` in both examples)
are not considered local and are generalized.  Of course, with implicit 
parameters this is not what one might hope for...

A while back there was a discussion about adding a construct for monomorphic 
bindings to the language (I think the proposed notation was something like x 
:= 2).
Perhaps we should revisit it, it seems much simpler than the rather surprising 
behavior of `MonoLocalBinds`.

-Iavor





On Thu, Mar 28, 2013 at 4:39 PM, Iavor Diatchki 
iavor.diatc...@gmail.commailto:iavor.diatc...@gmail.com wrote:
Hi,
This does not appear to be related to ImplicitParameters, rather 
`MonoLocalBinds` is not working as expected.

Here is an example without implicit parameters that compiles just fine, but 
would be rejected if `p` was monomorphic:

{-# LANGUAGE NoMonomorphismRestriction, MonoLocalBinds #-}

class C a where
  f :: a - ()

instance C Bool where f = const ()
instance C Char where f = const ()

g = let p = f
in (p 'a', p True)

-Iavor



On Fri, Mar 22, 2013 at 1:39 AM, Roman Cheplyaka 
r...@ro-che.infomailto:r...@ro-che.info wrote:
The value of the following expression

  let ?y = 2  in
  let  p = ?y in
  let ?y = 1  in
  p

depends on whether the second binding is generalised.

MonomorphismRestriction makes it not generalise, hence the value is 2.

What surprises me is that MonoLocalBinds doesn't have this effect.

  Prelude :set -XImplicitParams -XNoMonomorphismRestriction -XMonoLocalBinds
  Prelude let ?y = 2 in let p = ?y in let ?y = 1 in p
  1

What's going on here?

Roman

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.orgmailto: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: Allowing (Char ~ Bool = Void)?

2013-04-03 Thread Simon Peyton-Jones
What precisely is the proposal here?  That unreachable code be a warning 
rather than an error?  

Would you care to make a ticket with a clear specification?  Thanks!

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Richard Eisenberg
| Sent: 24 March 2013 14:49
| To: Shachaf Ben-Kiki
| Cc: glasgow-haskell-users
| Subject: Re: Allowing (Char ~ Bool = Void)?
| 
| Though I've never run into the problem Shachaf mentions, this certainly
| seems useful. However, when testing Shachaf's code, I get the same error
| that I get when writing an impossible branch of a case statement. I
| imagine that the same code in GHC powers both scenarios, so any change
| would have to be careful to preserve the case-branch behavior, which (I
| think) is useful.
| 
| Perhaps a general solution to this problem is to have some new term
| construct contra (supply a better name please!) that can be used only
| when there is an inconsistent equality in the context but can typecheck
| at any type. With contra, we could allow impossible case branches,
| because now there would be something sensible to put there. This would
| be an alternate effective solution to long-standing bug #3927, which is
| about checking exhaustiveness of case matches.
| 
| Richard
| 
| On Mar 24, 2013, at 5:16 AM, Shachaf Ben-Kiki shac...@gmail.com wrote:
| 
|  Is there a good reason that GHC doesn't allow any value of type (Char
|  ~ Bool = Void), even undefined?
| 
|  There are various use cases for this. It's allowed indirectly, via
|  GADT pattern matches -- foo :: Is Char Bool - Void; foo x = case x
|  of {} (with EmptyCase in HEAD) -- but not directly.
| 
|  One thing this prevents, for instance, is CPSifying GADTs:
| 
| data Foo a = a ~ Char = A | a ~ Bool = B -- valid
| newtype Bar a = Bar { runBar :: forall r. (a ~ Char = r) - (a ~
|  Bool = r) - r } -- unusable
| 
|  Trying to use a type like the latter in practice runs into problems
|  quickly because one needs to provide an absurd value of type (Char ~
|  Bool = r), which is generally impossible (even if we're willing to
|  cheat with ⊥!). It seems that this sort of thing should be doable.
| 
| Shachaf
| 
|  ___
|  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
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing (Char ~ Bool = Void)?

2013-04-03 Thread Richard Eisenberg
I would call this more of an idea than a proposal -- I'm not advocating that 
it's necessarily the right thing, but one possible solution both to Shachaf's 
original question and the problem of spurious warnings about bogus case 
branches.

The idea is to introduce some new keyword, which I've called contra, which 
has the type (a ~ b) = c, where a cannot unify with b (and c is totally 
unconstrained). Currently, whenever such an equality (a ~ b) is in the context, 
GHC issues an error and prevents any further code. This is often good behavior 
of a compiler, to prevent people from writing impossible code. However, Shachaf 
found a case where it would be nice to have code that executes in an 
inconsistent context. And, if we had contra, then we could just stick contra in 
any inconsistent pattern matches, and there would be no need to fix the 
warnings about incomplete pattern matches.

For example:

 data Nat = Zero | Succ Nat
 data SNat :: Nat - * where
   SZero :: SNat Zero
   SSucc :: SNat n - SNat (Succ n)
 
 safePred :: SNat (Succ n) - SNat n
 safePred (SSucc n) = n
 safePred SZero = contra

(Seeing the code here, perhaps impossible is a better name.)

The last clause of safePred is indeed impossible. GHC issues an error on the 
code above. If we remove the last line, GHC (rightly) does not issue a warning 
about an incomplete pattern match. But, as documented on Trac #3927, there are 
other places where GHC does issue a warning about missing impossible branches. 
With contra, we could fill out such pattern matches and suppress the warning.

When I initially wrote up my contra idea, I was remembering a case where GHC 
did not issue a warning on an inconsistent pattern match. In the process of 
writing this email, I found that old case, and I realized that it was my fault, 
not GHC's. I had originally thought that GHC's impossible code identification 
feature was incomplete, but now perhaps I was wrong. If GHC can always detect 
impossible code, the contra idea is less appealing than it once was to me, 
though it would still solve Shachaf's problem.

Does this clarify the idea?

Richard

On Apr 3, 2013, at 1:49 PM, Simon Peyton-Jones simo...@microsoft.com wrote:

 What precisely is the proposal here?  That unreachable code be a warning 
 rather than an error?  
 
 Would you care to make a ticket with a clear specification?  Thanks!
 
 Simon
 
 | -Original Message-
 | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
 | users-boun...@haskell.org] On Behalf Of Richard Eisenberg
 | Sent: 24 March 2013 14:49
 | To: Shachaf Ben-Kiki
 | Cc: glasgow-haskell-users
 | Subject: Re: Allowing (Char ~ Bool = Void)?
 | 
 | Though I've never run into the problem Shachaf mentions, this certainly
 | seems useful. However, when testing Shachaf's code, I get the same error
 | that I get when writing an impossible branch of a case statement. I
 | imagine that the same code in GHC powers both scenarios, so any change
 | would have to be careful to preserve the case-branch behavior, which (I
 | think) is useful.
 | 
 | Perhaps a general solution to this problem is to have some new term
 | construct contra (supply a better name please!) that can be used only
 | when there is an inconsistent equality in the context but can typecheck
 | at any type. With contra, we could allow impossible case branches,
 | because now there would be something sensible to put there. This would
 | be an alternate effective solution to long-standing bug #3927, which is
 | about checking exhaustiveness of case matches.
 | 
 | Richard
 | 
 | On Mar 24, 2013, at 5:16 AM, Shachaf Ben-Kiki shac...@gmail.com wrote:
 | 
 |  Is there a good reason that GHC doesn't allow any value of type (Char
 |  ~ Bool = Void), even undefined?
 | 
 |  There are various use cases for this. It's allowed indirectly, via
 |  GADT pattern matches -- foo :: Is Char Bool - Void; foo x = case x
 |  of {} (with EmptyCase in HEAD) -- but not directly.
 | 
 |  One thing this prevents, for instance, is CPSifying GADTs:
 | 
 | data Foo a = a ~ Char = A | a ~ Bool = B -- valid
 | newtype Bar a = Bar { runBar :: forall r. (a ~ Char = r) - (a ~
 |  Bool = r) - r } -- unusable
 | 
 |  Trying to use a type like the latter in practice runs into problems
 |  quickly because one needs to provide an absurd value of type (Char ~
 |  Bool = r), which is generally impossible (even if we're willing to
 |  cheat with ⊥!). It seems that this sort of thing should be doable.
 | 
 | Shachaf
 | 
 |  ___
 |  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
 


___