From ekmett at gmail.com Mon Dec 3 00:15:39 2018 From: ekmett at gmail.com (Edward Kmett) Date: Sun, 2 Dec 2018 19:15:39 -0500 Subject: TestEquality for references Message-ID: I'd like to propose adding a bunch of instances for TestEquality and TestCoercion to base and primitive types such as: IORef, STRef s, MVar as well as MutVar and any appropriately uncoercible array types we have in primitive. With these you can learn about the equality of the types of elements of an STRef when you go to testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) I've been using an ad hoc versions of this on my own for some time, across a wide array of packages, based on Atze van der Ploeg's paper: https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness that I get back in turn. =/ With this the notion of a "Key" introduced there can be safely modeled with an STRef s (Proxy a). This would make it {-# LANGUAGE Safe #-} for users to construct heterogeneous container types that don't need Typeable information about the values. Implementation wise, these can either use the value equality of those underlying primitive types and then produce a witness either by unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce the witness in a type-safe manner, giving us well typed core all the way down. -Edward -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Dec 3 00:55:21 2018 From: david.feuer at gmail.com (David Feuer) Date: Sun, 2 Dec 2018 19:55:21 -0500 Subject: TestEquality for references In-Reply-To: References: Message-ID: Unfortunately, testEquality for STRef is not at all safe, for reasons we've previously discussed in another context. testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) let x = [1, 2] foo :: STRef s [Int] <- newSTRef x let bar :: STRef s (ZipList Int) = coerce foo case testEquality foo bar of UH-OH I suspect testCoercion actually will work here. You could patch up the problem by giving STRef (and perhaps MutVar#) a stricter role signature: type role STRef nominal nominal That might not break enough code to worry about; I'm not sure. On Sun, Dec 2, 2018, 7:16 PM Edward Kmett I'd like to propose adding a bunch of instances for TestEquality and > TestCoercion to base and primitive types such as: IORef, STRef s, MVar as > well as MutVar and any appropriately uncoercible array types we have in > primitive. > > With these you can learn about the equality of the types of elements of an > STRef when you go to > > testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) > > I've been using an ad hoc versions of this on my own for some time, across > a wide array of packages, based on Atze van der Ploeg's paper: > https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by > unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness > that I get back in turn. =/ > > With this the notion of a "Key" introduced there can be safely modeled > with an STRef s (Proxy a). > > This would make it {-# LANGUAGE Safe #-} for users to construct > heterogeneous container types that don't need Typeable information about > the values. > > Implementation wise, these can either use the value equality of those > underlying primitive types and then produce a witness either by > unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce > the witness in a type-safe manner, giving us well typed core all the way > down. > > -Edward > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Mon Dec 3 01:04:23 2018 From: ekmett at gmail.com (Edward Kmett) Date: Sun, 2 Dec 2018 20:04:23 -0500 Subject: TestEquality for references In-Reply-To: References: Message-ID: On Sun, Dec 2, 2018 at 7:55 PM David Feuer wrote: > Unfortunately, testEquality for STRef is not at all safe, for reasons > we've previously discussed in another context. > > testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) > > let x = [1, 2] > foo :: STRef s [Int] <- newSTRef x > let bar :: STRef s (ZipList Int) = coerce foo > case testEquality foo bar of UH-OH > > I suspect testCoercion actually will work here. > > You could patch up the problem by giving STRef (and perhaps MutVar#) a > stricter role signature: > > type role STRef nominal nominal > > That might not break enough code to worry about; I'm not sure. > That is rather unfortunate, as it means most if not all of these would be limited to TestCoercion. -Edward > On Sun, Dec 2, 2018, 7:16 PM Edward Kmett >> I'd like to propose adding a bunch of instances for TestEquality and >> TestCoercion to base and primitive types such as: IORef, STRef s, MVar as >> well as MutVar and any appropriately uncoercible array types we have in >> primitive. >> >> With these you can learn about the equality of the types of elements of >> an STRef when you go to >> >> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >> >> I've been using an ad hoc versions of this on my own for some time, >> across a wide array of packages, based on Atze van der Ploeg's paper: >> https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by >> unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness >> that I get back in turn. =/ >> >> With this the notion of a "Key" introduced there can be safely modeled >> with an STRef s (Proxy a). >> >> This would make it {-# LANGUAGE Safe #-} for users to construct >> heterogeneous container types that don't need Typeable information about >> the values. >> >> Implementation wise, these can either use the value equality of those >> underlying primitive types and then produce a witness either by >> unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce >> the witness in a type-safe manner, giving us well typed core all the way >> down. >> >> -Edward >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at cs.brynmawr.edu Tue Dec 4 03:11:22 2018 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Mon, 3 Dec 2018 19:11:22 -0800 Subject: TestEquality for references In-Reply-To: References: Message-ID: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Why is it unfortunate? This looks like desired behavior to me. That is: I think these reference types should allow coercions between representationally equal types. Of course, that means that TestEquality is out. Richard > On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: > > On Sun, Dec 2, 2018 at 7:55 PM David Feuer > wrote: > Unfortunately, testEquality for STRef is not at all safe, for reasons we've previously discussed in another context. > > testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) > > let x = [1, 2] > foo :: STRef s [Int] <- newSTRef x > let bar :: STRef s (ZipList Int) = coerce foo > case testEquality foo bar of UH-OH > > I suspect testCoercion actually will work here. > > You could patch up the problem by giving STRef (and perhaps MutVar#) a stricter role signature: > > type role STRef nominal nominal > > That might not break enough code to worry about; I'm not sure. > > That is rather unfortunate, as it means most if not all of these would be limited to TestCoercion. > > -Edward > > > On Sun, Dec 2, 2018, 7:16 PM Edward Kmett wrote: > I'd like to propose adding a bunch of instances for TestEquality and TestCoercion to base and primitive types such as: IORef, STRef s, MVar as well as MutVar and any appropriately uncoercible array types we have in primitive. > > With these you can learn about the equality of the types of elements of an STRef when you go to > > testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) > > I've been using an ad hoc versions of this on my own for some time, across a wide array of packages, based on Atze van der Ploeg's paper: https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness that I get back in turn. =/ > > With this the notion of a "Key" introduced there can be safely modeled with an STRef s (Proxy a). > > This would make it {-# LANGUAGE Safe #-} for users to construct heterogeneous container types that don't need Typeable information about the values. > > Implementation wise, these can either use the value equality of those underlying primitive types and then produce a witness either by unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce the witness in a type-safe manner, giving us well typed core all the way down. > > -Edward > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Tue Dec 4 05:26:33 2018 From: ekmett at gmail.com (Edward Kmett) Date: Tue, 4 Dec 2018 00:26:33 -0500 Subject: TestEquality for references In-Reply-To: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> References: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Message-ID: Mostly because it means I wind up needing another construction to make it all go and can't just kick it all upstream. ;) -Edward On Mon, Dec 3, 2018 at 10:11 PM Richard Eisenberg wrote: > Why is it unfortunate? This looks like desired behavior to me. That is: I > think these reference types should allow coercions between > representationally equal types. Of course, that means that TestEquality is > out. > > Richard > > On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: > > On Sun, Dec 2, 2018 at 7:55 PM David Feuer wrote: > >> Unfortunately, testEquality for STRef is not at all safe, for reasons >> we've previously discussed in another context. >> >> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >> >> let x = [1, 2] >> foo :: STRef s [Int] <- newSTRef x >> let bar :: STRef s (ZipList Int) = coerce foo >> case testEquality foo bar of UH-OH >> >> I suspect testCoercion actually will work here. >> >> You could patch up the problem by giving STRef (and perhaps MutVar#) a >> stricter role signature: >> >> type role STRef nominal nominal >> >> That might not break enough code to worry about; I'm not sure. >> > > That is rather unfortunate, as it means most if not all of these would be > limited to TestCoercion. > > -Edward > > > >> On Sun, Dec 2, 2018, 7:16 PM Edward Kmett > >>> I'd like to propose adding a bunch of instances for TestEquality and >>> TestCoercion to base and primitive types such as: IORef, STRef s, MVar as >>> well as MutVar and any appropriately uncoercible array types we have in >>> primitive. >>> >>> With these you can learn about the equality of the types of elements of >>> an STRef when you go to >>> >>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>> >>> I've been using an ad hoc versions of this on my own for some time, >>> across a wide array of packages, based on Atze van der Ploeg's paper: >>> https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by >>> unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness >>> that I get back in turn. =/ >>> >>> With this the notion of a "Key" introduced there can be safely modeled >>> with an STRef s (Proxy a). >>> >>> This would make it {-# LANGUAGE Safe #-} for users to construct >>> heterogeneous container types that don't need Typeable information about >>> the values. >>> >>> Implementation wise, these can either use the value equality of those >>> underlying primitive types and then produce a witness either by >>> unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce >>> the witness in a type-safe manner, giving us well typed core all the way >>> down. >>> >>> -Edward >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Tue Dec 4 12:46:38 2018 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Tue, 4 Dec 2018 07:46:38 -0500 Subject: TestEquality for references In-Reply-To: References: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Message-ID: Given that each comes at the cost of the other, if I had to choose between which of these two STRef features I could have, I would pick being able to use it to recover equality over being able to lift newtype coercions through it. The former is increases expressivity while the latter accomplishes something that is achievable by simply using less newtypes in APIs where the need for this arises (not that I've ever actually needed to coerce an STRef in this way, but it would be interesting to hear from anyone who has needed this). On Tue, Dec 4, 2018 at 12:26 AM Edward Kmett wrote: > Mostly because it means I wind up needing another construction to make it > all go and can't just kick it all upstream. ;) > > -Edward > > On Mon, Dec 3, 2018 at 10:11 PM Richard Eisenberg > wrote: > >> Why is it unfortunate? This looks like desired behavior to me. That is: I >> think these reference types should allow coercions between >> representationally equal types. Of course, that means that TestEquality is >> out. >> >> Richard >> >> On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: >> >> On Sun, Dec 2, 2018 at 7:55 PM David Feuer wrote: >> >>> Unfortunately, testEquality for STRef is not at all safe, for reasons >>> we've previously discussed in another context. >>> >>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>> >>> let x = [1, 2] >>> foo :: STRef s [Int] <- newSTRef x >>> let bar :: STRef s (ZipList Int) = coerce foo >>> case testEquality foo bar of UH-OH >>> >>> I suspect testCoercion actually will work here. >>> >>> You could patch up the problem by giving STRef (and perhaps MutVar#) a >>> stricter role signature: >>> >>> type role STRef nominal nominal >>> >>> That might not break enough code to worry about; I'm not sure. >>> >> >> That is rather unfortunate, as it means most if not all of these would be >> limited to TestCoercion. >> >> -Edward >> >> >> >>> On Sun, Dec 2, 2018, 7:16 PM Edward Kmett >> >>>> I'd like to propose adding a bunch of instances for TestEquality and >>>> TestCoercion to base and primitive types such as: IORef, STRef s, MVar as >>>> well as MutVar and any appropriately uncoercible array types we have in >>>> primitive. >>>> >>>> With these you can learn about the equality of the types of elements of >>>> an STRef when you go to >>>> >>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>> >>>> I've been using an ad hoc versions of this on my own for some time, >>>> across a wide array of packages, based on Atze van der Ploeg's paper: >>>> https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by >>>> unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness >>>> that I get back in turn. =/ >>>> >>>> With this the notion of a "Key" introduced there can be safely modeled >>>> with an STRef s (Proxy a). >>>> >>>> This would make it {-# LANGUAGE Safe #-} for users to construct >>>> heterogeneous container types that don't need Typeable information about >>>> the values. >>>> >>>> Implementation wise, these can either use the value equality of those >>>> underlying primitive types and then produce a witness either by >>>> unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce >>>> the witness in a type-safe manner, giving us well typed core all the way >>>> down. >>>> >>>> -Edward >>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >>> >> _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Tue Dec 4 13:23:46 2018 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Tue, 4 Dec 2018 08:23:46 -0500 Subject: Safe FFI and Blocking IO Message-ID: According to the FFI chapter [1] in the GHC manual, the safe FFI is useful when you need to call a C function that can call back into haskell code. I had always assumed that the scheduler could somehow interrupt safe FFI calls, but the manual does not indicate this, and in some recent testing I did in the posix library [2], I found that scheduling interrupts definitely do not happen. With the non-threaded runtime, the following test always hangs: testSocketsD :: IO () testSocketsD = do (a,b) <- demand =<< S.socketPair P.unix P.datagram P.defaultProtocol _ <- forkIO $ do bytesSent <- demand =<< S.sendByteArray b sample 0 5 mempty when (bytesSent /= 5) (fail "testSocketsD: bytesSent was wrong") actual <- demand =<< S.receiveByteArray a 5 mempty actual @=? sample sample :: ByteArray sample = E.fromList [1,2,3,4,5] demand :: Either Errno a -> IO a demand = either (\e -> ioError (errnoToIOError "test" e Nothing Nothing)) pure In the above example, sendByteArray and receiveByteArray are safe FFI wrappers around send and recv. It is necessary to use threadWaitRead and threadWaitWrite before these calls to predictably get the correct behavior. This brings to my question. In issue #34 on the github library for the unix package [3], there is a discussion about whether to use the safe or unsafe FFI for various POSIX system calls. On the issue there is strong consensus that the safe FFI calls lead to better performance. Simon Marlow writes [4] that "Unsafe foreign imports which can block for unpredictable amounts of time cause performance problems that only emerge when scaling to multiple cores, because they delay the GC sync. This is a really annoying problem if it happens to you, because it's almost impossible to diagnose, and if it happens due to an unsafe call in a library then it's also really hard to fix." And Gregory Collins adds that "If the call would ever block (and that includes most filesystem functions) that means you want 'safe'." There's something I'm definitely missing. My experience is that safe FFI calls do not help with blocking IO (again, I've been using the non-threaded runtime, but I doubt this makes a difference), that they only help with C functions that call back into haskell. However, a lot of other people seem to have a difference experience. [1] https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ffi-chap.html#foreign-function-interface-ffi [2] https://github.com/andrewthad/posix [3] https://github.com/haskell/unix/issues/34 [4] https://github.com/haskell/unix/issues/34#issuecomment-68683424 -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Tue Dec 4 13:25:37 2018 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Tue, 4 Dec 2018 08:25:37 -0500 Subject: Safe FFI and Blocking IO In-Reply-To: References: Message-ID: Sorry. I just found the answer to this in the manual: "When you call a foreign imported function that is annotated as safe (the default), and the program was linked using -threaded, then the call will run concurrently with other running Haskell threads. If the program was linked without -threaded, then the other Haskell threads will be blocked until the call returns." "This means that if you need to make a foreign call to a function that takes a long time or blocks indefinitely, then you should mark it safe and use -threaded. Some library functions make such calls internally; their documentation should indicate when this is the case." On Tue, Dec 4, 2018 at 8:23 AM Andrew Martin wrote: > According to the FFI chapter [1] in the GHC manual, the safe FFI is useful > when you need to call a C function that can call back into haskell code. I > had always assumed that the scheduler could somehow interrupt safe FFI > calls, but the manual does not indicate this, and in some recent testing I > did in the posix library [2], I found that scheduling interrupts definitely > do not happen. With the non-threaded runtime, the following test always > hangs: > > testSocketsD :: IO () > testSocketsD = do > (a,b) <- demand =<< S.socketPair P.unix P.datagram P.defaultProtocol > _ <- forkIO $ do > bytesSent <- demand =<< S.sendByteArray b sample 0 5 mempty > when (bytesSent /= 5) (fail "testSocketsD: bytesSent was wrong") > actual <- demand =<< S.receiveByteArray a 5 mempty > actual @=? sample > > sample :: ByteArray > sample = E.fromList [1,2,3,4,5] > > demand :: Either Errno a -> IO a > demand = either (\e -> ioError (errnoToIOError "test" e Nothing > Nothing)) pure > > In the above example, sendByteArray and receiveByteArray are safe FFI > wrappers around send and recv. It is necessary to use threadWaitRead and > threadWaitWrite before these calls to predictably get the correct behavior. > > This brings to my question. In issue #34 on the github library for the > unix package [3], there is a discussion about whether to use the safe or > unsafe FFI for various POSIX system calls. On the issue there is strong > consensus that the safe FFI calls lead to better performance. > > Simon Marlow writes [4] that "Unsafe foreign imports which can block for > unpredictable amounts of time cause performance problems that only emerge > when scaling to multiple cores, because they delay the GC sync. This is a > really annoying problem if it happens to you, because it's almost > impossible to diagnose, and if it happens due to an unsafe call in a > library then it's also really hard to fix." > > And Gregory Collins adds that "If the call would ever block (and that > includes most filesystem functions) that means you want 'safe'." > > There's something I'm definitely missing. My experience is that safe FFI > calls do not help with blocking IO (again, I've been using the non-threaded > runtime, but I doubt this makes a difference), that they only help with C > functions that call back into haskell. However, a lot of other people seem > to have a difference experience. > > [1] > https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ffi-chap.html#foreign-function-interface-ffi > [2] https://github.com/andrewthad/posix > [3] https://github.com/haskell/unix/issues/34 > [4] https://github.com/haskell/unix/issues/34#issuecomment-68683424 > > -- > -Andrew Thaddeus Martin > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Tue Dec 4 14:58:33 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 4 Dec 2018 09:58:33 -0500 Subject: Safe FFI and Blocking IO In-Reply-To: References: Message-ID: yup! (this is also kinda related to how the IO manager only runs on -threaded built applications) I actually do the following pattern in some libraries i've written: bind both unsafe and safe versions of a functions, and when work input is below some size that i think will be less than ~ 1-10 microseconds, i do an unsafe call, otherwise i do a safe call! (unsafe calls block the GC, which is bad in say a server app, as you can well guess) the most recent and tiny example of this is a tiny sha3 implementation (still need to tweak it, i think i left another 4-6x performance on the table https://hackage.haskell.org/package/SecureHash-SHA3) On Tue, Dec 4, 2018 at 8:26 AM Andrew Martin wrote: > Sorry. I just found the answer to this in the manual: > > "When you call a foreign imported function that is annotated as safe (the > default), and the program was linked using -threaded, then the call will > run concurrently with other running Haskell threads. If the program was > linked without -threaded, then the other Haskell threads will be blocked > until the call returns." > > "This means that if you need to make a foreign call to a function that > takes a long time or blocks indefinitely, then you should mark it safe and > use -threaded. Some library functions make such calls internally; their > documentation should indicate when this is the case." > > > > On Tue, Dec 4, 2018 at 8:23 AM Andrew Martin > wrote: > >> According to the FFI chapter [1] in the GHC manual, the safe FFI is >> useful when you need to call a C function that can call back into haskell >> code. I had always assumed that the scheduler could somehow interrupt safe >> FFI calls, but the manual does not indicate this, and in some recent >> testing I did in the posix library [2], I found that scheduling interrupts >> definitely do not happen. With the non-threaded runtime, the following test >> always hangs: >> >> testSocketsD :: IO () >> testSocketsD = do >> (a,b) <- demand =<< S.socketPair P.unix P.datagram P.defaultProtocol >> _ <- forkIO $ do >> bytesSent <- demand =<< S.sendByteArray b sample 0 5 mempty >> when (bytesSent /= 5) (fail "testSocketsD: bytesSent was wrong") >> actual <- demand =<< S.receiveByteArray a 5 mempty >> actual @=? sample >> >> sample :: ByteArray >> sample = E.fromList [1,2,3,4,5] >> >> demand :: Either Errno a -> IO a >> demand = either (\e -> ioError (errnoToIOError "test" e Nothing >> Nothing)) pure >> >> In the above example, sendByteArray and receiveByteArray are safe FFI >> wrappers around send and recv. It is necessary to use threadWaitRead and >> threadWaitWrite before these calls to predictably get the correct behavior. >> >> This brings to my question. In issue #34 on the github library for the >> unix package [3], there is a discussion about whether to use the safe or >> unsafe FFI for various POSIX system calls. On the issue there is strong >> consensus that the safe FFI calls lead to better performance. >> >> Simon Marlow writes [4] that "Unsafe foreign imports which can block for >> unpredictable amounts of time cause performance problems that only emerge >> when scaling to multiple cores, because they delay the GC sync. This is a >> really annoying problem if it happens to you, because it's almost >> impossible to diagnose, and if it happens due to an unsafe call in a >> library then it's also really hard to fix." >> >> And Gregory Collins adds that "If the call would ever block (and that >> includes most filesystem functions) that means you want 'safe'." >> >> There's something I'm definitely missing. My experience is that safe FFI >> calls do not help with blocking IO (again, I've been using the non-threaded >> runtime, but I doubt this makes a difference), that they only help with C >> functions that call back into haskell. However, a lot of other people seem >> to have a difference experience. >> >> [1] >> https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ffi-chap.html#foreign-function-interface-ffi >> [2] https://github.com/andrewthad/posix >> [3] https://github.com/haskell/unix/issues/34 >> [4] https://github.com/haskell/unix/issues/34#issuecomment-68683424 >> >> -- >> -Andrew Thaddeus Martin >> > > > -- > -Andrew Thaddeus Martin > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Tue Dec 4 18:08:11 2018 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Tue, 4 Dec 2018 13:08:11 -0500 Subject: Safe FFI and Blocking IO In-Reply-To: References: Message-ID: What's your heuristic for deciding between safe and interruptible? I find that every time something takes long enough to warrant using the safe FFI, I also want to be able to kill it from a separate thread. On Tue, Dec 4, 2018 at 9:58 AM Carter Schonwald wrote: > yup! (this is also kinda related to how the IO manager only runs on > -threaded built applications) > > I actually do the following pattern in some libraries i've written: bind > both unsafe and safe versions of a functions, and when work input is below > some size that i think will be less than ~ 1-10 microseconds, i do an > unsafe call, otherwise i do a safe call! (unsafe calls block the GC, which > is bad in say a server app, as you can well guess) > > the most recent and tiny example of this is a tiny sha3 implementation > (still need to tweak it, i think i left another 4-6x performance on the > table https://hackage.haskell.org/package/SecureHash-SHA3) > > On Tue, Dec 4, 2018 at 8:26 AM Andrew Martin > wrote: > >> Sorry. I just found the answer to this in the manual: >> >> "When you call a foreign imported function that is annotated as safe (the >> default), and the program was linked using -threaded, then the call will >> run concurrently with other running Haskell threads. If the program was >> linked without -threaded, then the other Haskell threads will be blocked >> until the call returns." >> >> "This means that if you need to make a foreign call to a function that >> takes a long time or blocks indefinitely, then you should mark it safe and >> use -threaded. Some library functions make such calls internally; their >> documentation should indicate when this is the case." >> >> >> >> On Tue, Dec 4, 2018 at 8:23 AM Andrew Martin >> wrote: >> >>> According to the FFI chapter [1] in the GHC manual, the safe FFI is >>> useful when you need to call a C function that can call back into haskell >>> code. I had always assumed that the scheduler could somehow interrupt safe >>> FFI calls, but the manual does not indicate this, and in some recent >>> testing I did in the posix library [2], I found that scheduling interrupts >>> definitely do not happen. With the non-threaded runtime, the following test >>> always hangs: >>> >>> testSocketsD :: IO () >>> testSocketsD = do >>> (a,b) <- demand =<< S.socketPair P.unix P.datagram >>> P.defaultProtocol >>> _ <- forkIO $ do >>> bytesSent <- demand =<< S.sendByteArray b sample 0 5 mempty >>> when (bytesSent /= 5) (fail "testSocketsD: bytesSent was wrong") >>> actual <- demand =<< S.receiveByteArray a 5 mempty >>> actual @=? sample >>> >>> sample :: ByteArray >>> sample = E.fromList [1,2,3,4,5] >>> >>> demand :: Either Errno a -> IO a >>> demand = either (\e -> ioError (errnoToIOError "test" e Nothing >>> Nothing)) pure >>> >>> In the above example, sendByteArray and receiveByteArray are safe FFI >>> wrappers around send and recv. It is necessary to use threadWaitRead and >>> threadWaitWrite before these calls to predictably get the correct behavior. >>> >>> This brings to my question. In issue #34 on the github library for the >>> unix package [3], there is a discussion about whether to use the safe or >>> unsafe FFI for various POSIX system calls. On the issue there is strong >>> consensus that the safe FFI calls lead to better performance. >>> >>> Simon Marlow writes [4] that "Unsafe foreign imports which can block for >>> unpredictable amounts of time cause performance problems that only emerge >>> when scaling to multiple cores, because they delay the GC sync. This is a >>> really annoying problem if it happens to you, because it's almost >>> impossible to diagnose, and if it happens due to an unsafe call in a >>> library then it's also really hard to fix." >>> >>> And Gregory Collins adds that "If the call would ever block (and that >>> includes most filesystem functions) that means you want 'safe'." >>> >>> There's something I'm definitely missing. My experience is that safe FFI >>> calls do not help with blocking IO (again, I've been using the non-threaded >>> runtime, but I doubt this makes a difference), that they only help with C >>> functions that call back into haskell. However, a lot of other people seem >>> to have a difference experience. >>> >>> [1] >>> https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ffi-chap.html#foreign-function-interface-ffi >>> [2] https://github.com/andrewthad/posix >>> [3] https://github.com/haskell/unix/issues/34 >>> [4] https://github.com/haskell/unix/issues/34#issuecomment-68683424 >>> >>> -- >>> -Andrew Thaddeus Martin >>> >> >> >> -- >> -Andrew Thaddeus Martin >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Tue Dec 4 18:31:31 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 4 Dec 2018 13:31:31 -0500 Subject: Safe FFI and Blocking IO In-Reply-To: References: Message-ID: i only do unsafe vs safe ffi, most things i do i make sure that a c call running to completion (and associated system calls) dont prevent other work from happening. Interrupts can require resource cleanup. what sort of examples do you have in mind? you *could* do interruptable in lieu of safe as long as you have some way to cleanup memory allocations i guess? https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ffi-chap.html#interruptible-foreign-calls to quote the documentation " interruptible behaves exactly as safe, except that when a throwTo is directed at a thread in an interruptible foreign call, an OS-specific mechanism will be used to attempt to cause the foreign call to return: Unix systemsThe thread making the foreign call is sent a SIGPIPE signal using pthread_kill(). This is usually enough to cause a blocking system call to return with EINTR (GHC by default installs an empty signal handler for SIGPIPE, to override the default behaviour which is to terminate the process immediately).Windows systems[Vista and later only] The RTS calls the Win32 function CancelSynchronousIo, which will cause a blocking I/O operation to return with the error ERROR_OPERATION_ABORTED. " i dont know if the cffi overheads differ when doing an interruptable call, and you really do have to think carefully about state cleanup... I like avoiding needing to do state cleanup personally. if you mean to ask about SAFE vs UNSAFE, its mostly about often the code i'm binding has VERY predictable complexity / runtime behavior as a function of input size, and i choose an input size threshold thats more than ~ 1 microsecond and less than 10 microseconds. smaller stuff gets unsafe and larger gets safe. Last time i measure stuff years ago, safe ffi calls had ~ 200 nanosecond overhead on the applicable laptop, so as long as youre not doing scribbles to unpinned memory, you should always always use the SAFE ffi for operations that will likely take >= 1-10 microseconds ALWAYS. (theres lots of math C code on hackage which does unsafe FFI and yet the input sizes of interest will likely take several second to compute, a nasty combo in a server/networked env). tl;dr any network api / file system api, pretty safe to do safe api calls always, afaik few to none of those are sub microsecond, heck just a memory read from ram is 5-10 microseconds right? On Tue, Dec 4, 2018 at 1:08 PM Andrew Martin wrote: > What's your heuristic for deciding between safe and interruptible? I find > that every time something takes long enough to warrant using the safe FFI, > I also want to be able to kill it from a separate thread. > > On Tue, Dec 4, 2018 at 9:58 AM Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> yup! (this is also kinda related to how the IO manager only runs on >> -threaded built applications) >> >> I actually do the following pattern in some libraries i've written: bind >> both unsafe and safe versions of a functions, and when work input is below >> some size that i think will be less than ~ 1-10 microseconds, i do an >> unsafe call, otherwise i do a safe call! (unsafe calls block the GC, which >> is bad in say a server app, as you can well guess) >> >> the most recent and tiny example of this is a tiny sha3 implementation >> (still need to tweak it, i think i left another 4-6x performance on the >> table https://hackage.haskell.org/package/SecureHash-SHA3) >> >> On Tue, Dec 4, 2018 at 8:26 AM Andrew Martin >> wrote: >> >>> Sorry. I just found the answer to this in the manual: >>> >>> "When you call a foreign imported function that is annotated as safe >>> (the default), and the program was linked using -threaded, then the call >>> will run concurrently with other running Haskell threads. If the program >>> was linked without -threaded, then the other Haskell threads will be >>> blocked until the call returns." >>> >>> "This means that if you need to make a foreign call to a function that >>> takes a long time or blocks indefinitely, then you should mark it safe and >>> use -threaded. Some library functions make such calls internally; their >>> documentation should indicate when this is the case." >>> >>> >>> >>> On Tue, Dec 4, 2018 at 8:23 AM Andrew Martin >>> wrote: >>> >>>> According to the FFI chapter [1] in the GHC manual, the safe FFI is >>>> useful when you need to call a C function that can call back into haskell >>>> code. I had always assumed that the scheduler could somehow interrupt safe >>>> FFI calls, but the manual does not indicate this, and in some recent >>>> testing I did in the posix library [2], I found that scheduling interrupts >>>> definitely do not happen. With the non-threaded runtime, the following test >>>> always hangs: >>>> >>>> testSocketsD :: IO () >>>> testSocketsD = do >>>> (a,b) <- demand =<< S.socketPair P.unix P.datagram >>>> P.defaultProtocol >>>> _ <- forkIO $ do >>>> bytesSent <- demand =<< S.sendByteArray b sample 0 5 mempty >>>> when (bytesSent /= 5) (fail "testSocketsD: bytesSent was wrong") >>>> actual <- demand =<< S.receiveByteArray a 5 mempty >>>> actual @=? sample >>>> >>>> sample :: ByteArray >>>> sample = E.fromList [1,2,3,4,5] >>>> >>>> demand :: Either Errno a -> IO a >>>> demand = either (\e -> ioError (errnoToIOError "test" e Nothing >>>> Nothing)) pure >>>> >>>> In the above example, sendByteArray and receiveByteArray are safe FFI >>>> wrappers around send and recv. It is necessary to use threadWaitRead and >>>> threadWaitWrite before these calls to predictably get the correct behavior. >>>> >>>> This brings to my question. In issue #34 on the github library for the >>>> unix package [3], there is a discussion about whether to use the safe or >>>> unsafe FFI for various POSIX system calls. On the issue there is strong >>>> consensus that the safe FFI calls lead to better performance. >>>> >>>> Simon Marlow writes [4] that "Unsafe foreign imports which can block >>>> for unpredictable amounts of time cause performance problems that only >>>> emerge when scaling to multiple cores, because they delay the GC sync. This >>>> is a really annoying problem if it happens to you, because it's almost >>>> impossible to diagnose, and if it happens due to an unsafe call in a >>>> library then it's also really hard to fix." >>>> >>>> And Gregory Collins adds that "If the call would ever block (and that >>>> includes most filesystem functions) that means you want 'safe'." >>>> >>>> There's something I'm definitely missing. My experience is that safe >>>> FFI calls do not help with blocking IO (again, I've been using the >>>> non-threaded runtime, but I doubt this makes a difference), that they only >>>> help with C functions that call back into haskell. However, a lot of other >>>> people seem to have a difference experience. >>>> >>>> [1] >>>> https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ffi-chap.html#foreign-function-interface-ffi >>>> [2] https://github.com/andrewthad/posix >>>> [3] https://github.com/haskell/unix/issues/34 >>>> [4] https://github.com/haskell/unix/issues/34#issuecomment-68683424 >>>> >>>> -- >>>> -Andrew Thaddeus Martin >>>> >>> >>> >>> -- >>> -Andrew Thaddeus Martin >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >> > > -- > -Andrew Thaddeus Martin > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at nh2.me Tue Dec 4 19:07:22 2018 From: mail at nh2.me (=?UTF-8?Q?Niklas_Hamb=c3=bcchen?=) Date: Tue, 4 Dec 2018 20:07:22 +0100 Subject: Safe FFI and Blocking IO In-Reply-To: References: Message-ID: <08382bb8-5a00-279f-f736-1a4bee2daf52@nh2.me> Hello Andrew, I have done some work on interruptibility and accidental blocking in GHC and Unix over the last 2 years with FP Complete for our clients. Summarising from what was already written/linked, the key things to understand are: * `safe` calls run in a separate OS thread in -threaded, so they protect from any blocking. * The separate threads spawned by `safe` calls do not count to the +RTS -N limit. * `unsafe` calls block the entire capability, always (e.g. 1 out of 4 +RTS -N4 threads). * There is only one way to interrupt running system calls on Unix: Sending the thread that does them a signal. The syscalls then return an error and `errno = EINTR`. Many (but not all) syscalls can be interrupted that way. * `interruptible` is thus implemented by sending a signal to the thread that does the syscall. * That happens in particular when you send an exception via `throwTo` to a Haskell thread that's blocked in a foreign call (for example, `timeout` uses `throwTo`). * You can only use `interruptible` on FFI code that is written on purpose to return back to Haskell when EINTR is encountered, so that Haskell can then raise the exception. If the code doesn't do that, but instead just retries the syscall in C, then there's no point in using `interruptible`, as it won't have any effect. Important for non-threaded is: * In non`-threaded`, behaviour varies a lot across platforms. * On Linux it really has only a single thread. Some things happen to be more interruptible on Linux because the timer signal wakes up all kinds of syscalls regularly, so most things work like `interruptible` is implemented on Linux. * On e.g. OSX, non-threaded actually uses threads, namely 2: One for the timer signal, and one for the Haskell stuff. * These differences make it very difficult to expect similar behaviour from the non-threaded runtime across platforms. * I have an open proposal + half-done implementation to make non-threaded on Linux work like it does on OSX to unify these things. https://phabricator.haskell.org/D42#128355 The key rules are: * Do not use `unsafe` on anything that can block on non-CPU-bound tasks, ever. It will massively limit the ability to use multiple cores. * Use `unsafe` only for CPU-bound activities. * For all other things, `interruptible` is the best of all, but as mentioned above, the called code must be designed do return EINTR all the way up to Haskell. * Where this is not the case and you thus can't use `interruptible`, use `safe`. The `unix` package unfortunately uses `unsafe` calls in many places where it really shouldn't, such as `stat()` (see the ticket you linked). I think this is very bad and we must fix it. For some of my own tools (like a parallel file-copy tool designed to work well on network file systems), I use a fork of the package where everything uses `safe`. For many details on these topics, check out the tickets I filed / worked on: * https://ghc.haskell.org/trac/ghc/ticket/8684 - hWaitForInput cannot be interrupted by async exceptions on unix * https://ghc.haskell.org/trac/ghc/ticket/13497 - GHC does not use select()/poll() correctly on non-Linux platforms * https://ghc.haskell.org/trac/ghc/ticket/15153 - GHC uses O_NONBLOCK on regular files, which has no effect, and blocks the runtime Also happy to answer any questions! Niklas From ekmett at gmail.com Wed Dec 5 01:49:43 2018 From: ekmett at gmail.com (Edward Kmett) Date: Tue, 4 Dec 2018 20:49:43 -0500 Subject: TestEquality for references In-Reply-To: References: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Message-ID: You actually would need both types for full generality. Both provide useful power under different circumstances. Another thing I noticed when working on this is that TestEquality is missing TestCoercion as a superclass at present. This means you can't use the latter as merely a weaker TestEquality constraint, but have to plumb both independently. This feels wrong. Everything that can support TestEquality should be able to support TestCoercion. I do at least want the TestCoercion instances. -Edward On Tue, Dec 4, 2018 at 7:46 AM Andrew Martin wrote: > Given that each comes at the cost of the other, if I had to choose between > which of these two STRef features I could have, I would pick being able to > use it to recover equality over being able to lift newtype coercions > through it. The former is increases expressivity while the latter > accomplishes something that is achievable by simply using less newtypes in > APIs where the need for this arises (not that I've ever actually needed to > coerce an STRef in this way, but it would be interesting to hear from > anyone who has needed this). > > On Tue, Dec 4, 2018 at 12:26 AM Edward Kmett wrote: > >> Mostly because it means I wind up needing another construction to make it >> all go and can't just kick it all upstream. ;) >> >> -Edward >> >> On Mon, Dec 3, 2018 at 10:11 PM Richard Eisenberg >> wrote: >> >>> Why is it unfortunate? This looks like desired behavior to me. That is: >>> I think these reference types should allow coercions between >>> representationally equal types. Of course, that means that TestEquality is >>> out. >>> >>> Richard >>> >>> On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: >>> >>> On Sun, Dec 2, 2018 at 7:55 PM David Feuer >>> wrote: >>> >>>> Unfortunately, testEquality for STRef is not at all safe, for reasons >>>> we've previously discussed in another context. >>>> >>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>> >>>> let x = [1, 2] >>>> foo :: STRef s [Int] <- newSTRef x >>>> let bar :: STRef s (ZipList Int) = coerce foo >>>> case testEquality foo bar of UH-OH >>>> >>>> I suspect testCoercion actually will work here. >>>> >>>> You could patch up the problem by giving STRef (and perhaps MutVar#) a >>>> stricter role signature: >>>> >>>> type role STRef nominal nominal >>>> >>>> That might not break enough code to worry about; I'm not sure. >>>> >>> >>> That is rather unfortunate, as it means most if not all of these would >>> be limited to TestCoercion. >>> >>> -Edward >>> >>> >>> >>>> On Sun, Dec 2, 2018, 7:16 PM Edward Kmett >>> >>>>> I'd like to propose adding a bunch of instances for TestEquality and >>>>> TestCoercion to base and primitive types such as: IORef, STRef s, MVar as >>>>> well as MutVar and any appropriately uncoercible array types we have in >>>>> primitive. >>>>> >>>>> With these you can learn about the equality of the types of elements >>>>> of an STRef when you go to >>>>> >>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>> >>>>> I've been using an ad hoc versions of this on my own for some time, >>>>> across a wide array of packages, based on Atze van der Ploeg's paper: >>>>> https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by >>>>> unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness >>>>> that I get back in turn. =/ >>>>> >>>>> With this the notion of a "Key" introduced there can be safely modeled >>>>> with an STRef s (Proxy a). >>>>> >>>>> This would make it {-# LANGUAGE Safe #-} for users to construct >>>>> heterogeneous container types that don't need Typeable information about >>>>> the values. >>>>> >>>>> Implementation wise, these can either use the value equality of those >>>>> underlying primitive types and then produce a witness either by >>>>> unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce >>>>> the witness in a type-safe manner, giving us well typed core all the way >>>>> down. >>>>> >>>>> -Edward >>>>> _______________________________________________ >>>>> Libraries mailing list >>>>> Libraries at haskell.org >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>>> >>> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > > > -- > -Andrew Thaddeus Martin > -------------- next part -------------- An HTML attachment was scrubbed... URL: From zemyla at gmail.com Wed Dec 5 02:07:54 2018 From: zemyla at gmail.com (Zemyla) Date: Tue, 4 Dec 2018 20:07:54 -0600 Subject: TestEquality for references In-Reply-To: References: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Message-ID: I thought of this, but the problem is that Data.Type.Equality is Trustworthy, while Data.Type.Coercion is unsafe. Therefore, you can't define the superclass in a Safe module. The solution to this would be to have Data.Type.Equality export TestCoercion but not testCoercion, and have a a default implementation (with DefaultSignatures) that requires TestEquality and just turns the equality into a coercion. Another option is to include testCoercion, but not Coercion, and use the fact that Coercion is a Category here: toId :: Category p => (a :~: b) -> p a b toId Refl = id And then testCoercion a b = fmap toId $ testEquality a b On Tue, Dec 4, 2018, 19:50 Edward Kmett You actually would need both types for full generality. Both provide > useful power under different circumstances. > > Another thing I noticed when working on this is that TestEquality is > missing TestCoercion as a superclass at present. This means you can't use > the latter as merely a weaker TestEquality constraint, but have to plumb > both independently. This feels wrong. Everything that can support > TestEquality should be able to support TestCoercion. > > I do at least want the TestCoercion instances. > > -Edward > > On Tue, Dec 4, 2018 at 7:46 AM Andrew Martin > wrote: > >> Given that each comes at the cost of the other, if I had to choose >> between which of these two STRef features I could have, I would pick being >> able to use it to recover equality over being able to lift newtype >> coercions through it. The former is increases expressivity while the latter >> accomplishes something that is achievable by simply using less newtypes in >> APIs where the need for this arises (not that I've ever actually needed to >> coerce an STRef in this way, but it would be interesting to hear from >> anyone who has needed this). >> >> On Tue, Dec 4, 2018 at 12:26 AM Edward Kmett wrote: >> >>> Mostly because it means I wind up needing another construction to make >>> it all go and can't just kick it all upstream. ;) >>> >>> -Edward >>> >>> On Mon, Dec 3, 2018 at 10:11 PM Richard Eisenberg >>> wrote: >>> >>>> Why is it unfortunate? This looks like desired behavior to me. That is: >>>> I think these reference types should allow coercions between >>>> representationally equal types. Of course, that means that TestEquality is >>>> out. >>>> >>>> Richard >>>> >>>> On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: >>>> >>>> On Sun, Dec 2, 2018 at 7:55 PM David Feuer >>>> wrote: >>>> >>>>> Unfortunately, testEquality for STRef is not at all safe, for reasons >>>>> we've previously discussed in another context. >>>>> >>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>> >>>>> let x = [1, 2] >>>>> foo :: STRef s [Int] <- newSTRef x >>>>> let bar :: STRef s (ZipList Int) = coerce foo >>>>> case testEquality foo bar of UH-OH >>>>> >>>>> I suspect testCoercion actually will work here. >>>>> >>>>> You could patch up the problem by giving STRef (and perhaps MutVar#) a >>>>> stricter role signature: >>>>> >>>>> type role STRef nominal nominal >>>>> >>>>> That might not break enough code to worry about; I'm not sure. >>>>> >>>> >>>> That is rather unfortunate, as it means most if not all of these would >>>> be limited to TestCoercion. >>>> >>>> -Edward >>>> >>>> >>>> >>>>> On Sun, Dec 2, 2018, 7:16 PM Edward Kmett >>>> >>>>>> I'd like to propose adding a bunch of instances for TestEquality and >>>>>> TestCoercion to base and primitive types such as: IORef, STRef s, MVar as >>>>>> well as MutVar and any appropriately uncoercible array types we have in >>>>>> primitive. >>>>>> >>>>>> With these you can learn about the equality of the types of elements >>>>>> of an STRef when you go to >>>>>> >>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>>> >>>>>> I've been using an ad hoc versions of this on my own for some time, >>>>>> across a wide array of packages, based on Atze van der Ploeg's paper: >>>>>> https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by >>>>>> unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness >>>>>> that I get back in turn. =/ >>>>>> >>>>>> With this the notion of a "Key" introduced there can be safely >>>>>> modeled with an STRef s (Proxy a). >>>>>> >>>>>> This would make it {-# LANGUAGE Safe #-} for users to construct >>>>>> heterogeneous container types that don't need Typeable information about >>>>>> the values. >>>>>> >>>>>> Implementation wise, these can either use the value equality of those >>>>>> underlying primitive types and then produce a witness either by >>>>>> unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce >>>>>> the witness in a type-safe manner, giving us well typed core all the way >>>>>> down. >>>>>> >>>>>> -Edward >>>>>> _______________________________________________ >>>>>> Libraries mailing list >>>>>> Libraries at haskell.org >>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>> >>>>> >>>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >> >> >> -- >> -Andrew Thaddeus Martin >> > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Wed Dec 5 05:22:07 2018 From: ekmett at gmail.com (Edward Kmett) Date: Wed, 5 Dec 2018 00:22:07 -0500 Subject: TestEquality for references In-Reply-To: References: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Message-ID: I could live with that solution pretty well. Getting the default implementation would be a very nice bonus, as in most cases it is quite repetitive. Observation: In the second scenario is it really that exporting Coercion actually dangerous? Not in the sense that we should revisit the stance, but rather it seems that the things it exports that can actually use Coercible to coerce that are the problem point. Without coerce or coerceWith, everything in Data.Type.Coercion seems perfectly Trustworthy. We should just be able to split off the Trustworthy parts of Data.Type.Coercion via an Internal module and use them to put the superclass in place. Even gcoerceWith requires you to have access to coerce to do anything with it other than manipulate Coercible instances. The whole module is currently unsafe because of *one* combinator in it. GHC is even smart enough that you don't need `coerce` to implement sym, trans, etc. so `coerce` and `coerceWith` aren't even used when implementing the instances. -Edward On Tue, Dec 4, 2018 at 9:08 PM Zemyla wrote: > I thought of this, but the problem is that Data.Type.Equality is > Trustworthy, while Data.Type.Coercion is unsafe. Therefore, you can't > define the superclass in a Safe module. > > The solution to this would be to have Data.Type.Equality export > TestCoercion but not testCoercion, and have a a default implementation > (with DefaultSignatures) that requires TestEquality and just turns the > equality into a coercion. > > Another option is to include testCoercion, but not Coercion, and use the > fact that Coercion is a Category here: > > toId :: Category p => (a :~: b) -> p a b > toId Refl = id > > And then testCoercion a b = fmap toId $ testEquality a b > > On Tue, Dec 4, 2018, 19:50 Edward Kmett >> You actually would need both types for full generality. Both provide >> useful power under different circumstances. >> >> Another thing I noticed when working on this is that TestEquality is >> missing TestCoercion as a superclass at present. This means you can't use >> the latter as merely a weaker TestEquality constraint, but have to plumb >> both independently. This feels wrong. Everything that can support >> TestEquality should be able to support TestCoercion. >> >> I do at least want the TestCoercion instances. >> >> -Edward >> >> On Tue, Dec 4, 2018 at 7:46 AM Andrew Martin >> wrote: >> >>> Given that each comes at the cost of the other, if I had to choose >>> between which of these two STRef features I could have, I would pick being >>> able to use it to recover equality over being able to lift newtype >>> coercions through it. The former is increases expressivity while the latter >>> accomplishes something that is achievable by simply using less newtypes in >>> APIs where the need for this arises (not that I've ever actually needed to >>> coerce an STRef in this way, but it would be interesting to hear from >>> anyone who has needed this). >>> >>> On Tue, Dec 4, 2018 at 12:26 AM Edward Kmett wrote: >>> >>>> Mostly because it means I wind up needing another construction to make >>>> it all go and can't just kick it all upstream. ;) >>>> >>>> -Edward >>>> >>>> On Mon, Dec 3, 2018 at 10:11 PM Richard Eisenberg >>>> wrote: >>>> >>>>> Why is it unfortunate? This looks like desired behavior to me. That >>>>> is: I think these reference types should allow coercions between >>>>> representationally equal types. Of course, that means that TestEquality is >>>>> out. >>>>> >>>>> Richard >>>>> >>>>> On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: >>>>> >>>>> On Sun, Dec 2, 2018 at 7:55 PM David Feuer >>>>> wrote: >>>>> >>>>>> Unfortunately, testEquality for STRef is not at all safe, for reasons >>>>>> we've previously discussed in another context. >>>>>> >>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>>> >>>>>> let x = [1, 2] >>>>>> foo :: STRef s [Int] <- newSTRef x >>>>>> let bar :: STRef s (ZipList Int) = coerce foo >>>>>> case testEquality foo bar of UH-OH >>>>>> >>>>>> I suspect testCoercion actually will work here. >>>>>> >>>>>> You could patch up the problem by giving STRef (and perhaps MutVar#) >>>>>> a stricter role signature: >>>>>> >>>>>> type role STRef nominal nominal >>>>>> >>>>>> That might not break enough code to worry about; I'm not sure. >>>>>> >>>>> >>>>> That is rather unfortunate, as it means most if not all of these would >>>>> be limited to TestCoercion. >>>>> >>>>> -Edward >>>>> >>>>> >>>>> >>>>>> On Sun, Dec 2, 2018, 7:16 PM Edward Kmett >>>>> >>>>>>> I'd like to propose adding a bunch of instances for TestEquality and >>>>>>> TestCoercion to base and primitive types such as: IORef, STRef s, MVar as >>>>>>> well as MutVar and any appropriately uncoercible array types we have in >>>>>>> primitive. >>>>>>> >>>>>>> With these you can learn about the equality of the types of elements >>>>>>> of an STRef when you go to >>>>>>> >>>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>>>> >>>>>>> I've been using an ad hoc versions of this on my own for some time, >>>>>>> across a wide array of packages, based on Atze van der Ploeg's paper: >>>>>>> https://dl.acm.org/citation.cfm?id=2976008 and currently I get by >>>>>>> by unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the >>>>>>> witness that I get back in turn. =/ >>>>>>> >>>>>>> With this the notion of a "Key" introduced there can be safely >>>>>>> modeled with an STRef s (Proxy a). >>>>>>> >>>>>>> This would make it {-# LANGUAGE Safe #-} for users to construct >>>>>>> heterogeneous container types that don't need Typeable information about >>>>>>> the values. >>>>>>> >>>>>>> Implementation wise, these can either use the value equality of >>>>>>> those underlying primitive types and then produce a witness either by >>>>>>> unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce >>>>>>> the witness in a type-safe manner, giving us well typed core all the way >>>>>>> down. >>>>>>> >>>>>>> -Edward >>>>>>> _______________________________________________ >>>>>>> Libraries mailing list >>>>>>> Libraries at haskell.org >>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>>> >>>>>> >>>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>> >>> >>> -- >>> -Andrew Thaddeus Martin >>> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Wed Dec 5 05:46:03 2018 From: david.feuer at gmail.com (David Feuer) Date: Wed, 5 Dec 2018 00:46:03 -0500 Subject: TestEquality for references In-Reply-To: References: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Message-ID: I *do* think we should revisit that stance. Anyone who's still relying on coerce not existing to guard their otherwise *unsafe* operations without using role annotations is way behind the times and needs to fix their code. On Wed, Dec 5, 2018 at 12:22 AM Edward Kmett wrote: > > I could live with that solution pretty well. Getting the default implementation would be a very nice bonus, as in most cases it is quite repetitive. > > Observation: In the second scenario is it really that exporting Coercion actually dangerous? > > Not in the sense that we should revisit the stance, but rather it seems that the things it exports that can actually use Coercible to coerce that are the problem point. > > Without coerce or coerceWith, everything in Data.Type.Coercion seems perfectly Trustworthy. > > We should just be able to split off the Trustworthy parts of Data.Type.Coercion via an Internal module and use them to put the superclass in place. Even gcoerceWith requires you to have access to coerce to do anything with it other than manipulate Coercible instances. > > The whole module is currently unsafe because of one combinator in it. > > GHC is even smart enough that you don't need `coerce` to implement sym, trans, etc. so `coerce` and `coerceWith` aren't even used when implementing the instances. > > -Edward > > On Tue, Dec 4, 2018 at 9:08 PM Zemyla wrote: >> >> I thought of this, but the problem is that Data.Type.Equality is Trustworthy, while Data.Type.Coercion is unsafe. Therefore, you can't define the superclass in a Safe module. >> >> The solution to this would be to have Data.Type.Equality export TestCoercion but not testCoercion, and have a a default implementation (with DefaultSignatures) that requires TestEquality and just turns the equality into a coercion. >> >> Another option is to include testCoercion, but not Coercion, and use the fact that Coercion is a Category here: >> >> toId :: Category p => (a :~: b) -> p a b >> toId Refl = id >> >> And then testCoercion a b = fmap toId $ testEquality a b >> >> On Tue, Dec 4, 2018, 19:50 Edward Kmett >> >>> You actually would need both types for full generality. Both provide useful power under different circumstances. >>> >>> Another thing I noticed when working on this is that TestEquality is missing TestCoercion as a superclass at present. This means you can't use the latter as merely a weaker TestEquality constraint, but have to plumb both independently. This feels wrong. Everything that can support TestEquality should be able to support TestCoercion. >>> >>> I do at least want the TestCoercion instances. >>> >>> -Edward >>> >>> On Tue, Dec 4, 2018 at 7:46 AM Andrew Martin wrote: >>>> >>>> Given that each comes at the cost of the other, if I had to choose between which of these two STRef features I could have, I would pick being able to use it to recover equality over being able to lift newtype coercions through it. The former is increases expressivity while the latter accomplishes something that is achievable by simply using less newtypes in APIs where the need for this arises (not that I've ever actually needed to coerce an STRef in this way, but it would be interesting to hear from anyone who has needed this). >>>> >>>> On Tue, Dec 4, 2018 at 12:26 AM Edward Kmett wrote: >>>>> >>>>> Mostly because it means I wind up needing another construction to make it all go and can't just kick it all upstream. ;) >>>>> >>>>> -Edward >>>>> >>>>> On Mon, Dec 3, 2018 at 10:11 PM Richard Eisenberg wrote: >>>>>> >>>>>> Why is it unfortunate? This looks like desired behavior to me. That is: I think these reference types should allow coercions between representationally equal types. Of course, that means that TestEquality is out. >>>>>> >>>>>> Richard >>>>>> >>>>>> On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: >>>>>> >>>>>> On Sun, Dec 2, 2018 at 7:55 PM David Feuer wrote: >>>>>>> >>>>>>> Unfortunately, testEquality for STRef is not at all safe, for reasons we've previously discussed in another context. >>>>>>> >>>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>>>> >>>>>>> let x = [1, 2] >>>>>>> foo :: STRef s [Int] <- newSTRef x >>>>>>> let bar :: STRef s (ZipList Int) = coerce foo >>>>>>> case testEquality foo bar of UH-OH >>>>>>> >>>>>>> I suspect testCoercion actually will work here. >>>>>>> >>>>>>> You could patch up the problem by giving STRef (and perhaps MutVar#) a stricter role signature: >>>>>>> >>>>>>> type role STRef nominal nominal >>>>>>> >>>>>>> That might not break enough code to worry about; I'm not sure. >>>>>> >>>>>> >>>>>> That is rather unfortunate, as it means most if not all of these would be limited to TestCoercion. >>>>>> >>>>>> -Edward >>>>>> >>>>>> >>>>>>> >>>>>>> On Sun, Dec 2, 2018, 7:16 PM Edward Kmett >>>>>>> >>>>>>>> I'd like to propose adding a bunch of instances for TestEquality and TestCoercion to base and primitive types such as: IORef, STRef s, MVar as well as MutVar and any appropriately uncoercible array types we have in primitive. >>>>>>>> >>>>>>>> With these you can learn about the equality of the types of elements of an STRef when you go to >>>>>>>> >>>>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>>>>> >>>>>>>> I've been using an ad hoc versions of this on my own for some time, across a wide array of packages, based on Atze van der Ploeg's paper: https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness that I get back in turn. =/ >>>>>>>> >>>>>>>> With this the notion of a "Key" introduced there can be safely modeled with an STRef s (Proxy a). >>>>>>>> >>>>>>>> This would make it {-# LANGUAGE Safe #-} for users to construct heterogeneous container types that don't need Typeable information about the values. >>>>>>>> >>>>>>>> Implementation wise, these can either use the value equality of those underlying primitive types and then produce a witness either by unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce the witness in a type-safe manner, giving us well typed core all the way down. >>>>>>>> >>>>>>>> -Edward >>>>>>>> _______________________________________________ >>>>>>>> Libraries mailing list >>>>>>>> Libraries at haskell.org >>>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>>> >>>>>> >>>>> _______________________________________________ >>>>> Libraries mailing list >>>>> Libraries at haskell.org >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>>> >>>> >>>> -- >>>> -Andrew Thaddeus Martin >>> >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From rae at cs.brynmawr.edu Mon Dec 10 22:54:09 2018 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Mon, 10 Dec 2018 17:54:09 -0500 Subject: TestEquality for references In-Reply-To: References: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Message-ID: I put my 2¢ with David here. Though I agreed with the decision to make coerce Unsafe at first, I think we can revise that now. Richard > On Dec 5, 2018, at 12:46 AM, David Feuer wrote: > > I *do* think we should revisit that stance. Anyone who's still relying > on coerce not existing to guard their otherwise *unsafe* operations > without using role annotations is way behind the times and needs to > fix their code. > On Wed, Dec 5, 2018 at 12:22 AM Edward Kmett wrote: >> >> I could live with that solution pretty well. Getting the default implementation would be a very nice bonus, as in most cases it is quite repetitive. >> >> Observation: In the second scenario is it really that exporting Coercion actually dangerous? >> >> Not in the sense that we should revisit the stance, but rather it seems that the things it exports that can actually use Coercible to coerce that are the problem point. >> >> Without coerce or coerceWith, everything in Data.Type.Coercion seems perfectly Trustworthy. >> >> We should just be able to split off the Trustworthy parts of Data.Type.Coercion via an Internal module and use them to put the superclass in place. Even gcoerceWith requires you to have access to coerce to do anything with it other than manipulate Coercible instances. >> >> The whole module is currently unsafe because of one combinator in it. >> >> GHC is even smart enough that you don't need `coerce` to implement sym, trans, etc. so `coerce` and `coerceWith` aren't even used when implementing the instances. >> >> -Edward >> >> On Tue, Dec 4, 2018 at 9:08 PM Zemyla wrote: >>> >>> I thought of this, but the problem is that Data.Type.Equality is Trustworthy, while Data.Type.Coercion is unsafe. Therefore, you can't define the superclass in a Safe module. >>> >>> The solution to this would be to have Data.Type.Equality export TestCoercion but not testCoercion, and have a a default implementation (with DefaultSignatures) that requires TestEquality and just turns the equality into a coercion. >>> >>> Another option is to include testCoercion, but not Coercion, and use the fact that Coercion is a Category here: >>> >>> toId :: Category p => (a :~: b) -> p a b >>> toId Refl = id >>> >>> And then testCoercion a b = fmap toId $ testEquality a b >>> >>> On Tue, Dec 4, 2018, 19:50 Edward Kmett >>> >>>> You actually would need both types for full generality. Both provide useful power under different circumstances. >>>> >>>> Another thing I noticed when working on this is that TestEquality is missing TestCoercion as a superclass at present. This means you can't use the latter as merely a weaker TestEquality constraint, but have to plumb both independently. This feels wrong. Everything that can support TestEquality should be able to support TestCoercion. >>>> >>>> I do at least want the TestCoercion instances. >>>> >>>> -Edward >>>> >>>> On Tue, Dec 4, 2018 at 7:46 AM Andrew Martin wrote: >>>>> >>>>> Given that each comes at the cost of the other, if I had to choose between which of these two STRef features I could have, I would pick being able to use it to recover equality over being able to lift newtype coercions through it. The former is increases expressivity while the latter accomplishes something that is achievable by simply using less newtypes in APIs where the need for this arises (not that I've ever actually needed to coerce an STRef in this way, but it would be interesting to hear from anyone who has needed this). >>>>> >>>>> On Tue, Dec 4, 2018 at 12:26 AM Edward Kmett wrote: >>>>>> >>>>>> Mostly because it means I wind up needing another construction to make it all go and can't just kick it all upstream. ;) >>>>>> >>>>>> -Edward >>>>>> >>>>>> On Mon, Dec 3, 2018 at 10:11 PM Richard Eisenberg wrote: >>>>>>> >>>>>>> Why is it unfortunate? This looks like desired behavior to me. That is: I think these reference types should allow coercions between representationally equal types. Of course, that means that TestEquality is out. >>>>>>> >>>>>>> Richard >>>>>>> >>>>>>> On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: >>>>>>> >>>>>>> On Sun, Dec 2, 2018 at 7:55 PM David Feuer wrote: >>>>>>>> >>>>>>>> Unfortunately, testEquality for STRef is not at all safe, for reasons we've previously discussed in another context. >>>>>>>> >>>>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>>>>> >>>>>>>> let x = [1, 2] >>>>>>>> foo :: STRef s [Int] <- newSTRef x >>>>>>>> let bar :: STRef s (ZipList Int) = coerce foo >>>>>>>> case testEquality foo bar of UH-OH >>>>>>>> >>>>>>>> I suspect testCoercion actually will work here. >>>>>>>> >>>>>>>> You could patch up the problem by giving STRef (and perhaps MutVar#) a stricter role signature: >>>>>>>> >>>>>>>> type role STRef nominal nominal >>>>>>>> >>>>>>>> That might not break enough code to worry about; I'm not sure. >>>>>>> >>>>>>> >>>>>>> That is rather unfortunate, as it means most if not all of these would be limited to TestCoercion. >>>>>>> >>>>>>> -Edward >>>>>>> >>>>>>> >>>>>>>> >>>>>>>> On Sun, Dec 2, 2018, 7:16 PM Edward Kmett >>>>>>>> >>>>>>>>> I'd like to propose adding a bunch of instances for TestEquality and TestCoercion to base and primitive types such as: IORef, STRef s, MVar as well as MutVar and any appropriately uncoercible array types we have in primitive. >>>>>>>>> >>>>>>>>> With these you can learn about the equality of the types of elements of an STRef when you go to >>>>>>>>> >>>>>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) >>>>>>>>> >>>>>>>>> I've been using an ad hoc versions of this on my own for some time, across a wide array of packages, based on Atze van der Ploeg's paper: https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness that I get back in turn. =/ >>>>>>>>> >>>>>>>>> With this the notion of a "Key" introduced there can be safely modeled with an STRef s (Proxy a). >>>>>>>>> >>>>>>>>> This would make it {-# LANGUAGE Safe #-} for users to construct heterogeneous container types that don't need Typeable information about the values. >>>>>>>>> >>>>>>>>> Implementation wise, these can either use the value equality of those underlying primitive types and then produce a witness either by unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce the witness in a type-safe manner, giving us well typed core all the way down. >>>>>>>>> >>>>>>>>> -Edward >>>>>>>>> _______________________________________________ >>>>>>>>> Libraries mailing list >>>>>>>>> Libraries at haskell.org >>>>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>>>> >>>>>>> >>>>>> _______________________________________________ >>>>>> Libraries mailing list >>>>>> Libraries at haskell.org >>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>> >>>>> >>>>> >>>>> -- >>>>> -Andrew Thaddeus Martin >>>> >>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From ekmett at gmail.com Thu Dec 13 09:14:36 2018 From: ekmett at gmail.com (Edward Kmett) Date: Thu, 13 Dec 2018 04:14:36 -0500 Subject: TestEquality for references In-Reply-To: References: <118057E5-974B-4BDA-B9DD-396EA0F035EE@cs.brynmawr.edu> Message-ID: I'm definitely open to revisiting it as well. -Edward On Mon, Dec 10, 2018 at 5:54 PM Richard Eisenberg wrote: > I put my 2¢ with David here. Though I agreed with the decision to make > coerce Unsafe at first, I think we can revise that now. > > Richard > > > On Dec 5, 2018, at 12:46 AM, David Feuer wrote: > > > > I *do* think we should revisit that stance. Anyone who's still relying > > on coerce not existing to guard their otherwise *unsafe* operations > > without using role annotations is way behind the times and needs to > > fix their code. > > On Wed, Dec 5, 2018 at 12:22 AM Edward Kmett wrote: > >> > >> I could live with that solution pretty well. Getting the default > implementation would be a very nice bonus, as in most cases it is quite > repetitive. > >> > >> Observation: In the second scenario is it really that exporting > Coercion actually dangerous? > >> > >> Not in the sense that we should revisit the stance, but rather it seems > that the things it exports that can actually use Coercible to coerce that > are the problem point. > >> > >> Without coerce or coerceWith, everything in Data.Type.Coercion seems > perfectly Trustworthy. > >> > >> We should just be able to split off the Trustworthy parts of > Data.Type.Coercion via an Internal module and use them to put the > superclass in place. Even gcoerceWith requires you to have access to coerce > to do anything with it other than manipulate Coercible instances. > >> > >> The whole module is currently unsafe because of one combinator in it. > >> > >> GHC is even smart enough that you don't need `coerce` to implement sym, > trans, etc. so `coerce` and `coerceWith` aren't even used when implementing > the instances. > >> > >> -Edward > >> > >> On Tue, Dec 4, 2018 at 9:08 PM Zemyla wrote: > >>> > >>> I thought of this, but the problem is that Data.Type.Equality is > Trustworthy, while Data.Type.Coercion is unsafe. Therefore, you can't > define the superclass in a Safe module. > >>> > >>> The solution to this would be to have Data.Type.Equality export > TestCoercion but not testCoercion, and have a a default implementation > (with DefaultSignatures) that requires TestEquality and just turns the > equality into a coercion. > >>> > >>> Another option is to include testCoercion, but not Coercion, and use > the fact that Coercion is a Category here: > >>> > >>> toId :: Category p => (a :~: b) -> p a b > >>> toId Refl = id > >>> > >>> And then testCoercion a b = fmap toId $ testEquality a b > >>> > >>> On Tue, Dec 4, 2018, 19:50 Edward Kmett >>>> > >>>> You actually would need both types for full generality. Both provide > useful power under different circumstances. > >>>> > >>>> Another thing I noticed when working on this is that TestEquality is > missing TestCoercion as a superclass at present. This means you can't use > the latter as merely a weaker TestEquality constraint, but have to plumb > both independently. This feels wrong. Everything that can support > TestEquality should be able to support TestCoercion. > >>>> > >>>> I do at least want the TestCoercion instances. > >>>> > >>>> -Edward > >>>> > >>>> On Tue, Dec 4, 2018 at 7:46 AM Andrew Martin < > andrew.thaddeus at gmail.com> wrote: > >>>>> > >>>>> Given that each comes at the cost of the other, if I had to choose > between which of these two STRef features I could have, I would pick being > able to use it to recover equality over being able to lift newtype > coercions through it. The former is increases expressivity while the latter > accomplishes something that is achievable by simply using less newtypes in > APIs where the need for this arises (not that I've ever actually needed to > coerce an STRef in this way, but it would be interesting to hear from > anyone who has needed this). > >>>>> > >>>>> On Tue, Dec 4, 2018 at 12:26 AM Edward Kmett > wrote: > >>>>>> > >>>>>> Mostly because it means I wind up needing another construction to > make it all go and can't just kick it all upstream. ;) > >>>>>> > >>>>>> -Edward > >>>>>> > >>>>>> On Mon, Dec 3, 2018 at 10:11 PM Richard Eisenberg < > rae at cs.brynmawr.edu> wrote: > >>>>>>> > >>>>>>> Why is it unfortunate? This looks like desired behavior to me. > That is: I think these reference types should allow coercions between > representationally equal types. Of course, that means that TestEquality is > out. > >>>>>>> > >>>>>>> Richard > >>>>>>> > >>>>>>> On Dec 2, 2018, at 5:04 PM, Edward Kmett wrote: > >>>>>>> > >>>>>>> On Sun, Dec 2, 2018 at 7:55 PM David Feuer > wrote: > >>>>>>>> > >>>>>>>> Unfortunately, testEquality for STRef is not at all safe, for > reasons we've previously discussed in another context. > >>>>>>>> > >>>>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) > >>>>>>>> > >>>>>>>> let x = [1, 2] > >>>>>>>> foo :: STRef s [Int] <- newSTRef x > >>>>>>>> let bar :: STRef s (ZipList Int) = coerce foo > >>>>>>>> case testEquality foo bar of UH-OH > >>>>>>>> > >>>>>>>> I suspect testCoercion actually will work here. > >>>>>>>> > >>>>>>>> You could patch up the problem by giving STRef (and perhaps > MutVar#) a stricter role signature: > >>>>>>>> > >>>>>>>> type role STRef nominal nominal > >>>>>>>> > >>>>>>>> That might not break enough code to worry about; I'm not sure. > >>>>>>> > >>>>>>> > >>>>>>> That is rather unfortunate, as it means most if not all of these > would be limited to TestCoercion. > >>>>>>> > >>>>>>> -Edward > >>>>>>> > >>>>>>> > >>>>>>>> > >>>>>>>> On Sun, Dec 2, 2018, 7:16 PM Edward Kmett wrote: > >>>>>>>>> > >>>>>>>>> I'd like to propose adding a bunch of instances for TestEquality > and TestCoercion to base and primitive types such as: IORef, STRef s, MVar > as well as MutVar and any appropriately uncoercible array types we have in > primitive. > >>>>>>>>> > >>>>>>>>> With these you can learn about the equality of the types of > elements of an STRef when you go to > >>>>>>>>> > >>>>>>>>> testEquality :: STRef s a -> STRef s b -> Maybe (a :~: b) > >>>>>>>>> > >>>>>>>>> I've been using an ad hoc versions of this on my own for some > time, across a wide array of packages, based on Atze van der Ploeg's paper: > https://dl.acm.org/citation.cfm?id=2976008 and currently I get by by > unsafeCoercing reallyUnsafePointerEquality# and unsafeCoercing the witness > that I get back in turn. =/ > >>>>>>>>> > >>>>>>>>> With this the notion of a "Key" introduced there can be safely > modeled with an STRef s (Proxy a). > >>>>>>>>> > >>>>>>>>> This would make it {-# LANGUAGE Safe #-} for users to construct > heterogeneous container types that don't need Typeable information about > the values. > >>>>>>>>> > >>>>>>>>> Implementation wise, these can either use the value equality of > those underlying primitive types and then produce a witness either by > unsafeCoerce, or by adding new stronger primitives in ghc-prim to produce > the witness in a type-safe manner, giving us well typed core all the way > down. > >>>>>>>>> > >>>>>>>>> -Edward > >>>>>>>>> _______________________________________________ > >>>>>>>>> Libraries mailing list > >>>>>>>>> Libraries at haskell.org > >>>>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > >>>>>>> > >>>>>>> > >>>>>> _______________________________________________ > >>>>>> Libraries mailing list > >>>>>> Libraries at haskell.org > >>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > >>>>> > >>>>> > >>>>> > >>>>> -- > >>>>> -Andrew Thaddeus Martin > >>>> > >>>> _______________________________________________ > >>>> Libraries mailing list > >>>> Libraries at haskell.org > >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > >>> > >>> _______________________________________________ > >>> Libraries mailing list > >>> Libraries at haskell.org > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > >> > >> _______________________________________________ > >> Libraries mailing list > >> Libraries at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > _______________________________________________ > > Libraries mailing list > > Libraries at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Fri Dec 14 05:03:01 2018 From: david.feuer at gmail.com (David Feuer) Date: Fri, 14 Dec 2018 00:03:01 -0500 Subject: Proposal: Change Alternative law for some and many Message-ID: Currently, we document this law: > If defined, some and many should be the least solutions of the equations: > > some v = (:) <$> v <*> many v > many v = some v <|> pure [] This seems a bit too strong. I believe we should weaken "should be the least solutions of" to "should obey". This allows non-bottoming implementations for more types. I would be surprised if the change would meaningfully weaken the value of the law for reasoning about real programs. For example, we currently require some Nothing = Nothing some (Just x) = _|_ many Nothing = Just [] many (Just x) = _|_ But if we weaken the law, we could instead use some Nothing = Nothing some (Just x) = Just (repeat x) many Nothing = Just [] many (Just x) = Just (repeat x) This seems strictly, albeit slightly, more interesting. More significantly, I think, the instance for functor products can also get much better-defined: some (x :*: y) = some x :*: some y many (x :*: y) = many x :*: many y That strikes me as an improvement that may actually be of some practical value. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Fri Dec 14 05:12:09 2018 From: gershomb at gmail.com (Gershom B) Date: Fri, 14 Dec 2018 00:12:09 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: Can you give an example of where the new definitions and current definitions of functor products would yield different behavior? -g On December 14, 2018 at 12:03:32 AM, David Feuer (david.feuer at gmail.com) wrote: Currently, we document this law: > If defined, some and many should be the least solutions of the equations: > >   some v = (:) <$> v <*> many v >   many v = some v <|> pure [] This seems a bit too strong. I believe we should weaken "should be the least solutions of" to "should obey". This allows non-bottoming implementations for more types. I would be surprised if the change would meaningfully weaken the value of the law for reasoning about real programs. For example, we currently require     some Nothing = Nothing     some (Just x) = _|_     many Nothing = Just []     many (Just x) = _|_ But if we weaken the law, we could instead use     some Nothing = Nothing     some (Just x) = Just (repeat x)     many Nothing = Just []     many (Just x) = Just (repeat x) This seems strictly, albeit slightly, more interesting. More significantly, I think, the instance for functor products can also get much better-defined:     some (x :*: y) = some x :*: some y     many (x :*: y) = many x :*: many y That strikes me as an improvement that may actually be of some practical value. _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Fri Dec 14 05:22:52 2018 From: david.feuer at gmail.com (David Feuer) Date: Fri, 14 Dec 2018 00:22:52 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: With the current law and (default) definitions, some (x :*: y) = liftA2 (:) (x :*: y) (many (x :*: y)) many (x :*: y) = some (x :*: y) <|> pure [] Since liftA2 is strict in its third argument, and (<|>) is strict in its first argument, some = many = const _|_ regardless of the underlying functors. On the other hand, with the proposed law and the proposed definitions, the methods will behave well for products if they behave well for the underlying functors. On Fri, Dec 14, 2018 at 12:12 AM Gershom B wrote: > Can you give an example of where the new definitions and current > definitions of functor products would yield different behavior? > > -g > > > On December 14, 2018 at 12:03:32 AM, David Feuer (david.feuer at gmail.com) > wrote: > > Currently, we document this law: > > > If defined, some and many should be the least solutions of the equations: > > > > some v = (:) <$> v <*> many v > > many v = some v <|> pure [] > > This seems a bit too strong. I believe we should weaken "should be the > least solutions of" to "should obey". This allows non-bottoming > implementations for more types. I would be surprised if the change would > meaningfully weaken the value of the law for reasoning about real programs. > > For example, we currently require > > some Nothing = Nothing > some (Just x) = _|_ > > many Nothing = Just [] > many (Just x) = _|_ > > But if we weaken the law, we could instead use > > some Nothing = Nothing > some (Just x) = Just (repeat x) > > many Nothing = Just [] > many (Just x) = Just (repeat x) > > This seems strictly, albeit slightly, more interesting. > > More significantly, I think, the instance for functor products can also > get much better-defined: > > some (x :*: y) = some x :*: some y > many (x :*: y) = many x :*: many y > > That strikes me as an improvement that may actually be of some practical > value. > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Fri Dec 14 05:30:22 2018 From: david.feuer at gmail.com (David Feuer) Date: Fri, 14 Dec 2018 00:30:22 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: Note: even making liftA2 and (<|>) lazy ends up leading to some bottoms that the proposed definition avoids. I don't honestly understand just why that is. On Fri, Dec 14, 2018 at 12:22 AM David Feuer wrote: > With the current law and (default) definitions, > > some (x :*: y) = liftA2 (:) (x :*: y) (many (x :*: y)) > many (x :*: y) = some (x :*: y) <|> pure [] > > Since liftA2 is strict in its third argument, and (<|>) is strict in its > first argument, some = many = const _|_ regardless of the underlying > functors. > > On the other hand, with the proposed law and the proposed definitions, the > methods will behave well for products if they behave well for the > underlying functors. > > On Fri, Dec 14, 2018 at 12:12 AM Gershom B wrote: > >> Can you give an example of where the new definitions and current >> definitions of functor products would yield different behavior? >> >> -g >> >> >> On December 14, 2018 at 12:03:32 AM, David Feuer (david.feuer at gmail.com) >> wrote: >> >> Currently, we document this law: >> >> > If defined, some and many should be the least solutions of the >> equations: >> > >> > some v = (:) <$> v <*> many v >> > many v = some v <|> pure [] >> >> This seems a bit too strong. I believe we should weaken "should be the >> least solutions of" to "should obey". This allows non-bottoming >> implementations for more types. I would be surprised if the change would >> meaningfully weaken the value of the law for reasoning about real programs. >> >> For example, we currently require >> >> some Nothing = Nothing >> some (Just x) = _|_ >> >> many Nothing = Just [] >> many (Just x) = _|_ >> >> But if we weaken the law, we could instead use >> >> some Nothing = Nothing >> some (Just x) = Just (repeat x) >> >> many Nothing = Just [] >> many (Just x) = Just (repeat x) >> >> This seems strictly, albeit slightly, more interesting. >> >> More significantly, I think, the instance for functor products can also >> get much better-defined: >> >> some (x :*: y) = some x :*: some y >> many (x :*: y) = many x :*: many y >> >> That strikes me as an improvement that may actually be of some practical >> value. >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Fri Dec 14 05:47:05 2018 From: gershomb at gmail.com (Gershom B) Date: Fri, 14 Dec 2018 00:47:05 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: Some interesting prior discussion on the topic. I haven’t worked out how much of what’s discussed there would do better in this setting… https://www.reddit.com/r/haskell/comments/2j8bvl/laws_of_some_and_many/ That said, I think this probably is a good improvement. -g On December 14, 2018 at 12:30:52 AM, David Feuer (david.feuer at gmail.com) wrote: Note: even making liftA2 and (<|>) lazy ends up leading to some bottoms that the proposed definition avoids. I don't honestly understand just why that is. On Fri, Dec 14, 2018 at 12:22 AM David Feuer wrote: With the current law and (default) definitions, some (x :*: y) = liftA2 (:) (x :*: y) (many (x :*: y)) many (x :*: y) = some (x :*: y) <|> pure [] Since liftA2 is strict in its third argument, and (<|>) is strict in its first argument, some = many = const _|_ regardless of the underlying functors. On the other hand, with the proposed law and the proposed definitions, the methods will behave well for products if they behave well for the underlying functors. On Fri, Dec 14, 2018 at 12:12 AM Gershom B wrote: Can you give an example of where the new definitions and current definitions of functor products would yield different behavior? -g On December 14, 2018 at 12:03:32 AM, David Feuer (david.feuer at gmail.com) wrote: Currently, we document this law: > If defined, some and many should be the least solutions of the equations: > >   some v = (:) <$> v <*> many v >   many v = some v <|> pure [] This seems a bit too strong. I believe we should weaken "should be the least solutions of" to "should obey". This allows non-bottoming implementations for more types. I would be surprised if the change would meaningfully weaken the value of the law for reasoning about real programs. For example, we currently require     some Nothing = Nothing     some (Just x) = _|_     many Nothing = Just []     many (Just x) = _|_ But if we weaken the law, we could instead use     some Nothing = Nothing     some (Just x) = Just (repeat x)     many Nothing = Just []     many (Just x) = Just (repeat x) This seems strictly, albeit slightly, more interesting. More significantly, I think, the instance for functor products can also get much better-defined:     some (x :*: y) = some x :*: some y     many (x :*: y) = many x :*: many y That strikes me as an improvement that may actually be of some practical value. _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Fri Dec 14 05:57:51 2018 From: david.feuer at gmail.com (David Feuer) Date: Fri, 14 Dec 2018 00:57:51 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: Some of it, for sure. Where Capriotti mentioned "It's a fixpoint, but not the least," this fixes it. Another potentially interesting relaxation would be some v >= (:) <$> v <*> many v many v >= some v <|> pure [] but that seems considerably more likely to limit practically useful reasoning. On Fri, Dec 14, 2018 at 12:47 AM Gershom B wrote: > Some interesting prior discussion on the topic. I haven’t worked out how > much of what’s discussed there would do better in this setting… > https://www.reddit.com/r/haskell/comments/2j8bvl/laws_of_some_and_many/ > > That said, I think this probably is a good improvement. > > -g > > > On December 14, 2018 at 12:30:52 AM, David Feuer (david.feuer at gmail.com) > wrote: > > Note: even making liftA2 and (<|>) lazy ends up leading to some bottoms > that the proposed definition avoids. I don't honestly understand just why > that is. > > On Fri, Dec 14, 2018 at 12:22 AM David Feuer > wrote: > >> With the current law and (default) definitions, >> >> some (x :*: y) = liftA2 (:) (x :*: y) (many (x :*: y)) >> many (x :*: y) = some (x :*: y) <|> pure [] >> >> Since liftA2 is strict in its third argument, and (<|>) is strict in its >> first argument, some = many = const _|_ regardless of the underlying >> functors. >> >> On the other hand, with the proposed law and the proposed definitions, >> the methods will behave well for products if they behave well for the >> underlying functors. >> >> On Fri, Dec 14, 2018 at 12:12 AM Gershom B wrote: >> >>> Can you give an example of where the new definitions and current >>> definitions of functor products would yield different behavior? >>> >>> -g >>> >>> >>> On December 14, 2018 at 12:03:32 AM, David Feuer (david.feuer at gmail.com) >>> wrote: >>> >>> Currently, we document this law: >>> >>> > If defined, some and many should be the least solutions of the >>> equations: >>> > >>> > some v = (:) <$> v <*> many v >>> > many v = some v <|> pure [] >>> >>> This seems a bit too strong. I believe we should weaken "should be the >>> least solutions of" to "should obey". This allows non-bottoming >>> implementations for more types. I would be surprised if the change would >>> meaningfully weaken the value of the law for reasoning about real programs. >>> >>> For example, we currently require >>> >>> some Nothing = Nothing >>> some (Just x) = _|_ >>> >>> many Nothing = Just [] >>> many (Just x) = _|_ >>> >>> But if we weaken the law, we could instead use >>> >>> some Nothing = Nothing >>> some (Just x) = Just (repeat x) >>> >>> many Nothing = Just [] >>> many (Just x) = Just (repeat x) >>> >>> This seems strictly, albeit slightly, more interesting. >>> >>> More significantly, I think, the instance for functor products can also >>> get much better-defined: >>> >>> some (x :*: y) = some x :*: some y >>> many (x :*: y) = many x :*: many y >>> >>> That strikes me as an improvement that may actually be of some practical >>> value. >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >>> _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Dec 14 14:49:51 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 14 Dec 2018 09:49:51 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: Hello! Am I correct in reading the example definitions you provided as being the greatest fixed points? On Fri, Dec 14, 2018 at 12:58 AM David Feuer wrote: > Some of it, for sure. Where Capriotti mentioned "It's a fixpoint, but not > the least," this fixes it. Another potentially interesting relaxation would > be > > some v >= (:) <$> v <*> many v > many v >= some v <|> pure [] > > but that seems considerably more likely to limit practically useful > reasoning. > > On Fri, Dec 14, 2018 at 12:47 AM Gershom B wrote: > >> Some interesting prior discussion on the topic. I haven’t worked out how >> much of what’s discussed there would do better in this setting… >> https://www.reddit.com/r/haskell/comments/2j8bvl/laws_of_some_and_many/ >> >> That said, I think this probably is a good improvement. >> >> -g >> >> >> On December 14, 2018 at 12:30:52 AM, David Feuer (david.feuer at gmail.com) >> wrote: >> >> Note: even making liftA2 and (<|>) lazy ends up leading to some bottoms >> that the proposed definition avoids. I don't honestly understand just why >> that is. >> >> On Fri, Dec 14, 2018 at 12:22 AM David Feuer >> wrote: >> >>> With the current law and (default) definitions, >>> >>> some (x :*: y) = liftA2 (:) (x :*: y) (many (x :*: y)) >>> many (x :*: y) = some (x :*: y) <|> pure [] >>> >>> Since liftA2 is strict in its third argument, and (<|>) is strict in its >>> first argument, some = many = const _|_ regardless of the underlying >>> functors. >>> >>> On the other hand, with the proposed law and the proposed definitions, >>> the methods will behave well for products if they behave well for the >>> underlying functors. >>> >>> On Fri, Dec 14, 2018 at 12:12 AM Gershom B wrote: >>> >>>> Can you give an example of where the new definitions and current >>>> definitions of functor products would yield different behavior? >>>> >>>> -g >>>> >>>> >>>> On December 14, 2018 at 12:03:32 AM, David Feuer (david.feuer at gmail.com) >>>> wrote: >>>> >>>> Currently, we document this law: >>>> >>>> > If defined, some and many should be the least solutions of the >>>> equations: >>>> > >>>> > some v = (:) <$> v <*> many v >>>> > many v = some v <|> pure [] >>>> >>>> This seems a bit too strong. I believe we should weaken "should be the >>>> least solutions of" to "should obey". This allows non-bottoming >>>> implementations for more types. I would be surprised if the change would >>>> meaningfully weaken the value of the law for reasoning about real programs. >>>> >>>> For example, we currently require >>>> >>>> some Nothing = Nothing >>>> some (Just x) = _|_ >>>> >>>> many Nothing = Just [] >>>> many (Just x) = _|_ >>>> >>>> But if we weaken the law, we could instead use >>>> >>>> some Nothing = Nothing >>>> some (Just x) = Just (repeat x) >>>> >>>> many Nothing = Just [] >>>> many (Just x) = Just (repeat x) >>>> >>>> This seems strictly, albeit slightly, more interesting. >>>> >>>> More significantly, I think, the instance for functor products can also >>>> get much better-defined: >>>> >>>> some (x :*: y) = some x :*: some y >>>> many (x :*: y) = many x :*: many y >>>> >>>> That strikes me as an improvement that may actually be of some >>>> practical value. >>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>>> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Dec 14 15:11:40 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 14 Dec 2018 10:11:40 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: I guess I’m just surprised that some can’t return just a singleton list of x. Or maybe I’m reading the notation of this discussion wrong. On Fri, Dec 14, 2018 at 9:49 AM Carter Schonwald wrote: > Hello! > > Am I correct in reading the example definitions you provided as being the > greatest fixed points? > > On Fri, Dec 14, 2018 at 12:58 AM David Feuer > wrote: > >> Some of it, for sure. Where Capriotti mentioned "It's a fixpoint, but not >> the least," this fixes it. Another potentially interesting relaxation would >> be >> >> some v >= (:) <$> v <*> many v >> many v >= some v <|> pure [] >> >> but that seems considerably more likely to limit practically useful >> reasoning. >> >> On Fri, Dec 14, 2018 at 12:47 AM Gershom B wrote: >> >>> Some interesting prior discussion on the topic. I haven’t worked out how >>> much of what’s discussed there would do better in this setting… >>> https://www.reddit.com/r/haskell/comments/2j8bvl/laws_of_some_and_many/ >>> >>> That said, I think this probably is a good improvement. >>> >>> -g >>> >>> >>> On December 14, 2018 at 12:30:52 AM, David Feuer (david.feuer at gmail.com) >>> wrote: >>> >>> Note: even making liftA2 and (<|>) lazy ends up leading to some bottoms >>> that the proposed definition avoids. I don't honestly understand just why >>> that is. >>> >>> On Fri, Dec 14, 2018 at 12:22 AM David Feuer >>> wrote: >>> >>>> With the current law and (default) definitions, >>>> >>>> some (x :*: y) = liftA2 (:) (x :*: y) (many (x :*: y)) >>>> many (x :*: y) = some (x :*: y) <|> pure [] >>>> >>>> Since liftA2 is strict in its third argument, and (<|>) is strict in >>>> its first argument, some = many = const _|_ regardless of the underlying >>>> functors. >>>> >>>> On the other hand, with the proposed law and the proposed definitions, >>>> the methods will behave well for products if they behave well for the >>>> underlying functors. >>>> >>>> On Fri, Dec 14, 2018 at 12:12 AM Gershom B wrote: >>>> >>>>> Can you give an example of where the new definitions and current >>>>> definitions of functor products would yield different behavior? >>>>> >>>>> -g >>>>> >>>>> >>>>> On December 14, 2018 at 12:03:32 AM, David Feuer ( >>>>> david.feuer at gmail.com) wrote: >>>>> >>>>> Currently, we document this law: >>>>> >>>>> > If defined, some and many should be the least solutions of the >>>>> equations: >>>>> > >>>>> > some v = (:) <$> v <*> many v >>>>> > many v = some v <|> pure [] >>>>> >>>>> This seems a bit too strong. I believe we should weaken "should be the >>>>> least solutions of" to "should obey". This allows non-bottoming >>>>> implementations for more types. I would be surprised if the change would >>>>> meaningfully weaken the value of the law for reasoning about real programs. >>>>> >>>>> For example, we currently require >>>>> >>>>> some Nothing = Nothing >>>>> some (Just x) = _|_ >>>>> >>>>> many Nothing = Just [] >>>>> many (Just x) = _|_ >>>>> >>>>> But if we weaken the law, we could instead use >>>>> >>>>> some Nothing = Nothing >>>>> some (Just x) = Just (repeat x) >>>>> >>>>> many Nothing = Just [] >>>>> many (Just x) = Just (repeat x) >>>>> >>>>> This seems strictly, albeit slightly, more interesting. >>>>> >>>>> More significantly, I think, the instance for functor products can >>>>> also get much better-defined: >>>>> >>>>> some (x :*: y) = some x :*: some y >>>>> many (x :*: y) = many x :*: many y >>>>> >>>>> That strikes me as an improvement that may actually be of some >>>>> practical value. >>>>> _______________________________________________ >>>>> Libraries mailing list >>>>> Libraries at haskell.org >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>> >>>>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >>> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Fri Dec 14 17:18:37 2018 From: david.feuer at gmail.com (David Feuer) Date: Fri, 14 Dec 2018 12:18:37 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: No, you can't return just a singleton list. If many (Just 3) = Just [3], then some (Just 3) = liftA2 (:) (Just 3) (Just [3]) = Just [3,3]. But then many (Just 3) = some (Just 3) <|> pure [] = Just [3,3], a contradiction. If instead some (Just 3) = Just [3], then many (Just 3) = Just [3] <|> pure [] = Just [3], which gets us back where we started. The definitions I gave for Maybe (and also the ones for [], which I haven't mentioned) are equivalent to "lazifying" the defaults in a straightforward manner. -- This one is the default some v = liftA2 (:) v (many v) -- This one is much like the default. But note that (barring non-termination), -- isJust (m <|> pure []) == True -- So we push the case match under the constructor application: many v = Just $ case some v <|> pure [] of Just x -> x These definitions give the same results as the repeat-based ones I showed before. Are these greatest fixed points? I believe so, but I don't really know enough about domain theory and such to say for sure. On Fri, Dec 14, 2018 at 10:11 AM Carter Schonwald < carter.schonwald at gmail.com> wrote: > I guess I’m just surprised that some can’t return just a singleton list of > x. Or maybe I’m reading the notation of this discussion wrong. > > On Fri, Dec 14, 2018 at 9:49 AM Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> Hello! >> >> Am I correct in reading the example definitions you provided as being the >> greatest fixed points? >> >> On Fri, Dec 14, 2018 at 12:58 AM David Feuer >> wrote: >> >>> Some of it, for sure. Where Capriotti mentioned "It's a fixpoint, but >>> not the least," this fixes it. Another potentially interesting relaxation >>> would be >>> >>> some v >= (:) <$> v <*> many v >>> many v >= some v <|> pure [] >>> >>> but that seems considerably more likely to limit practically useful >>> reasoning. >>> >>> On Fri, Dec 14, 2018 at 12:47 AM Gershom B wrote: >>> >>>> Some interesting prior discussion on the topic. I haven’t worked out >>>> how much of what’s discussed there would do better in this setting… >>>> https://www.reddit.com/r/haskell/comments/2j8bvl/laws_of_some_and_many/ >>>> >>>> That said, I think this probably is a good improvement. >>>> >>>> -g >>>> >>>> >>>> On December 14, 2018 at 12:30:52 AM, David Feuer (david.feuer at gmail.com) >>>> wrote: >>>> >>>> Note: even making liftA2 and (<|>) lazy ends up leading to some bottoms >>>> that the proposed definition avoids. I don't honestly understand just why >>>> that is. >>>> >>>> On Fri, Dec 14, 2018 at 12:22 AM David Feuer >>>> wrote: >>>> >>>>> With the current law and (default) definitions, >>>>> >>>>> some (x :*: y) = liftA2 (:) (x :*: y) (many (x :*: y)) >>>>> many (x :*: y) = some (x :*: y) <|> pure [] >>>>> >>>>> Since liftA2 is strict in its third argument, and (<|>) is strict in >>>>> its first argument, some = many = const _|_ regardless of the underlying >>>>> functors. >>>>> >>>>> On the other hand, with the proposed law and the proposed definitions, >>>>> the methods will behave well for products if they behave well for the >>>>> underlying functors. >>>>> >>>>> On Fri, Dec 14, 2018 at 12:12 AM Gershom B wrote: >>>>> >>>>>> Can you give an example of where the new definitions and current >>>>>> definitions of functor products would yield different behavior? >>>>>> >>>>>> -g >>>>>> >>>>>> >>>>>> On December 14, 2018 at 12:03:32 AM, David Feuer ( >>>>>> david.feuer at gmail.com) wrote: >>>>>> >>>>>> Currently, we document this law: >>>>>> >>>>>> > If defined, some and many should be the least solutions of the >>>>>> equations: >>>>>> > >>>>>> > some v = (:) <$> v <*> many v >>>>>> > many v = some v <|> pure [] >>>>>> >>>>>> This seems a bit too strong. I believe we should weaken "should be >>>>>> the least solutions of" to "should obey". This allows non-bottoming >>>>>> implementations for more types. I would be surprised if the change would >>>>>> meaningfully weaken the value of the law for reasoning about real programs. >>>>>> >>>>>> For example, we currently require >>>>>> >>>>>> some Nothing = Nothing >>>>>> some (Just x) = _|_ >>>>>> >>>>>> many Nothing = Just [] >>>>>> many (Just x) = _|_ >>>>>> >>>>>> But if we weaken the law, we could instead use >>>>>> >>>>>> some Nothing = Nothing >>>>>> some (Just x) = Just (repeat x) >>>>>> >>>>>> many Nothing = Just [] >>>>>> many (Just x) = Just (repeat x) >>>>>> >>>>>> This seems strictly, albeit slightly, more interesting. >>>>>> >>>>>> More significantly, I think, the instance for functor products can >>>>>> also get much better-defined: >>>>>> >>>>>> some (x :*: y) = some x :*: some y >>>>>> many (x :*: y) = many x :*: many y >>>>>> >>>>>> That strikes me as an improvement that may actually be of some >>>>>> practical value. >>>>>> _______________________________________________ >>>>>> Libraries mailing list >>>>>> Libraries at haskell.org >>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>>> >>>>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Dec 14 17:34:15 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 14 Dec 2018 12:34:15 -0500 Subject: Proposal: Change Alternative law for some and many In-Reply-To: References: Message-ID: I understand that in terms of the specified applicative operations it wouldn’t work. I guess my confusion is that I think of some and many combinators in terms of parser combinators style behavior, where some p can return any positive length list of consecutive values. If we were to model these algrbrsically as formal power series I’d think of many x = sum_k (x^k / k! ) = exp x And then some x = many x -1. —- because size zero products of x aren’t a valid element A lot of expressive power in Haskell comes from being able to use laziness to have the same code work on values that act strict (least fixed point) and those which arent (greatest fixed point). My questions are this 1) how would this change impact expected behavior of parser combinator libraries using some and many? 2) what is a calculation I can do today with some and many that I can’t do with this change? 3) what’s a calculation I can do with some and many only once we have this change ? On Fri, Dec 14, 2018 at 12:18 PM David Feuer wrote: > No, you can't return just a singleton list. If many (Just 3) = Just [3], > then > some (Just 3) = liftA2 (:) (Just 3) (Just [3]) = Just [3,3]. But then > many (Just 3) = some (Just 3) <|> pure [] = Just [3,3], a contradiction. > If instead some (Just 3) = Just [3], then many (Just 3) = Just [3] <|> > pure [] = Just [3], > which gets us back where we started. > > The definitions I gave for Maybe (and also the ones for [], which I > haven't mentioned) are equivalent to "lazifying" the defaults in a > straightforward manner. > > -- This one is the default > some v = liftA2 (:) v (many v) > > -- This one is much like the default. But note that (barring > non-termination), > -- isJust (m <|> pure []) == True > -- So we push the case match under the constructor application: > many v = Just $ > case some v <|> pure [] of > Just x -> x > > These definitions give the same results as the repeat-based ones I showed > before. Are these greatest fixed points? I believe so, but I don't really > know enough about domain theory and such to say for sure. > > On Fri, Dec 14, 2018 at 10:11 AM Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> I guess I’m just surprised that some can’t return just a singleton list >> of x. Or maybe I’m reading the notation of this discussion wrong. >> >> On Fri, Dec 14, 2018 at 9:49 AM Carter Schonwald < >> carter.schonwald at gmail.com> wrote: >> >>> Hello! >>> >>> Am I correct in reading the example definitions you provided as being >>> the greatest fixed points? >>> >>> On Fri, Dec 14, 2018 at 12:58 AM David Feuer >>> wrote: >>> >>>> Some of it, for sure. Where Capriotti mentioned "It's a fixpoint, but >>>> not the least," this fixes it. Another potentially interesting relaxation >>>> would be >>>> >>>> some v >= (:) <$> v <*> many v >>>> many v >= some v <|> pure [] >>>> >>>> but that seems considerably more likely to limit practically useful >>>> reasoning. >>>> >>>> On Fri, Dec 14, 2018 at 12:47 AM Gershom B wrote: >>>> >>>>> Some interesting prior discussion on the topic. I haven’t worked out >>>>> how much of what’s discussed there would do better in this setting… >>>>> https://www.reddit.com/r/haskell/comments/2j8bvl/laws_of_some_and_many/ >>>>> >>>>> That said, I think this probably is a good improvement. >>>>> >>>>> -g >>>>> >>>>> >>>>> On December 14, 2018 at 12:30:52 AM, David Feuer ( >>>>> david.feuer at gmail.com) wrote: >>>>> >>>>> Note: even making liftA2 and (<|>) lazy ends up leading to some >>>>> bottoms that the proposed definition avoids. I don't honestly understand >>>>> just why that is. >>>>> >>>>> On Fri, Dec 14, 2018 at 12:22 AM David Feuer >>>>> wrote: >>>>> >>>>>> With the current law and (default) definitions, >>>>>> >>>>>> some (x :*: y) = liftA2 (:) (x :*: y) (many (x :*: y)) >>>>>> many (x :*: y) = some (x :*: y) <|> pure [] >>>>>> >>>>>> Since liftA2 is strict in its third argument, and (<|>) is strict in >>>>>> its first argument, some = many = const _|_ regardless of the underlying >>>>>> functors. >>>>>> >>>>>> On the other hand, with the proposed law and the proposed >>>>>> definitions, the methods will behave well for products if they behave well >>>>>> for the underlying functors. >>>>>> >>>>>> On Fri, Dec 14, 2018 at 12:12 AM Gershom B >>>>>> wrote: >>>>>> >>>>>>> Can you give an example of where the new definitions and current >>>>>>> definitions of functor products would yield different behavior? >>>>>>> >>>>>>> -g >>>>>>> >>>>>>> >>>>>>> On December 14, 2018 at 12:03:32 AM, David Feuer ( >>>>>>> david.feuer at gmail.com) wrote: >>>>>>> >>>>>>> Currently, we document this law: >>>>>>> >>>>>>> > If defined, some and many should be the least solutions of the >>>>>>> equations: >>>>>>> > >>>>>>> > some v = (:) <$> v <*> many v >>>>>>> > many v = some v <|> pure [] >>>>>>> >>>>>>> This seems a bit too strong. I believe we should weaken "should be >>>>>>> the least solutions of" to "should obey". This allows non-bottoming >>>>>>> implementations for more types. I would be surprised if the change would >>>>>>> meaningfully weaken the value of the law for reasoning about real programs. >>>>>>> >>>>>>> For example, we currently require >>>>>>> >>>>>>> some Nothing = Nothing >>>>>>> some (Just x) = _|_ >>>>>>> >>>>>>> many Nothing = Just [] >>>>>>> many (Just x) = _|_ >>>>>>> >>>>>>> But if we weaken the law, we could instead use >>>>>>> >>>>>>> some Nothing = Nothing >>>>>>> some (Just x) = Just (repeat x) >>>>>>> >>>>>>> many Nothing = Just [] >>>>>>> many (Just x) = Just (repeat x) >>>>>>> >>>>>>> This seems strictly, albeit slightly, more interesting. >>>>>>> >>>>>>> More significantly, I think, the instance for functor products can >>>>>>> also get much better-defined: >>>>>>> >>>>>>> some (x :*: y) = some x :*: some y >>>>>>> many (x :*: y) = many x :*: many y >>>>>>> >>>>>>> That strikes me as an improvement that may actually be of some >>>>>>> practical value. >>>>>>> _______________________________________________ >>>>>>> Libraries mailing list >>>>>>> Libraries at haskell.org >>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>>>> >>>>>>> _______________________________________________ >>>>> Libraries mailing list >>>>> Libraries at haskell.org >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>> >>>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>> -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Wed Dec 19 19:25:44 2018 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Wed, 19 Dec 2018 14:25:44 -0500 Subject: Dump core of base Message-ID: How does one go about using -ddump-simpl -dsuppress-all -ddump-to-file (or variations of this) when building base? I've got some strong suspicions that that are arguments to event manager functions that are morally strict that go unnoticed by demand analysis. However, I need to dump base's core to confirm this. -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Wed Dec 19 19:32:52 2018 From: david.feuer at gmail.com (David Feuer) Date: Wed, 19 Dec 2018 14:32:52 -0500 Subject: Dump core of base In-Reply-To: References: Message-ID: I don't happen to know the answer to your question, but when hacking on base, you can often get the job done much faster by copying the necessary source files somewhere else and renaming modules as necessary. Recompiling base is a pain and a half. On Wed, Dec 19, 2018 at 2:26 PM Andrew Martin wrote: > How does one go about using -ddump-simpl -dsuppress-all -ddump-to-file (or > variations of this) when building base? I've got some strong suspicions > that that are arguments to event manager functions that are morally strict > that go unnoticed by demand analysis. However, I need to dump base's core > to confirm this. > > -- > -Andrew Thaddeus Martin > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Wed Dec 19 20:04:29 2018 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Wed, 19 Dec 2018 20:04:29 +0000 Subject: Dump core of base In-Reply-To: References: Message-ID: Looking at the doc/user-setting.md file for Hadrian, I would guess the following. https://github.com/ghc/ghc/blob/master/hadrian/doc/user-settings.md 1. Copy hadrian/src/UserSettings.hs to hadrian/UserSetting.hs 2. Define ``` dumpArgs = userArgs = builder Ghc ? package base ? arg "-ddump-simpl -ddump-to-file -ddump-dir=foo" ``` 3. Create a build flavour something like userFlavour = quickestFlavour { name = "user", args = (args quickestFlavour) <> dumpArgs } 4. Compile with `./hadrian.sh -j --flavour=user` On Wed, Dec 19, 2018 at 7:33 PM David Feuer wrote: > > I don't happen to know the answer to your question, but when hacking on base, you can often get the job done much faster by copying the necessary source files somewhere else and renaming modules as necessary. Recompiling base is a pain and a half. > > On Wed, Dec 19, 2018 at 2:26 PM Andrew Martin wrote: >> >> How does one go about using -ddump-simpl -dsuppress-all -ddump-to-file (or variations of this) when building base? I've got some strong suspicions that that are arguments to event manager functions that are morally strict that go unnoticed by demand analysis. However, I need to dump base's core to confirm this. >> >> -- >> -Andrew Thaddeus Martin >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From rae at cs.brynmawr.edu Wed Dec 19 20:08:02 2018 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Wed, 19 Dec 2018 15:08:02 -0500 Subject: Dump core of base In-Reply-To: References: Message-ID: <15A1F876-4EB8-42BF-A784-379FC7693FE5@cs.brynmawr.edu> > On Dec 19, 2018, at 2:25 PM, Andrew Martin wrote: > > How does one go about using -ddump-simpl -dsuppress-all -ddump-to-file (or variations of this) when building base? Add a line like GhcLibHcOpts += -ddump-simpl -dsuppress-all -ddump-to-file at the end of your build.mk. You can see other similar options in the files in the flavours subdirectory of the mk directory. I hope this helps! Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Wed Dec 19 20:18:46 2018 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Wed, 19 Dec 2018 15:18:46 -0500 Subject: Dump core of base In-Reply-To: <15A1F876-4EB8-42BF-A784-379FC7693FE5@cs.brynmawr.edu> References: <15A1F876-4EB8-42BF-A784-379FC7693FE5@cs.brynmawr.edu> Message-ID: Awesome, thanks! That's good to know. On Wed, Dec 19, 2018 at 3:08 PM Richard Eisenberg wrote: > > > On Dec 19, 2018, at 2:25 PM, Andrew Martin > wrote: > > How does one go about using -ddump-simpl -dsuppress-all -ddump-to-file (or > variations of this) when building base? > > > Add a line like > > GhcLibHcOpts += -ddump-simpl -dsuppress-all -ddump-to-file > > at the end of your build.mk. You can see other similar options in the > files in the flavours subdirectory of the mk directory. > > I hope this helps! > Richard > > -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Dec 20 03:22:15 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 19 Dec 2018 22:22:15 -0500 Subject: Dump core of base In-Reply-To: References: <15A1F876-4EB8-42BF-A784-379FC7693FE5@cs.brynmawr.edu> Message-ID: cool! please do share if you can construct a scenario/usage where the thunkery becomes the bottleneck! On Wed, Dec 19, 2018 at 3:19 PM Andrew Martin wrote: > Awesome, thanks! That's good to know. > > On Wed, Dec 19, 2018 at 3:08 PM Richard Eisenberg > wrote: > >> >> >> On Dec 19, 2018, at 2:25 PM, Andrew Martin >> wrote: >> >> How does one go about using -ddump-simpl -dsuppress-all -ddump-to-file >> (or variations of this) when building base? >> >> >> Add a line like >> >> GhcLibHcOpts += -ddump-simpl -dsuppress-all -ddump-to-file >> >> at the end of your build.mk. You can see other similar options in the >> files in the flavours subdirectory of the mk directory. >> >> I hope this helps! >> Richard >> >> > > -- > -Andrew Thaddeus Martin > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From isaace71295 at gmail.com Fri Dec 21 01:22:22 2018 From: isaace71295 at gmail.com (Isaac Elliott) Date: Fri, 21 Dec 2018 11:22:22 +1000 Subject: Fwd: Applicative-based definitions in Data.Foldable In-Reply-To: References: Message-ID: With the introduction of the 'Ap' monoid in base-4.13, it seems like Applicative based definitions for common folds would be appropriate in base. For example: > allA :: (Applicative f, Foldable t) => (a -> f Bool) -> t a -> f Bool > allA f = fmap getAll . getAp . foldMap (Ap . fmap All . f) > > all :: Foldable t => (a -> Bool) -> t a -> Bool > all f = runIdentity . allA (Identity . f) I've personally written the Applicative version in everyday code. Thoughts? Isaac -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Fri Dec 21 02:57:45 2018 From: david.feuer at gmail.com (David Feuer) Date: Thu, 20 Dec 2018 21:57:45 -0500 Subject: Applicative-based definitions in Data.Foldable In-Reply-To: References: Message-ID: Can you give a few examples of where you'd want that? I can't think of a good application off the top of my head. On Thu, Dec 20, 2018 at 8:22 PM Isaac Elliott wrote: > With the introduction of the 'Ap' monoid in base-4.13, it seems like > Applicative based definitions for common folds would be appropriate in base. > > For example: > >> allA :: (Applicative f, Foldable t) => (a -> f Bool) -> t a -> f Bool >> allA f = fmap getAll . getAp . foldMap (Ap . fmap All . f) >> > > >> all :: Foldable t => (a -> Bool) -> t a -> Bool >> all f = runIdentity . allA (Identity . f) > > > I've personally written the Applicative version in everyday code. Thoughts? > > Isaac > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.thaddeus at gmail.com Fri Dec 21 16:37:08 2018 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Fri, 21 Dec 2018 11:37:08 -0500 Subject: Benchmarks for the Event Manager? Message-ID: Are there any easy-to-build benchmarks for the GHC event manager? There's some stuff in https://github.com/tibbe/event, but that repo hasn't been touched in 9 years, and it looks like the benchmarks in it were not pulled into GHC itself. I've found some stuff for benchmarking the event manager against stdio (an alternative event manager than builds on top of libuv), but I wanted to check and see if there are any other benchmark suites out there. -- -Andrew Thaddeus Martin -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Dec 22 02:23:39 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 21 Dec 2018 21:23:39 -0500 Subject: Benchmarks for the Event Manager? In-Reply-To: References: Message-ID: i suspect not :) note well: this sort of stuff is super tricky to measure well / reproducibly. I remember some discussions I had with folks a few years ago where I learned it was a bit tricky to replicate the configurations of various systems for the benchmarks! On Fri, Dec 21, 2018 at 11:37 AM Andrew Martin wrote: > Are there any easy-to-build benchmarks for the GHC event manager? There's > some stuff in https://github.com/tibbe/event, but that repo hasn't been > touched in 9 years, and it looks like the benchmarks in it were not pulled > into GHC itself. I've found some stuff for benchmarking the event manager > against stdio (an alternative event manager than builds on top of libuv), > but I wanted to check and see if there are any other benchmark suites out > there. > > -- > -Andrew Thaddeus Martin > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Dec 22 02:24:24 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 21 Dec 2018 21:24:24 -0500 Subject: Benchmarks for the Event Manager? In-Reply-To: References: Message-ID: (point being: if you do have a go at it, the more its easy to replicate your systems config etc, the better :) ) On Fri, Dec 21, 2018 at 9:23 PM Carter Schonwald wrote: > i suspect not :) > > note well: this sort of stuff is super tricky to measure well / > reproducibly. > > I remember some discussions I had with folks a few years ago where I > learned it was a bit tricky to replicate the configurations of various > systems for the benchmarks! > > On Fri, Dec 21, 2018 at 11:37 AM Andrew Martin > wrote: > >> Are there any easy-to-build benchmarks for the GHC event manager? There's >> some stuff in https://github.com/tibbe/event, but that repo hasn't been >> touched in 9 years, and it looks like the benchmarks in it were not pulled >> into GHC itself. I've found some stuff for benchmarking the event manager >> against stdio (an alternative event manager than builds on top of libuv), >> but I wanted to check and see if there are any other benchmark suites out >> there. >> >> -- >> -Andrew Thaddeus Martin >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Sat Dec 22 04:11:24 2018 From: ben at smart-cactus.org (Ben Gamari) Date: Fri, 21 Dec 2018 23:11:24 -0500 Subject: Benchmarks for the Event Manager? In-Reply-To: References: Message-ID: <12EDC478-D021-46DA-AA64-48C2AFFB7479@smart-cactus.org> On December 21, 2018 9:23:39 PM EST, Carter Schonwald wrote: >i suspect not :) > >note well: this sort of stuff is super tricky to measure well / >reproducibly. > I also don't know of any benchmarks beyond the recent work on stdio. However, Carter is quite right in saying that this sort of thing is quite tricky to benchmark properly. Cheers, - Ben -- Sent from my Android device with K-9 Mail. Please excuse my brevity. From carter.schonwald at gmail.com Sat Dec 22 15:54:21 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 22 Dec 2018 10:54:21 -0500 Subject: Benchmarks for the Event Manager? In-Reply-To: <12EDC478-D021-46DA-AA64-48C2AFFB7479@smart-cactus.org> References: <12EDC478-D021-46DA-AA64-48C2AFFB7479@smart-cactus.org> Message-ID: Yeah, this can’t be emphasized enough: different setups and workloads will measure different things / possibly contradict if you don’t look at what they measure carefully. On Fri, Dec 21, 2018 at 11:11 PM Ben Gamari wrote: > > > On December 21, 2018 9:23:39 PM EST, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >i suspect not :) > > > >note well: this sort of stuff is super tricky to measure well / > >reproducibly. > > > I also don't know of any benchmarks beyond the recent work on stdio. > However, Carter is quite right in saying that this sort of thing is quite > tricky to benchmark properly. > > Cheers, > > - Ben > > > -- > Sent from my Android device with K-9 Mail. Please excuse my brevity. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Fri Dec 28 13:18:54 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Fri, 28 Dec 2018 14:18:54 +0100 Subject: Data.List.maximumBy uses counter-intuitive ordering Message-ID: <01bece8d-8846-a8a4-3b38-acf90270f5e7@htwk-leipzig.de> Dear all, this was brought up on the GHC tracker (not by me) https://ghc.haskell.org/trac/ghc/ticket/15921 and it was suggested for discussion here. my summary: Data.List.maximumBy is right-biased, minimumBy is left-biased, and none of this is documented. - J.W. From emertens at gmail.com Fri Dec 28 15:26:37 2018 From: emertens at gmail.com (Eric Mertens) Date: Fri, 28 Dec 2018 09:26:37 -0600 Subject: Data.List.maximumBy uses counter-intuitive ordering In-Reply-To: <01bece8d-8846-a8a4-3b38-acf90270f5e7@htwk-leipzig.de> References: <01bece8d-8846-a8a4-3b38-acf90270f5e7@htwk-leipzig.de> Message-ID: <36AD0CE4-12DA-4402-B1BE-ACA4AF9FB4D0@gmail.com> Hello, My opinion on this issue is that code should not be relying on the ordering of the choice made by maximumBy or minimumBy. If we changed something I’d prefer to document that it is undefined what element is chosen when two are considered equal by the comparison function. Code that relies on a particular earlier or later bias should use a function that makes it clear in the name that that’s what it’s doing. Readers should not be required to memorize the behavior of minimumBy or maximumBy in this regard to understand the code they are reading. Best regards, Eric > On Dec 28, 2018, at 7:18 AM, Johannes Waldmann wrote: > > Dear all, > > this was brought up on the GHC tracker (not by me) > > https://ghc.haskell.org/trac/ghc/ticket/15921 > > and it was suggested for discussion here. > > my summary: Data.List.maximumBy is right-biased, > minimumBy is left-biased, and none of this is documented. > > - J.W. > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From lemming at henning-thielemann.de Fri Dec 28 15:37:50 2018 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 28 Dec 2018 16:37:50 +0100 (CET) Subject: Data.List.maximumBy uses counter-intuitive ordering In-Reply-To: <01bece8d-8846-a8a4-3b38-acf90270f5e7@htwk-leipzig.de> References: <01bece8d-8846-a8a4-3b38-acf90270f5e7@htwk-leipzig.de> Message-ID: On Fri, 28 Dec 2018, Johannes Waldmann wrote: > Dear all, > > this was brought up on the GHC tracker (not by me) > > https://ghc.haskell.org/trac/ghc/ticket/15921 > > and it was suggested for discussion here. > > my summary: Data.List.maximumBy is right-biased, > minimumBy is left-biased, and none of this is documented. Btw. Data.Semigroup exports Min and Max that are both left-biased: Prelude Data.Semigroup> min (Arg 2 3) (Arg 2 2) :: Arg Int Int Arg 2 3 Prelude Data.Semigroup> max (Arg 2 3) (Arg 2 2) :: Arg Int Int Arg 2 3 From w-m at wmcode.nl Fri Dec 28 22:25:15 2018 From: w-m at wmcode.nl (Wiebe-Marten Wijnja) Date: Fri, 28 Dec 2018 23:25:15 +0100 Subject: Data.List.maximumBy uses counter-intuitive ordering Message-ID: <00cb7901-8f27-bbb1-5a03-351be8855e77@wmcode.nl> //>/> my summary: Data.List.maximumBy is right-biased, />/> minimumBy is left-biased, and none of this is documented. / > Btw. Data.Semigroup exports Min and Max that are both left-biased The difference between these two pairs of functions that are very similar (and one will with high probability first or more frequently use `Data.Semigroup.min/max` until one encounters a data-structure that e.g. needs to be sorted in different ways in different contexts, which is when minimumBy/maximumBy enter the stage.) All five Haskell developers I know personally that I asked about what they expected of the code snippet (that was also given in the GHC issue, #15921): ``` Data.List.maximumBy (Data.Ord.comparing snd) [(0, 1), (3, 2), (2, 2), (1, 1)] ``` expected it to use right-biased ordering in the implementation. (making the outcome `(3, 2)` whereas in reality it will be `(2, 2)` I believe that we should: - align the implementations of minimumBy/maximumBy with Data.Semigroup.min/max to make sure it follows the principle of least surprise. - If not possible (for instance, if there is a good reason that is as of yet unknown to me to keep the current behaviour), we should improve the current documentation with the current bias behaviour. (or potentially instead make it explicitly implementation-defined with a statement like 'you should not assume a specific ordering between items that are considered equal by the chosen relation'). Thank you, ~Wiebe-Marten Wijnja/Qqwy -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 833 bytes Desc: OpenPGP digital signature URL: