Re: enumFromThenTo for Doubles

2016-08-10 Thread Evan Laforge
Way back when I started with haskell I noticed this, and switched to using
this:

-- | Enumerate an inclusive range.  Uses multiplication instead of
successive
-- addition to avoid loss of precision.
--
-- Also it doesn't require an Enum instance.
range :: (Num a, Ord a) => a -> a -> a -> [a]
range start end step = go 0
where
go i
| step >= 0 && val > end = []
| step < 0 && val < end = []
| otherwise = val : go (i+1)
where val = start + (i*step)

It's always seemed better in every way, except syntax convenience.

Wouldn't any approach with successive addition lose precision?

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/a90085bd45239fffd65c01c24752a9
> bbcef346f1/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
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: enumFromThenTo for Doubles

2016-08-10 Thread Simon Peyton Jones via ghc-devs
Sounds somewhat plausible.  By all means give it a try.

S

-Original Message-
From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Andrew Farmer
Sent: 10 August 2016 04:22
To: ghc-devs@haskell.org
Subject: enumFromThenTo for Doubles

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
https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-devs&data=02%7c01%7csimonpj%40microsoft.com%7c65f112900fb44b7186a408d3c0cd8631%7c72f988bf86f141af91ab2d7cd011db47%7c1%7c0%7c636063961357184976&sdata=Gz0DQ%2fGEUIyfHtmAjdbxpBt3YEnxbpoKKiygnCb%2fhYo%3d
___
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-10 Thread Ryan Newton
Hi Simon,

On Wed, Aug 10, 2016 at 4:24 AM, Simon Marlow https://mail.google.com/mail/?view=cm&fs=1&tf=1&to=marlo...@gmail.com>>
wrote:

> Definining a safe subset of IO is usually  an application-specific
> decision, e.g. do you want to allow access to the filesystem but without
> allowing openFile "/dev/mem"?  It's a minefield.
>

I respect your intuition that this is a "minefield" (and Edward's "big
mess"), but I still want to unpack this further.

I would propose that a MemSafe app is a two-part contract that is half an
OS responsibility and half language/runtime responsibility.

   1. OS: guarantee that all system calls (including file access) from the
   process do not violate the processes memory, outside of certain opt-in DMA
   regions.
   2. Lang/runtime: create a binary "ensuring" that all instructions
   executed in the process maintain the type safety of memory and follow the
   memory model.  (Scare quotes due to large TCB.)

With this division, "/dev/mem" and subprocess/ptrace are definitely the job
of the OS or containerization.  Blame for a bug would fall to category 1.

A MemSafe app needs a launcher/harness to check that category 1 is enforced
properly.  I'm not proposing that GHC needs to generate that.  It should be
separate.

Ryan, if you want to give an operational semantics for memory in IO, why
> not start from the subset of IO that you can accurately model - the basic
> IO structure together with a set of primitives - and define the semantics
> for that?  That's typically what we do when we're talking about something
> in the IO monad.
>

Yes, indeed, that has been the

approach  for
decades (and the same thing you and I do with other monads like Par
).
There's something unsatisfying here though -- we love to build model
languages that include the effects we want to talk about *at that time* --
perhaps just MVars, just putChar, or just STM.  But of course there's a big
leap from these small treatments to GHC, with its multitude of moving
parts.  That's partly why I think SafeHaskell is so great; it's a Full
Language which aims for serious, statically enforced guarantees.

Well, almost a full language ;-).  You can't run programs in it, unless you
*extend* the TCB.  It's kind of like Rust if you were required to use an
"unsafe" block to write main().

Anyway, here's a draft paper that does propose a small model language.  It
adds a memory model to Haskell plus IORefs/STRefs/TVars, and explains how,
when executed on a machine with relaxed TSO memory (store buffers), the IO
writes need to be fenced, but the ST and STM ones don't:

   http://www.cs.indiana.edu/~rrnewton/papers/sc-haskell_draft.pdf

Do we need a memory model?  I concur with David Terei's arguments from 5
years ago
.
Note however, that the implementation in this paper is TSO only.
Implementation on ARM would be a bit different, but the relationship
between IO/ST and IO/STM would stay the same.

Ryan Yates & others, I'm curious if you think the treatment of STM is
satisfactory.  Like ppopp05, we do not model retrying explicitly, and our
goal here is to show the interaction of the different effects.

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


[ANNOUNCE] Hac φ: a Haskell Exchange in Philadelphia, Oct 21–23

2016-08-10 Thread Kenny Foner
Hello Haskellers,


Hac Phi, a yearly weekend of Haskell in Philadelphia, will take place Oct.
21–23, 2016, at the University of Pennsylvania. Hac Phi is a gathering of
hackers and Haskell enthusiasts. Come bring a project you’re working on or
offer to help someone else on a project of theirs. Come give a talk if
you’ve got something to share. Come to learn something new.


What do we mean by a “Haskell Exchange”? Less pressurized than a hackathon,
more informal than a conference, bigger than a meetup – Hac Phi is a
weekend where academics, professionals, and hobbyists can all meet, mingle,
hack on each others’ projects, and generally have a good time. (And it’s
not to be confused with the Haskell eXchange, an entirely different event.)


All the details are on the wiki page ;
please register online

if you’re coming.


We hope to see you there!


—The Hac φ team

Antal Spector-Zabusky

