Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Edward Kmett
I see three major stories here:

1.) If you remove IO from being able to be compiled inside Safe code _at
all_ most packages I have that bother to expose Safe information will have
to stop bothering. I'd have to cut up too many APIs into too many
fine-grained pieces. This would considerably reduce the utility of Safe
Haskell to me. Many of them expose a few combinators here and there that
happen to live in IO and I can view offering Safe or Trustworthy to users
as a 'the pure stuff looks really pure' guarantee. For the most part it
'just works' and Trustworthy annotations can be put in when I know the
semantics of the hacks I'm using under the hood.

2.) Assuming instead that you're talking about a stronger-than-Safe
additional language extension, say ReallySafe or SafeIO, it all comes down
to what the user is allowed to do in IO, doesn't it? What effects are users
granted access to? We don't have a very fine-grained system for IO-effect
management, and it seems pretty much any choice you pick for what to put in
the sandbox will be wrong for some users, so you'd need some sort of pragma
for each IO operation saying what bins it falls into and to track that
while type checking, etc. At least then you could say what you are safe
with respect to. That all seems to be rather a big mess, roughly equivalent
to modeling an effect system for IO operations, and then retroactively
categorizing everything, putting a big burden on maintainers and requiring
a lot of community buy-in, sight unseen.

3.) On the other hand, someone could _build_ an effect system in Haskell
that happens to sit on top of IO, holding effects in an HList, undischarged
nullary class constraint, etc. then pull a couple of Trustworthy modules
around it for embedding the effects they want to permit and build this
today without any compiler support, they'd just have to make a final
application-specific Trustworthy wrapper to run whatever effects they want
to permit into their program. It is more invasive to the code in question,
but it requires zero community organizing and we've already got all the
compiler mojo we need. The downside is the Trustworthy wrappers at the
bottom of the heap and that it doesn't interoperate with basically anything
already written.

-Edward

On Tue, Aug 9, 2016 at 10:45 PM, Ryan Newton  wrote:

> I'm hearing that Safe Haskell is great for pure use cases (lambda bot).
> But that doesn't depend on being able to write arbitrary IO code inside the
> Safe bubble, does it?  In fact *all* of IO could be outside the safe
> boundary for this use case, could it not?  Are there any existing cases
> where it is important to be able to build up unsafe IO values inside -XSafe
> code?
>
> Edward, why does it seem like a losing proposition?  Are there further
> problems that come to mind?  ezyang mentioned the subprocess problem.  I
> don't have a strong opinion on that one.  But I tend to think the safe IO
> language *should* allow subprocess calls, and its a matter of configuring
> your OS to not allow ptrace in that situation.  This would be part of a set
> of requirements for how to compile and launch a complete "Safe Haskell"
> *program* in order to get a guarantee.
>
> My primary interest is actually not segfault-freedom, per-se, but being
> able to define a memory model for Safe Haskell (for which I'd suggest
> sequential consistency).  FFI undermines that, and peek/poke seems like it
> should cluster with FFI as an unsafe feature.  I'm not inclined to give a
> memory model to peek or FFI -- at that level you get what the architecture
> gives you -- but I do want a memory model for IORefs, IOVectors, etc.
>
> We're poking at the Stackage package set now to figure out what pressure
> point to push on to increase the percentage of Stackage that is Safe.  I'll
> be able to say more when we have more data on dependencies and problem
> points.  Across all of hackage, Safe Haskell has modest use: of the ~100K
> modules on Hackage, ~636 are marked Safe, ~874 trustworthy, and ~118
> Unsafe.  It should be easy to check if any of this Safe code is currently
> importing "Foreign.*" or using FFI.
>
> My general plea is that we not give the imperative partition of Haskell
> too much the short end of the stick [1]. There is oodles of code in IO (or
> MonadIO), and probably relatively little in "RIO".  To my knowledge, we
> don't have great ways to coin "RIO" newtypes without having to wrap and
> reexport rather a lot of IO functions.  Maybe if APIs like MVars or files
> were overloaded in a class then GND could do some of the work...
>
>   -Ryan
>
> [1] In safety guarantees, in optimizations, primops, whatever...  For
> instance, I find in microbenchmarks that IO code still runs 2X slower than
> pure code, even if no IO effects are performed.
>
>
>
> On Tue, Aug 9, 2016 at 5:13 PM, Edward Kmett  wrote:
>
>> I've always treated Safe Haskell as "Safe until you allow IO" -- in that
>> all 'evil' things get 