Kenny Foner
___
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-10 Thread Ryan Yates
Hi Ryan,

I have similar concerns with safety and STM.  In particular, lazy
validation allows for execution after inconsistent reads from TVars.  The
obvious problem to avoid is falling into an infinite loop.  As long as
-fno-omit-yields is used (on every module?) and maybe some other conditions
like eventually GC happens, the transaction will be validated and killed
off. But other problems can happen.  Consider a transactional hash table
with an array and some hashes already computed to be inside the array.  If
an execution sees updated hashes, but not the updated array, then using
unsafeRead could lead to a segfault.  I don't think this is completely
obvious, especially when people will reach for STM precisely to avoid this
sort of problem.  I worry about code that abstracts over mutable variables
that work given sequential execution, but could fail with STM.  ByteString
can lead to similar issues.  Data.ByteString.replicate can be asked to
allocate very large pinned data leading to immediate heap overflow.  But if
the request is from an inconsistent view of data it seams the programmer
has already done their due diligence in preventing this from happening!

Anyway, I would like to work toward reasoning about these things more
precisely.

On Wed, Aug 10, 2016 at 10:23 AM, Ryan Newton  wrote:

> Hi Edward,
>
> On Tue, Aug 9, 2016 at 11:58 PM, Edward Kmett  wrote:
>>
>> 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 definitely wouldn't argue for removing it entirely.  But it's good to
> know that there are instances where IO functions get mixed up in safe
> modules.  I'll try to systematically find all of these on hackage, but in
> the meantime do you have a sample list of modules?
>
> My modest starting proposal is marking certain Foreign.* modules as Unsafe
> rather than Trustworthy.  We'll find all the modules affected.  But, again,
> are there any modules you know of offhand that are affected?  They should
> fall into two categories:
>
>1. Safe modules that must become Trustworthy (if they import Foreign
>bits, but don't expose the ability to corrupt memory to the clients of
>their APIs).
>2. Safe modules that must become Unsafe or be split further into
>smaller modules.
>
> Obviously (2) is the biggest source of potential disruption.
>
> I wouldn't ask anyone to accept a patch on GHC until we'd explored these
> impacts pretty thoroughly.
>
> I'd have to cut up too many APIs into too many fine-grained pieces.
>>
>
> Yeah, the module-level business is pretty annoying.  "vector' removed
> ".Safe" modules and no one has gotten around to adding the ".Unsafe".
>
>
>> 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.
>>
>
> Well, *maybe* it is a slippery slope that leads to a full effect system.
> But I'd like to see these issues enumerated.  Does memory safety as a goal
> really involve so many different effects?  Do you think there will be 1, 3,
> 10, or 100 things beyond Foreign.Ptr to worry about?
>
> 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.
>>
>
> Well, sure, I hope we will continue to aim for this as well.  This is
> effectively what we do with our "LVish" Par monad, where we use Safe
> Haskell to ensure users cannot break the effect system in -XSafe code.
>
> Best,
>  -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-10 Thread Ryan Newton
Hi Edward,

On Tue, Aug 9, 2016 at 11:58 PM, Edward Kmett  wrote:
>
> 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 definitely wouldn't argue for removing it entirely.  But it's good to
know that there are instances where IO functions get mixed up in safe
modules.  I'll try to systematically find all of these on hackage, but in
the meantime do you have a sample list of modules?

My modest starting proposal is marking certain Foreign.* modules as Unsafe
rather than Trustworthy.  We'll find all the modules affected.  But, again,
are there any modules you know of offhand that are affected?  They should
fall into two categories:

   1. Safe modules that must become Trustworthy (if they import Foreign
   bits, but don't expose the ability to corrupt memory to the clients of
   their APIs).
   2. Safe modules that must become Unsafe or be split further into smaller
   modules.

Obviously (2) is the biggest source of potential disruption.

I wouldn't ask anyone to accept a patch on GHC until we'd explored these
impacts pretty thoroughly.

I'd have to cut up too many APIs into too many fine-grained pieces.
>

Yeah, the module-level business is pretty annoying.  "vector' removed
".Safe" modules and no one has gotten around to adding the ".Unsafe".


> 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.
>

Well, *maybe* it is a slippery slope that leads to a full effect system.
But I'd like to see these issues enumerated.  Does memory safety as a goal
really involve so many different effects?  Do you think there will be 1, 3,
10, or 100 things beyond Foreign.Ptr to worry about?

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.
>

Well, sure, I hope we will continue to aim for this as well.  This is
effectively what we do with our "LVish" Par monad, where we use Safe
Haskell to ensure users cannot break the effect system in -XSafe code.

Best,
 -Ryan
___
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-10 Thread Simon Marlow
Right - Safe Haskell provides the minimum that you need to be able to
safely run untrusted code: the ability to trust the type system and the
module system.  Definining a safe subset of IO is usually  an
application-specific decision, e.g. do you want to allow access to the
filesystem but without allowing openFile "/dev/mem"?  It's a minefield.

Ryan, if you want to give an operational semantics for memory in IO, why
not start from the subset of IO that you can accurately model - the basic
IO structure together with a set of primitives - and define the semantics
for that?  That's typically what we do when we're talking about something
in the IO monad.

Cheers
Simon


On 10 August 2016 at 04:58, Edward Kmett  wrote:

> 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 tha