Re: enumFromThenTo for Doubles

2016-08-09 Thread Andrew Farmer
Turns out the accumulated error is even worse:

Prelude> let old x y z = let eftt i j = i : eftt j (j+j-i) in let d =
y - x in maximum $ takeWhile (<= z + d) $ eftt x y
Prelude> old 0.0 0.1 86400.0
86400.005062
Prelude> let new x y z = let d = y - x in let go i = i : go (i + d) in
maximum $ takeWhile (<= z + d) $ go x
Prelude> new 0.0 0.1 86400.0
86400.0054126

Sorry to spam the list. :-P Floating point is hard.

On Tue, Aug 9, 2016 at 8:22 PM, Andrew Farmer  wrote:
> Noticed this today:
>
> ghci> let xs = [0.0,0.1 .. 86400.0] in maximum xs
> 86400.005062
>
> enumFromThenTo is implemented by numericEnumFromThenTo:
>
> https://github.com/ghc/ghc/blob/a90085bd45239fffd65c01c24752a9bbcef346f1/libraries/base/GHC/Real.hs#L227
>
> Which probably accumulates error in numericEnumFromThen with the (m+m-n):
>
> numericEnumFromThen n m = n `seq` m `seq` (n : numericEnumFromThen m (m+m-n))
>
> Why not define numericEnumFromThen as:
>
> numericEnumFromThen n m = let d = m - n in d `seq` go d n
> where go delta x = x `seq` (x : go delta (x + delta))
>
> (or with BangPatterns)
>
> numericEnumFromThen n m = go (m - n) n
> where go !delta !x = x : go delta (x + delta)
>
> Seems like we'd save a lot of subtractions by using the worker function.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


enumFromThenTo for Doubles

2016-08-09 Thread Andrew Farmer
Noticed this today:

ghci> let xs = [0.0,0.1 .. 86400.0] in maximum xs
86400.005062

enumFromThenTo is implemented by numericEnumFromThenTo:

https://github.com/ghc/ghc/blob/a90085bd45239fffd65c01c24752a9bbcef346f1/libraries/base/GHC/Real.hs#L227

Which probably accumulates error in numericEnumFromThen with the (m+m-n):

numericEnumFromThen n m = n `seq` m `seq` (n : numericEnumFromThen m (m+m-n))

Why not define numericEnumFromThen as:

numericEnumFromThen n m = let d = m - n in d `seq` go d n
where go delta x = x `seq` (x : go delta (x + delta))

(or with BangPatterns)

numericEnumFromThen n m = go (m - n) n
where go !delta !x = x : go delta (x + delta)

Seems like we'd save a lot of subtractions by using the worker function.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Ryan Newton
Heh, ok, segfaults themselves are a red herring.  More precisely:

The operational semantics for a SafeIO language should always accurately
model its memory state.  The application should not compute (take a step in
the semantics) in a way that exposes corrupt memory or arbitrary undefined
behavior.  Nor should it violate the memory model.

Moving immediately to the "Terminated" state is fine, whether it be due to
out-of-memory, kill -SEGV, cosmic rays, or hardware failure.  An FFI call
that corrupts memory is bad (may result in arbitrary behavior, not just
termination) as is ptrace'ing.

Naturally, all Unsafe code is part of the TCB, as is the OS and GHC, and
low-level data structure libs and bindings.  It's a big TCB.  Still, it's
something to be able to write an app that doesn't automatically get added
to this TCB just by virtue of being an *app* (main::IO).




On Tue, Aug 9, 2016 at 10:52 PM, Brandon Allbery 
wrote:

> On Tue, Aug 9, 2016 at 4:19 PM, Edward Z. Yang  wrote:
>
>> If you can execute subprocesses, you could always spawn gdb to
>> attach via ptrace() to the parent process and then poke around
>> memory.
>>
>
> Don't even need that if you're just talking segfaults, you can always
> spawn a subprocess "kill -SEGV $PPID" :)
>
> Unless you have full control over all the code that could be run in
> subprocesses, it's not going to be safe much less Safe.
>
> --
> brandon s allbery kf8nh   sine nomine
> associates
> allber...@gmail.com
> ballb...@sinenomine.net
> unix, openafs, kerberos, infrastructure, xmonad
> http://sinenomine.net
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Brandon Allbery
On Tue, Aug 9, 2016 at 4:19 PM, Edward Z. Yang  wrote:

> If you can execute subprocesses, you could always spawn gdb to
> attach via ptrace() to the parent process and then poke around
> memory.
>

Don't even need that if you're just talking segfaults, you can always spawn
a subprocess "kill -SEGV $PPID" :)

Unless you have full control over all the code that could be run in
subprocesses, it's not going to be safe much less Safe.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Ryan Newton
I'm hearing that Safe Haskell is great for pure use cases (lambda bot).
But that doesn't depend on being able to write arbitrary IO code inside the
Safe bubble, does it?  In fact *all* of IO could be outside the safe
boundary for this use case, could it not?  Are there any existing cases
where it is important to be able to build up unsafe IO values inside -XSafe
code?

Edward, why does it seem like a losing proposition?  Are there further
problems that come to mind?  ezyang mentioned the subprocess problem.  I
don't have a strong opinion on that one.  But I tend to think the safe IO
language *should* allow subprocess calls, and its a matter of configuring
your OS to not allow ptrace in that situation.  This would be part of a set
of requirements for how to compile and launch a complete "Safe Haskell"
*program* in order to get a guarantee.

My primary interest is actually not segfault-freedom, per-se, but being
able to define a memory model for Safe Haskell (for which I'd suggest
sequential consistency).  FFI undermines that, and peek/poke seems like it
should cluster with FFI as an unsafe feature.  I'm not inclined to give a
memory model to peek or FFI -- at that level you get what the architecture
gives you -- but I do want a memory model for IORefs, IOVectors, etc.

We're poking at the Stackage package set now to figure out what pressure
point to push on to increase the percentage of Stackage that is Safe.  I'll
be able to say more when we have more data on dependencies and problem
points.  Across all of hackage, Safe Haskell has modest use: of the ~100K
modules on Hackage, ~636 are marked Safe, ~874 trustworthy, and ~118
Unsafe.  It should be easy to check if any of this Safe code is currently
importing "Foreign.*" or using FFI.

My general plea is that we not give the imperative partition of Haskell too
much the short end of the stick [1]. There is oodles of code in IO (or
MonadIO), and probably relatively little in "RIO".  To my knowledge, we
don't have great ways to coin "RIO" newtypes without having to wrap and
reexport rather a lot of IO functions.  Maybe if APIs like MVars or files
were overloaded in a class then GND could do some of the work...

  -Ryan

[1] In safety guarantees, in optimizations, primops, whatever...  For
instance, I find in microbenchmarks that IO code still runs 2X slower than
pure code, even if no IO effects are performed.



On Tue, Aug 9, 2016 at 5:13 PM, Edward Kmett  wrote:

> I've always treated Safe Haskell as "Safe until you allow IO" -- in that
> all 'evil' things get tainted by an IO type that you can't get rid of by
> the usual means. So if you go to run pure Safe Haskell code in say,
> lambdabot, which doesn't give the user a means to execute IO, it can't
> segfault if all of the Trustworthy modules you depend upon actually are
> trustworthy.
>
> Trying to shore up segfault safety under Safe in IO seems like a losing
> proposition.
>
> -Edward
>
> On Mon, Aug 8, 2016 at 1:27 PM, Ryan Newton  wrote:
>
>> We're trying to spend some cycles pushing on Safe Haskell within the
>> stackage packages.  (It's looking like a slog.)
>>
>> But we're running up against some basic questions regarding the core
>> packages and Safe Haskell guarantees.  The manual currently says:
>> 
>>
>>
>> *Functions in the IO monad are still allowed and behave as usual. *
>> As usual?  So it is ok to segfault GHC?  Elsewhere it says "in the safe
>> language you can trust the types", and I'd always assumed that meant Safe
>> Haskell is a type safe language, even in the IO fragment.
>>
>> Was there an explicit decision to allow segfaults and memory corruption?
>> This can happen not just with FFI calls but with uses of Ptrs within
>> Haskell, for example the following:
>>
>>
>> ```
>>
>> {-# LANGUAGE Safe #-}
>>
>> module Main where
>>
>> import Foreign.Marshal.Alloc
>>
>> import Foreign.Storable
>>
>> import Foreign.Ptr
>>
>> import System.Random
>>
>>
>> fn :: Ptr Int -> IO ()
>>
>> fn p = do
>>
>>   -- This is kosher:
>>
>>   poke p 3
>>
>>   print =<< peek p
>>
>>   -- This should crash the system:
>>
>>   ix <- randomIO
>>
>>   pokeElemOff p ix 0xcc
>>
>>
>>
>> main = alloca fn
>>
>> ```
>>
>>
>>   -Ryan
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Edward Kmett
I've always treated Safe Haskell as "Safe until you allow IO" -- in that
all 'evil' things get tainted by an IO type that you can't get rid of by
the usual means. So if you go to run pure Safe Haskell code in say,
lambdabot, which doesn't give the user a means to execute IO, it can't
segfault if all of the Trustworthy modules you depend upon actually are
trustworthy.

Trying to shore up segfault safety under Safe in IO seems like a losing
proposition.

-Edward

On Mon, Aug 8, 2016 at 1:27 PM, Ryan Newton  wrote:

> We're trying to spend some cycles pushing on Safe Haskell within the
> stackage packages.  (It's looking like a slog.)
>
> But we're running up against some basic questions regarding the core
> packages and Safe Haskell guarantees.  The manual currently says:
> 
>
>
> *Functions in the IO monad are still allowed and behave as usual. *
> As usual?  So it is ok to segfault GHC?  Elsewhere it says "in the safe
> language you can trust the types", and I'd always assumed that meant Safe
> Haskell is a type safe language, even in the IO fragment.
>
> Was there an explicit decision to allow segfaults and memory corruption?
> This can happen not just with FFI calls but with uses of Ptrs within
> Haskell, for example the following:
>
>
> ```
>
> {-# LANGUAGE Safe #-}
>
> module Main where
>
> import Foreign.Marshal.Alloc
>
> import Foreign.Storable
>
> import Foreign.Ptr
>
> import System.Random
>
>
> fn :: Ptr Int -> IO ()
>
> fn p = do
>
>   -- This is kosher:
>
>   poke p 3
>
>   print =<< peek p
>
>   -- This should crash the system:
>
>   ix <- randomIO
>
>   pokeElemOff p ix 0xcc
>
>
>
> main = alloca fn
>
> ```
>
>
>   -Ryan
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Edward Z. Yang
If you can execute subprocesses, you could always spawn gdb to
attach via ptrace() to the parent process and then poke around
memory.

Yes this is a "dumb" example but I think it goes to show how
important it is to correctly characterize what the threat model
is.  A "no-segfault" fragment of Haskell doesn't seem so much
as a security feature as it is a "good practices" lint pass.

Edward

Excerpts from Ryan Newton's message of 2016-08-09 10:41:44 -0400:
> On Mon, Aug 8, 2016 at 8:46 PM, Mikhail Glushenkov  glushen...@gmail.com> wrote:
> >
> > Yes, this can be done with JNI, see e.g. [1]. Additionally, by using
> > sun.misc.Unsafe [2], one can cause segfaults even from pure Java.
> > [1] https://www.cs.princeton.edu/~appel/papers/safejni.pdf
> > [2] http://www.inf.usi.ch/faculty/lanza/Downloads/Mast2015a.pdf
> 
> 
> Ah, I see. I thought that, ruling out FFI, that you couldn't segfault with
> pure Java code.  Good to know about the unsafe interface.
> 
> On Mon, Aug 8, 2016 at 7:32 PM, David Terei  wrote:
> >
> > If you have the energy, it'd be great to put some of this thinking
> > into a wiki page (https://ghc.haskell.org/trac/ghc/wiki/SafeHaskell)
> > and flesh out a first approximation of what IO API's cause issues. Is
> > it just Ptr not carrying bounds around with it? Maybe, but then we
> > need to secure how Ptr's can be created, which excludes FFI returning
> > Ptr's.
> >
> 
> Yes, we can add a Wiki page.
> 
> Btw I was thinking more of kicking FFI/peek/poke outside of the Safe
> bubble, not changing their operational behavior.  First of all, it's nigh
> impossible to lock down FFI calls.
> 
> When someone, e.g. Bob Harper
> ,
> points out a problem in Haskell, we sometimes respond "hey, *Safe Haskell*
> is the real objet d'art!  It's a safe language."  Yet it isn't really a
> full *language* if people cannot write and run programs in it!  (Because
> every program must be ultimately be `main::IO()`.)  Kicking out segfaulty
> features would still leave a safe language that people can write complete
> programs in.
> 
> Best,
>   -Ryan
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Fwd: Help on first ticket

2016-08-09 Thread Richard Fung
-- Forwarded message --
From: Richard Fung 
Date: Tue, Aug 9, 2016 at 8:33 AM
Subject: Re: Help on first ticket
To: Simon Peyton Jones 


It's been a while but I've been able to spend more time on it recently made
some progress.

I believe I have an idea of what I need to fix in terms of the generating
of ModDetails/ModInfo. First off, please tell me if this is wrong.. it
seems like ModDetails is made in mkBootModDetailsTc and tidyProgram. In
tidyProgram there are several functions which take omit_prags, which I
think is automatically set to True on -O0. These are the things we'll have
to change because they are used in mkIface_ to generate the [IfaceDecl]
used to make ModInfo in addFingerprints.

Hopefully I'm understanding that part correctly. However, I'm not really
sure how to write a proper test case for this ticket. Also, I think I have
an idea of where to start looking for the place the inlining/unfolding
happens but pointers definitely wouldn't hurt.

Thanks and sorry this is taking me so long!

On Fri, Jun 24, 2016 at 12:26 PM, Simon Peyton Jones 
wrote:

> Great.  No rush.  Yell if you need help.
>
>
>
> Simon
>
>
>
> *From:* Richard Fung [mailto:minesasec...@gmail.com]
> *Sent:* 24 June 2016 19:05
> *To:* Simon Peyton Jones 
> *Cc:* ghc-devs@haskell.org
>
> *Subject:* Re: Help on first ticket
>
>
>
> Hi Simon, I am making progress but slowly (I only have time to work on
> this outside of work unfortunately).
>
>
>
> If this needs to be done soon feel free to reassign it to someone else!
> Otherwise, while at times I feel like I'm over my head I would like to keep
> at it.
>
>
>
> On Fri, Jun 24, 2016 at 4:20 AM, Simon Peyton Jones 
> wrote:
>
> Richard, did you get on ok?
>
> Simon
>
>
> |  -Original Message-
> |  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ben
> |  Gamari
> |  Sent: 04 June 2016 23:20
> |  To: Richard Fung ; ghc-devs@haskell.org
> |  Subject: Re: Help on first ticket
> |
> |  Richard Fung  writes:
> |
> |  > Hello! I apologize if this isn't the right place to ask; if it isn't
> |  > please steer me in the right direction.
> |  >
> |  Hi Richard!
> |
> |  > Would anyone be willing to advise me on my first ticket? I've been
> |  > trying to work on it on and off but haven't made much progress on my
> |  own.
> |  >
> |  > It's ticket #9370: https://ghc.haskell.org/trac/ghc/ticket/9370
> |  >
> |  Great, I'm happy to hear that someone has picked this one up. I think
> |  it is a nice choice for a self-contained newcomers project.
> |
> |  > I think I understand the issue conceptually but I don't know where
> |  to
> |  > look for the code that needs to be changed..
> |  >
> |  I don't know where the code responsible for this is off the top of my
> |  head, however I can provide some pointers.
> |
> |  So the unfoldings you are looking to preserve come from interface
> |  files.
> |  The machinery for all of this is in compiler/iface. IfaceSyn.hs is of
> |  particular interest and there you will find the definition of
> |  IfaceUnfolding, which is the unfolding representation which is stored
> |  in the interface file. Unfoldings live inside of IdInfo values, which
> |  hold various miscellaneous information which we need to preserve about
> |  a particular Id (identifier).
> |
> |  There is a somewhat useful comment regarding how IdInfo is treated
> |  above the definition of IfaceIdInfo in IfaceSyn. In particular it
> |  seems that interface files for modules compiled with -O0 will have
> |  their IdInfo fields set to NoInfo. It's not clear what happens when an
> |  interface file is read. However, grepping for NoInfo reveals a use-
> |  site in TcIface.tcIdInfo which looks interesting (in particular the
> |  ignore_prags guard). I think this should be enough to get you going on
> |  the interface file part of this.
> |
> |  The other part of this ticket is deciding whether to use an unfolding
> |  when considering whether to inline. This will be done in the
> |  simplifier (compiler/simplCore). Grepping for "inline" and "unfold" in
> |  simplCore/Simplify.hs (as well as reading the notes in that file) will
> |  likely be enough to get you started.
> |
> |  Do let me know if you still feel lost or want to discuss this further.
> |  I look forward to hearing how it goes.
> |
> |  Cheers,
> |
> |  - Ben
>
> |  ___
> |  ghc-devs mailing list
> |  ghc-devs@haskell.org
> |  https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h
> |  askell.org
> 
> 

Re: Is Safe Haskell intended to allow segfaults?

2016-08-09 Thread Ryan Newton
On Mon, Aug 8, 2016 at 8:46 PM, Mikhail Glushenkov  wrote:
>
> Yes, this can be done with JNI, see e.g. [1]. Additionally, by using
> sun.misc.Unsafe [2], one can cause segfaults even from pure Java.
> [1] https://www.cs.princeton.edu/~appel/papers/safejni.pdf
> [2] http://www.inf.usi.ch/faculty/lanza/Downloads/Mast2015a.pdf


Ah, I see. I thought that, ruling out FFI, that you couldn't segfault with
pure Java code.  Good to know about the unsafe interface.

On Mon, Aug 8, 2016 at 7:32 PM, David Terei  wrote:
>
> If you have the energy, it'd be great to put some of this thinking
> into a wiki page (https://ghc.haskell.org/trac/ghc/wiki/SafeHaskell)
> and flesh out a first approximation of what IO API's cause issues. Is
> it just Ptr not carrying bounds around with it? Maybe, but then we
> need to secure how Ptr's can be created, which excludes FFI returning
> Ptr's.
>

Yes, we can add a Wiki page.

Btw I was thinking more of kicking FFI/peek/poke outside of the Safe
bubble, not changing their operational behavior.  First of all, it's nigh
impossible to lock down FFI calls.

When someone, e.g. Bob Harper
,
points out a problem in Haskell, we sometimes respond "hey, *Safe Haskell*
is the real objet d'art!  It's a safe language."  Yet it isn't really a
full *language* if people cannot write and run programs in it!  (Because
every program must be ultimately be `main::IO()`.)  Kicking out segfaulty
features would still leave a safe language that people can write complete
programs in.

Best,
  -Ryan
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs