From m at jaspervdj.be Fri Nov 2 11:01:42 2018 From: m at jaspervdj.be (Jasper Van der Jeugt) Date: Fri, 2 Nov 2018 12:01:42 +0100 Subject: [Haskell-cafe] 2018 State of Haskell Survey Message-ID: <20181102110142.GA2010@colony6.localdomain> Hi all, (apologies if you receive multiple copies of this email) We are running a 2018 State of Haskell Survey here: https://airtable.com/shr8G4RBPD9T6tnDf If you have some time to spare, please submit a response. This goes a long way in helping the community. The survey closes on the 15th of November. This survey is co-sponsored by Haskell.org and Haskell Weekly, but I'd like to give credit where credit is due, so I'll add that Taylor Fausak did almost all of the hard work -- thanks a lot! Kind regards Jasper Van der Jeugt on behalf of the Haskell.org committee From theedge456 at free.fr Fri Nov 2 12:08:40 2018 From: theedge456 at free.fr (Fabien R) Date: Fri, 2 Nov 2018 13:08:40 +0100 Subject: [Haskell-cafe] reading file content with conduit Message-ID: <6861b11c-e5d6-8896-2b28-9f441e0297d0@free.fr> Hello, I have a strange behaviour with my code when reading data from a file saved by sinkFile. I only see the first record of the file, although the file seems to contain several records. Any hints ? -- built in a sandbox with GHC 8.2.2, base 4.10.1.0, binary 0.8.5.1, bytestring 0.8.10.2, conduit 1.3.1 {-# LANGUAGE DeriveGeneric #-} import qualified Data.ByteString as DB import qualified Data.ByteString.Lazy as DBL import qualified Data.Binary as DBI import GHC.Generics (Generic) import Conduit import Data.Int (Int64) data MySubRec = MySubRec { sr1 :: Float, sr2 :: Float } deriving (Generic, Show) data MyRec = MyRec { r1 :: Int64, r2 :: String, r3 :: [MySubRec], r4 :: [MySubRec] } deriving (Generic, Show) instance DBI.Binary MySubRec instance DBI.Binary MyRec es = MySubRec { sr1 =1.0, sr2 =1000.5 } myList = repeat es e1 = MyRec{ r1=1, r2="e1", r3=take 2 myList, r4=take 1 myList} e2 = MyRec{ r1=2, r2="e2", r3=take 2 myList, r4=take 1 myList} myData = concat $ repeat [e1,e2] dataToBs :: Monad m => ConduitT MyRec DB.ByteString m () dataToBs = do d <- await case d of Just bs -> do yield $ DBL.toStrict $ DBI.encode bs dataToBs _ -> return () bsToData :: Monad m => ConduitT DB.ByteString MyRec m () bsToData = do d <- await case d of Just bs -> do yield $ DBI.decode $ DBL.fromStrict bs bsToData _ -> return () main = do runConduitRes $ yieldMany (take 10 myData) .| dataToBs .| sinkFile "/tmp/res.bin" runConduitRes $ sourceFile "/tmp/res.bin" .| bsToData .| mapM_C (liftIO . putStrLn . show) From alexander.vershilov at gmail.com Fri Nov 2 12:15:36 2018 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Fri, 2 Nov 2018 15:15:36 +0300 Subject: [Haskell-cafe] reading file content with conduit In-Reply-To: <6861b11c-e5d6-8896-2b28-9f441e0297d0@free.fr> References: <6861b11c-e5d6-8896-2b28-9f441e0297d0@free.fr> Message-ID: Hello Fabien, in your example, the problem is that sourceFile gives you a bytestring chunk that contains more than one record and decoding function does not return a list of values, instead return only one. So you need to pass the leftover data to the next decoding round. You may consider using https://hackage.haskell.org/package/binary-conduit package that does that (see https://hackage.haskell.org/package/binary-conduit-1.3.1/docs/src/Data.Conduit.Serialization.Binary.html#conduitGet) -- Best regards, Alexander. On Fri, 2 Nov 2018 at 15:09, Fabien R wrote: > > Hello, > I have a strange behaviour with my code when reading data from a file saved by sinkFile. > I only see the first record of the file, although the file seems to contain several records. > > Any hints ? > > -- built in a sandbox with GHC 8.2.2, base 4.10.1.0, binary 0.8.5.1, bytestring 0.8.10.2, conduit 1.3.1 > {-# LANGUAGE DeriveGeneric #-} > import qualified Data.ByteString as DB > import qualified Data.ByteString.Lazy as DBL > import qualified Data.Binary as DBI > import GHC.Generics (Generic) > import Conduit > import Data.Int (Int64) > > data MySubRec = MySubRec { sr1 :: Float, > sr2 :: Float } > deriving (Generic, Show) > > data MyRec = MyRec { r1 :: Int64, > r2 :: String, > r3 :: [MySubRec], > r4 :: [MySubRec] > } > deriving (Generic, Show) > > instance DBI.Binary MySubRec > instance DBI.Binary MyRec > > es = MySubRec { sr1 =1.0, sr2 =1000.5 } > myList = repeat es > e1 = MyRec{ r1=1, r2="e1", r3=take 2 myList, r4=take 1 myList} > e2 = MyRec{ r1=2, r2="e2", r3=take 2 myList, r4=take 1 myList} > myData = concat $ repeat [e1,e2] > > dataToBs :: Monad m => > ConduitT MyRec DB.ByteString m () > dataToBs = do > d <- await > case d of > Just bs -> do > yield $ DBL.toStrict $ DBI.encode bs > dataToBs > _ -> return () > bsToData :: Monad m => > ConduitT DB.ByteString MyRec m () > bsToData = do > d <- await > case d of > Just bs -> do > yield $ DBI.decode $ DBL.fromStrict bs > bsToData > _ -> return () > main = do > runConduitRes $ yieldMany (take 10 myData) .| dataToBs .| sinkFile "/tmp/res.bin" > runConduitRes $ sourceFile "/tmp/res.bin" .| bsToData .| mapM_C (liftIO . putStrLn . show) > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Alexander From leiva.steven at gmail.com Fri Nov 2 15:32:09 2018 From: leiva.steven at gmail.com (Steven Leiva) Date: Fri, 2 Nov 2018 11:32:09 -0400 Subject: [Haskell-cafe] 2018 State of Haskell Survey In-Reply-To: <20181102110142.GA2010@colony6.localdomain> References: <20181102110142.GA2010@colony6.localdomain> Message-ID: No one likes doing surveys, but I feel that it is the least I can do for the Haskell community, especially considering all the help and benefits I get from it. Thanks Jasper for posting this - I’m filling mine out now. On November 2, 2018 at 6:02:14 AM, Jasper Van der Jeugt (m at jaspervdj.be) wrote: Hi all, (apologies if you receive multiple copies of this email) We are running a 2018 State of Haskell Survey here: https://airtable.com/shr8G4RBPD9T6tnDf If you have some time to spare, please submit a response. This goes a long way in helping the community. The survey closes on the 15th of November. This survey is co-sponsored by Haskell.org and Haskell Weekly, but I'd like to give credit where credit is due, so I'll add that Taylor Fausak did almost all of the hard work -- thanks a lot! Kind regards Jasper Van der Jeugt on behalf of the Haskell.org committee _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From andre at popovit.ch Sat Nov 3 01:46:32 2018 From: andre at popovit.ch (=?UTF-8?Q?Andr=C3=A9_Popovitch?=) Date: Fri, 2 Nov 2018 21:46:32 -0400 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource Message-ID: If you follow /r/haskell you may have seen it posted there as well, but I've written a short guide called Wise Man's Haskell which I hope people will find useful. However, I'm not extremely knowledgeable about Haskell and I wouldn't say I'm the best teacher, so if anyone is willing to skim it or provide feedback that would be much appreciated! -------------- next part -------------- An HTML attachment was scrubbed... URL: From jo at durchholz.org Sat Nov 3 08:22:59 2018 From: jo at durchholz.org (Joachim Durchholz) Date: Sat, 3 Nov 2018 09:22:59 +0100 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: Message-ID: Am 03.11.18 um 02:46 schrieb André Popovitch: > However, > I'm not extremely knowledgeable about Haskell and I wouldn't say I'm the > best teacher, so if anyone is willing to skim it or provide feedback > that would be much appreciated! One kind of typo that's common enough to become annoying: comma/fullstop and subsequent space were interchanged. Well-written overall. I'm pretty sure different people will have different ideas about what's important about Haskell, but I think your take is valid. Besides, the knowledgeable people won't know what a newbie will find most interesting or enlightening about Haskell, so you'll have to get feedback from non-Haskellers to judge how successful that site is. Some details aren't quite right (as is to be expected with anything that goes beyond a dozen pages). E.g. mutability does increase the number of variables you have to keep track of, it multiplies the amount of information you have to keep track of for each variable (namely the set of locations where it is changed). Stating that Haskell does not have side effects will cause cognitive dissonance. Technically, Haskell does not have it, but there's that technique to put state into a function that you return, hiding the state not in a transparent data object but in a pretty opaque function object. This is being systematically (ab?)used in many monads, and in practice, it has exactly the same benefit as a mutable global state (you don't have to thread it through every function call, it's globally available), and the same problems (you don't know where it might be changed). And then there's IO, which is a different way to do mutability except by name. (I have never been able to find out what the concept behind IO is. My best guess is that it's a framework to set up descriptions of IO interactions, which tend to be infinite which isn't a problem since Haskell is lazy, but this may well be totally wrong. SPJ seemingly takes this for granted, and all the docs I could find just described the mechanics of using it, often with an implicit assumption that IO is a magical mutability enclave in Haskell, which I'm pretty sure is not actually the case.) I don't know enough to give good advice how to be neither wrong enough to confuse newbies with cognitive dissonance nor correct enough to confuse newbies with the full truth. You should mention that `rem` needs to be typed including backquotes. With some fonts, they might look similar enough to normal quotes, and then be ignored. (That point in the presentation might be a good place for a side remark, explaining how Haskell allows using operators as functions, and how it allows using functions as operators.) A sidebar notice might help to explain that Haskell's function call syntax is nearer to mathematical than programming language conventions: Mathematicians write "sin x", not "sin(x)"; they use parentheses only when precedences get in the way, e.g. they'll write "(sin x) + 1" if needed, or maybe "sin (x + 1)" but the "(x + 1)" isn't function-call syntax, it's precedence-altering syntax. (As conventions go in mathematics, it's just a common one, not a universal one. Mathematicians are horribly sloppy about their conventions. In fact they are sloppy about anything except the topic they're currently interested in. Well, programmers are obsessed about irrelevant detail because compilers force them into that habit, from their perspective, so both sides are right in a sense ;-) Okay, enough for now. Regards, Jo From allbery.b at gmail.com Sat Nov 3 08:31:46 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 3 Nov 2018 04:31:46 -0400 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: Message-ID: Conceptualization of IO is difficult. One way to think about it is the result of (main :: IO a) is a program sent to an impure runtime to execute, with IO actions being compositions of instructions for the runtime… but this breaks down as soon as you discover unsafePerformIO. The closest that you'll get to the reality for GHC is that it pretty much is a haven for impurity: that it forces all impure functions to declare that in their types. (Not necessarily for mutability as such; ST gives you that without impurity.) On Sat, Nov 3, 2018 at 4:23 AM Joachim Durchholz wrote: > Am 03.11.18 um 02:46 schrieb André Popovitch: > > However, > > I'm not extremely knowledgeable about Haskell and I wouldn't say I'm the > > best teacher, so if anyone is willing to skim it or provide feedback > > that would be much appreciated! > > One kind of typo that's common enough to become annoying: > comma/fullstop and subsequent space were interchanged. > > Well-written overall. I'm pretty sure different people will have > different ideas about what's important about Haskell, but I think your > take is valid. > Besides, the knowledgeable people won't know what a newbie will find > most interesting or enlightening about Haskell, so you'll have to get > feedback from non-Haskellers to judge how successful that site is. > > Some details aren't quite right (as is to be expected with anything that > goes beyond a dozen pages). > > E.g. mutability does increase the number of variables you have to keep > track of, it multiplies the amount of information you have to keep track > of for each variable (namely the set of locations where it is changed). > > Stating that Haskell does not have side effects will cause cognitive > dissonance. > Technically, Haskell does not have it, but there's that technique to put > state into a function that you return, hiding the state not in a > transparent data object but in a pretty opaque function object. This is > being systematically (ab?)used in many monads, and in practice, it has > exactly the same benefit as a mutable global state (you don't have to > thread it through every function call, it's globally available), and the > same problems (you don't know where it might be changed). > And then there's IO, which is a different way to do mutability except by > name. (I have never been able to find out what the concept behind IO is. > My best guess is that it's a framework to set up descriptions of IO > interactions, which tend to be infinite which isn't a problem since > Haskell is lazy, but this may well be totally wrong. SPJ seemingly takes > this for granted, and all the docs I could find just described the > mechanics of using it, often with an implicit assumption that IO is a > magical mutability enclave in Haskell, which I'm pretty sure is not > actually the case.) > I don't know enough to give good advice how to be neither wrong enough > to confuse newbies with cognitive dissonance nor correct enough to > confuse newbies with the full truth. > > You should mention that `rem` needs to be typed including backquotes. > With some fonts, they might look similar enough to normal quotes, and > then be ignored. > (That point in the presentation might be a good place for a side remark, > explaining how Haskell allows using operators as functions, and how it > allows using functions as operators.) > > A sidebar notice might help to explain that Haskell's function call > syntax is nearer to mathematical than programming language conventions: > Mathematicians write "sin x", not "sin(x)"; they use parentheses only > when precedences get in the way, e.g. they'll write "(sin x) + 1" if > needed, or maybe "sin (x + 1)" but the "(x + 1)" isn't function-call > syntax, it's precedence-altering syntax. > (As conventions go in mathematics, it's just a common one, not a > universal one. Mathematicians are horribly sloppy about their > conventions. In fact they are sloppy about anything except the topic > they're currently interested in. Well, programmers are obsessed about > irrelevant detail because compilers force them into that habit, from > their perspective, so both sides are right in a sense ;-) > > Okay, enough for now. > > Regards, > Jo > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From jo at durchholz.org Sat Nov 3 08:59:57 2018 From: jo at durchholz.org (Joachim Durchholz) Date: Sat, 3 Nov 2018 09:59:57 +0100 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: Message-ID: Am 03.11.18 um 09:31 schrieb Brandon Allbery: > Conceptualization of IO is difficult. One way to think about it is the > result of (main :: IO a) is a program sent to an impure runtime to > execute, with IO actions being compositions of instructions for the > runtime… but this breaks down as soon as you discover unsafePerformIO. I have been thinking that that's just a conceptual accident: pure functions are enough to get all the useful effects (and most of the downsides) of global variables and mutable state, but pure functions cannot do IO. So unsafePerformIO is the one unsafe thing that was kept, other unsafe operations were either dropped or never made it into Haskell (remember that Haskell was designed by people who had been doing pure nonstrict languages for a decade or more). > The closest that you'll get to the reality for GHC is that it pretty > much is a haven for impurity: that it forces all impure functions to > declare that in their types. If Haskell is truly pure, then IO must be pure as well. That's why I think that IO functions are just describing impure activity, not doing it. I have not been able to verify whether this is actually true. Maybe IO is really a wart on Haskell's purity. I'd hate it if it were, and I think the Haskell design group would have hated that as well. OTOH IO is one of three approaches, and it happened to be the one that became usable first, so it's not part of the initial design process. Then again I like to think that SPJ wouldn't even contemplate something impure - but I don't really know. From allbery.b at gmail.com Sat Nov 3 09:05:00 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 3 Nov 2018 05:05:00 -0400 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: Message-ID: Go look at accursedUnutterablePerformIO (aka inlinePerformIO) sometime. IO's just a barrier for impurity, and if you make the barrier leaky then you can expect weird behavior at best. On Sat, Nov 3, 2018 at 5:00 AM Joachim Durchholz wrote: > Am 03.11.18 um 09:31 schrieb Brandon Allbery: > > Conceptualization of IO is difficult. One way to think about it is the > > result of (main :: IO a) is a program sent to an impure runtime to > > execute, with IO actions being compositions of instructions for the > > runtime… but this breaks down as soon as you discover unsafePerformIO. > > I have been thinking that that's just a conceptual accident: pure > functions are enough to get all the useful effects (and most of the > downsides) of global variables and mutable state, but pure functions > cannot do IO. So unsafePerformIO is the one unsafe thing that was kept, > other unsafe operations were either dropped or never made it into > Haskell (remember that Haskell was designed by people who had been doing > pure nonstrict languages for a decade or more). > > > The closest that you'll get to the reality for GHC is that it pretty > > much is a haven for impurity: that it forces all impure functions to > > declare that in their types. > If Haskell is truly pure, then IO must be pure as well. > That's why I think that IO functions are just describing impure > activity, not doing it. > I have not been able to verify whether this is actually true. Maybe IO > is really a wart on Haskell's purity. > I'd hate it if it were, and I think the Haskell design group would have > hated that as well. OTOH IO is one of three approaches, and it happened > to be the one that became usable first, so it's not part of the initial > design process. Then again I like to think that SPJ wouldn't even > contemplate something impure - but I don't really know. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From doug at cs.dartmouth.edu Sat Nov 3 15:23:54 2018 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Sat, 03 Nov 2018 11:23:54 -0400 Subject: [Haskell-cafe] 2018 State of Haskell Survey Message-ID: <201811031523.wA3FNsNp060253@tahoe.cs.Dartmouth.EDU> The survey didn't work for me in either Internet Explorer or Microsoft Edge: In IE an attempt to scroll a pull-down "Add an option" menu would dismiss the menu. In ME the same menus needed a scroll bar, but the bar was missing. Doug McIlroy From markus.l2ll at gmail.com Sat Nov 3 17:06:59 2018 From: markus.l2ll at gmail.com (=?UTF-8?B?TWFya3VzIEzDpGxs?=) Date: Sat, 3 Nov 2018 18:06:59 +0100 Subject: [Haskell-cafe] Get number of fields for non-record ADTs using Data type class? In-Reply-To: References: <72c4ff57-d397-5be5-73c3-642f993221d4@gmail.com> Message-ID: Hi and thank you for the answers -- I'll use Data for now since generics seem scary at this point. Another question :): is there a better way to get the constructor of some partially applied data constructor. My current solution follows (and it works), but I'm wondering if there is a better way? The issue is that I'm feeding `undefined`s until the constructor is saturated and then get the Constr, but it feels like using a loophole (the existence of `undefined`) to achieve the result. class GetConstr a where getConstr :: a -> Constr instance {-# OVERLAPPING #-} (GetConstr b) => GetConstr (a -> b) where getConstr f = getConstr (f undefined) instance {-# OVERLAPPABLE #-} (Data a) => GetConstr a where getConstr a = toConstr a On Mon, Oct 29, 2018 at 11:07 PM Artem Pelenitsyn wrote: > Oh, didn't know about `one-liner`. This looks v. nice. Thank you! > > -- Artem > > On Mon, 29 Oct 2018 at 17:52 Li-yao Xia wrote: > >> On 10/29/18 4:42 PM, Artem Pelenitsyn wrote: >> > I don't think there is a point in looking for >> > GHC.Generics-based solution, as Data.Data is the exact match for this >> > kind of problem. >> >> Although GHC.Generics has its shortcomings (usage complexity and compile >> times), I still find it worthwhile to advocate as a statically-typed >> alternative to the dynamically-typed Data.Data for many problems, >> including this one. >> >> Using the one-liner library (which is built around GHC.Generics), the >> equivalent line of code is: >> >> getSum . gfoldMap @AnyType (const 1) :: T -> Int >> >> Data.Data is more visible mainly because it comes with a lot of >> functionality baked into the standard library, whereas GHC.Generics >> provides only a minimal interface and we have to find everything else in >> separate packages. However, there is no fundamental reason why one is a >> better fit than the other for the task of counting constructor fields. >> >> Li-yao >> >> > >> > On Mon, 29 Oct 2018 at 16:35 Li-yao Xia > > > wrote: >> > >> > This maps every field to 1, and folds them together using (+): >> > >> > Data.Data.gmapQl (+) 0 (const 1) :: T -> Int >> > >> > (There has to be a similarly easy solution using GHC.Generics >> instead >> > but I can't think of one...) >> > >> > Li-yao >> > >> > On 10/29/18 2:56 PM, Markus Läll wrote: >> > > Dear list, >> > > >> > > Is it possible te get the number of fields for data constructors >> > for a >> > > plain ADT, i.e something with no record fields? E.g for >> > > >> > > data T = A Int Double | B String (Maybe String) >> > > >> > > it would give 2 for both `A` and `B`. >> > > >> > > For a record it's possible using the `constrFields` function from >> > Data.Data. >> > > >> > > I was trying to follow this tutorial by Christopher Done >> > > https://chrisdone.com/posts/data-typeable, and I feel that it >> > must be >> > > possible somehow to get these numbers with the gmap*/gfold* >> > functions, >> > > but the use of them is over my head at the moment. >> > > >> > > >> > > Best, >> > > >> > > >> > > >> > > -- >> > > Markus Läll >> > > >> > > _______________________________________________ >> > > Haskell-Cafe mailing list >> > > To (un)subscribe, modify options or view archives go to: >> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > Only members subscribed via the mailman list are allowed to post. >> > > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > To (un)subscribe, modify options or view archives go to: >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > Only members subscribed via the mailman list are allowed to post. >> > >> > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Markus Läll -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Sat Nov 3 21:14:19 2018 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Sat, 3 Nov 2018 22:14:19 +0100 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource Message-ID: <423EE1BF-CA40-4B05-B96D-3876857F0F43@aatal-apotheke.de> This guide would be a perfect fit for literate Haskell [1]. It is a file format where you mix markup (e.g. LaTeX) and Haskell, so the file can be interpreted either way. In a nutshell, your html content becomes Haskell comments or the Haskell becomes blocks in html. In that way, your readers could just load your document into ghci and play with it. Not sure whether html is supported out of the box, though. You might need to pass the .lhs file through pandoc [2] or another tool. Can anyone clarify/help on this? Cheers, Olaf [1] https://wiki.haskell.org/Literate_programming [2] https://groups.google.com/forum/#!topic/hakyll/lFfHAk2nxbs From amindfv at gmail.com Sat Nov 3 21:35:38 2018 From: amindfv at gmail.com (amindfv at gmail.com) Date: Sat, 3 Nov 2018 17:35:38 -0400 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: Message-ID: I don't really enjoy being "that person," but I read the title as meaning "Haskell for wise men" (as opposed to "wise people"). I don't know if you want to workshop names ("Haskell for the Wise"?), but as you've asked for feedback that's a glaring thing I'd note. Cheers, Tom > El 2 nov 2018, a las 21:46, André Popovitch escribió: > > If you follow /r/haskell you may have seen it posted there as well, but I've written a short guide called Wise Man's Haskell which I hope people will find useful. However, I'm not extremely knowledgeable about Haskell and I wouldn't say I'm the best teacher, so if anyone is willing to skim it or provide feedback that would be much appreciated! > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From theedge456 at free.fr Sun Nov 4 08:48:03 2018 From: theedge456 at free.fr (Fabien R) Date: Sun, 4 Nov 2018 09:48:03 +0100 Subject: [Haskell-cafe] reading file content with conduit In-Reply-To: References: <6861b11c-e5d6-8896-2b28-9f441e0297d0@free.fr> Message-ID: <97ccf78b-013b-c495-690c-7e6adbafafea@free.fr> Thanks Alexander, The package fixed the problem. I thought that, since a conduit is driven by downstream, if bsToData requested a record, sourceFile would only send the corresponding Bytestrings. -- Fabien From carter.schonwald at gmail.com Sun Nov 4 17:56:32 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 4 Nov 2018 12:56:32 -0500 Subject: [Haskell-cafe] Network deprecation In-Reply-To: References: Message-ID: can't say i have. maybe contact the libraries committee and or the libraries list to get the right eyeballs? On Wed, Oct 31, 2018 at 7:51 PM Evan Laforge wrote: > I'm starting to get deprecation warnings about Network in the network > package. I know this has been in the works for a long time, but now > that I search I can't find any info about the rationale and suggested > replacement (the deprecation message suggests Network.Socket, but this > is a completely different lower level api). Does anyone out there > have links to discussions, articles, or whatnot? > > Thanks in advance! > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Nov 4 18:27:30 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 4 Nov 2018 13:27:30 -0500 Subject: [Haskell-cafe] Network deprecation In-Reply-To: References: Message-ID: and or ask the authors? On Sun, Nov 4, 2018 at 12:56 PM Carter Schonwald wrote: > can't say i have. > > maybe contact the libraries committee and or the libraries list to get the > right eyeballs? > > On Wed, Oct 31, 2018 at 7:51 PM Evan Laforge wrote: > >> I'm starting to get deprecation warnings about Network in the network >> package. I know this has been in the works for a long time, but now >> that I search I can't find any info about the rationale and suggested >> replacement (the deprecation message suggests Network.Socket, but this >> is a completely different lower level api). Does anyone out there >> have links to discussions, articles, or whatnot? >> >> Thanks in advance! >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From Graham.Hutton at nottingham.ac.uk Mon Nov 5 09:51:22 2018 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Mon, 5 Nov 2018 09:51:22 +0000 Subject: [Haskell-cafe] Journal of Functional Programming - Call for PhD Abstracts Message-ID: Dear all, If you or one of your students recently completed a PhD in the area of functional programming, please submit the dissertation abstract for publication in JFP: simple process, no refereeing, open access, deadline 30th November 2018. Please share! Best wishes, Graham Hutton ============================================================ CALL FOR PHD ABSTRACTS Journal of Functional Programming Deadline: 30th November 2018 http://tinyurl.com/jfp-phd-abstracts ============================================================ PREAMBLE: Many students complete PhDs in functional programming each year. As a service to the community, the Journal of Functional Programming publishes the abstracts from PhD dissertations completed during the previous year. The abstracts are made freely available on the JFP website, i.e. not behind any paywall. They do not require any transfer of copyright, merely a license from the author. A dissertation is eligible for inclusion if parts of it have or could have appeared in JFP, that is, if it is in the general area of functional programming. The abstracts are not reviewed. Please submit dissertation abstracts according to the instructions below. We welcome submissions from both the PhD student and PhD advisor/supervisor although we encourage them to coordinate. ============================================================ SUBMISSION: Please submit the following information to Graham Hutton by 30th November 2018. o Dissertation title: (including any subtitle) o Student: (full name) o Awarding institution: (full name and country) o Date of PhD award: (month and year; depending on the institution, this may be the date of the viva, corrections being approved, graduation ceremony, or otherwise) o Advisor/supervisor: (full names) o Dissertation URL: (please provide a permanently accessible link to the dissertation if you have one, such as to an institutional repository or other public archive; links to personal web pages should be considered a last resort) o Dissertation abstract: (plain text, maximum 350 words; you may use \emph{...} for emphasis, but we prefer no other markup or formatting; if your original abstract exceeds the word limit, please submit an abridged version within the limit) Please do not submit a copy of the dissertation itself, as this is not required. JFP reserves the right to decline to publish abstracts that are not deemed appropriate. ============================================================ PHD ABSTRACT EDITOR: Graham Hutton School of Computer Science University of Nottingham Nottingham NG8 1BB United Kingdom ============================================================ This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please contact the sender and delete the email and attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. Email communications with the University of Nottingham may be monitored where permitted by law. From alexander.vershilov at gmail.com Mon Nov 5 10:17:46 2018 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Mon, 5 Nov 2018 13:17:46 +0300 Subject: [Haskell-cafe] reading file content with conduit In-Reply-To: <97ccf78b-013b-c495-690c-7e6adbafafea@free.fr> References: <6861b11c-e5d6-8896-2b28-9f441e0297d0@free.fr> <97ccf78b-013b-c495-690c-7e6adbafafea@free.fr> Message-ID: Hello Fabien, your expectations are correct, but in order to make this really happen your consumer function should be aware of the conduit pipeline in order to consume only the required amount of data. That may happen automatically in two cases: 1. your function consumes an entire chunk 2. your function can work in an iterative way and can return unprocessed data or continuation that may consume more data (the case of iterative API in binary) A nice example of the function that is related to your use case and aware of the conduit pipeline: https://hackage.haskell.org/package/conduit-extra-1.3.0/docs/Data-Conduit-Attoparsec.html If you pass a parser in sinkParser, it will consume only the required amount of data. -- Alexander On Sun, 4 Nov 2018 at 11:48, Fabien R wrote: > > Thanks Alexander, > The package fixed the problem. > I thought that, since a conduit is driven by downstream, > if bsToData requested a record, sourceFile would only send the corresponding Bytestrings. > > -- > Fabien > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Alexander From Andrew.Butterfield at scss.tcd.ie Mon Nov 5 10:40:17 2018 From: Andrew.Butterfield at scss.tcd.ie (Andrew Butterfield) Date: Mon, 5 Nov 2018 10:40:17 +0000 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: Message-ID: > On 3 Nov 2018, at 08:59, Joachim Durchholz wrote: > If Haskell is truly pure, then IO must be pure as well. > That's why I think that IO functions are just describing impure activity, not doing it. I think that is exactly the best way to think about it (thanks!). Right now I am teaching "Introduction to Functional Programming" here, and have just introduced IO last week, so this is all in my head right now. A Haskell IO program is just a description of a sequence of IO actions (IO a), which *when evaluated* will produce side-.effects A function evaluation that produces side-effects when evaluated is a dangerous thing if used in an arbitrary fashion, but the IO abstraction(*) prevents danger by (i) having a fixed sequence of such actions, and (ii) never allowing a Haskell program to have a direct reference to the part of I/O state that gets modified. Haskell I/O is referentially transparent in that if you can show that two expressions of type IO a have the same I/O side-effecting behaviour (using the monad laws plus some IO-action semantics) then one can replace the other in any Haskell context without altering the IO behaviour of that context. Caveat: provided you don't use "unsafeXXXX" anywhere... (*) the IO abstraction happens to be an instance of a class called "Monad" that captures an interesting and useful pattern of sequential behaviour, but this is really a bit of a red-herring when it come to understanding how Haskell has both side-effecting IO and "purity" PS - "purity" and "referential transparency" are slippy concepts, quite hard to pin down, so it is unwise to put too much value into those terms... > I have not been able to verify whether this is actually true. Maybe IO is really a wart on Haskell's purity. > I'd hate it if it were, and I think the Haskell design group would have hated that as well. OTOH IO is one of three approaches, and it happened to be the one that became usable first, so it's not part of the initial design process. Then again I like to think that SPJ wouldn't even contemplate something impure - but I don't really know. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero at TCD, Head of Foundations & Methods Research Group School of Computer Science and Statistics, Room G.39, O'Reilly Institute, Trinity College, University of Dublin http://www.scss.tcd.ie/Andrew.Butterfield/ -------------------------------------------------------------------- -------------- next part -------------- An HTML attachment was scrubbed... URL: From gk at ninebynine.org Mon Nov 5 11:17:38 2018 From: gk at ninebynine.org (Graham Klyne) Date: Mon, 05 Nov 2018 11:17:38 +0000 Subject: [Haskell-cafe] Network deprecation In-Reply-To: References: Message-ID: <5BE026D2.1090408@ninebynine.org> Does this help?: http://mail.haskell.org/pipermail/haskell-cafe/2018-October/130086.html #g -- On 31/10/2018 23:50, Evan Laforge wrote: > I'm starting to get deprecation warnings about Network in the network > package. I know this has been in the works for a long time, but now > that I search I can't find any info about the rationale and suggested > replacement (the deprecation message suggests Network.Socket, but this > is a completely different lower level api). Does anyone out there > have links to discussions, articles, or whatnot? > > Thanks in advance! > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > From twhitehead at gmail.com Mon Nov 5 19:00:39 2018 From: twhitehead at gmail.com (Tyson Whitehead) Date: Mon, 5 Nov 2018 14:00:39 -0500 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? Message-ID: I would expect the following to consume all the computer's memory and die due to a buildup of lazy pattern matches for the `y` value. ``` import Data.Either main = print x >> print y where (length -> x, length -> y) = paritionEithers $ repeat (Left ()) ``` That is, `partitionEithers` is ``` partitionEithers :: [Either a b] -> ([a],[b]) partitionEithers = foldr go ([],[]) where go (Left x) ~(xs,ys) = (x:xs,ys) go (Right y) ~(xs,ys) = (xs,y:ys) ``` and, in the -ddump-simpl we see the `go Left` branch returns a thunk on both the right and left sides that hold onto the evaluation of (x:xs,ys) as we would expect ``` Left x_aqy -> (GHC.Types.: @ a_a1q8 x_aqy (case ds1_d1rO of { (xs_aqz, ys_aqA) -> xs_aqz }), case ds1_d1rO of { (xs_aqz, ys_aqA) -> ys_aqA }); ``` Our code keeps generating more and more of these thunks as the left-hand side chases down the infinite list of `Left ()` values, and the machine cannot let go of them because, as far as it knows, we are going to reach the end sometime and then need the right-hand side. Thus I expect it would consume all the memory and crash. But it doesn't. It just sits there forever consuming 100% CPU at a constant memory limit. This means my mental model is defective and I'm unable to properly reason about the space usage of my programs. Could someone please enlighten me as to were I'm missing? Is there some sort of optimization going on here? When can it be depend on? Thanks very much! -Tyson I would expect From twhitehead at gmail.com Mon Nov 5 19:25:50 2018 From: twhitehead at gmail.com (Tyson Whitehead) Date: Mon, 5 Nov 2018 14:25:50 -0500 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: References: Message-ID: I believe I actually figured it out. There is not buildup because y is just forever bound to y = length . snd $ paritionEithers $ repeat (Left ()) I guess the thing to realize is that this function will traverse the list twice. That is, what I wrote is essentially x = length . fst $ paritionEithers $ repeat (Left ()) y = length . snd $ paritionEithers $ repeat (Left ()) where both x and y independently traverse the entire list repeating any work that needs to be done to generate the elements. Thanks! -Tyson On Mon, 5 Nov 2018 at 14:00, Tyson Whitehead wrote: > > I would expect the following to consume all the computer's memory and > die due to a buildup of lazy pattern matches for the `y` value. > > ``` > import Data.Either > > main = print x >> print y > where > (length -> x, length -> y) = paritionEithers $ repeat (Left ()) > ``` > > That is, `partitionEithers` is > > ``` > partitionEithers :: [Either a b] -> ([a],[b]) > partitionEithers = foldr go ([],[]) > where > go (Left x) ~(xs,ys) = (x:xs,ys) > go (Right y) ~(xs,ys) = (xs,y:ys) > ``` > > and, in the -ddump-simpl we see the `go Left` branch returns a thunk > on both the right and left sides that hold onto the evaluation of > (x:xs,ys) as we would expect > > ``` > Left x_aqy -> > (GHC.Types.: > @ a_a1q8 x_aqy > (case ds1_d1rO of { (xs_aqz, ys_aqA) -> xs_aqz }), > case ds1_d1rO of { (xs_aqz, ys_aqA) -> ys_aqA }); > ``` > > Our code keeps generating more and more of these thunks as the > left-hand side chases down the infinite list of `Left ()` values, and > the machine cannot let go of them because, as far as it knows, we are > going to reach the end sometime and then need the right-hand side. > > Thus I expect it would consume all the memory and crash. But it > doesn't. It just sits there forever consuming 100% CPU at a constant > memory limit. This means my mental model is defective and I'm unable > to properly reason about the space usage of my programs. > > Could someone please enlighten me as to were I'm missing? Is there > some sort of optimization going on here? When can it be depend on? > > Thanks very much! -Tyson > > I would expect From jo at durchholz.org Mon Nov 5 21:53:56 2018 From: jo at durchholz.org (Joachim Durchholz) Date: Mon, 5 Nov 2018 22:53:56 +0100 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: Message-ID: <175f1306-d687-bc6e-de04-15c9a3a905e1@durchholz.org> Am 05.11.18 um 11:40 schrieb Andrew Butterfield: > >> On 3 Nov 2018, at 08:59, Joachim Durchholz > > wrote: >> If Haskell is truly pure, then IO must be pure as well. >> That's why I think that IO functions are just describing impure >> activity, not doing it. > > I think that is exactly the best way to think about it (thanks!).  Right > now I am teaching "Introduction to Functional Programming" > here, and have just introduced IO last week, so this is all in my head >  right now. > > A Haskell IO program is just a description of a sequence of IO actions > (IO a), which *when evaluated* will produce side-.effects > A function evaluation that produces side-effects when evaluated is a > dangerous thing if used in an arbitrary fashion, but the IO abstraction(*) > prevents danger by (i) having a fixed sequence of such actions, and (ii) > never allowing a Haskell program to have a direct reference to the part > of I/O state that gets modified. I'm not sure how this model explains the sequencing that happens in IO. Haskell's evaluation model for function calls is lazy, i.e. it doesn't impose an order (and it does not even trigger evaluation). AFAIK the one strict thing in Haskell is pattern matching, so I'd look how pattern matching drives IO's sequencing - but I don't see it. > Caveat: provided you don't use "unsafeXXXX" anywhere... Sure, that's just the loophole. Another red herring I think. > (*) the IO abstraction happens to be an instance of a class called > "Monad" that captures an interesting and useful pattern of sequential > behaviour, > but this is really a bit of a red-herring when it come to understanding > how Haskell has both side-effecting IO and "purity" I like to say that "'monadic IO' is akin to saying 'associative arithmetic'." I.e. associativity is an important aspect of arithmetic just like monadicity for IO, but it's not what it was made for. I am not sure how far this analogy holds water. > PS - "purity" and "referential transparency" are slippy concepts, quite > hard to pin down, so it is unwise to put too much value into those terms... The definition I've been using is that an expression and its value are interchangeable without changing the semantics. I never ran into trouble with this - either because of my ignorance, or because that definition has the exactly right kind of vagueness, neither implying too much nor too little. Just my 2c. Regards, Jo From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Mon Nov 5 22:16:11 2018 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 5 Nov 2018 22:16:11 +0000 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: References: Message-ID: <20181105221611.4fx7cugtztad7jzz@weber> It can't be as simple as you make out. The semantics of ViewPatterns cannot be such that (length -> x, length -> y) = partitionEithers $ repeat (Left ()) means x = length . fst $ partitionEithers $ repeat (Left ()) y = length . snd $ partitionEithers $ repeat (Left ()) It must surely mean (px, py) = partitionEithers $ repeat (Left ()) x = length px y = length py With that interpretation my by-hand evaluations show a space leak, see below. The only way I can reconcile this with the observed behaviour is that GHC's garbage collector can "see through" simple case statements. I vaguely remember reading something like this. Can any GHC developer confirm? Tom main = print x >> print y where (length -> x, length -> y) = partitionEithers $ repeat (Left ()) main = case (partitionEithers (repeat (Left ()))) of (px, py) -> let x = length px y = length py in print x >> print y (let z = ([], [])) main = case (foldr go z (repeat (Left ()))) of (px, py) -> ... main = case (foldr go z (Left () : repeat (Left ()))) of (px, py) -> ... main = case (go (Left ()) (foldr go z (repeat (Left ()))) of (px, py) -> ... main = case (let t = foldr go z (repeat (Left ())) in (fst t, snd t)) of (px, py) -> ... t = foldr go z (repeat (Left ())) main = case (fst t, snd t) of (px, py) -> ... t = foldr go z (repeat (Left ())) main = case (fst t, snd t) of (px, py) -> ... t = foldr go z (repeat (Left ())) main = let x = length (fst t) y = length (snd t) in print x >> print y t = foldr go z (repeat (Left ())) main = let x = length (fst t) y = length (snd t) in print x >> print y (omitting a few steps ...) t = go (Left ()) z (foldr go z (repeat (Left ()))) main = let x = length (fst t) y = length (snd t) in print x >> print y t = let t2 = foldr go z (repeat (Left ())) in (fst t2, snd t2) ... t = (fst t2, snd t2) t2 = foldr go z (repeat (Left ())) ... t = (fst t2, snd t2) t2 = (fst t3, snd t3) t3 = foldr go z (repeat (Left ())) ... t = (fst t3, snd t2) t2 = (fst t3, snd t3) t3 = foldr go z (repeat (Left ())) ... On Mon, Nov 05, 2018 at 02:25:50PM -0500, Tyson Whitehead wrote: > I believe I actually figured it out. There is not buildup because y > is just forever bound to > > y = length . snd $ paritionEithers $ repeat (Left ()) > > I guess the thing to realize is that this function will traverse the > list twice. That is, what I wrote is essentially > > x = length . fst $ paritionEithers $ repeat (Left ()) > y = length . snd $ paritionEithers $ repeat (Left ()) > > where both x and y independently traverse the entire list repeating > any work that needs to be done to generate the elements. > > Thanks! -Tyson > On Mon, 5 Nov 2018 at 14:00, Tyson Whitehead wrote: > > > > I would expect the following to consume all the computer's memory and > > die due to a buildup of lazy pattern matches for the `y` value. > > > > ``` > > import Data.Either > > > > main = print x >> print y > > where > > (length -> x, length -> y) = paritionEithers $ repeat (Left ()) > > ``` > > > > That is, `partitionEithers` is > > > > ``` > > partitionEithers :: [Either a b] -> ([a],[b]) > > partitionEithers = foldr go ([],[]) > > where > > go (Left x) ~(xs,ys) = (x:xs,ys) > > go (Right y) ~(xs,ys) = (xs,y:ys) > > ``` > > > > and, in the -ddump-simpl we see the `go Left` branch returns a thunk > > on both the right and left sides that hold onto the evaluation of > > (x:xs,ys) as we would expect > > > > ``` > > Left x_aqy -> > > (GHC.Types.: > > @ a_a1q8 x_aqy > > (case ds1_d1rO of { (xs_aqz, ys_aqA) -> xs_aqz }), > > case ds1_d1rO of { (xs_aqz, ys_aqA) -> ys_aqA }); > > ``` > > > > Our code keeps generating more and more of these thunks as the > > left-hand side chases down the infinite list of `Left ()` values, and > > the machine cannot let go of them because, as far as it knows, we are > > going to reach the end sometime and then need the right-hand side. > > > > Thus I expect it would consume all the memory and crash. But it > > doesn't. It just sits there forever consuming 100% CPU at a constant > > memory limit. This means my mental model is defective and I'm unable > > to properly reason about the space usage of my programs. > > > > Could someone please enlighten me as to were I'm missing? Is there > > some sort of optimization going on here? When can it be depend on? From allbery.b at gmail.com Mon Nov 5 22:27:10 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 5 Nov 2018 17:27:10 -0500 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: <175f1306-d687-bc6e-de04-15c9a3a905e1@durchholz.org> References: <175f1306-d687-bc6e-de04-15c9a3a905e1@durchholz.org> Message-ID: No state is modified, at least in ghc's implementation of IO. IO does carry "state" around, but never modifies it; it exists solely to establish a data dependency (passed to and returned from all IO actions; think s -> (a, s), but IO uses unboxed state) that thereby enforces sequencing. Once it reaches code generation, it discovers the runtime representation of the "state" is nonexistent (size 0) as well as unboxed, and eliminates it and all code related to it. On Mon, Nov 5, 2018 at 4:54 PM Joachim Durchholz wrote: > Am 05.11.18 um 11:40 schrieb Andrew Butterfield: > > > >> On 3 Nov 2018, at 08:59, Joachim Durchholz >> > wrote: > >> If Haskell is truly pure, then IO must be pure as well. > >> That's why I think that IO functions are just describing impure > >> activity, not doing it. > > > > I think that is exactly the best way to think about it (thanks!). Right > > now I am teaching "Introduction to Functional Programming" > > here, and have just introduced IO last week, so this is all in my head > > right now. > > > > A Haskell IO program is just a description of a sequence of IO actions > > (IO a), which *when evaluated* will produce side-.effects > > A function evaluation that produces side-effects when evaluated is a > > dangerous thing if used in an arbitrary fashion, but the IO > abstraction(*) > > prevents danger by (i) having a fixed sequence of such actions, and (ii) > > never allowing a Haskell program to have a direct reference to the part > > of I/O state that gets modified. > > I'm not sure how this model explains the sequencing that happens in IO. > Haskell's evaluation model for function calls is lazy, i.e. it doesn't > impose an order (and it does not even trigger evaluation). > AFAIK the one strict thing in Haskell is pattern matching, so I'd look > how pattern matching drives IO's sequencing - but I don't see it. > > > Caveat: provided you don't use "unsafeXXXX" anywhere... > > Sure, that's just the loophole. > Another red herring I think. > > > (*) the IO abstraction happens to be an instance of a class called > > "Monad" that captures an interesting and useful pattern of sequential > > behaviour, > > but this is really a bit of a red-herring when it come to understanding > > how Haskell has both side-effecting IO and "purity" > > I like to say that "'monadic IO' is akin to saying 'associative > arithmetic'." > I.e. associativity is an important aspect of arithmetic just like > monadicity for IO, but it's not what it was made for. > > I am not sure how far this analogy holds water. > > > PS - "purity" and "referential transparency" are slippy concepts, quite > > hard to pin down, so it is unwise to put too much value into those > terms... > > The definition I've been using is that an expression and its value are > interchangeable without changing the semantics. > I never ran into trouble with this - either because of my ignorance, or > because that definition has the exactly right kind of vagueness, neither > implying too much nor too little. > > Just my 2c. > > Regards, > Jo > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From qdunkan at gmail.com Tue Nov 6 01:39:57 2018 From: qdunkan at gmail.com (Evan Laforge) Date: Mon, 5 Nov 2018 17:39:57 -0800 Subject: [Haskell-cafe] Network deprecation In-Reply-To: <5BE026D2.1090408@ninebynine.org> References: <5BE026D2.1090408@ninebynine.org> Message-ID: That's about Network.BSD being split off, which is a different thing. I'll ask Kazu Yamamoto directly, he seems to be primary maintainer nowadays. On Mon, Nov 5, 2018 at 3:17 AM Graham Klyne wrote: > > Does this help?: > > http://mail.haskell.org/pipermail/haskell-cafe/2018-October/130086.html > > #g > -- > > > On 31/10/2018 23:50, Evan Laforge wrote: > > I'm starting to get deprecation warnings about Network in the network > > package. I know this has been in the works for a long time, but now > > that I search I can't find any info about the rationale and suggested > > replacement (the deprecation message suggests Network.Socket, but this > > is a completely different lower level api). Does anyone out there > > have links to discussions, articles, or whatnot? > > > > Thanks in advance! > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > From jo at durchholz.org Tue Nov 6 06:42:15 2018 From: jo at durchholz.org (Joachim Durchholz) Date: Tue, 6 Nov 2018 07:42:15 +0100 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: <175f1306-d687-bc6e-de04-15c9a3a905e1@durchholz.org> Message-ID: Am 05.11.18 um 23:27 schrieb Brandon Allbery: > No state is modified, at least in ghc's implementation of IO. That's what I'd expect. > IO does carry "state" around, but never modifies it; it exists solely > to establish a data dependency (passed to and returned from all IO > actions; think s -> (a, s), In Haskell, a data dependency can impose constraints on evaluation order, but it isn't always linear: which subexpression is evaluated first depends on what a pattern match requests (at least in Haskell: Haskell's strict operation is the pattern match). The ordering constraint becomes linear if each function calls just a single other function. I'm not sure that that's what happens with IO; input operations must allow choices and loops, making me wonder how linearity is established. It also makes me wonder how an IO expression would look like if fully evaluated; is it an infinite data structure, made useful only through Haskell's laziness, or is it something that's happening in the runtime? The other thing that's confusing me is that I don't see anything that starts the IO processing. There's no pattern match that triggers an evaluation. Not that this would explain much: If IO were constructed in a way that a pattern match starts IO execution, there'd still be the question what starts this first pattern match. Then there's the open question what happens if a program has two IO expressions. How does the runtime know which one to execute? Forgive me for my basic questions; I have tried to understand Haskell, but I never got the opportunity to really use it so I cannot easily test my hypotheses. Regards, Jo From allbery.b at gmail.com Tue Nov 6 07:11:34 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 6 Nov 2018 02:11:34 -0500 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: <175f1306-d687-bc6e-de04-15c9a3a905e1@durchholz.org> Message-ID: Conceptually, the runtime does (runIO# Main.main RealWorld#). Practically, ghc's implementation makes the sequencing stuff go away during code generation, so the runtime just sticks Main.main on the pattern stack and jumps into the STG to reduce it; there's your initial pattern match. I guess I wasn't clear enough with respect to the state. Every IO action is passed the "current state" and produces a "new state" (except that in reality there is no state to pass or update, since it has no runtime representation). A loop would be a sort of fold, where each iteration gets the "current state" and produces (thisResult,"new state"), then the "new state" is passed into the next loop iteration and the final result is the collection of thisResult-s and the final "new state". Again, conceptually, since the state vanishes during code generation, having served its purpose in ensuring everything happens in order. This is a bit hacky, since it assumes ghc never gets to see that nothing ever actually uses or updates the state so it's forced to assume it's updated and must be preserved. This is where bytestring's inlinePerformIO (better known as accursedUnutterable…) went wrong, since it inlined the whole thing so ghc could spot that the injected state (it being inlined unsafePerformIO) was fake and never used, and started lifting stuff out of loops, etc. — basically optimizing it as if it were pure code internally instead of IO because it could see through IO's "purity mask". On Tue, Nov 6, 2018 at 1:42 AM Joachim Durchholz wrote: > Am 05.11.18 um 23:27 schrieb Brandon Allbery: > > No state is modified, at least in ghc's implementation of IO. > > That's what I'd expect. > > > IO does carry "state" around, but never modifies it; it exists solely > > to establish a data dependency (passed to and returned from all IO > > actions; think s -> (a, s), > In Haskell, a data dependency can impose constraints on evaluation > order, but it isn't always linear: which subexpression is evaluated > first depends on what a pattern match requests (at least in Haskell: > Haskell's strict operation is the pattern match). > > The ordering constraint becomes linear if each function calls just a > single other function. I'm not sure that that's what happens with IO; > input operations must allow choices and loops, making me wonder how > linearity is established. It also makes me wonder how an IO expression > would look like if fully evaluated; is it an infinite data structure, > made useful only through Haskell's laziness, or is it something that's > happening in the runtime? > > The other thing that's confusing me is that I don't see anything that > starts the IO processing. There's no pattern match that triggers an > evaluation. > Not that this would explain much: If IO were constructed in a way that a > pattern match starts IO execution, there'd still be the question what > starts this first pattern match. > > Then there's the open question what happens if a program has two IO > expressions. How does the runtime know which one to execute? > > Forgive me for my basic questions; I have tried to understand Haskell, > but I never got the opportunity to really use it so I cannot easily test > my hypotheses. > > Regards, > Jo > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben.franksen at online.de Tue Nov 6 09:42:51 2018 From: ben.franksen at online.de (Ben Franksen) Date: Tue, 6 Nov 2018 10:42:51 +0100 Subject: [Haskell-cafe] Looking for feedback on my beginner's Haskell resource In-Reply-To: References: <175f1306-d687-bc6e-de04-15c9a3a905e1@durchholz.org> Message-ID: I prefer to think about IO as an abstract data type of atomic "actions" i.e. the IO primitives (which we can extend via the FFI). The "run time system" to me is a black box that "executes" these actions. A Haskell program combines abstract IO primitives into a larger and more complex action using IO's bind and return, and it does so in a purely functional way. Evaluation order is completely irrelevant to this, because what matters is the result, not how we arrive at it. The bind operator instructs the run-time system to execute its left hand side, resulting in a value to be passed to the right hand side, which is then evaluated (in a purely functional way) to yield the next action etc. There is nothing mysterious about this IMO. If you have a working model for each of the IO primitives, this gives you a working model of what a complete Haskell program does. Cheers Ben From bertram.felgenhauer at googlemail.com Tue Nov 6 11:49:05 2018 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Tue, 6 Nov 2018 12:49:05 +0100 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: References: Message-ID: <20181106114904.GB7068@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Tyson Whitehead wrote: > and, in the -ddump-simpl we see the `go Left` branch returns a thunk > on both the right and left sides that hold onto the evaluation of > (x:xs,ys) as we would expect > > ``` > Left x_aqy -> > (GHC.Types.: > @ a_a1q8 x_aqy > (case ds1_d1rO of { (xs_aqz, ys_aqA) -> xs_aqz }), > case ds1_d1rO of { (xs_aqz, ys_aqA) -> ys_aqA }); > ``` These two expressions are selectors (accessing a field from a single constructor data type), which the compiler recoginizes (not sure where and how exactly) and implemented in terms of special stg_sel_ closures. At runtime, applying such a closure results in special THUNK_SELECTOR thunks. These thunks are evaluated by the garbage collector (see rts/sm/Scav.c). So this is a very special optimization in the garbage collector, not a flaw in your general mental model. Cheers, Bertram From bertram.felgenhauer at googlemail.com Tue Nov 6 12:06:56 2018 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Tue, 6 Nov 2018 13:06:56 +0100 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: <20181106114904.GB7068@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> References: <20181106114904.GB7068@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Message-ID: <20181106120655.GC7068@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Bertram Felgenhauer via Haskell-Cafe wrote: > Tyson Whitehead wrote: > > and, in the -ddump-simpl we see the `go Left` branch returns a thunk > > on both the right and left sides that hold onto the evaluation of > > (x:xs,ys) as we would expect > > > > ``` > > Left x_aqy -> > > (GHC.Types.: > > @ a_a1q8 x_aqy > > (case ds1_d1rO of { (xs_aqz, ys_aqA) -> xs_aqz }), > > case ds1_d1rO of { (xs_aqz, ys_aqA) -> ys_aqA }); > > ``` > > These two expressions are selectors (accessing a field from a single > constructor data type), which the compiler recoginizes (not sure where > and how exactly) and implemented in terms of special stg_sel_ > closures. At runtime, applying such a closure results in special > THUNK_SELECTOR thunks. These thunks are evaluated by the garbage > collector (see rts/sm/Scav.c). Or rather rts/sm/Evac.c, which has functions unchain_thunk_selectors() and eval_thunk_selector() that do the actual work. Cheers, Bertram From gurudev.devanla at gmail.com Tue Nov 6 16:35:56 2018 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Tue, 6 Nov 2018 08:35:56 -0800 Subject: [Haskell-cafe] Help understanding this type Message-ID: Hello Haskell-Cafe, I have been recently studying the XMonad code and some related types available in the X11 bindings library. I came across this type: newtype XEvent = XEvent XEventPtr type XEventPtr = Ptr XEvent Available here: http://hackage.haskell.org/package/X11-1.9/docs/Graphics-X11-Xlib-Event.html#t:XEvent It seems that this type is circular here. how does one use this type? Is it possible to create a value out of this type? What is the use of this type? Please could someone help me wrap my head around this? Thanks -------------- next part -------------- An HTML attachment was scrubbed... URL: From zemyla at gmail.com Tue Nov 6 16:40:18 2018 From: zemyla at gmail.com (Zemyla) Date: Tue, 6 Nov 2018 10:40:18 -0600 Subject: [Haskell-cafe] Help understanding this type In-Reply-To: References: Message-ID: The type on "Ptr" doesn't actually affect what's inside; it's a convenience for programmers. The functions that do things with XEvents just read bytes from the Ptr's location. On Tue, Nov 6, 2018, 10:36 Guru Devanla Hello Haskell-Cafe, > > I have been recently studying the XMonad code and some related types > available in the X11 bindings library. > > I came across this type: > > newtype XEvent = XEvent XEventPtr > > type XEventPtr = Ptr > > XEvent > > > Available here: > > http://hackage.haskell.org/package/X11-1.9/docs/Graphics-X11-Xlib-Event.html#t:XEvent > > It seems that this type is circular here. how does one use this type? Is > it possible to create a value out of this type? What is the use of this > type? > > Please could someone help me wrap my head around this? > > Thanks > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From branimir.maksimovic at gmail.com Tue Nov 6 16:46:39 2018 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Tue, 6 Nov 2018 17:46:39 +0100 Subject: [Haskell-cafe] Help understanding this type In-Reply-To: References: Message-ID: I use that all the time. It is for typechecking things passed to C functions. Greets, Branimir. On 11/6/18 5:35 PM, Guru Devanla wrote: > Hello Haskell-Cafe, > > I have been recently studying the XMonad code and some related types > available in the X11 bindings library. > > I came across this type: > > newtype XEvent = XEvent XEventPtr > > type XEventPtr = Ptr > > XEvent > > > Available here: > http://hackage.haskell.org/package/X11-1.9/docs/Graphics-X11-Xlib-Event.html#t:XEvent > > It seems that this type is circular here. how does one use this type? > Is it possible to create a value out of this type? What is the use of > this type? > > Please could someone help me wrap my head around this? > > Thanks > > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanuki at gmail.com Wed Nov 7 10:28:53 2018 From: tanuki at gmail.com (Theodore Lief Gannon) Date: Wed, 7 Nov 2018 02:28:53 -0800 Subject: [Haskell-cafe] Help understanding this type In-Reply-To: References: Message-ID: The meaning of XEvent is different on the left and right sides of the newtype declaration. On the left, it's a type; on the right, it's a data constructor. The constructor wraps a value which refers to the type, but not recursively back to the constructor itself. On Tue, Nov 6, 2018, 8:36 AM Guru Devanla Hello Haskell-Cafe, > > I have been recently studying the XMonad code and some related types > available in the X11 bindings library. > > I came across this type: > > newtype XEvent = XEvent XEventPtr > > type XEventPtr = Ptr > > XEvent > > > Available here: > > http://hackage.haskell.org/package/X11-1.9/docs/Graphics-X11-Xlib-Event.html#t:XEvent > > It seems that this type is circular here. how does one use this type? Is > it possible to create a value out of this type? What is the use of this > type? > > Please could someone help me wrap my head around this? > > Thanks > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gurudev.devanla at gmail.com Wed Nov 7 13:20:16 2018 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Wed, 7 Nov 2018 05:20:16 -0800 Subject: [Haskell-cafe] Help understanding this type In-Reply-To: References: Message-ID: Thank you all for the responses, After reading through the responses, it became clear that this is a commonly pattern used in Haskell FFI programming. I went back and reviewed the chapter in RWH. There is a discussion on this pattern, under 'Typed Pointers'. http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html Which means similar to the type listed in the chapter newtype PCRE = PCRE (Ptr PCRE) The example I provided reduces to: newtype XEvent = XEvent (Ptr XEvent). -- a recursive newtype that cannot be dereferenced In summary: 1. This pattern can be use to specify the types just for type-checking within Haskell. They do not contain any data. Therefore, not data can be cerated for XEvent. 2. Data can be created for type `Ptr XEvent` using the `alloca` interface, and only way to de-reference these values would be through `peek`. But, while derefencing the resulting values will have other types. Next, I plan to spend some time working on these examples to get a better sense. Thank you all! On Wed, Nov 7, 2018 at 2:29 AM Theodore Lief Gannon wrote: > The meaning of XEvent is different on the left and right sides of the > newtype declaration. On the left, it's a type; on the right, it's a data > constructor. The constructor wraps a value which refers to the type, but > not recursively back to the constructor itself. > > On Tue, Nov 6, 2018, 8:36 AM Guru Devanla wrote: > >> Hello Haskell-Cafe, >> >> I have been recently studying the XMonad code and some related types >> available in the X11 bindings library. >> >> I came across this type: >> >> newtype XEvent = XEvent XEventPtr >> >> type XEventPtr = Ptr >> >> XEvent >> >> >> Available here: >> >> http://hackage.haskell.org/package/X11-1.9/docs/Graphics-X11-Xlib-Event.html#t:XEvent >> >> It seems that this type is circular here. how does one use this type? Is >> it possible to create a value out of this type? What is the use of this >> type? >> >> Please could someone help me wrap my head around this? >> >> Thanks >> >> >> >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Wed Nov 7 15:49:59 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Wed, 7 Nov 2018 10:49:59 -0500 Subject: [Haskell-cafe] Help understanding this type In-Reply-To: References: Message-ID: The concept you are looking for is "phantom type": a type that is used solely as a "tag" of sorts, with no associated data. The Ptr type constructor uses a phantom type so you can differentiate between machine addresses pointing at different kinds of data and gain some small measure of safety. On Wed, Nov 7, 2018 at 8:20 AM Guru Devanla wrote: > Thank you all for the responses, After reading through the responses, it > became clear that this is a commonly pattern used in Haskell FFI > programming. > > I went back and reviewed the chapter in RWH. There is a discussion on this > pattern, under 'Typed Pointers'. > http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html > > Which means similar to the type listed in the chapter > > newtype PCRE = PCRE (Ptr PCRE) > > The example I provided reduces to: > newtype XEvent = XEvent (Ptr XEvent). -- a recursive newtype that cannot be dereferenced > > In summary: > > 1. This pattern can be use to specify the types just for type-checking within Haskell. They do not contain any data. Therefore, not data can be cerated for XEvent. > 2. Data can be created for type `Ptr XEvent` using the `alloca` interface, and only way to de-reference these values would be through `peek`. But, while derefencing the resulting values will have other types. > > Next, I plan to spend some time working on these examples to get a better sense. > > Thank you all! > > > > > > > > > > > > > > On Wed, Nov 7, 2018 at 2:29 AM Theodore Lief Gannon > wrote: > >> The meaning of XEvent is different on the left and right sides of the >> newtype declaration. On the left, it's a type; on the right, it's a data >> constructor. The constructor wraps a value which refers to the type, but >> not recursively back to the constructor itself. >> >> On Tue, Nov 6, 2018, 8:36 AM Guru Devanla > wrote: >> >>> Hello Haskell-Cafe, >>> >>> I have been recently studying the XMonad code and some related types >>> available in the X11 bindings library. >>> >>> I came across this type: >>> >>> newtype XEvent = XEvent XEventPtr >>> >>> type XEventPtr = Ptr >>> >>> XEvent >>> >>> >>> Available here: >>> >>> http://hackage.haskell.org/package/X11-1.9/docs/Graphics-X11-Xlib-Event.html#t:XEvent >>> >>> It seems that this type is circular here. how does one use this type? Is >>> it possible to create a value out of this type? What is the use of this >>> type? >>> >>> Please could someone help me wrap my head around this? >>> >>> Thanks >>> >>> >>> >>> >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From ky3 at atamo.com Thu Nov 8 03:42:48 2018 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Thu, 8 Nov 2018 10:42:48 +0700 Subject: [Haskell-cafe] Help understanding this type In-Reply-To: References: Message-ID: Normally phantom types do add type safety. But Ptr provides castPtr :: Ptr a -> Pt r b, which throws type safety out the window. Newtype is applied to ameliorate the situation, but I don't see how to make type safety airtight, do you? On Wednesday, November 7, 2018, Brandon Allbery wrote: > The concept you are looking for is "phantom type": a type that is used > solely as a "tag" of sorts, with no associated data. The Ptr type > constructor uses a phantom type so you can differentiate between machine > addresses pointing at different kinds of data and gain some small measure > of safety. > > On Wed, Nov 7, 2018 at 8:20 AM Guru Devanla > wrote: > >> Thank you all for the responses, After reading through the responses, it >> became clear that this is a commonly pattern used in Haskell FFI >> programming. >> >> I went back and reviewed the chapter in RWH. There is a discussion on >> this pattern, under 'Typed Pointers'. >> http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html >> >> Which means similar to the type listed in the chapter >> >> newtype PCRE = PCRE (Ptr PCRE) >> >> The example I provided reduces to: >> newtype XEvent = XEvent (Ptr XEvent). -- a recursive newtype that cannot be dereferenced >> >> In summary: >> >> 1. This pattern can be use to specify the types just for type-checking within Haskell. They do not contain any data. Therefore, not data can be cerated for XEvent. >> 2. Data can be created for type `Ptr XEvent` using the `alloca` interface, and only way to de-reference these values would be through `peek`. But, while derefencing the resulting values will have other types. >> >> Next, I plan to spend some time working on these examples to get a better sense. >> >> Thank you all! >> >> >> >> >> >> >> >> >> >> >> >> >> >> On Wed, Nov 7, 2018 at 2:29 AM Theodore Lief Gannon >> wrote: >> >>> The meaning of XEvent is different on the left and right sides of the >>> newtype declaration. On the left, it's a type; on the right, it's a data >>> constructor. The constructor wraps a value which refers to the type, but >>> not recursively back to the constructor itself. >>> >>> On Tue, Nov 6, 2018, 8:36 AM Guru Devanla >> wrote: >>> >>>> Hello Haskell-Cafe, >>>> >>>> I have been recently studying the XMonad code and some related types >>>> available in the X11 bindings library. >>>> >>>> I came across this type: >>>> >>>> newtype XEvent = XEvent XEventPtr >>>> >>>> type XEventPtr = Ptr >>>> >>>> XEvent >>>> >>>> >>>> Available here: >>>> http://hackage.haskell.org/package/X11-1.9/docs/Graphics- >>>> X11-Xlib-Event.html#t:XEvent >>>> >>>> It seems that this type is circular here. how does one use this type? >>>> Is it possible to create a value out of this type? What is the use of this >>>> type? >>>> >>>> Please could someone help me wrap my head around this? >>>> >>>> Thanks >>>> >>>> >>>> >>>> >>>> >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >>> >>> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > > > -- > brandon s allbery kf8nh > allbery.b at gmail.com > -- -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Nov 8 03:46:54 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Wed, 7 Nov 2018 22:46:54 -0500 Subject: [Haskell-cafe] Help understanding this type In-Reply-To: References: Message-ID: It's a pointer to raw memory, presumably obtained from C code; full type safety is impossible, and no type system can help you with things like C not distinguishing between pointers and arrays in function parameters and not having arrays that know their sizes. On Wed, Nov 7, 2018 at 10:42 PM Kim-Ee Yeoh wrote: > Normally phantom types do add type safety. > > But Ptr provides castPtr :: Ptr > a > -> Pt > r > b, which throws type safety out the window. > > Newtype is applied to ameliorate the situation, but I don't see how to > make type safety airtight, do you? > > > > On Wednesday, November 7, 2018, Brandon Allbery > wrote: > >> The concept you are looking for is "phantom type": a type that is used >> solely as a "tag" of sorts, with no associated data. The Ptr type >> constructor uses a phantom type so you can differentiate between machine >> addresses pointing at different kinds of data and gain some small measure >> of safety. >> >> On Wed, Nov 7, 2018 at 8:20 AM Guru Devanla >> wrote: >> >>> Thank you all for the responses, After reading through the responses, it >>> became clear that this is a commonly pattern used in Haskell FFI >>> programming. >>> >>> I went back and reviewed the chapter in RWH. There is a discussion on >>> this pattern, under 'Typed Pointers'. >>> http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html >>> >>> Which means similar to the type listed in the chapter >>> >>> newtype PCRE = PCRE (Ptr PCRE) >>> >>> The example I provided reduces to: >>> newtype XEvent = XEvent (Ptr XEvent). -- a recursive newtype that cannot be dereferenced >>> >>> In summary: >>> >>> 1. This pattern can be use to specify the types just for type-checking within Haskell. They do not contain any data. Therefore, not data can be cerated for XEvent. >>> 2. Data can be created for type `Ptr XEvent` using the `alloca` interface, and only way to de-reference these values would be through `peek`. But, while derefencing the resulting values will have other types. >>> >>> Next, I plan to spend some time working on these examples to get a better sense. >>> >>> Thank you all! >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> On Wed, Nov 7, 2018 at 2:29 AM Theodore Lief Gannon >>> wrote: >>> >>>> The meaning of XEvent is different on the left and right sides of the >>>> newtype declaration. On the left, it's a type; on the right, it's a data >>>> constructor. The constructor wraps a value which refers to the type, but >>>> not recursively back to the constructor itself. >>>> >>>> On Tue, Nov 6, 2018, 8:36 AM Guru Devanla >>> wrote: >>>> >>>>> Hello Haskell-Cafe, >>>>> >>>>> I have been recently studying the XMonad code and some related types >>>>> available in the X11 bindings library. >>>>> >>>>> I came across this type: >>>>> >>>>> newtype XEvent = XEvent XEventPtr >>>>> >>>>> type XEventPtr = Ptr >>>>> >>>>> XEvent >>>>> >>>>> >>>>> Available here: >>>>> >>>>> http://hackage.haskell.org/package/X11-1.9/docs/Graphics-X11-Xlib-Event.html#t:XEvent >>>>> >>>>> It seems that this type is circular here. how does one use this type? >>>>> Is it possible to create a value out of this type? What is the use of this >>>>> type? >>>>> >>>>> Please could someone help me wrap my head around this? >>>>> >>>>> Thanks >>>>> >>>>> >>>>> >>>>> >>>>> >>>>> >>>>> _______________________________________________ >>>>> Haskell-Cafe mailing list >>>>> To (un)subscribe, modify options or view archives go to: >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>>> Only members subscribed via the mailman list are allowed to post. >>>> >>>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> >> >> -- >> brandon s allbery kf8nh >> allbery.b at gmail.com >> > > > -- > -- Kim-Ee > -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From twhitehead at gmail.com Thu Nov 8 04:42:11 2018 From: twhitehead at gmail.com (Tyson Whitehead) Date: Wed, 7 Nov 2018 23:42:11 -0500 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: References: Message-ID: I take back my follow up comment. I still don't understand why there isn't a buildup of thunks. I've written an updated/simplified variant and posted it on r/haskellquestions. Hopefully someone will enlighten me. https://www.reddit.com/r/haskellquestions/comments/9v6z49/why_does_this_code_not_eat_all_the_memory_and_die/ Thanks! -Tyson On Mon, 5 Nov 2018 at 14:25, Tyson Whitehead wrote: > > I believe I actually figured it out. There is not buildup because y > is just forever bound to > > y = length . snd $ paritionEithers $ repeat (Left ()) > > I guess the thing to realize is that this function will traverse the > list twice. That is, what I wrote is essentially > > x = length . fst $ paritionEithers $ repeat (Left ()) > y = length . snd $ paritionEithers $ repeat (Left ()) > > where both x and y independently traverse the entire list repeating > any work that needs to be done to generate the elements. > > Thanks! -Tyson > On Mon, 5 Nov 2018 at 14:00, Tyson Whitehead wrote: > > > > I would expect the following to consume all the computer's memory and > > die due to a buildup of lazy pattern matches for the `y` value. > > > > ``` > > import Data.Either > > > > main = print x >> print y > > where > > (length -> x, length -> y) = paritionEithers $ repeat (Left ()) > > ``` > > > > That is, `partitionEithers` is > > > > ``` > > partitionEithers :: [Either a b] -> ([a],[b]) > > partitionEithers = foldr go ([],[]) > > where > > go (Left x) ~(xs,ys) = (x:xs,ys) > > go (Right y) ~(xs,ys) = (xs,y:ys) > > ``` > > > > and, in the -ddump-simpl we see the `go Left` branch returns a thunk > > on both the right and left sides that hold onto the evaluation of > > (x:xs,ys) as we would expect > > > > ``` > > Left x_aqy -> > > (GHC.Types.: > > @ a_a1q8 x_aqy > > (case ds1_d1rO of { (xs_aqz, ys_aqA) -> xs_aqz }), > > case ds1_d1rO of { (xs_aqz, ys_aqA) -> ys_aqA }); > > ``` > > > > Our code keeps generating more and more of these thunks as the > > left-hand side chases down the infinite list of `Left ()` values, and > > the machine cannot let go of them because, as far as it knows, we are > > going to reach the end sometime and then need the right-hand side. > > > > Thus I expect it would consume all the memory and crash. But it > > doesn't. It just sits there forever consuming 100% CPU at a constant > > memory limit. This means my mental model is defective and I'm unable > > to properly reason about the space usage of my programs. > > > > Could someone please enlighten me as to were I'm missing? Is there > > some sort of optimization going on here? When can it be depend on? > > > > Thanks very much! -Tyson > > > > I would expect From twhitehead at gmail.com Thu Nov 8 06:09:08 2018 From: twhitehead at gmail.com (Tyson Whitehead) Date: Thu, 8 Nov 2018 01:09:08 -0500 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: References: Message-ID: Sorry for all the noise. I believe I finally tracked down the eat all the memory/don't eat all the memory trigger. It is the view pattern. When I calculate the length in a view pattern, memory stays constant, when I calculate it outside, it explodes. I'll have to examine the simpl dump some more to see if I can figure out the difference between these two. Sorry for the noise on the list. Cheers! -Tyson On Wed, 7 Nov 2018 at 23:42, Tyson Whitehead wrote: > > I take back my follow up comment. I still don't understand why there > isn't a buildup of thunks. > > I've written an updated/simplified variant and posted it on > r/haskellquestions. Hopefully someone will enlighten me. > > https://www.reddit.com/r/haskellquestions/comments/9v6z49/why_does_this_code_not_eat_all_the_memory_and_die/ > > Thanks! -Tyson > On Mon, 5 Nov 2018 at 14:25, Tyson Whitehead wrote: > > > > I believe I actually figured it out. There is not buildup because y > > is just forever bound to > > > > y = length . snd $ paritionEithers $ repeat (Left ()) > > > > I guess the thing to realize is that this function will traverse the > > list twice. That is, what I wrote is essentially > > > > x = length . fst $ paritionEithers $ repeat (Left ()) > > y = length . snd $ paritionEithers $ repeat (Left ()) > > > > where both x and y independently traverse the entire list repeating > > any work that needs to be done to generate the elements. > > > > Thanks! -Tyson > > On Mon, 5 Nov 2018 at 14:00, Tyson Whitehead wrote: > > > > > > I would expect the following to consume all the computer's memory and > > > die due to a buildup of lazy pattern matches for the `y` value. > > > > > > ``` > > > import Data.Either > > > > > > main = print x >> print y > > > where > > > (length -> x, length -> y) = paritionEithers $ repeat (Left ()) > > > ``` > > > > > > That is, `partitionEithers` is > > > > > > ``` > > > partitionEithers :: [Either a b] -> ([a],[b]) > > > partitionEithers = foldr go ([],[]) > > > where > > > go (Left x) ~(xs,ys) = (x:xs,ys) > > > go (Right y) ~(xs,ys) = (xs,y:ys) > > > ``` > > > > > > and, in the -ddump-simpl we see the `go Left` branch returns a thunk > > > on both the right and left sides that hold onto the evaluation of > > > (x:xs,ys) as we would expect > > > > > > ``` > > > Left x_aqy -> > > > (GHC.Types.: > > > @ a_a1q8 x_aqy > > > (case ds1_d1rO of { (xs_aqz, ys_aqA) -> xs_aqz }), > > > case ds1_d1rO of { (xs_aqz, ys_aqA) -> ys_aqA }); > > > ``` > > > > > > Our code keeps generating more and more of these thunks as the > > > left-hand side chases down the infinite list of `Left ()` values, and > > > the machine cannot let go of them because, as far as it knows, we are > > > going to reach the end sometime and then need the right-hand side. > > > > > > Thus I expect it would consume all the memory and crash. But it > > > doesn't. It just sits there forever consuming 100% CPU at a constant > > > memory limit. This means my mental model is defective and I'm unable > > > to properly reason about the space usage of my programs. > > > > > > Could someone please enlighten me as to were I'm missing? Is there > > > some sort of optimization going on here? When can it be depend on? > > > > > > Thanks very much! -Tyson > > > > > > I would expect From twhitehead at gmail.com Thu Nov 8 16:04:34 2018 From: twhitehead at gmail.com (Tyson Whitehead) Date: Thu, 8 Nov 2018 11:04:34 -0500 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: References: Message-ID: On Thu, 8 Nov 2018 at 01:09, Tyson Whitehead wrote: > Sorry for all the noise. I believe I finally tracked down the eat all the memory/don't eat all the memory trigger. It is the view pattern. There was a request to post both codes as it seems a bit unexpected that a view pattern would make that difference. Here they are. I compiled both with `ghc file.hs` using the standard GHC 8.4.3 from NixOS 18.09. Constant memory code (RES 6MB): {-# LANGUAGE ViewPatterns #-} module Main (main) where import Data.Either (length -> lx,length -> ly) = partitionEithers (repeat $ Left ()) main = do print lx print ly Unbounded memory: module Main (main) where import Data.Either (xs, ys) = partitionEithers (repeat $ Left ()) main = do print $ length xs print $ length ys Cheers! -Tyson PS: The constant-memory view-pattern version seems to compile down to lxly = case partitionEithers (repeat $ Left ()) of (xs,ys) -> (length xs,length ys) main = do print (case lxly of (lx,_) -> lx) print (case lxly of (_,ly) -> ly) while the unbounded-memory non-view-pattern one compiles down to xsys = partitionEithers (repeat $ Left ()) xs = case xsys of (xs,_) -> xs ys = case xsys of (_,ys) -> ys main = do print (length xs) print (length ys) From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Thu Nov 8 18:13:01 2018 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 8 Nov 2018 18:13:01 +0000 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: References: Message-ID: <20181108181301.sy76eqsqgx4jj6bx@weber> I must admit I'm stumped! I don't see any significant difference between those two programs. On Thu, Nov 08, 2018 at 11:04:34AM -0500, Tyson Whitehead wrote: > Constant memory code (RES 6MB): > > {-# LANGUAGE ViewPatterns #-} > > module Main (main) where > > import Data.Either > > (length -> lx,length -> ly) = partitionEithers (repeat $ Left ()) > > main = do > print lx > print ly > > Unbounded memory: > > module Main (main) where > > import Data.Either > > (xs, ys) = partitionEithers (repeat $ Left ()) > > main = do > print $ length xs > print $ length ys > > Cheers! -Tyson > > PS: The constant-memory view-pattern version seems to compile down to > > lxly = case partitionEithers (repeat $ Left ()) of > (xs,ys) -> (length xs,length ys) > > main = do > print (case lxly of (lx,_) -> lx) > print (case lxly of (_,ly) -> ly) > > while the unbounded-memory non-view-pattern one compiles down to > > xsys = partitionEithers (repeat $ Left ()) > xs = case xsys of (xs,_) -> xs > ys = case xsys of (_,ys) -> ys > > main = do > print (length xs) > print (length ys) From ietf-dane at dukhovni.org Thu Nov 8 19:15:36 2018 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Thu, 8 Nov 2018 14:15:36 -0500 Subject: [Haskell-cafe] Why doesn't this consume all the computer's memory? In-Reply-To: <20181108181301.sy76eqsqgx4jj6bx@weber> References: <20181108181301.sy76eqsqgx4jj6bx@weber> Message-ID: It seems that it only runs in constant space when the two lengths compile to a pre-evaluated CAF. In the below version, at low optimization levels the evaluation of lx/ly is deferred to the "forkIO" thread, and memory use grows linearly with the timeout. At high optimization levels, memory use is constant, but the timeout never happens, and it seems plausible that the CAF is lifted out to the top level, and is evaluated in constant space (but infinite time). So it seems, that as a CAF, the generated code does not attempt to memoize the input infinite list. It may be worth noting that if "repeat" is replaced with "replicate 10000", "replicate 1000000", ... memory usage grows with the size of the generated list. Only the infinite list when pre-computed as a CAF seems to "run" in constant space. (Scare quotes around "run" since in this it never completes the computation. You either never finish, or use unbounded space, pick your poison). ------ snip ------ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ViewPatterns #-} module Main (main) where import System.Environment import System.Timeout import Control.Concurrent import Control.Concurrent.MVar import Data.List partitionEithers :: [Either a b] -> ([a],[b]) partitionEithers = foldr go ([],[]) where go (Left x) ~(xs,ys) = (x:xs,ys) go (Right y) ~(xs,ys) = (xs,y:ys) main = do n <- getArgs >>= \case [] -> return 100 a:_ -> return $ read a m <- newEmptyMVar forkIO $ do let (length -> lx, length -> ly) = partitionEithers $ repeat $ Left () print lx print ly putMVar m () timeout n $ takeMVar m ------ snip ------ > On Nov 8, 2018, at 1:13 PM, Tom Ellis wrote: > > I must admit I'm stumped! I don't see any significant difference between > those two programs. > > On Thu, Nov 08, 2018 at 11:04:34AM -0500, Tyson Whitehead wrote: >> Constant memory code (RES 6MB): >> >> {-# LANGUAGE ViewPatterns #-} >> >> module Main (main) where >> >> import Data.Either >> >> (length -> lx,length -> ly) = partitionEithers (repeat $ Left ()) >> >> main = do >> print lx >> print ly >> >> Unbounded memory: >> >> module Main (main) where >> >> import Data.Either >> >> (xs, ys) = partitionEithers (repeat $ Left ()) >> >> main = do >> print $ length xs >> print $ length ys -- Viktor. From alec.theriault at gmail.com Thu Nov 8 23:29:33 2018 From: alec.theriault at gmail.com (Alec Theriault) Date: Thu, 8 Nov 2018 15:29:33 -0800 Subject: [Haskell-cafe] Feedback on Haskell theme redesign Message-ID: Hi all, There’s been an ongoing effort to redesign Haddock’s theme to match the new purple Hackage theme. Nuno Alexandre, the original author of these changes, has [blogged][0] and [posted to reddit][1] about this before (and gotten positive feedback), but it’s only now that we are actually on the verge of merging these changes. I’ve generated sample docs for the Haskell Hierarchical Libraries (that includes a bunch of packages including `base`, `containers`, `template-haskell`, and `parsec`). You can compare the new theme to the old one via the “style” dropdown in the top right corner: https://harpocrates.github.io/ghc-head-libraries If you have time to spare, it would be very helpful to gather feedback to further optimize/tune the existing work prior to merging. The Haddock pull request on GitHub is the best place to collect that feedback: https://github.com/haskell/haddock/pull/949. Whenever relevant, please accompany issues and suggestions with screenshots! Thanks in advance, Alec Theriault [0]: https://nunoalexandre.com/2018/02/04/redesigning-haskell-docs [1]: https://www.reddit.com/r/haskell/comments/7vatew/redesigning_haddock_docs_and_hackage_pages -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanuki at gmail.com Fri Nov 9 02:11:23 2018 From: tanuki at gmail.com (Theodore Lief Gannon) Date: Thu, 8 Nov 2018 18:11:23 -0800 Subject: [Haskell-cafe] Feedback on Haskell theme redesign In-Reply-To: References: Message-ID: It's definitely looking nice! One note: visited links look very close in color to header text. I'd suggest lightening the links slightly. (Unvisited links are fine.) On Thu, Nov 8, 2018, 3:30 PM Alec Theriault Hi all, > > There’s been an ongoing effort to redesign Haddock’s theme to match the > new purple Hackage theme. Nuno Alexandre, the original author of these > changes, has [blogged][0] and [posted to reddit][1] about this before (and > gotten positive feedback), but it’s only now that we are actually on the > verge of merging these changes. > > I’ve generated sample docs for the Haskell Hierarchical Libraries (that > includes a bunch of packages including `base`, `containers`, > `template-haskell`, and `parsec`). You can compare the new theme to the old > one via the “style” dropdown in the top right corner: > > https://harpocrates.github.io/ghc-head-libraries > > If you have time to spare, it would be very helpful to gather feedback to > further optimize/tune the existing work prior to merging. The Haddock pull > request on GitHub is the best place to collect that feedback: > https://github.com/haskell/haddock/pull/949. Whenever relevant, please > accompany issues and suggestions with screenshots! > > Thanks in advance, > Alec Theriault > > [0]: https://nunoalexandre.com/2018/02/04/redesigning-haskell-docs > [1]: > https://www.reddit.com/r/haskell/comments/7vatew/redesigning_haddock_docs_and_hackage_pages > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From icfp.publicity at googlemail.com Fri Nov 9 02:45:00 2018 From: icfp.publicity at googlemail.com (Sam Tobin-Hochstadt) Date: Thu, 08 Nov 2018 21:45:00 -0500 Subject: [Haskell-cafe] First Call for Papers: PACMPL issue ICFP 2019 Message-ID: <5be4f4ac3d1ee_1c8812990cc39732@hermes.mail> PACMPL Volume 3, Issue ICFP 2019 Call for Papers accepted papers to be invited for presentation at The 24th ACM SIGPLAN International Conference on Functional Programming Berlin, Germany http://icfp19.sigplan.org/ ### Important dates Submissions due: 1 March 2019 (Friday) Anywhere on Earth https://icfp19.hotcrp.com Author response: 16 April (Tuesday) - 18 Apri (Friday) 14:00 UTC Notification: 3 May (Friday) Final copy due: 22 June (Saturday) Conference: 18 August (Sunday) - 23 August (Friday) ### About PACMPL Proceedings of the ACM on Programming Languages (PACMPL ) is a Gold Open Access journal publishing research on all aspects of programming languages, from design to implementation and from mathematical formalisms to empirical studies. Each issue of the journal is devoted to a particular subject area within programming languages and will be announced through publicized Calls for Papers, like this one. ### Scope [PACMPL](https://pacmpl.acm.org/) issue ICFP 2019 seeks original papers on the art and science of functional programming. Submissions are invited on all topics from principles to practice, from foundations to features, and from abstraction to application. The scope includes all languages that encourage functional programming, including both purely applicative and imperative languages, as well as languages with objects, concurrency, or parallelism. Topics of interest include (but are not limited to): * *Language Design*: concurrency, parallelism, and distribution; modules; components and composition; metaprogramming; type systems; interoperability; domain-specific languages; and relations to imperative, object-oriented, or logic programming. * *Implementation*: abstract machines; virtual machines; interpretation; compilation; compile-time and run-time optimization; garbage collection and memory management; multi-threading; exploiting parallel hardware; interfaces to foreign functions, services, components, or low-level machine resources. * *Software-Development Techniques*: algorithms and data structures; design patterns; specification; verification; validation; proof assistants; debugging; testing; tracing; profiling. * *Foundations*: formal semantics; lambda calculus; rewriting; type theory; monads; continuations; control; state; effects; program verification; dependent types. * *Analysis and Transformation*: control-flow; data-flow; abstract interpretation; partial evaluation; program calculation. * *Applications*: symbolic computing; formal-methods tools; artificial intelligence; systems programming; distributed-systems and web programming; hardware design; databases; XML processing; scientific and numerical computing; graphical user interfaces; multimedia and 3D graphics programming; scripting; system administration; security. * *Education*: teaching introductory programming; parallel programming; mathematical proof; algebra. Submissions will be evaluated according to their relevance, correctness, significance, originality, and clarity. Each submission should explain its contributions in both general and technical terms, clearly identifying what has been accomplished, explaining why it is significant, and comparing it with previous work. The technical content should be accessible to a broad audience. PACMPL issue ICFP 2019 also welcomes submissions in two separate categories — Functional Pearls and Experience Reports — that must be marked as such at the time of submission and that need not report original research results. Detailed guidelines on both categories are given at the end of this call. Please contact the principal editor if you have questions or are concerned about the appropriateness of a topic. ### Preparation of submissions **Deadline**: The deadline for submissions is **Friday, March 1, 2019**, Anywhere on Earth (). This deadline will be strictly enforced. **Formatting**: Submissions must be in PDF format, printable in black and white on US Letter sized paper, and interpretable by common PDF tools. All submissions must adhere to the "ACM Small" template that is available (in both LaTeX and Word formats) from . For authors using LaTeX, a lighter-weight package, including only the essential files, is available from . There is a limit of **25 pages for a full paper or Functional Pearl** and **12 pages for an Experience Report**; in either case, the bibliography will not be counted against these limits. Submissions that exceed the page limits or, for other reasons, do not meet the requirements for formatting, will be summarily rejected. Supplementary material can and should be **separately** submitted (see below). See also PACMPL's Information and Guidelines for Authors at . **Submission**: Submissions will be accepted at Improved versions of a paper may be submitted at any point before the submission deadline using the same web interface. **Author Response Period**: Authors will have a 72-hour period, starting at 14:00 UTC on **Tuesday, April 16, 2019**, to read reviews and respond to them. **Supplementary Material**: Authors have the option to attach supplementary material to a submission, on the understanding that reviewers may choose not to look at it. This supplementary material should **not** be submitted as part of the main document; instead, it should be uploaded as a **separate** PDF document or tarball. Supplementary material should be uploaded **at submission time**, not by providing a URL in the paper that points to an external repository. Authors are free to upload both anonymized and non-anonymized supplementary material. Anonymized supplementary material will be visible to reviewers immediately; non-anonymized supplementary material will be revealed to reviewers only after they have submitted their review of the paper and learned the identity of the author(s). **Authorship Policies**: All submissions are expected to comply with the ACM Policies for Authorship that are detailed at . **Republication Policies**: Each submission must adhere to SIGPLAN's republication policy, as explained on the web at . **Resubmitted Papers**: Authors who submit a revised version of a paper that has previously been rejected by another conference have the option to attach an annotated copy of the reviews of their previous submission(s), explaining how they have addressed these previous reviews in the present submission. If a reviewer identifies him/herself as a reviewer of this previous submission and wishes to see how his/her comments have been addressed, the principal editor will communicate to this reviewer the annotated copy of his/her previous review. Otherwise, no reviewer will read the annotated copies of the previous reviews. ### Review Process This section outlines the two-stage process with lightweight double-blind reviewing that will be used to select papers for PACMPL issue ICFP 2019. We anticipate that there will be a need to clarify and expand on this process, and we will maintain a list of frequently asked questions and answers on the conference website to address common concerns. **PACMPL issue ICFP 2019 will employ a two-stage review process.** The first stage in the review process will assess submitted papers using the criteria stated above and will allow for feedback and input on initial reviews through the author response period mentioned previously. At the review meeting, a set of papers will be conditionally accepted and all other papers will be rejected. Authors will be notified of these decisions on **May 3, 2019**. Authors of conditionally accepted papers will be provided with committee reviews (just as in previous conferences) along with a set of mandatory revisions. After four weeks (May 31, 2019), the authors will provide a second submission. The second and final reviewing phase assesses whether the mandatory revisions have been adequately addressed by the authors and thereby determines the final accept/reject status of the paper. The intent and expectation is that the mandatory revisions can be addressed within four weeks and hence that conditionally accepted papers will in general be accepted in the second phase. The second submission should clearly identify how the mandatory revisions were addressed. To that end, the second submission must be accompanied by a cover letter mapping each mandatory revision request to specific parts of the paper. The cover letter will facilitate a quick second review, allowing for confirmation of final acceptance within two weeks. Conversely, the absence of a cover letter will be grounds for the paper’s rejection. **PACMPL issue ICFP 2019 will employ a lightweight double-blind reviewing process.** To facilitate this, submitted papers must adhere to two rules: 1. **author names and institutions must be omitted**, and 2. **references to authors' own related work should be in the third person** (e.g., not "We build on our previous work ..." but rather "We build on the work of ..."). The purpose of this process is to help the reviewers come to an initial judgement about the paper without bias, not to make it impossible for them to discover the authors if they were to try. Nothing should be done in the name of anonymity that weakens the submission or makes the job of reviewing the paper more difficult (e.g., important background references should not be omitted or anonymized). In addition, authors should feel free to disseminate their ideas or draft versions of their paper as they normally would. For instance, authors may post drafts of their papers on the web or give talks on their research ideas. ### Information for Authors of Accepted Papers * As a condition of acceptance, final versions of all papers must adhere to the new ACM Small format. The page limit for the final versions of papers will be increased by two pages to help authors respond to reviewer comments and mandatory revisions: **27 pages plus bibliography for a regular paper or Functional Pearl, 14 pages plus bibliography for an Experience Report**. * Authors of accepted submissions will be required to agree to one of the three ACM licensing options: open access on payment of a fee (**recommended**, and SIGPLAN can cover the cost as described next); copyright transfer to ACM; or retaining copyright but granting ACM exclusive publication rights. Further information about ACM author rights is available from . * PACMPL is a Gold Open Access journal. It will be archived in ACM’s Digital Library, but no membership or fee is required for access. Gold Open Access has been made possible by generous funding through ACM SIGPLAN, which will cover all open access costs in the event authors cannot. Authors who can cover the costs may do so by paying an Article Processing Charge (APC). PACMPL, SIGPLAN, and ACM Headquarters are committed to exploring routes to making Gold Open Access publication both affordable and sustainable. * ACM offers authors a range of copyright options, one of which is Creative Commons CC-BY publication; this is the option recommended by the PACMPL editorial board. A reasoned argument in favour of this option can be found in the article [Why CC-BY?](https://oaspa.org/why-cc-by/) published by OASPA, the Open Access Scholarly Publishers Association. * We intend that the papers will be freely available for download from the ACM Digital Library in perpetuity via the OpenTOC mechanism. * ACM Author-Izer is a unique service that enables ACM authors to generate and post links on either their home page or institutional repository for visitors to download the definitive version of their articles from the ACM Digital Library at no charge. Downloads through Author-Izer links are captured in official ACM statistics, improving the accuracy of usage and impact measurements. Consistently linking to the definitive version of an ACM article should reduce user confusion over article versioning. After an article has been published and assigned to the appropriate ACM Author Profile pages, authors should visit to learn how to create links for free downloads from the ACM DL. * At least one author of each accepted submissions will be expected to attend and present their paper at the conference. The schedule for presentations will be determined and shared with authors after the full program has been selected. Presentations will be videotaped and released online if the presenter consents. * The official publication date is the date the papers are made available in the ACM Digital Library. This date may be up to *two weeks prior* to the first day of the conference. The official publication date affects the deadline for any patent filings related to published work. ### Artifact Evaluation Authors of papers that are conditionally accepted in the first phase of the review process will be encouraged (but not required) to submit supporting materials for Artifact Evaluation. These items will then be reviewed by an Artifact Evaluation Committee, separate from the paper Review Committee, whose task is to assess how the artifacts support the work described in the associated paper. Papers that go through the Artifact Evaluation process successfully will receive a seal of approval printed on the papers themselves. Authors of accepted papers will be encouraged to make the supporting materials publicly available upon publication of the papers, for example, by including them as "source materials" in the ACM Digital Library. An additional seal will mark papers whose artifacts are made available, as outlined in the ACM guidelines for artifact badging. Participation in Artifact Evaluation is voluntary and will not influence the final decision regarding paper acceptance. ### Special categories of papers In addition to research papers, PACMPL issue ICFP solicits two kinds of papers that do not require original research contributions: Functional Pearls, which are full papers, and Experience Reports, which are limited to half the length of a full paper. Authors submitting such papers should consider the following guidelines. #### Functional Pearls A Functional Pearl is an elegant essay about something related to functional programming. Examples include, but are not limited to: * a new and thought-provoking way of looking at an old idea * an instructive example of program calculation or proof * a nifty presentation of an old or new data structure * an interesting application of functional programming techniques * a novel use or exposition of functional programming in the classroom While pearls often demonstrate an idea through the development of a short program, there is no requirement or expectation that they do so. Thus, they encompass the notions of theoretical and educational pearls. Functional Pearls are valued as highly and judged as rigorously as ordinary papers, but using somewhat different criteria. In particular, a pearl is not required to report original research, but, it should be concise, instructive, and entertaining. A pearl is likely to be rejected if its readers get bored, if the material gets too complicated, if too much specialized knowledge is needed, or if the writing is inelegant. The key to writing a good pearl is polishing. A submission that is intended to be treated as a pearl must be marked as such on the submission web page, and should contain the words "Functional Pearl" somewhere in its title or subtitle. These steps will alert reviewers to use the appropriate evaluation criteria. Pearls will be combined with ordinary papers, however, for the purpose of computing the conference's acceptance rate. #### Experience Reports The purpose of an Experience Report is to help create a body of published, refereed, citable evidence that functional programming really works — or to describe what obstacles prevent it from working. Possible topics for an Experience Report include, but are not limited to: * insights gained from real-world projects using functional programming * comparison of functional programming with conventional programming in the context of an industrial project or a university curriculum * project-management, business, or legal issues encountered when using functional programming in a real-world project * curricular issues encountered when using functional programming in education * real-world constraints that created special challenges for an implementation of a functional language or for functional programming in general An Experience Report is distinguished from a normal PACMPL issue ICFP paper by its title, by its length, and by the criteria used to evaluate it. * Both in the papers and in any citations, the title of each accepted Experience Report must end with the words "(Experience Report)" in parentheses. The acceptance rate for Experience Reports will be computed and reported separately from the rate for ordinary papers. * Experience Report submissions can be at most 12 pages long, excluding bibliography. * Each accepted Experience Report will be presented at the conference, but depending on the number of Experience Reports and regular papers accepted, authors of Experience reports may be asked to give shorter talks. * Because the purpose of Experience Reports is to enable our community to accumulate a body of evidence about the efficacy of functional programming, an acceptable Experience Report need not add to the body of knowledge of the functional-programming community by presenting novel results or conclusions. It is sufficient if the Report states a clear thesis and provides supporting evidence. The thesis must be relevant to ICFP, but it need not be novel. The review committee will accept or reject Experience Reports based on whether they judge the evidence to be convincing. Anecdotal evidence will be acceptable provided it is well argued and the author explains what efforts were made to gather as much evidence as possible. Typically, more convincing evidence is obtained from papers which show how functional programming was used than from papers which only say that functional programming was used. The most convincing evidence often includes comparisons of situations before and after the introduction or discontinuation of functional programming. Evidence drawn from a single person's experience may be sufficient, but more weight will be given to evidence drawn from the experience of groups of people. An Experience Report should be short and to the point: it should make a claim about how well functional programming worked on a particular project and why, and produce evidence to substantiate this claim. If functional programming worked in this case in the same ways it has worked for others, the paper need only summarize the results — the main part of the paper should discuss how well it worked and in what context. Most readers will not want to know all the details of the project and its implementation, but the paper should characterize the project and its context well enough so that readers can judge to what degree this experience is relevant to their own projects. The paper should take care to highlight any unusual aspects of the project. Specifics about the project are more valuable than generalities about functional programming; for example, it is more valuable to say that the team delivered its software a month ahead of schedule than it is to say that functional programming made the team more productive. If the paper not only describes experience but also presents new technical results, or if the experience refutes cherished beliefs of the functional-programming community, it may be better to submit it as a full paper, which will be judged by the usual criteria of novelty, originality, and relevance. The principal editor will be happy to advise on any concerns about which category to submit to. ### ICFP Organizers General Chair: Derek Dreyer (MPI-SWS, Germany) Artifact Evaluation Co-Chairs: Simon Marlow (Facebook, UK) Industrial Relations Chair: Alan Jeffrey (Mozilla Research, USA) Programming Contest Organiser: Ilya Sergey (Yale-NUS College, Singapore) Publicity and Web Chair: Sam Tobin-Hochstadt (Indiana University, USA) Student Research Competition Chair: William J. Bowman (University of British Columbia, Canada) Workshops Co-Chair: Christophe Scholliers (Universiteit Gent, Belgium) Jennifer Hackett (University of Nottingham, UK) Conference Manager: Annabel Satin (P.C.K.) ### PACMPL Volume 3, Issue ICFP 2019 Principal Editor: François Pottier (Inria, France) Review Committee: Lennart Beringer (Princeton University, United States) Joachim Breitner (DFINITY Foundation, Germany) Laura M. Castro (University of A Coruña, Spain) Ezgi Çiçek (Facebook London, United Kingdom) Pierre-Evariste Dagand (LIP6/CNRS, France) Christos Dimoulas (Northwestern University, United States) Jacques-Henri Jourdan (CNRS, LRI, Université Paris-Sud, France) Andrew Kennedy (Facebook London, United Kingdom) Daan Leijen (Microsoft Research, United States) Kazutaka Matsuda (Tohoku University, Japan) Bruno C. d. S. Oliveira (University of Hong Kong, China) Klaus Ostermann (University of Tübingen, Germany) Jennifer Paykin (Galois, United States) Frank Pfenning (Carnegie Mellon University, USA) Mike Rainey (Indiana University, USA) Chung-chieh Shan (Indiana University, USA) Sam Staton (University of Oxford, UK) Pierre-Yves Strub (Ecole Polytechnique, France) German Vidal (Universitat Politecnica de Valencia, Spain) External Review Committee: Michael D. Adams (University of Utah, USA) Robert Atkey (University of Strathclyde, IK) Sheng Chen (University of Louisiana at Lafayette, USA) James Cheney (University of Edinburgh, UK) Adam Chlipala (Massachusetts Institute of Technology, USA) Evelyne Contejean (LRI, Université Paris-Sud, France) Germán Andrés Delbianco (IRIF, Université Paris Diderot, France) Dominique Devriese (Vrije Universiteit Brussel, Belgium) Richard A. Eisenberg (Bryn Mawr College, USA) Conal Elliott (Target, USA) Sebastian Erdweg (Delft University of Technology, Netherlands) Michael Greenberg (Pomona College, USA) Adrien Guatto (IRIF, Université Paris Diderot, France) Jennifer Hackett (University of Nottingham, UK) Troels Henriksen (University of Copenhagen, Denmark) Chung-Kil Hur (Seoul National University, Republic of Korea) Roberto Ierusalimschy (PUC-Rio, Brazil) Ranjit Jhala (University of California, San Diego, USA) Ralf Jung (MPI-SWS, Germany) Ohad Kammar (University of Oxford, UK) Oleg Kiselyov (Tohoku University, Japan) Hsiang-Shang ‘Josh’ Ko (National Institute of Informatics, Japan) Ondřej Lhoták (University of Waterloo, Canada) Dan Licata (Wesleyan University, USA) Geoffrey Mainland (Drexel University, USA) Simon Marlow (Facebook, UK) Akimasa Morihata (University of Tokyo, Japan) Shin-Cheng Mu (Academia Sinica, Taiwan) Guillaume Munch-Maccagnoni (Inria, France) Kim Nguyễn (University of Paris-Sud, France) Ulf Norell (Gothenburg University, Sweden) Atsushi Ohori (Tohoku University, Japan) Rex Page (University of Oklahoma, USA) Zoe Paraskevopoulou (Princeton University, USA) Nadia Polikarpova (University of California, San Diego, USA) Jonathan Protzenko (Microsoft Research, USA) Tiark Rompf (Purdue University, USA) Andreas Rossberg (Dfinity, Germany) KC Sivaramakrishnan (University of Cambridge, UI) Nicholas Smallbone (Chalmers University of Technology, Sweden) Matthieu Sozeau (Inria, France) Sandro Stucki (Chalmers | University of Gothenburg, Sweden) Don Syme (Microsoft, UK) Zachary Tatlock (University of Washington, USA) Sam Tobin-Hochstadt (Indiana University, USA) Takeshi Tsukada (University of Tokyo, Japan) Tarmo Uustalu (Reykjavik University, Iceland) Benoit Valiron (LRI, CentraleSupelec, Univ. Paris Saclay, France) Daniel Winograd-Cort (University of Pennsylvania, USA) Nicolas Wu (University of Bristol, UK) From johannes.waldmann at htwk-leipzig.de Fri Nov 9 09:59:03 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Fri, 9 Nov 2018 10:59:03 +0100 Subject: [Haskell-cafe] find functions that produce / consume a type? Message-ID: <3e70fd9e-377a-7a4b-4a84-a0bd5e374c46@htwk-leipzig.de> Dear Cafe, can we automate something like the following for any type T that appears in signatures (shown by haddock), add (separate) lists of "functions that produce T", "functions that consume T". Hoogle can type-search approximately, but * it would always (want to) match the full type AST (matching with a subtree incurs a penalty?), * and not distinguish between producer and consumer? E.g., https://ndmitchell.com/downloads/slides-hoogle_finding_functions_from_types-16_may_2011.pdf Slide #29 "Per Argument Searching" uses "search arguments", "search results" - only to merge the results immediately. Can we keep them separate? - J.W. From me at abn.sh Sat Nov 10 13:51:03 2018 From: me at abn.sh (Alexander Ben Nasrallah) Date: Sat, 10 Nov 2018 14:51:03 +0100 Subject: [Haskell-cafe] wxneeded on OpenBSD Message-ID: <20181110135103.GA4565@relaxo.my.domain> Hello Haskell-Cafe, I hope this is the right place for my question. Is there any progress or news on getting rid of the wxneeded flag on OpenBSD? https://phabricator.haskell.org/D2454 mentions a new ticket but I can't find any. Thanks Alex From danburton.email at gmail.com Sat Nov 10 17:39:53 2018 From: danburton.email at gmail.com (Dan Burton) Date: Sat, 10 Nov 2018 12:39:53 -0500 Subject: [Haskell-cafe] Fwd: [Haskell] [ANNOUNCE] GHC 8.6.2 is now available In-Reply-To: References: <87h8gvwkrp.fsf@smart-cactus.org> Message-ID: (fwd to the real haskell cafe list) -- Dan Burton ---------- Forwarded message --------- From: Dan Burton Date: Sat, Nov 10, 2018 at 11:30 AM Subject: Re: [Haskell] [ANNOUNCE] GHC 8.6.2 is now available To: Ben Gamari Cc: Haskell-cafe I have two trivialities to bring up: 1. Could you update https://downloads.haskell.org/~ghc/latest/ to point to 8.6.2? (It's currently showing 8.6.1.) 2. The SHA1SUMS and SHA256SUMS for 8.6.2 list a file "./ghc-8.6.2-x86_64-darwin.tar.xz", but that is a broken link; the corresponding file is found at "./ghc-8.6.2-x86_64*-apple*-darwin.tar.xz". Can these be harmonized? Thanks! -- Dan Burton On Mon, Nov 5, 2018 at 11:29 AM Ben Gamari wrote: > Hello everyone, > > The GHC team is very happy to announce the availability of GHC 8.6.2, a > bugfix release to GHC 8.6.1. The source distribution, binary > distributions, and documentation for this release are available at > > https://downloads.haskell.org/~ghc/8.6.2 > > The 8.6 release fixes several regressions present in 8.6.1 including: > > * A long-standing (but previously hard to manifest) bug resulting in > undefined behavior for some applications of dataToTag# has been fixed > (#15696) > > * An incorrect linker path to libgmp in the Mac OS binary distributions > (#15404) > > * A regression rendering Windows installations to read-only directories > unusable (#15667) > > * A regression resulting in panics while compiling some record updates > of GADTs constructors (#15499) > > * A regression resulting in incorrect type errors when splicing types > into constraint contexts has been fixed (#15815) > > * Around a dozen other issues. > > See Trac [1] for a full list of issues resolved in this release. > > Note that this release ships with one significant but long-standing bug > (#14251): Calls to functions taking both Float# and Double# may result > in incorrect code generation when compiled using the LLVM code generator. > This is not a new issue, it has existed as long as the LLVM code > generator has existed; however, changes in code generation in 8.6 made > it more likely that user code using only lifted types will trigger it. > > Happy compiling! > > Cheers, > > - Ben > > > > [1] > https://ghc.haskell.org/trac/ghc/query?status=closed&milestone=8.6.2&col=id&col=summary&col=status&col=type&col=priority&col=milestone&col=component&order=priority > _______________________________________________ > Haskell mailing list > Haskell at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Nov 11 10:21:15 2018 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 11 Nov 2018 10:21:15 +0000 Subject: [Haskell-cafe] find functions that produce / consume a type? In-Reply-To: <3e70fd9e-377a-7a4b-4a84-a0bd5e374c46@htwk-leipzig.de> References: <3e70fd9e-377a-7a4b-4a84-a0bd5e374c46@htwk-leipzig.de> Message-ID: <20181111102115.xwkt3aj7wobm3cen@weber> On Fri, Nov 09, 2018 at 10:59:03AM +0100, Johannes Waldmann wrote: > can we automate something like the following > > for any type T that appears in signatures (shown by haddock), > add (separate) lists of "functions that produce T", > "functions that consume T". This is a very nice idea. From eric at seidel.io Sun Nov 11 14:45:43 2018 From: eric at seidel.io (Eric Seidel) Date: Sun, 11 Nov 2018 09:45:43 -0500 Subject: [Haskell-cafe] find functions that produce / consume a type? In-Reply-To: <3e70fd9e-377a-7a4b-4a84-a0bd5e374c46@htwk-leipzig.de> References: <3e70fd9e-377a-7a4b-4a84-a0bd5e374c46@htwk-leipzig.de> Message-ID: Hoogle does let you restrict the search to the output type by prefixing your query with “::”. For example, “:: Maybe a” produces a list of functions that return a Maybe. https://www.haskell.org/hoogle/?hoogle=%3A%3A+Maybe+a Unfortunately this doesn’t seem to work in the new Hoogle hosted at hoogle.haskell.org. Sent from my iPhone > On Nov 9, 2018, at 04:59, Johannes Waldmann wrote: > > Dear Cafe, > > can we automate something like the following > > for any type T that appears in signatures (shown by haddock), > add (separate) lists of "functions that produce T", > "functions that consume T". > > Hoogle can type-search approximately, but > * it would always (want to) match the full type AST > (matching with a subtree incurs a penalty?), > * and not distinguish between producer and consumer? > > E.g., > https://ndmitchell.com/downloads/slides-hoogle_finding_functions_from_types-16_may_2011.pdf > Slide #29 "Per Argument Searching" > uses "search arguments", "search results" - > only to merge the results immediately. > Can we keep them separate? > > - J.W. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From danburton.email at gmail.com Mon Nov 12 04:28:38 2018 From: danburton.email at gmail.com (Dan Burton) Date: Sun, 11 Nov 2018 23:28:38 -0500 Subject: [Haskell-cafe] Let's plan BayHac 2019! Message-ID: It's time to start thinking about the next BayHac! I am assembling a group of organizers for next year's event. Anyone who has been involved in organizing past BayHac events will be automatically accepted. (I have BCCed a number of past organizers; please reach out to any you know in case I missed anyone.) Anyone else who is interested in helping to plan BayHac, please contact me. Depending on how many past organizers rejoin, we will discuss the applicants and accept 1 to 3 new organizers. BayHac is a weekend of learning, sharing, and hacking on a variety of projects for the Haskell community. BayHac usually occurs in San Francisco, California, Mountain View, California, or thereabouts. I'd like to aim for April/May 2019, though that is, of course, subject to change. A rough outline, in rough chronological order, of what the BayHac organizers will be doing: 0. Assemble the organizers. 1. Select date and venue for BayHac 2019. 2. Secure corporate sponsors to cover costs (mainly, food). 3. Invite talk proposals and select speakers. 4. Open online registration and publicize the event. 5. Plan details like catering, registration desk, recording, and make it happen! If any of that sounds like fun to you, then I'd love to hear from you! -- Dan Burton -------------- next part -------------- An HTML attachment was scrubbed... URL: From lukacbanjalukamaraton at gmail.com Tue Nov 13 21:57:10 2018 From: lukacbanjalukamaraton at gmail.com (Aleksandar Lukac) Date: Tue, 13 Nov 2018 22:57:10 +0100 Subject: [Haskell-cafe] Request for Haskell account Message-ID: Hello, I would like to have Haskell account. I would like to start to solve 99 problems and to submit it. My name is Aleksandar Lukac, and i would like to have similar user name Aeksandar, Lukac or aleksandar.lukac or something likewise for example Aleksandar111 Thank you in advance *Aleksandar Lukač* | *Koordinator volontera**- Half Marathon ”MTEL City Race Banja Luka 2015” * *p**:* +387 66 40 77 22 *e*: lukaclukacbanjalukamaraton at gmail.com | *w:* banjalukamarathon.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From danburton.email at gmail.com Tue Nov 13 22:14:37 2018 From: danburton.email at gmail.com (Dan Burton) Date: Tue, 13 Nov 2018 17:14:37 -0500 Subject: [Haskell-cafe] Request for Haskell account In-Reply-To: References: Message-ID: +wiki-account-request I believe you're referring to a Haskell Wiki account, correct? -- Dan Burton On Tue, Nov 13, 2018 at 4:57 PM Aleksandar Lukac < lukacbanjalukamaraton at gmail.com> wrote: > > Hello, I would like to have Haskell account. I would like to start to > solve 99 problems and to submit it. > My name is Aleksandar Lukac, and i would like to have similar user name > Aeksandar, Lukac or aleksandar.lukac or something likewise for example > Aleksandar111 > Thank you in advance > > > > *Aleksandar Lukač* | > *Koordinator volontera**- Half Marathon ”MTEL City Race Banja Luka 2015” * > > > *p**:* +387 66 40 77 22 > > *e*: lukaclukacbanjalukamaraton at gmail.com | > *w:* banjalukamarathon.com > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lukacbanjalukamaraton at gmail.com Tue Nov 13 22:16:41 2018 From: lukacbanjalukamaraton at gmail.com (Aleksandar Lukac) Date: Tue, 13 Nov 2018 23:16:41 +0100 Subject: [Haskell-cafe] Request for Haskell account In-Reply-To: References: Message-ID: Yes, that is correct. *Aleksandar Lukač* | *Koordinator volontera**- Half Marathon ”MTEL City Race Banja Luka 2015” * *p**:* +387 66 40 77 22 *e*: lukaclukacbanjalukamaraton at gmail.com | *w:* banjalukamarathon.com uto, 13. stu 2018. u 23:15 Dan Burton napisao je: > +wiki-account-request > > I believe you're referring to a Haskell Wiki account, correct? > > -- Dan Burton > > > On Tue, Nov 13, 2018 at 4:57 PM Aleksandar Lukac < > lukacbanjalukamaraton at gmail.com> wrote: > >> >> Hello, I would like to have Haskell account. I would like to start to >> solve 99 problems and to submit it. >> My name is Aleksandar Lukac, and i would like to have similar user name >> Aeksandar, Lukac or aleksandar.lukac or something likewise for example >> Aleksandar111 >> Thank you in advance >> >> >> >> *Aleksandar Lukač* | >> *Koordinator volontera**- Half Marathon ”MTEL City Race Banja Luka 2015” >> * >> >> >> *p**:* +387 66 40 77 22 >> >> *e*: lukaclukacbanjalukamaraton at gmail.com | >> *w:* banjalukamarathon.com >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Thu Nov 15 15:42:31 2018 From: ekmett at gmail.com (Edward Kmett) Date: Thu, 15 Nov 2018 10:42:31 -0500 Subject: [Haskell-cafe] Let's plan BayHac 2019! In-Reply-To: References: Message-ID: At the very least, I'd be interesting in giving a talk, and I can probably convince MIRI to help sponsor if you have a sense of what you need. (They were quite happy with how their sponsorship of ICFP went this year.) My one personal time constraint in April/May is whenever it turns out Yow! LambdaJam is going to be scheduled. Last year it was May 21-23 and it has held consistently to that part of May. -Edward On Sun, Nov 11, 2018 at 11:29 PM Dan Burton wrote: > It's time to start thinking about the next BayHac! > > I am assembling a group of organizers for next year's event. Anyone who > has been involved in organizing past BayHac events will be automatically > accepted. (I have BCCed a number of past organizers; please reach out to > any you know in case I missed anyone.) > > Anyone else who is interested in helping to plan BayHac, please contact > me. Depending on how many past organizers rejoin, we will discuss the > applicants and accept 1 to 3 new organizers. > > BayHac is a weekend of learning, sharing, and hacking on a variety of > projects for the Haskell community. BayHac usually occurs in San Francisco, > California, Mountain View, California, or thereabouts. > > I'd like to aim for April/May 2019, though that is, of course, subject to > change. > > A rough outline, in rough chronological order, of what the BayHac > organizers will be doing: > > 0. Assemble the organizers. > 1. Select date and venue for BayHac 2019. > 2. Secure corporate sponsors to cover costs (mainly, food). > 3. Invite talk proposals and select speakers. > 4. Open online registration and publicize the event. > 5. Plan details like catering, registration desk, recording, and make it > happen! > > If any of that sounds like fun to you, then I'd love to hear from you! > > -- Dan Burton > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From cdsmith at gmail.com Thu Nov 15 16:24:42 2018 From: cdsmith at gmail.com (Chris Smith) Date: Thu, 15 Nov 2018 11:24:42 -0500 Subject: [Haskell-cafe] Let's plan BayHac 2019! In-Reply-To: References: Message-ID: Hi Dan, I'm in New York now, so I won't be around as much to help out with organizing. However, it's likely I could be convinced to come give a talk and participate. I can also follow some of the same paths that I did this year, to ask about sponsorship by Google. It was a bit of a mess the last time around, and I don't even remember what ended up happening; but asking earlier is usually better. Thanks, Chris On Sun, Nov 11, 2018 at 11:28 PM Dan Burton wrote: > It's time to start thinking about the next BayHac! > > I am assembling a group of organizers for next year's event. Anyone who > has been involved in organizing past BayHac events will be automatically > accepted. (I have BCCed a number of past organizers; please reach out to > any you know in case I missed anyone.) > > Anyone else who is interested in helping to plan BayHac, please contact > me. Depending on how many past organizers rejoin, we will discuss the > applicants and accept 1 to 3 new organizers. > > BayHac is a weekend of learning, sharing, and hacking on a variety of > projects for the Haskell community. BayHac usually occurs in San Francisco, > California, Mountain View, California, or thereabouts. > > I'd like to aim for April/May 2019, though that is, of course, subject to > change. > > A rough outline, in rough chronological order, of what the BayHac > organizers will be doing: > > 0. Assemble the organizers. > 1. Select date and venue for BayHac 2019. > 2. Secure corporate sponsors to cover costs (mainly, food). > 3. Invite talk proposals and select speakers. > 4. Open online registration and publicize the event. > 5. Plan details like catering, registration desk, recording, and make it > happen! > > If any of that sounds like fun to you, then I'd love to hear from you! > > -- Dan Burton > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Nov 15 17:20:16 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 15 Nov 2018 12:20:16 -0500 Subject: [Haskell-cafe] wxneeded on OpenBSD In-Reply-To: <20181110135103.GA4565@relaxo.my.domain> References: <20181110135103.GA4565@relaxo.my.domain> Message-ID: https://ghc.haskell.org/trac/ghc/ticket/14069 is perhaps the ticket you wanted to google (i searched trac for linker and openbsd) On Sat, Nov 10, 2018 at 8:51 AM Alexander Ben Nasrallah wrote: > Hello Haskell-Cafe, > > I hope this is the right place for my question. > > Is there any progress or news on getting rid of the wxneeded flag on > OpenBSD? > > https://phabricator.haskell.org/D2454 mentions a new ticket but I can't > find any. > > Thanks > Alex > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From me at abn.sh Fri Nov 16 05:18:43 2018 From: me at abn.sh (Alexander Ben Nasrallah) Date: Fri, 16 Nov 2018 06:18:43 +0100 Subject: [Haskell-cafe] wxneeded on OpenBSD In-Reply-To: References: <20181110135103.GA4565@relaxo.my.domain> Message-ID: <20181116051843.GA28610@relaxo.my.domain> On Thu, Nov 15, 2018 at 12:20:16PM -0500, Carter Schonwald wrote: > https://ghc.haskell.org/trac/ghc/ticket/14069 is perhaps the ticket you > wanted to google (i searched trac for linker and openbsd) That seems to be it. Thank you very much! From ryan.reich at gmail.com Sat Nov 17 23:21:53 2018 From: ryan.reich at gmail.com (Ryan Reich) Date: Sat, 17 Nov 2018 15:21:53 -0800 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself Message-ID: I want to time out a pure computation. My experience, and that described in various previous questions here and elsewhere (the best of which is https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), is that this doesn't always work: for instance, >>> timeout 1 $ evaluate $ let x = 0 : x in last x does not time out because, apparently, the fact that the expression evaluates in constant space (i.e. never allocates) means that it never yields to the timeout monitor thread that would kill it. The solution that is described in the other iterations is to embed checkpoints in the expression that do allocate, giving the RTS a chance to switch contexts. However, in my application, the expression is /arbitrary/ and I do not have the freedom to inject alterations into it. (Don't argue this point, please. The expression is arbitrary.) How can I time out a tight loop like the above? Clearly, it can be done, because I can, say, alt-tab over to another terminal and kill the process, which exploits the operating system's more aggressively pre-emptive scheduling. Is there a solution using bound threads, say 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? Unix signals? Some FFI-based workaround? Etc. Keep in mind that notwithstanding that comment, I don't actually want to kill the whole process, but just the one evaluation. Thanks in advance, Ryan Reich -------------- next part -------------- An HTML attachment was scrubbed... URL: From dhelta.diaz at gmail.com Sun Nov 18 00:51:58 2018 From: dhelta.diaz at gmail.com (=?UTF-8?Q?Daniel_D=C3=ADaz_Casanueva?=) Date: Sun, 18 Nov 2018 01:51:58 +0100 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: Message-ID: Hello Ryan. Try evaluating the expression to normal form instead of weak head normal form in your expression. So: >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x The function `force` comes from the deepseq package. You can read the docs here: http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html I hope that helps. Best regards, Daniel Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich : > I want to time out a pure computation. My experience, and that described > in various previous questions here and elsewhere (the best of which is > https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), > is that this doesn't always work: for instance, > > >>> timeout 1 $ evaluate $ let x = 0 : x in last x > > does not time out because, apparently, the fact that the expression > evaluates in constant space (i.e. never allocates) means that it never > yields to the timeout monitor thread that would kill it. > > The solution that is described in the other iterations is to embed > checkpoints in the expression that do allocate, giving the RTS a chance to > switch contexts. However, in my application, the expression is /arbitrary/ > and I do not have the freedom to inject alterations into it. (Don't argue > this point, please. The expression is arbitrary.) > > How can I time out a tight loop like the above? Clearly, it can be done, > because I can, say, alt-tab over to another terminal and kill the process, > which exploits the operating system's more aggressively pre-emptive > scheduling. Is there a solution using bound threads, say 'forkOS' instead > of 'forkIO' in the implementation of 'timeout'? Unix signals? Some > FFI-based workaround? Etc. Keep in mind that notwithstanding that > comment, I don't actually want to kill the whole process, but just the one > evaluation. > > Thanks in advance, > Ryan Reich > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From dhelta.diaz at gmail.com Sun Nov 18 00:55:56 2018 From: dhelta.diaz at gmail.com (=?UTF-8?Q?Daniel_D=C3=ADaz_Casanueva?=) Date: Sun, 18 Nov 2018 01:55:56 +0100 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: Message-ID: Actually, after reading the question again, it seems like my response wasn't quite right. You are not actually building the list. In that case, I am as confused as you. :) Sorry! Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < dhelta.diaz at gmail.com>: > Hello Ryan. > > Try evaluating the expression to normal form instead of weak head normal > form in your expression. So: > > >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x > > The function `force` comes from the deepseq package. You can read the docs > here: > http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html > > I hope that helps. > > Best regards, > Daniel > > Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < > ryan.reich at gmail.com>: > >> I want to time out a pure computation. My experience, and that described >> in various previous questions here and elsewhere (the best of which is >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >> is that this doesn't always work: for instance, >> >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >> >> does not time out because, apparently, the fact that the expression >> evaluates in constant space (i.e. never allocates) means that it never >> yields to the timeout monitor thread that would kill it. >> >> The solution that is described in the other iterations is to embed >> checkpoints in the expression that do allocate, giving the RTS a chance to >> switch contexts. However, in my application, the expression is /arbitrary/ >> and I do not have the freedom to inject alterations into it. (Don't argue >> this point, please. The expression is arbitrary.) >> >> How can I time out a tight loop like the above? Clearly, it can be done, >> because I can, say, alt-tab over to another terminal and kill the process, >> which exploits the operating system's more aggressively pre-emptive >> scheduling. Is there a solution using bound threads, say 'forkOS' instead >> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >> FFI-based workaround? Etc. Keep in mind that notwithstanding that >> comment, I don't actually want to kill the whole process, but just the one >> evaluation. >> >> Thanks in advance, >> Ryan Reich >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.reich at gmail.com Sun Nov 18 00:57:56 2018 From: ryan.reich at gmail.com (Ryan Reich) Date: Sat, 17 Nov 2018 16:57:56 -0800 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: Message-ID: I was just about to reply with an observation to that effect :) The place that I'd want to put 'force' is actually inside the 'let' clause, which of course you can't do just by applying a function. The expression as a whole is just an Integer. On Sat, Nov 17, 2018 at 4:56 PM Daniel Díaz Casanueva wrote: > Actually, after reading the question again, it seems like my response > wasn't quite right. You are not actually building the list. In that case, I > am as confused as you. :) > > Sorry! > > Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < > dhelta.diaz at gmail.com>: > >> Hello Ryan. >> >> Try evaluating the expression to normal form instead of weak head normal >> form in your expression. So: >> >> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x >> >> The function `force` comes from the deepseq package. You can read the >> docs here: >> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html >> >> I hope that helps. >> >> Best regards, >> Daniel >> >> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < >> ryan.reich at gmail.com>: >> >>> I want to time out a pure computation. My experience, and that >>> described in various previous questions here and elsewhere (the best of >>> which is >>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >>> is that this doesn't always work: for instance, >>> >>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >>> >>> does not time out because, apparently, the fact that the expression >>> evaluates in constant space (i.e. never allocates) means that it never >>> yields to the timeout monitor thread that would kill it. >>> >>> The solution that is described in the other iterations is to embed >>> checkpoints in the expression that do allocate, giving the RTS a chance to >>> switch contexts. However, in my application, the expression is /arbitrary/ >>> and I do not have the freedom to inject alterations into it. (Don't argue >>> this point, please. The expression is arbitrary.) >>> >>> How can I time out a tight loop like the above? Clearly, it can be >>> done, because I can, say, alt-tab over to another terminal and kill the >>> process, which exploits the operating system's more aggressively >>> pre-emptive scheduling. Is there a solution using bound threads, say >>> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? Unix >>> signals? Some FFI-based workaround? Etc. Keep in mind that >>> notwithstanding that comment, I don't actually want to kill the whole >>> process, but just the one evaluation. >>> >>> Thanks in advance, >>> Ryan Reich >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From ducis_cn at 126.com Sun Nov 18 04:01:25 2018 From: ducis_cn at 126.com (ducis) Date: Sun, 18 Nov 2018 12:01:25 +0800 (CST) Subject: [Haskell-cafe] Specialize a function on types of arguments? Message-ID: <552773e2.1be5.16724faf3d0.Coremail.ducis_cn@126.com> Hi, everyone, Is it possible to make combine the following "f" and "g" into one function? f:: a -> b -> b f x y = y g:: a -> a -> a g x y = x Or similarly, "eq1" and "eq2" into one function? eq1 :: (Eq a)=>a->a->Bool eq1 = (==) eq2 :: (Eq a,Eq b)=>a->b->Bool eq2 _ _ = False Looks like it would require some typeclasses, but at least in the first case, "a" and "b" should be any types. Best! -------------- next part -------------- An HTML attachment was scrubbed... URL: From anthony_clayden at clear.net.nz Sun Nov 18 04:40:51 2018 From: anthony_clayden at clear.net.nz (Anthony Clayden) Date: Sun, 18 Nov 2018 17:40:51 +1300 Subject: [Haskell-cafe] Specialize a function on types of arguments? Message-ID: Hi Ducis, > Is it possible to make combine the following "f" and "g" into one function? "combine" is vague. You perhaps mean: look at the types of the arguments, and choose one function or the other? > Looks like it would require some typeclasses, I'll answer the question as put (yes it needs typeclasses), but I can't help feel there's a backstory, and you might well be doing something that could be done better, if I knew what you're trying to achieve. Let's take the second one first > "eq1" and "eq2" into one function? > eq1 :: (Eq a)=>a->a->Bool > eq1 = (==) > eq2 :: (Eq a,Eq b)=>a->b->Bool > eq2 _ _ = False class Eqbytype a b where eqt :: a -> b -> Bool instance {-# OVERLAPPING #-} (Eq a) => Eqbytype a a where eqt = (==) instance {-# OVERLAPPABLE #-} Eqbytype a b where eqt _ _ = False Look at the Users Guide for what the OVERLAPPING/OVERLAPPABLE pragmas are doing. Note for the first instance I repeated type var `a` in the head, meaning: pick this instance if the two arguments to the method are of the same type. Note for the second instance, I didn't bother with the `Eq` constraint, since we can't compare values of distinct types. > f:: a -> b -> b > f x y = y > g:: a -> a -> a > g x y = x So you want same argument types to drive which argument to pick? Or you want the return type to drive which argument? That's possible: look at the definition of class `Read` in the Prelude. Again we can pick instances depending on a repeated type. But your requirements are not clear. > but at least in the first case [which I've put second], "a" and "b" should be any types. No they can't: as you state it, you require either all three the same, or the second to be the same as the return type. Come back and ask a more focussed question once you've worked through the above. (And explain why you're asking.) The above code is untested, BTW. AntC -------------- next part -------------- An HTML attachment was scrubbed... URL: From arjenvanweelden at gmail.com Sun Nov 18 08:22:08 2018 From: arjenvanweelden at gmail.com (arjenvanweelden at gmail.com) Date: Sun, 18 Nov 2018 09:22:08 +0100 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: Message-ID: <27e9100ff70dd67791ed34e152c58239499bba65.camel@gmail.com> On Sat, 2018-11-17 at 15:21 -0800, Ryan Reich wrote: > I want to time out a pure computation. My experience, and that > described in various previous questions here and elsewhere (the best > of which is > https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html > ), is that this doesn't always work: for instance, > > >>> timeout 1 $ evaluate $ let x = 0 : x in last x > > does not time out because, apparently, the fact that the expression > evaluates in constant space (i.e. never allocates) means that it > never yields to the timeout monitor thread that would kill it. > > The solution that is described in the other iterations is to embed > checkpoints in the expression that do allocate, giving the RTS a > chance to switch contexts. However, in my application, the > expression is /arbitrary/ and I do not have the freedom to inject > alterations into it. (Don't argue this point, please. The > expression is arbitrary.) > > How can I time out a tight loop like the above? Clearly, it can be > done, because I can, say, alt-tab over to another terminal and kill > the process, which exploits the operating system's more aggressively > pre-emptive scheduling. Is there a solution using bound threads, say > 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? > Unix signals? Some FFI-based workaround? Etc. Keep in mind that > notwithstanding that comment, I don't actually want to kill the whole > process, but just the one evaluation. > > Thanks in advance, > Ryan Reich > If you are using GHC, the -fno-omit-yields compiler option might be of help, which does not optimize out the allocation check that is also used for interrupting threads. See also: https://stackoverflow.com/questions/34317730/haskell-timeout-diverging-computation Are you using the threaded runtime (GHC option -threaded)? hope this helps, Arjen From theedge456 at free.fr Sun Nov 18 11:53:50 2018 From: theedge456 at free.fr (Fabien R) Date: Sun, 18 Nov 2018 12:53:50 +0100 Subject: [Haskell-cafe] external git dependency source in .cabal Message-ID: <660c8ca8-3879-b5e5-52c4-682f6e4be80b@free.fr> Hello, I'm trying to reference an external source of a package within a sandbox, using cabal 2.0.0.1: source-repository head type: git location: executable myExe build-depends: base==4.10.1.0, pack1 -any But "cabal -v install --only-dependencies" fails: cabal: Encountered missing dependencies: pack1 -any Any hint ? -- Fabien From ivanperezdominguez at gmail.com Sun Nov 18 14:56:43 2018 From: ivanperezdominguez at gmail.com (Ivan Perez) Date: Sun, 18 Nov 2018 09:56:43 -0500 Subject: [Haskell-cafe] external git dependency source in .cabal In-Reply-To: <660c8ca8-3879-b5e5-52c4-682f6e4be80b@free.fr> References: <660c8ca8-3879-b5e5-52c4-682f6e4be80b@free.fr> Message-ID: If you can do this, this is news to me. See: https://www.haskell.org/cabal/users-guide/developing-packages.html >From what I understand, you cannot use this to point to repos for dependencies, only to indicate the repo for the package you are defining. You'd have to publish pack1 somewhere (on hackage or in your own hackage server), or use a different tool to declare the dependency. I don't know if cabal's new-build system addresses this at all. Ivan On Sun, 18 Nov 2018 at 06:54, Fabien R wrote: > Hello, > I'm trying to reference an external source of a package within a sandbox, > using cabal 2.0.0.1: > > source-repository head > type: git > location: > > executable myExe > build-depends: base==4.10.1.0, pack1 -any > > But "cabal -v install --only-dependencies" fails: > > cabal: Encountered missing dependencies: > pack1 -any > > Any hint ? > > -- > Fabien > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sun Nov 18 15:05:39 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Sun, 18 Nov 2018 10:05:39 -0500 Subject: [Haskell-cafe] external git dependency source in .cabal In-Reply-To: References: <660c8ca8-3879-b5e5-52c4-682f6e4be80b@free.fr> Message-ID: It doesn't. The source repo is for hackage documentation, not package retrieval. On Sun, Nov 18, 2018 at 9:57 AM Ivan Perez wrote: > If you can do this, this is news to me. > > See: https://www.haskell.org/cabal/users-guide/developing-packages.html > > From what I understand, you cannot use this to point to repos for > dependencies, only to indicate the repo for the package you are defining. > > You'd have to publish pack1 somewhere (on hackage or in your own hackage > server), or use a different tool to declare the dependency. I don't know if > cabal's new-build system addresses this at all. > > Ivan > > On Sun, 18 Nov 2018 at 06:54, Fabien R wrote: > >> Hello, >> I'm trying to reference an external source of a package within a sandbox, >> using cabal 2.0.0.1: >> >> source-repository head >> type: git >> location: >> >> executable myExe >> build-depends: base==4.10.1.0, pack1 -any >> >> But "cabal -v install --only-dependencies" fails: >> >> cabal: Encountered missing dependencies: >> pack1 -any >> >> Any hint ? >> >> -- >> Fabien >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From ducis_cn at 126.com Sun Nov 18 15:31:06 2018 From: ducis_cn at 126.com (ducis) Date: Sun, 18 Nov 2018 23:31:06 +0800 (CST) Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 183, Issue 14 In-Reply-To: References: Message-ID: Hi, Anthony, The top-level story is that I am trying to create a monad that somehow records the "intermediate steps" of computation. e.g. something like Prelude> return 1 ([],1) Prelude> return 1 >>= return.(+1) ([1],2) Prelude> return 1 >>= return.(+1)>>=return.(+3) ([2,1],5) (the list has the intermediate steps placed right-to-left so that new steps are appended to the left of the older steps) Of course all "intermediate steps of computation" actually form a graph, but we are frequently focused on, say, the transformation of a parse tree, where we want to take a series of snapshots of one "thing". Since a "lifted function" (e.g. return.(+1)) has in general the type a->m b, there are two ways to deal with input and output being not necessarily equal. The first approach I tried is to only record latest steps starting with the last change of type > newtype WithHistory b = WH ([b], b) and just discard the older steps when the input and output are of different types. > newtype WithHistory b = WH ([b], b) deriving (Show,Eq) > instance Monad WithHistory where > return b = WH ([], b) > (>>=) :: forall a b. WithHistory a -> (a -> WithHistory b) -> WithHistory b > WH (h,a) >>= fm = WH (h1++coerceHistory (a:h),b) > where > WH (h1, b) = fm a > class CoerceHistory a b where > coerceHistory :: [a] -> [b] > instance CoerceHistory a a where > coerceHistory = id > instance CoerceHistory a b where > coerceHistory _ = [] I have got the coerceHistory function to (appear to) work in GHCi *Main> coerceHistory [2::Int] :: [Int] [2] *Main> coerceHistory "c" :: [Int] [] But the Monad instanciation does not really work. GHC(7.6.3) hints for -XIncoherentInstances, which when enabled seems to force the (>>=) to always use the instance of coerceHistory returning [] The second approach is to use [Dynamic] for steps, i.e., > newtype WithHistory b = WH ([Dynamic], b) > instance Monad WithHistory where > return b = WH ([], b) > WH (h,a) >>= fm = WH (h1++forceDynList a++h, b) > where WH (h1, b) = fm a and presumably > class ForceDynList a where forceDynList :: a -> [Dynamic] > instance (Typeable a) => ForceDynList a where forceDynList x = [toDyn x] > instance ForceDynList a where forceDynList x = [] which is far from correct with error "Duplicate instance declarations" Thanks! Ducis -- ----------------------------- At 2018-11-18 20:00:01, haskell-cafe-request at haskell.org wrote: >Send Haskell-Cafe mailing list submissions to > haskell-cafe at haskell.org > >To subscribe or unsubscribe via the World Wide Web, visit > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >or, via email, send a message with subject or body 'help' to > haskell-cafe-request at haskell.org > >You can reach the person managing the list at > haskell-cafe-owner at haskell.org > >When replying, please edit your Subject line so it is more specific >than "Re: Contents of Haskell-Cafe digest..." > > >Today's Topics: > > 1. Timing out a pure evaluation of an expression I did not write > myself (Ryan Reich) > 2. Re: Timing out a pure evaluation of an expression I did not > write myself (Daniel Díaz Casanueva) > 3. Re: Timing out a pure evaluation of an expression I did not > write myself (Daniel Díaz Casanueva) > 4. Re: Timing out a pure evaluation of an expression I did not > write myself (Ryan Reich) > 5. Specialize a function on types of arguments? (ducis) > 6. Re: Specialize a function on types of arguments? (Anthony Clayden) > 7. Re: Timing out a pure evaluation of an expression I did not > write myself (arjenvanweelden at gmail.com) > 8. external git dependency source in .cabal (Fabien R) > > >---------------------------------------------------------------------- > >Message: 1 >Date: Sat, 17 Nov 2018 15:21:53 -0800 >From: Ryan Reich >To: haskell-cafe >Subject: [Haskell-cafe] Timing out a pure evaluation of an expression > I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >I want to time out a pure computation. My experience, and that described >in various previous questions here and elsewhere (the best of which is >https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >is that this doesn't always work: for instance, > >>>> timeout 1 $ evaluate $ let x = 0 : x in last x > >does not time out because, apparently, the fact that the expression >evaluates in constant space (i.e. never allocates) means that it never >yields to the timeout monitor thread that would kill it. > >The solution that is described in the other iterations is to embed >checkpoints in the expression that do allocate, giving the RTS a chance to >switch contexts. However, in my application, the expression is /arbitrary/ >and I do not have the freedom to inject alterations into it. (Don't argue >this point, please. The expression is arbitrary.) > >How can I time out a tight loop like the above? Clearly, it can be done, >because I can, say, alt-tab over to another terminal and kill the process, >which exploits the operating system's more aggressively pre-emptive >scheduling. Is there a solution using bound threads, say 'forkOS' instead >of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >FFI-based workaround? Etc. Keep in mind that notwithstanding that >comment, I don't actually want to kill the whole process, but just the one >evaluation. > >Thanks in advance, >Ryan Reich >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 2 >Date: Sun, 18 Nov 2018 01:51:58 +0100 >From: Daniel Díaz Casanueva >To: ryan.reich at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Hello Ryan. > >Try evaluating the expression to normal form instead of weak head normal >form in your expression. So: > >>>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x > >The function `force` comes from the deepseq package. You can read the docs >here: >http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html > >I hope that helps. > >Best regards, >Daniel > >Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich >: > >> I want to time out a pure computation. My experience, and that described >> in various previous questions here and elsewhere (the best of which is >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >> is that this doesn't always work: for instance, >> >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >> >> does not time out because, apparently, the fact that the expression >> evaluates in constant space (i.e. never allocates) means that it never >> yields to the timeout monitor thread that would kill it. >> >> The solution that is described in the other iterations is to embed >> checkpoints in the expression that do allocate, giving the RTS a chance to >> switch contexts. However, in my application, the expression is /arbitrary/ >> and I do not have the freedom to inject alterations into it. (Don't argue >> this point, please. The expression is arbitrary.) >> >> How can I time out a tight loop like the above? Clearly, it can be done, >> because I can, say, alt-tab over to another terminal and kill the process, >> which exploits the operating system's more aggressively pre-emptive >> scheduling. Is there a solution using bound threads, say 'forkOS' instead >> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >> FFI-based workaround? Etc. Keep in mind that notwithstanding that >> comment, I don't actually want to kill the whole process, but just the one >> evaluation. >> >> Thanks in advance, >> Ryan Reich >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 3 >Date: Sun, 18 Nov 2018 01:55:56 +0100 >From: Daniel Díaz Casanueva >To: ryan.reich at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Actually, after reading the question again, it seems like my response >wasn't quite right. You are not actually building the list. In that case, I >am as confused as you. :) > >Sorry! > >Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < >dhelta.diaz at gmail.com>: > >> Hello Ryan. >> >> Try evaluating the expression to normal form instead of weak head normal >> form in your expression. So: >> >> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x >> >> The function `force` comes from the deepseq package. You can read the docs >> here: >> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html >> >> I hope that helps. >> >> Best regards, >> Daniel >> >> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < >> ryan.reich at gmail.com>: >> >>> I want to time out a pure computation. My experience, and that described >>> in various previous questions here and elsewhere (the best of which is >>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >>> is that this doesn't always work: for instance, >>> >>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >>> >>> does not time out because, apparently, the fact that the expression >>> evaluates in constant space (i.e. never allocates) means that it never >>> yields to the timeout monitor thread that would kill it. >>> >>> The solution that is described in the other iterations is to embed >>> checkpoints in the expression that do allocate, giving the RTS a chance to >>> switch contexts. However, in my application, the expression is /arbitrary/ >>> and I do not have the freedom to inject alterations into it. (Don't argue >>> this point, please. The expression is arbitrary.) >>> >>> How can I time out a tight loop like the above? Clearly, it can be done, >>> because I can, say, alt-tab over to another terminal and kill the process, >>> which exploits the operating system's more aggressively pre-emptive >>> scheduling. Is there a solution using bound threads, say 'forkOS' instead >>> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >>> FFI-based workaround? Etc. Keep in mind that notwithstanding that >>> comment, I don't actually want to kill the whole process, but just the one >>> evaluation. >>> >>> Thanks in advance, >>> Ryan Reich >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 4 >Date: Sat, 17 Nov 2018 16:57:56 -0800 >From: Ryan Reich >To: dhelta.diaz at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >I was just about to reply with an observation to that effect :) The place >that I'd want to put 'force' is actually inside the 'let' clause, which of >course you can't do just by applying a function. The expression as a whole >is just an Integer. > >On Sat, Nov 17, 2018 at 4:56 PM Daniel Díaz Casanueva >wrote: > >> Actually, after reading the question again, it seems like my response >> wasn't quite right. You are not actually building the list. In that case, I >> am as confused as you. :) >> >> Sorry! >> >> Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < >> dhelta.diaz at gmail.com>: >> >>> Hello Ryan. >>> >>> Try evaluating the expression to normal form instead of weak head normal >>> form in your expression. So: >>> >>> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x >>> >>> The function `force` comes from the deepseq package. You can read the >>> docs here: >>> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html >>> >>> I hope that helps. >>> >>> Best regards, >>> Daniel >>> >>> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < >>> ryan.reich at gmail.com>: >>> >>>> I want to time out a pure computation. My experience, and that >>>> described in various previous questions here and elsewhere (the best of >>>> which is >>>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >>>> is that this doesn't always work: for instance, >>>> >>>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >>>> >>>> does not time out because, apparently, the fact that the expression >>>> evaluates in constant space (i.e. never allocates) means that it never >>>> yields to the timeout monitor thread that would kill it. >>>> >>>> The solution that is described in the other iterations is to embed >>>> checkpoints in the expression that do allocate, giving the RTS a chance to >>>> switch contexts. However, in my application, the expression is /arbitrary/ >>>> and I do not have the freedom to inject alterations into it. (Don't argue >>>> this point, please. The expression is arbitrary.) >>>> >>>> How can I time out a tight loop like the above? Clearly, it can be >>>> done, because I can, say, alt-tab over to another terminal and kill the >>>> process, which exploits the operating system's more aggressively >>>> pre-emptive scheduling. Is there a solution using bound threads, say >>>> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? Unix >>>> signals? Some FFI-based workaround? Etc. Keep in mind that >>>> notwithstanding that comment, I don't actually want to kill the whole >>>> process, but just the one evaluation. >>>> >>>> Thanks in advance, >>>> Ryan Reich >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >>> >>> >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 5 >Date: Sun, 18 Nov 2018 12:01:25 +0800 (CST) >From: ducis >To: haskell-cafe at haskell.org >Subject: [Haskell-cafe] Specialize a function on types of arguments? >Message-ID: <552773e2.1be5.16724faf3d0.Coremail.ducis_cn at 126.com> >Content-Type: text/plain; charset="gbk" > >Hi, everyone, > >Is it possible to make combine the following "f" and "g" into one function? >f:: a -> b -> b >f x y = y >g:: a -> a -> a >g x y = x > >Or similarly, "eq1" and "eq2" into one function? >eq1 :: (Eq a)=>a->a->Bool >eq1 = (==) >eq2 :: (Eq a,Eq b)=>a->b->Bool >eq2 _ _ = False > >Looks like it would require some typeclasses, but at least in the first case, "a" and "b" should be any types. > >Best! >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 6 >Date: Sun, 18 Nov 2018 17:40:51 +1300 >From: Anthony Clayden >To: haskell-cafe at haskell.org >Subject: Re: [Haskell-cafe] Specialize a function on types of > arguments? >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Hi Ducis, > >> Is it possible to make combine the following "f" and "g" into one >function? > >"combine" is vague. You perhaps mean: look at the types of the arguments, >and choose one function or the other? > >> Looks like it would require some typeclasses, > >I'll answer the question as put (yes it needs typeclasses), but I can't >help feel there's a backstory, and you might well be doing something that >could be done better, if I knew what you're trying to achieve. Let's take >the second one first > >> "eq1" and "eq2" into one function? >> eq1 :: (Eq a)=>a->a->Bool >> eq1 = (==) >> eq2 :: (Eq a,Eq b)=>a->b->Bool >> eq2 _ _ = False > >class Eqbytype a b where > eqt :: a -> b -> Bool > >instance {-# OVERLAPPING #-} (Eq a) => Eqbytype a a where > eqt = (==) > >instance {-# OVERLAPPABLE #-} Eqbytype a b where > eqt _ _ = False > >Look at the Users Guide for what the OVERLAPPING/OVERLAPPABLE pragmas are doing. > >Note for the first instance I repeated type var `a` in the head, >meaning: pick this instance if the two arguments to the method are of >the same type. > >Note for the second instance, I didn't bother with the `Eq` >constraint, since we can't compare values of distinct types. > > >> f:: a -> b -> b >> f x y = y >> g:: a -> a -> a >> g x y = x >So you want same argument types to drive which argument to pick? Or >you want the return type to drive which argument? That's possible: >look at the definition of class `Read` in the Prelude. Again we can >pick instances depending on a repeated type. But your requirements are >not clear. > > >> but at least in the first case [which I've put second], "a" and "b" should be any types. > >No they can't: as you state it, you require either all three the same, >or the second to be the same as the return type. > >Come back and ask a more focussed question once you've worked through the >above. (And explain why you're asking.) The above code is untested, BTW. > >AntC >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 7 >Date: Sun, 18 Nov 2018 09:22:08 +0100 >From: arjenvanweelden at gmail.com >To: haskell-cafe at haskell.org >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: <27e9100ff70dd67791ed34e152c58239499bba65.camel at gmail.com> >Content-Type: text/plain; charset="UTF-8" > >On Sat, 2018-11-17 at 15:21 -0800, Ryan Reich wrote: >> I want to time out a pure computation. My experience, and that >> described in various previous questions here and elsewhere (the best >> of which is >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html >> ), is that this doesn't always work: for instance, >> >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >> >> does not time out because, apparently, the fact that the expression >> evaluates in constant space (i.e. never allocates) means that it >> never yields to the timeout monitor thread that would kill it. >> >> The solution that is described in the other iterations is to embed >> checkpoints in the expression that do allocate, giving the RTS a >> chance to switch contexts. However, in my application, the >> expression is /arbitrary/ and I do not have the freedom to inject >> alterations into it. (Don't argue this point, please. The >> expression is arbitrary.) >> >> How can I time out a tight loop like the above? Clearly, it can be >> done, because I can, say, alt-tab over to another terminal and kill >> the process, which exploits the operating system's more aggressively >> pre-emptive scheduling. Is there a solution using bound threads, say >> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? >> Unix signals? Some FFI-based workaround? Etc. Keep in mind that >> notwithstanding that comment, I don't actually want to kill the whole >> process, but just the one evaluation. >> >> Thanks in advance, >> Ryan Reich >> >If you are using GHC, the -fno-omit-yields compiler option might be of >help, which does not optimize out the allocation check that is also >used for interrupting threads. > >See also: >https://stackoverflow.com/questions/34317730/haskell-timeout-diverging-computation > >Are you using the threaded runtime (GHC option -threaded)? > >hope this helps, Arjen > > > >------------------------------ > >Message: 8 >Date: Sun, 18 Nov 2018 12:53:50 +0100 >From: Fabien R >To: haskell-cafe at haskell.org >Subject: [Haskell-cafe] external git dependency source in .cabal >Message-ID: <660c8ca8-3879-b5e5-52c4-682f6e4be80b at free.fr> >Content-Type: text/plain; charset=utf-8 > >Hello, >I'm trying to reference an external source of a package within a sandbox, using cabal 2.0.0.1: > >source-repository head > type: git > location: > >executable myExe > build-depends: base==4.10.1.0, pack1 -any > >But "cabal -v install --only-dependencies" fails: > >cabal: Encountered missing dependencies: >pack1 -any > >Any hint ? > >-- >Fabien > > >------------------------------ > >Subject: Digest Footer > >_______________________________________________ >Haskell-Cafe mailing list >Haskell-Cafe at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > >------------------------------ > >End of Haskell-Cafe Digest, Vol 183, Issue 14 >********************************************* -------------- next part -------------- An HTML attachment was scrubbed... URL: From ducis_cn at 126.com Sun Nov 18 15:32:38 2018 From: ducis_cn at 126.com (ducis) Date: Sun, 18 Nov 2018 23:32:38 +0800 (CST) Subject: [Haskell-cafe] Specialize a function on types of arguments? In-Reply-To: References: Message-ID: <741530a.492d.1672773c691.Coremail.ducis_cn@126.com> Hi, Anthony, The top-level story is that I am trying to create a monad that somehow records the "intermediate steps" of computation. e.g. something like Prelude> return 1 ([],1) Prelude> return 1 >>= return.(+1) ([1],2) Prelude> return 1 >>= return.(+1)>>=return.(+3) ([2,1],5) (the list has the intermediate steps placed right-to-left so that new steps are appended to the left of the older steps) Of course all "intermediate steps of computation" actually form a graph, but we are frequently focused on, say, the transformation of a parse tree, where we want to take a series of snapshots of one "thing". Since a "lifted function" (e.g. return.(+1)) has in general the type a->m b, there are two ways to deal with input and output being not necessarily equal. The first approach I tried is to only record latest steps starting with the last change of type > newtype WithHistory b = WH ([b], b) and just discard the older steps when the input and output are of different types. > newtype WithHistory b = WH ([b], b) deriving (Show,Eq) > instance Monad WithHistory where > return b = WH ([], b) > (>>=) :: forall a b. WithHistory a -> (a -> WithHistory b) -> WithHistory b > WH (h,a) >>= fm = WH (h1++coerceHistory (a:h),b) > where > WH (h1, b) = fm a > class CoerceHistory a b where > coerceHistory :: [a] -> [b] > instance CoerceHistory a a where > coerceHistory = id > instance CoerceHistory a b where > coerceHistory _ = [] I have got the coerceHistory function to (appear to) work in GHCi *Main> coerceHistory [2::Int] :: [Int] [2] *Main> coerceHistory "c" :: [Int] [] But the Monad instanciation does not really work. GHC(7.6.3) hints for -XIncoherentInstances, which when enabled seems to force the (>>=) to always use the instance of coerceHistory returning [] The second approach is to use [Dynamic] for steps, i.e., > newtype WithHistory b = WH ([Dynamic], b) > instance Monad WithHistory where > return b = WH ([], b) > WH (h,a) >>= fm = WH (h1++forceDynList a++h, b) > where WH (h1, b) = fm a and presumably > class ForceDynList a where forceDynList :: a -> [Dynamic] > instance (Typeable a) => ForceDynList a where forceDynList x = [toDyn x] > instance ForceDynList a where forceDynList x = [] which is far from correct with error "Duplicate instance declarations" Thanks! Ducis -- ----------------------------- At 2018-11-18 20:00:01, haskell-cafe-request at haskell.org wrote: >Send Haskell-Cafe mailing list submissions to > haskell-cafe at haskell.org > >To subscribe or unsubscribe via the World Wide Web, visit > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >or, via email, send a message with subject or body 'help' to > haskell-cafe-request at haskell.org > >You can reach the person managing the list at > haskell-cafe-owner at haskell.org > >When replying, please edit your Subject line so it is more specific >than "Re: Contents of Haskell-Cafe digest..." > > >Today's Topics: > > 1. Timing out a pure evaluation of an expression I did not write > myself (Ryan Reich) > 2. Re: Timing out a pure evaluation of an expression I did not > write myself (Daniel Díaz Casanueva) > 3. Re: Timing out a pure evaluation of an expression I did not > write myself (Daniel Díaz Casanueva) > 4. Re: Timing out a pure evaluation of an expression I did not > write myself (Ryan Reich) > 5. Specialize a function on types of arguments? (ducis) > 6. Re: Specialize a function on types of arguments? (Anthony Clayden) > 7. Re: Timing out a pure evaluation of an expression I did not > write myself (arjenvanweelden at gmail.com) > 8. external git dependency source in .cabal (Fabien R) > > >---------------------------------------------------------------------- > >Message: 1 >Date: Sat, 17 Nov 2018 15:21:53 -0800 >From: Ryan Reich >To: haskell-cafe >Subject: [Haskell-cafe] Timing out a pure evaluation of an expression > I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >I want to time out a pure computation. My experience, and that described >in various previous questions here and elsewhere (the best of which is >https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >is that this doesn't always work: for instance, > >>>> timeout 1 $ evaluate $ let x = 0 : x in last x > >does not time out because, apparently, the fact that the expression >evaluates in constant space (i.e. never allocates) means that it never >yields to the timeout monitor thread that would kill it. > >The solution that is described in the other iterations is to embed >checkpoints in the expression that do allocate, giving the RTS a chance to >switch contexts. However, in my application, the expression is /arbitrary/ >and I do not have the freedom to inject alterations into it. (Don't argue >this point, please. The expression is arbitrary.) > >How can I time out a tight loop like the above? Clearly, it can be done, >because I can, say, alt-tab over to another terminal and kill the process, >which exploits the operating system's more aggressively pre-emptive >scheduling. Is there a solution using bound threads, say 'forkOS' instead >of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >FFI-based workaround? Etc. Keep in mind that notwithstanding that >comment, I don't actually want to kill the whole process, but just the one >evaluation. > >Thanks in advance, >Ryan Reich >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 2 >Date: Sun, 18 Nov 2018 01:51:58 +0100 >From: Daniel Díaz Casanueva >To: ryan.reich at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Hello Ryan. > >Try evaluating the expression to normal form instead of weak head normal >form in your expression. So: > >>>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x > >The function `force` comes from the deepseq package. You can read the docs >here: >http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html > >I hope that helps. > >Best regards, >Daniel > >Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich >: > >> I want to time out a pure computation. My experience, and that described >> in various previous questions here and elsewhere (the best of which is >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >> is that this doesn't always work: for instance, >> >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >> >> does not time out because, apparently, the fact that the expression >> evaluates in constant space (i.e. never allocates) means that it never >> yields to the timeout monitor thread that would kill it. >> >> The solution that is described in the other iterations is to embed >> checkpoints in the expression that do allocate, giving the RTS a chance to >> switch contexts. However, in my application, the expression is /arbitrary/ >> and I do not have the freedom to inject alterations into it. (Don't argue >> this point, please. The expression is arbitrary.) >> >> How can I time out a tight loop like the above? Clearly, it can be done, >> because I can, say, alt-tab over to another terminal and kill the process, >> which exploits the operating system's more aggressively pre-emptive >> scheduling. Is there a solution using bound threads, say 'forkOS' instead >> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >> FFI-based workaround? Etc. Keep in mind that notwithstanding that >> comment, I don't actually want to kill the whole process, but just the one >> evaluation. >> >> Thanks in advance, >> Ryan Reich >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 3 >Date: Sun, 18 Nov 2018 01:55:56 +0100 >From: Daniel Díaz Casanueva >To: ryan.reich at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Actually, after reading the question again, it seems like my response >wasn't quite right. You are not actually building the list. In that case, I >am as confused as you. :) > >Sorry! > >Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < >dhelta.diaz at gmail.com>: > >> Hello Ryan. >> >> Try evaluating the expression to normal form instead of weak head normal >> form in your expression. So: >> >> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x >> >> The function `force` comes from the deepseq package. You can read the docs >> here: >> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html >> >> I hope that helps. >> >> Best regards, >> Daniel >> >> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < >> ryan.reich at gmail.com>: >> >>> I want to time out a pure computation. My experience, and that described >>> in various previous questions here and elsewhere (the best of which is >>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >>> is that this doesn't always work: for instance, >>> >>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >>> >>> does not time out because, apparently, the fact that the expression >>> evaluates in constant space (i.e. never allocates) means that it never >>> yields to the timeout monitor thread that would kill it. >>> >>> The solution that is described in the other iterations is to embed >>> checkpoints in the expression that do allocate, giving the RTS a chance to >>> switch contexts. However, in my application, the expression is /arbitrary/ >>> and I do not have the freedom to inject alterations into it. (Don't argue >>> this point, please. The expression is arbitrary.) >>> >>> How can I time out a tight loop like the above? Clearly, it can be done, >>> because I can, say, alt-tab over to another terminal and kill the process, >>> which exploits the operating system's more aggressively pre-emptive >>> scheduling. Is there a solution using bound threads, say 'forkOS' instead >>> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >>> FFI-based workaround? Etc. Keep in mind that notwithstanding that >>> comment, I don't actually want to kill the whole process, but just the one >>> evaluation. >>> >>> Thanks in advance, >>> Ryan Reich >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 4 >Date: Sat, 17 Nov 2018 16:57:56 -0800 >From: Ryan Reich >To: dhelta.diaz at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >I was just about to reply with an observation to that effect :) The place >that I'd want to put 'force' is actually inside the 'let' clause, which of >course you can't do just by applying a function. The expression as a whole >is just an Integer. > >On Sat, Nov 17, 2018 at 4:56 PM Daniel Díaz Casanueva >wrote: > >> Actually, after reading the question again, it seems like my response >> wasn't quite right. You are not actually building the list. In that case, I >> am as confused as you. :) >> >> Sorry! >> >> Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < >> dhelta.diaz at gmail.com>: >> >>> Hello Ryan. >>> >>> Try evaluating the expression to normal form instead of weak head normal >>> form in your expression. So: >>> >>> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x >>> >>> The function `force` comes from the deepseq package. You can read the >>> docs here: >>> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html >>> >>> I hope that helps. >>> >>> Best regards, >>> Daniel >>> >>> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < >>> ryan.reich at gmail.com>: >>> >>>> I want to time out a pure computation. My experience, and that >>>> described in various previous questions here and elsewhere (the best of >>>> which is >>>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >>>> is that this doesn't always work: for instance, >>>> >>>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >>>> >>>> does not time out because, apparently, the fact that the expression >>>> evaluates in constant space (i.e. never allocates) means that it never >>>> yields to the timeout monitor thread that would kill it. >>>> >>>> The solution that is described in the other iterations is to embed >>>> checkpoints in the expression that do allocate, giving the RTS a chance to >>>> switch contexts. However, in my application, the expression is /arbitrary/ >>>> and I do not have the freedom to inject alterations into it. (Don't argue >>>> this point, please. The expression is arbitrary.) >>>> >>>> How can I time out a tight loop like the above? Clearly, it can be >>>> done, because I can, say, alt-tab over to another terminal and kill the >>>> process, which exploits the operating system's more aggressively >>>> pre-emptive scheduling. Is there a solution using bound threads, say >>>> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? Unix >>>> signals? Some FFI-based workaround? Etc. Keep in mind that >>>> notwithstanding that comment, I don't actually want to kill the whole >>>> process, but just the one evaluation. >>>> >>>> Thanks in advance, >>>> Ryan Reich >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >>> >>> >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 5 >Date: Sun, 18 Nov 2018 12:01:25 +0800 (CST) >From: ducis >To: haskell-cafe at haskell.org >Subject: [Haskell-cafe] Specialize a function on types of arguments? >Message-ID: <552773e2.1be5.16724faf3d0.Coremail.ducis_cn at 126.com> >Content-Type: text/plain; charset="gbk" > >Hi, everyone, > >Is it possible to make combine the following "f" and "g" into one function? >f:: a -> b -> b >f x y = y >g:: a -> a -> a >g x y = x > >Or similarly, "eq1" and "eq2" into one function? >eq1 :: (Eq a)=>a->a->Bool >eq1 = (==) >eq2 :: (Eq a,Eq b)=>a->b->Bool >eq2 _ _ = False > >Looks like it would require some typeclasses, but at least in the first case, "a" and "b" should be any types. > >Best! >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 6 >Date: Sun, 18 Nov 2018 17:40:51 +1300 >From: Anthony Clayden >To: haskell-cafe at haskell.org >Subject: Re: [Haskell-cafe] Specialize a function on types of > arguments? >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Hi Ducis, > >> Is it possible to make combine the following "f" and "g" into one >function? > >"combine" is vague. You perhaps mean: look at the types of the arguments, >and choose one function or the other? > >> Looks like it would require some typeclasses, > >I'll answer the question as put (yes it needs typeclasses), but I can't >help feel there's a backstory, and you might well be doing something that >could be done better, if I knew what you're trying to achieve. Let's take >the second one first > >> "eq1" and "eq2" into one function? >> eq1 :: (Eq a)=>a->a->Bool >> eq1 = (==) >> eq2 :: (Eq a,Eq b)=>a->b->Bool >> eq2 _ _ = False > >class Eqbytype a b where > eqt :: a -> b -> Bool > >instance {-# OVERLAPPING #-} (Eq a) => Eqbytype a a where > eqt = (==) > >instance {-# OVERLAPPABLE #-} Eqbytype a b where > eqt _ _ = False > >Look at the Users Guide for what the OVERLAPPING/OVERLAPPABLE pragmas are doing. > >Note for the first instance I repeated type var `a` in the head, >meaning: pick this instance if the two arguments to the method are of >the same type. > >Note for the second instance, I didn't bother with the `Eq` >constraint, since we can't compare values of distinct types. > > >> f:: a -> b -> b >> f x y = y >> g:: a -> a -> a >> g x y = x >So you want same argument types to drive which argument to pick? Or >you want the return type to drive which argument? That's possible: >look at the definition of class `Read` in the Prelude. Again we can >pick instances depending on a repeated type. But your requirements are >not clear. > > >> but at least in the first case [which I've put second], "a" and "b" should be any types. > >No they can't: as you state it, you require either all three the same, >or the second to be the same as the return type. > >Come back and ask a more focussed question once you've worked through the >above. (And explain why you're asking.) The above code is untested, BTW. > >AntC >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 7 >Date: Sun, 18 Nov 2018 09:22:08 +0100 >From: arjenvanweelden at gmail.com >To: haskell-cafe at haskell.org >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: <27e9100ff70dd67791ed34e152c58239499bba65.camel at gmail.com> >Content-Type: text/plain; charset="UTF-8" > >On Sat, 2018-11-17 at 15:21 -0800, Ryan Reich wrote: >> I want to time out a pure computation. My experience, and that >> described in various previous questions here and elsewhere (the best >> of which is >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html >> ), is that this doesn't always work: for instance, >> >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >> >> does not time out because, apparently, the fact that the expression >> evaluates in constant space (i.e. never allocates) means that it >> never yields to the timeout monitor thread that would kill it. >> >> The solution that is described in the other iterations is to embed >> checkpoints in the expression that do allocate, giving the RTS a >> chance to switch contexts. However, in my application, the >> expression is /arbitrary/ and I do not have the freedom to inject >> alterations into it. (Don't argue this point, please. The >> expression is arbitrary.) >> >> How can I time out a tight loop like the above? Clearly, it can be >> done, because I can, say, alt-tab over to another terminal and kill >> the process, which exploits the operating system's more aggressively >> pre-emptive scheduling. Is there a solution using bound threads, say >> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? >> Unix signals? Some FFI-based workaround? Etc. Keep in mind that >> notwithstanding that comment, I don't actually want to kill the whole >> process, but just the one evaluation. >> >> Thanks in advance, >> Ryan Reich >> >If you are using GHC, the -fno-omit-yields compiler option might be of >help, which does not optimize out the allocation check that is also >used for interrupting threads. > >See also: >https://stackoverflow.com/questions/34317730/haskell-timeout-diverging-computation > >Are you using the threaded runtime (GHC option -threaded)? > >hope this helps, Arjen > > > >------------------------------ > >Message: 8 >Date: Sun, 18 Nov 2018 12:53:50 +0100 >From: Fabien R >To: haskell-cafe at haskell.org >Subject: [Haskell-cafe] external git dependency source in .cabal >Message-ID: <660c8ca8-3879-b5e5-52c4-682f6e4be80b at free.fr> >Content-Type: text/plain; charset=utf-8 > >Hello, >I'm trying to reference an external source of a package within a sandbox, using cabal 2.0.0.1: > >source-repository head > type: git > location: > >executable myExe > build-depends: base==4.10.1.0, pack1 -any > >But "cabal -v install --only-dependencies" fails: > >cabal: Encountered missing dependencies: >pack1 -any > >Any hint ? > >-- >Fabien > > >------------------------------ > >Subject: Digest Footer > >_______________________________________________ >Haskell-Cafe mailing list >Haskell-Cafe at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > >------------------------------ > >End of Haskell-Cafe Digest, Vol 183, Issue 14 >********************************************* -------------- next part -------------- An HTML attachment was scrubbed... URL: From marc at lamarciana.com Sun Nov 18 17:29:01 2018 From: marc at lamarciana.com (=?ISO-8859-15?Q?Marc_Busqu=E9?=) Date: Sun, 18 Nov 2018 18:29:01 +0100 (CET) Subject: [Haskell-cafe] Help with DataKinds example Message-ID: I'm reading Sandy Maguire book Thinking with Types, and I'm stuck understanding an example about `DataKinds` language extension. In the book, it is said that it can be used to prevent at the type level that non admin users perform some action for which admin privileges are required. So, in the example, having `DataKinds` enabled, we define: ``` data UserType = User | Admin ``` Then, we change User type: ``` data User = User { userAdminToken :: Maybe (Proxy 'Admin) } ``` And then it is said that we can enforce that sensitive operations are performed by a user with the admin token: ``` doSensitiveThings :: Proxy 'Admin -> IO () ``` No other language extensions have been explained before in the book, and I simply don't understand how it is works... First, I guess that when writing `data User = ...` we are overriding `'User` promoted data constructor. Isn't it? Also, I don't understand how I could define a type `Proxy 'Admin`. If I'm not wrong, `Proxy` should have the kind `UserType -> *`, but I don't know how to do that. Besides that, I would like some guidance in the general idea of the example, because I'm quite puzzled :) Thanks in advance! Marc Busqué http://waiting-for-dev.github.io/about/ From danburton.email at gmail.com Sun Nov 18 17:34:33 2018 From: danburton.email at gmail.com (Dan Burton) Date: Sun, 18 Nov 2018 12:34:33 -0500 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 183, Issue 14 In-Reply-To: References: Message-ID: I would recommend against this, since having >>= "record history" breaks monad laws. Particularly, this one: f >>= return === f Instead, why not use a plain old `Writer [Dynamic]` monad and explicitly `tell` whenever you want to add a historical record? import Control.Monad.Trans.Writer (Writer, tell) import Data.Dynamic (Dynamic, toDyn) import Data.Typeable (Typeable) newtype WithHistory b = WH (Writer [Dynamic] b) deriving (Functor, Applicative, Monad) tellHistory :: Typeable a => a -> WithHistory () tellHistory a = WH $ tell [toDyn a] someComputation :: WithHistory Int someComputation = do let x = 1 tellHistory x let y = x + 1 tellHistory y let yStr = show y tellHistory yStr let z = y + 3 tellHistory z return z -- Dan Burton On Sun, Nov 18, 2018 at 10:31 AM ducis wrote: > Hi, Anthony, > > The top-level story is that I am trying to create a monad that somehow > records the "intermediate steps" of computation. > e.g. something like > Prelude> return 1 > ([],1) > Prelude> return 1 >>= return.(+1) > ([1],2) > Prelude> return 1 >>= return.(+1)>>=return.(+3) > ([2,1],5) > (the list has the intermediate steps placed right-to-left so that new > steps are appended to the left of the older steps) > Of course all "intermediate steps of computation" actually form a graph, > but we are frequently focused on, say, > the transformation of a parse tree, where we want to take a series of > snapshots of one "thing". > > Since a "lifted function" (e.g. return.(+1)) has in general the type a->m > b, there are two ways > to deal with input and output being not necessarily equal. > > The first approach I tried is to only record latest steps starting with > the last change of type > > newtype WithHistory b = WH ([b], b) > and just discard the older steps when the input and output are of > different types. > > newtype WithHistory b = WH ([b], b) deriving > (Show,Eq) > > instance Monad WithHistory where > > return b = WH ([], b) > > (>>=) :: forall a b. WithHistory a -> (a -> WithHistory b) -> > WithHistory b > > WH (h,a) >>= fm = WH (h1++coerceHistory (a:h),b) > > where > > WH (h1, b) = fm a > > class CoerceHistory a b where > > coerceHistory :: [a] -> [b] > > instance CoerceHistory a a where > > coerceHistory = id > > instance CoerceHistory a b where > > coerceHistory _ = [] > I have got the coerceHistory function to (appear to) work in GHCi > *Main> coerceHistory [2::Int] :: [Int] > [2] > *Main> coerceHistory "c" :: [Int] > [] > But the Monad instanciation does not really work. > GHC(7.6.3) hints for -XIncoherentInstances, which when > enabled seems to force the (>>=) to always use the instance > of coerceHistory returning [] > > The second approach is to use [Dynamic] for steps, i.e., > > newtype WithHistory b = WH ([Dynamic], b) > > instance Monad WithHistory where > > return b = WH ([], b) > > WH (h,a) >>= fm = WH (h1++forceDynList a++h, b) > > where WH (h1, b) = fm a > and presumably > > class ForceDynList a where > forceDynList :: a -> [Dynamic] > > instance (Typeable a) => ForceDynList a where forceDynList x = [toDyn > x] > > instance ForceDynList a where forceDynList > x = [] > which is far from correct with error "Duplicate instance declarations" > > Thanks! > Ducis > > > -- > ----------------------------- > > > At 2018-11-18 20:00:01, haskell-cafe-request at haskell.org wrote: > >Send Haskell-Cafe mailing list submissions to > > haskell-cafe at haskell.org > > > >To subscribe or unsubscribe via the World Wide Web, visit > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >or, via email, send a message with subject or body 'help' to > > haskell-cafe-request at haskell.org > > > >You can reach the person managing the list at > > haskell-cafe-owner at haskell.org > > > >When replying, please edit your Subject line so it is more specific > >than "Re: Contents of Haskell-Cafe digest..." > > > > > >Today's Topics: > > > > 1. Timing out a pure evaluation of an expression I did not write > > myself (Ryan Reich) > > 2. Re: Timing out a pure evaluation of an expression I did not > > write myself (Daniel Díaz Casanueva) > > 3. Re: Timing out a pure evaluation of an expression I did not > > write myself (Daniel Díaz Casanueva) > > 4. Re: Timing out a pure evaluation of an expression I did not > > write myself (Ryan Reich) > > 5. Specialize a function on types of arguments? (ducis) > > 6. Re: Specialize a function on types of arguments? (Anthony Clayden) > > 7. Re: Timing out a pure evaluation of an expression I did not > > write myself (arjenvanweelden at gmail.com) > > 8. external git dependency source in .cabal (Fabien R) > > > > > >---------------------------------------------------------------------- > > > >Message: 1 > >Date: Sat, 17 Nov 2018 15:21:53 -0800 > >From: Ryan Reich > >To: haskell-cafe > >Subject: [Haskell-cafe] Timing out a pure evaluation of an expression > > I did not write myself > >Message-ID: > > > >Content-Type: text/plain; charset="utf-8" > > > >I want to time out a pure computation. My experience, and that described > >in various previous questions here and elsewhere (the best of which is > >https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), > >is that this doesn't always work: for instance, > > > >>>> timeout 1 $ evaluate $ let x = 0 : x in last x > > > >does not time out because, apparently, the fact that the expression > >evaluates in constant space (i.e. never allocates) means that it never > >yields to the timeout monitor thread that would kill it. > > > >The solution that is described in the other iterations is to embed > >checkpoints in the expression that do allocate, giving the RTS a chance to > >switch contexts. However, in my application, the expression is /arbitrary/ > >and I do not have the freedom to inject alterations into it. (Don't argue > >this point, please. The expression is arbitrary.) > > > >How can I time out a tight loop like the above? Clearly, it can be done, > >because I can, say, alt-tab over to another terminal and kill the process, > >which exploits the operating system's more aggressively pre-emptive > >scheduling. Is there a solution using bound threads, say 'forkOS' instead > >of 'forkIO' in the implementation of 'timeout'? Unix signals? Some > >FFI-based workaround? Etc. Keep in mind that notwithstanding that > >comment, I don't actually want to kill the whole process, but just the one > >evaluation. > > > >Thanks in advance, > >Ryan Reich > >-------------- next part -------------- > >An HTML attachment was scrubbed... > >URL: > > > >------------------------------ > > > >Message: 2 > >Date: Sun, 18 Nov 2018 01:51:58 +0100 > >From: Daniel Díaz Casanueva > >To: ryan.reich at gmail.com > >Cc: haskell-cafe > >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > > expression I did not write myself > >Message-ID: > > > >Content-Type: text/plain; charset="utf-8" > > > >Hello Ryan. > > > >Try evaluating the expression to normal form instead of weak head normal > >form in your expression. So: > > > >>>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x > > > >The function `force` comes from the deepseq package. You can read the docs > >here: > >http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html > > > >I hope that helps. > > > >Best regards, > >Daniel > > > >Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich >>: > > > >> I want to time out a pure computation. My experience, and that described > >> in various previous questions here and elsewhere (the best of which is > >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), > >> is that this doesn't always work: for instance, > >> > >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x > >> > >> does not time out because, apparently, the fact that the expression > >> evaluates in constant space (i.e. never allocates) means that it never > >> yields to the timeout monitor thread that would kill it. > >> > >> The solution that is described in the other iterations is to embed > >> checkpoints in the expression that do allocate, giving the RTS a chance to > >> switch contexts. However, in my application, the expression is /arbitrary/ > >> and I do not have the freedom to inject alterations into it. (Don't argue > >> this point, please. The expression is arbitrary.) > >> > >> How can I time out a tight loop like the above? Clearly, it can be done, > >> because I can, say, alt-tab over to another terminal and kill the process, > >> which exploits the operating system's more aggressively pre-emptive > >> scheduling. Is there a solution using bound threads, say 'forkOS' instead > >> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some > >> FFI-based workaround? Etc. Keep in mind that notwithstanding that > >> comment, I don't actually want to kill the whole process, but just the one > >> evaluation. > >> > >> Thanks in advance, > >> Ryan Reich > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> To (un)subscribe, modify options or view archives go to: > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >> Only members subscribed via the mailman list are allowed to post. > >-------------- next part -------------- > >An HTML attachment was scrubbed... > >URL: > > > >------------------------------ > > > >Message: 3 > >Date: Sun, 18 Nov 2018 01:55:56 +0100 > >From: Daniel Díaz Casanueva > >To: ryan.reich at gmail.com > >Cc: haskell-cafe > >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > > expression I did not write myself > >Message-ID: > > > >Content-Type: text/plain; charset="utf-8" > > > >Actually, after reading the question again, it seems like my response > >wasn't quite right. You are not actually building the list. In that case, I > >am as confused as you. :) > > > >Sorry! > > > >Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < > >dhelta.diaz at gmail.com>: > > > >> Hello Ryan. > >> > >> Try evaluating the expression to normal form instead of weak head normal > >> form in your expression. So: > >> > >> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x > >> > >> The function `force` comes from the deepseq package. You can read the docs > >> here: > >> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html > >> > >> I hope that helps. > >> > >> Best regards, > >> Daniel > >> > >> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < > >> ryan.reich at gmail.com>: > >> > >>> I want to time out a pure computation. My experience, and that described > >>> in various previous questions here and elsewhere (the best of which is > >>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), > >>> is that this doesn't always work: for instance, > >>> > >>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x > >>> > >>> does not time out because, apparently, the fact that the expression > >>> evaluates in constant space (i.e. never allocates) means that it never > >>> yields to the timeout monitor thread that would kill it. > >>> > >>> The solution that is described in the other iterations is to embed > >>> checkpoints in the expression that do allocate, giving the RTS a chance to > >>> switch contexts. However, in my application, the expression is /arbitrary/ > >>> and I do not have the freedom to inject alterations into it. (Don't argue > >>> this point, please. The expression is arbitrary.) > >>> > >>> How can I time out a tight loop like the above? Clearly, it can be done, > >>> because I can, say, alt-tab over to another terminal and kill the process, > >>> which exploits the operating system's more aggressively pre-emptive > >>> scheduling. Is there a solution using bound threads, say 'forkOS' instead > >>> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some > >>> FFI-based workaround? Etc. Keep in mind that notwithstanding that > >>> comment, I don't actually want to kill the whole process, but just the one > >>> evaluation. > >>> > >>> Thanks in advance, > >>> Ryan Reich > >>> _______________________________________________ > >>> Haskell-Cafe mailing list > >>> To (un)subscribe, modify options or view archives go to: > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >>> Only members subscribed via the mailman list are allowed to post. > >> > >> > >-------------- next part -------------- > >An HTML attachment was scrubbed... > >URL: > > > >------------------------------ > > > >Message: 4 > >Date: Sat, 17 Nov 2018 16:57:56 -0800 > >From: Ryan Reich > >To: dhelta.diaz at gmail.com > >Cc: haskell-cafe > >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > > expression I did not write myself > >Message-ID: > > > >Content-Type: text/plain; charset="utf-8" > > > >I was just about to reply with an observation to that effect :) The place > >that I'd want to put 'force' is actually inside the 'let' clause, which of > >course you can't do just by applying a function. The expression as a whole > >is just an Integer. > > > >On Sat, Nov 17, 2018 at 4:56 PM Daniel Díaz Casanueva > >wrote: > > > >> Actually, after reading the question again, it seems like my response > >> wasn't quite right. You are not actually building the list. In that case, I > >> am as confused as you. :) > >> > >> Sorry! > >> > >> Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < > >> dhelta.diaz at gmail.com>: > >> > >>> Hello Ryan. > >>> > >>> Try evaluating the expression to normal form instead of weak head normal > >>> form in your expression. So: > >>> > >>> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x > >>> > >>> The function `force` comes from the deepseq package. You can read the > >>> docs here: > >>> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html > >>> > >>> I hope that helps. > >>> > >>> Best regards, > >>> Daniel > >>> > >>> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < > >>> ryan.reich at gmail.com>: > >>> > >>>> I want to time out a pure computation. My experience, and that > >>>> described in various previous questions here and elsewhere (the best of > >>>> which is > >>>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), > >>>> is that this doesn't always work: for instance, > >>>> > >>>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x > >>>> > >>>> does not time out because, apparently, the fact that the expression > >>>> evaluates in constant space (i.e. never allocates) means that it never > >>>> yields to the timeout monitor thread that would kill it. > >>>> > >>>> The solution that is described in the other iterations is to embed > >>>> checkpoints in the expression that do allocate, giving the RTS a chance to > >>>> switch contexts. However, in my application, the expression is /arbitrary/ > >>>> and I do not have the freedom to inject alterations into it. (Don't argue > >>>> this point, please. The expression is arbitrary.) > >>>> > >>>> How can I time out a tight loop like the above? Clearly, it can be > >>>> done, because I can, say, alt-tab over to another terminal and kill the > >>>> process, which exploits the operating system's more aggressively > >>>> pre-emptive scheduling. Is there a solution using bound threads, say > >>>> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? Unix > >>>> signals? Some FFI-based workaround? Etc. Keep in mind that > >>>> notwithstanding that comment, I don't actually want to kill the whole > >>>> process, but just the one evaluation. > >>>> > >>>> Thanks in advance, > >>>> Ryan Reich > >>>> _______________________________________________ > >>>> Haskell-Cafe mailing list > >>>> To (un)subscribe, modify options or view archives go to: > >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >>>> Only members subscribed via the mailman list are allowed to post. > >>> > >>> > >-------------- next part -------------- > >An HTML attachment was scrubbed... > >URL: > > > >------------------------------ > > > >Message: 5 > >Date: Sun, 18 Nov 2018 12:01:25 +0800 (CST) > >From: ducis > >To: haskell-cafe at haskell.org > >Subject: [Haskell-cafe] Specialize a function on types of arguments? > >Message-ID: <552773e2.1be5.16724faf3d0.Coremail.ducis_cn at 126.com> > >Content-Type: text/plain; charset="gbk" > > > >Hi, everyone, > > > >Is it possible to make combine the following "f" and "g" into one function? > >f:: a -> b -> b > >f x y = y > >g:: a -> a -> a > >g x y = x > > > >Or similarly, "eq1" and "eq2" into one function? > >eq1 :: (Eq a)=>a->a->Bool > >eq1 = (==) > >eq2 :: (Eq a,Eq b)=>a->b->Bool > >eq2 _ _ = False > > > >Looks like it would require some typeclasses, but at least in the first case, "a" and "b" should be any types. > > > >Best! > >-------------- next part -------------- > >An HTML attachment was scrubbed... > >URL: > > > >------------------------------ > > > >Message: 6 > >Date: Sun, 18 Nov 2018 17:40:51 +1300 > >From: Anthony Clayden > >To: haskell-cafe at haskell.org > >Subject: Re: [Haskell-cafe] Specialize a function on types of > > arguments? > >Message-ID: > > > >Content-Type: text/plain; charset="utf-8" > > > >Hi Ducis, > > > >> Is it possible to make combine the following "f" and "g" into one > >function? > > > >"combine" is vague. You perhaps mean: look at the types of the arguments, > >and choose one function or the other? > > > >> Looks like it would require some typeclasses, > > > >I'll answer the question as put (yes it needs typeclasses), but I can't > >help feel there's a backstory, and you might well be doing something that > >could be done better, if I knew what you're trying to achieve. Let's take > >the second one first > > > >> "eq1" and "eq2" into one function? > >> eq1 :: (Eq a)=>a->a->Bool > >> eq1 = (==) > >> eq2 :: (Eq a,Eq b)=>a->b->Bool > >> eq2 _ _ = False > > > >class Eqbytype a b where > > eqt :: a -> b -> Bool > > > >instance {-# OVERLAPPING #-} (Eq a) => Eqbytype a a where > > eqt = (==) > > > >instance {-# OVERLAPPABLE #-} Eqbytype a b where > > eqt _ _ = False > > > >Look at the Users Guide for what the OVERLAPPING/OVERLAPPABLE pragmas are doing. > > > >Note for the first instance I repeated type var `a` in the head, > >meaning: pick this instance if the two arguments to the method are of > >the same type. > > > >Note for the second instance, I didn't bother with the `Eq` > >constraint, since we can't compare values of distinct types. > > > > > >> f:: a -> b -> b > >> f x y = y > >> g:: a -> a -> a > >> g x y = x > >So you want same argument types to drive which argument to pick? Or > >you want the return type to drive which argument? That's possible: > >look at the definition of class `Read` in the Prelude. Again we can > >pick instances depending on a repeated type. But your requirements are > >not clear. > > > > > >> but at least in the first case [which I've put second], "a" and "b" should be any types. > > > >No they can't: as you state it, you require either all three the same, > >or the second to be the same as the return type. > > > >Come back and ask a more focussed question once you've worked through the > >above. (And explain why you're asking.) The above code is untested, BTW. > > > >AntC > >-------------- next part -------------- > >An HTML attachment was scrubbed... > >URL: > > > >------------------------------ > > > >Message: 7 > >Date: Sun, 18 Nov 2018 09:22:08 +0100 > >From: arjenvanweelden at gmail.com > >To: haskell-cafe at haskell.org > >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > > expression I did not write myself > >Message-ID: <27e9100ff70dd67791ed34e152c58239499bba65.camel at gmail.com> > >Content-Type: text/plain; charset="UTF-8" > > > >On Sat, 2018-11-17 at 15:21 -0800, Ryan Reich wrote: > >> I want to time out a pure computation. My experience, and that > >> described in various previous questions here and elsewhere (the best > >> of which is > >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html > >> ), is that this doesn't always work: for instance, > >> > >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x > >> > >> does not time out because, apparently, the fact that the expression > >> evaluates in constant space (i.e. never allocates) means that it > >> never yields to the timeout monitor thread that would kill it. > >> > >> The solution that is described in the other iterations is to embed > >> checkpoints in the expression that do allocate, giving the RTS a > >> chance to switch contexts. However, in my application, the > >> expression is /arbitrary/ and I do not have the freedom to inject > >> alterations into it. (Don't argue this point, please. The > >> expression is arbitrary.) > >> > >> How can I time out a tight loop like the above? Clearly, it can be > >> done, because I can, say, alt-tab over to another terminal and kill > >> the process, which exploits the operating system's more aggressively > >> pre-emptive scheduling. Is there a solution using bound threads, say > >> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? > >> Unix signals? Some FFI-based workaround? Etc. Keep in mind that > >> notwithstanding that comment, I don't actually want to kill the whole > >> process, but just the one evaluation. > >> > >> Thanks in advance, > >> Ryan Reich > >> > >If you are using GHC, the -fno-omit-yields compiler option might be of > >help, which does not optimize out the allocation check that is also > >used for interrupting threads. > > > >See also: > >https://stackoverflow.com/questions/34317730/haskell-timeout-diverging-computation > > > >Are you using the threaded runtime (GHC option -threaded)? > > > >hope this helps, Arjen > > > > > > > >------------------------------ > > > >Message: 8 > >Date: Sun, 18 Nov 2018 12:53:50 +0100 > >From: Fabien R > >To: haskell-cafe at haskell.org > >Subject: [Haskell-cafe] external git dependency source in .cabal > >Message-ID: <660c8ca8-3879-b5e5-52c4-682f6e4be80b at free.fr> > >Content-Type: text/plain; charset=utf-8 > > > >Hello, > >I'm trying to reference an external source of a package within a sandbox, using cabal 2.0.0.1: > > > >source-repository head > > type: git > > location: > > > >executable myExe > > build-depends: base==4.10.1.0, pack1 -any > > > >But "cabal -v install --only-dependencies" fails: > > > >cabal: Encountered missing dependencies: > >pack1 -any > > > >Any hint ? > > > >-- > >Fabien > > > > > >------------------------------ > > > >Subject: Digest Footer > > > >_______________________________________________ > >Haskell-Cafe mailing list > >Haskell-Cafe at haskell.org > >http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > > >------------------------------ > > > >End of Haskell-Cafe Digest, Vol 183, Issue 14 > >********************************************* > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From vanessa.mchale at iohk.io Sun Nov 18 19:34:53 2018 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Sun, 18 Nov 2018 13:34:53 -0600 Subject: [Haskell-cafe] external git dependency source in .cabal In-Reply-To: <660c8ca8-3879-b5e5-52c4-682f6e4be80b@free.fr> References: <660c8ca8-3879-b5e5-52c4-682f6e4be80b@free.fr> Message-ID: Here's an example: source-repository-package     type: git     location: https://github.com/well-typed/cborg     tag: 3d274c14ca3077c3a081ba7ad57c5182da65c8c1     subdir: cborg Maybe you forgot to specify a subdirectory? Cheers, Vanessa McHale -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 488 bytes Desc: OpenPGP digital signature URL: From vanessa.mchale at iohk.io Sun Nov 18 19:45:52 2018 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Sun, 18 Nov 2018 13:45:52 -0600 Subject: [Haskell-cafe] external git dependency source in .cabal In-Reply-To: References: <660c8ca8-3879-b5e5-52c4-682f6e4be80b@free.fr> Message-ID: <3aa2bf50-fbfc-5e07-b56a-f30f88ee14a7@iohk.io> In your .cabal file, yes, but the cabal.project file can reference external packages. It has a slightly different syntax, though. I don't think it's supported with cabal-install 2.0.0.1. You may have to use HEAD instead of 2.4.0.0, I don't know. On 11/18/18 9:05 AM, Brandon Allbery wrote: > It doesn't. The source repo is for hackage documentation, not package > retrieval. > > On Sun, Nov 18, 2018 at 9:57 AM Ivan Perez > > > wrote: > > If you can do this, this is news to me. > > See: > https://www.haskell.org/cabal/users-guide/developing-packages.html > > From what I understand, you cannot use this to point to repos for > dependencies, only to indicate the repo for the package you are > defining. > > You'd have to publish pack1 somewhere (on hackage or in your own > hackage server), or use a different tool to declare the > dependency. I don't know if cabal's new-build system addresses > this at all. > > Ivan > > On Sun, 18 Nov 2018 at 06:54, Fabien R > wrote: > > Hello, > I'm trying to reference an external source of a package within > a sandbox, using cabal 2.0.0.1 : > > source-repository head >    type: git >    location: > > executable myExe >     build-depends: base==4.10.1.0, pack1 -any > > But "cabal -v install --only-dependencies" fails: > > cabal: Encountered missing dependencies: > pack1 -any > > Any hint ? > > -- > Fabien > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > > > -- > brandon s allbery kf8nh > allbery.b at gmail.com > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 488 bytes Desc: OpenPGP digital signature URL: From rudy at matela.com.br Sun Nov 18 20:27:33 2018 From: rudy at matela.com.br (Rudy Matela) Date: Sun, 18 Nov 2018 17:27:33 -0300 Subject: [Haskell-cafe] ANN: LeanCheck v0.8.0 -- enumerative property testing Message-ID: <20181118202733.454jtplw23ozj7wg@zero.localdomain> Hello Haskell Café, A new version of LeanCheck is out (v0.8.0). LeanCheck is a property testing library (like QuickCheck) that tests values enumeratively. _Whats new?_ Among several changes, the most notable and significant are: * improvements in [LeanCheck's Haddock documentation]; * removal of a few experimental function enumeration modules; * and improved reporting of functional counter-examples (see below). [LeanCheck's changelog] provides more details. Take for example the following higher-order property that takes a functional argument and states an equivalence between `foldl` and `foldr`: prop_foldlr' :: (Int->Int->Int) -> Int -> [Int] -> Bool prop_foldlr' f z xs = foldl (flip f) z (reverse xs) == foldr f z xs You can check that it is correct by: > import Test.LeanCheck > import Test.LeanCheck.Function > check prop_foldlr' +++ OK, passed 200 tests. Now here is an incorrect version of the above property: prop_foldlr :: (A -> A -> A) -> A -> [A] -> Bool prop_foldlr f z xs = foldr f z xs == foldl f z xs You can check that it is incorrect by: > check prop_foldlr *** Failed! Falsifiable (after 75 tests): \x _ -> case x of 0 -> 1 _ -> 0 0 [0,0] LeanCheck reports the smallest counterexample it finds. The functional argument is now reported very concisely: a function that returns 1 whenever the first argument is 0 and returns 0 otherwise. Here's one last incorrect example property with two functional arguments: prop_mapFilter :: (Int->Int) -> (Int->Bool) -> [Int] -> Bool prop_mapFilter f p xs = filter p (map f xs) == map f (filter p xs) > check prop_mapFilter *** Failed! Falsifiable (after 36 tests): \_ -> 0 \x -> case x of 0 -> True _ -> False [1] The functions `map` and `filter` do not commute, the three values above are a counterexample. You can find LeanCheck on [Hackage] or [GitHub]. As usual, you can install it with: $ cabal install leancheck [Hackage]: https://hackage.haskell.org/package/leancheck [GitHub]: https://github.com/rudymatela/leancheck [LeanCheck's changelog]: https://hackage.haskell.org/package/leancheck/changelog [LeanCheck's Haddock documentation]: https://hackage.haskell.org/package/leancheck/docs/Test-LeanCheck.html -------------- next part -------------- An HTML attachment was scrubbed... URL: From cdsmith at gmail.com Mon Nov 19 01:22:30 2018 From: cdsmith at gmail.com (Chris Smith) Date: Sun, 18 Nov 2018 20:22:30 -0500 Subject: [Haskell-cafe] education@haskell.org mailing list Message-ID: Hello Haskellers, I'd like to invite you to join education at haskell.org This mailing list is a place to discuss the use of Haskell and similar languages (such as Elm, PureScript, ML, etc.) in education, particularly for broader audiences such as teaching children in schools, the broader public, etc. If this is of interest to you, I would like to invite you to join us. Please use this mailing list to talk about things you're doing in education, ask for advice or ideas or help with getting started, announce new projects, conferences, or research results, and/or seek collaborations with others. You can subscribe at https://mail.haskell.org/cgi-bin/mailman/listinfo/education If you're not yet involved in using Haskell in education, but are interested in the idea, please also join, and reach out for information. I started doing this about 7 years ago, and I've now taught something I love at a dozen different schools to hundreds of children, and it's been the most rewarding experience of my life. If you've got the interest and a bit of free time, I'd love to help you get started doing the same! Thanks, Chris Smith -------------- next part -------------- An HTML attachment was scrubbed... URL: From ducis_cn at 126.com Mon Nov 19 02:34:42 2018 From: ducis_cn at 126.com (ducis) Date: Mon, 19 Nov 2018 10:34:42 +0800 (CST) Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 183, Issue 14 In-Reply-To: References: Message-ID: <5235e2e2.36f1.16729d1eb67.Coremail.ducis_cn@126.com> Thanks for pointing that out. I haven't been seriously dealing with the monad laws as the code is not even working yet. But I guess it should be able to adjust the definition to fit the monad laws. Say, with current definition we have return 1 >>= return === WH ([],1) >>= \x->WH ([],x) === WH ([1],1) But if we change the definition of >>= to WH (h,a) >>= fm = WH (h1++if a == b then coerceHistory h else coerceHistory (a:h),b) where ... then return 1 >>= return === WH ([],1) while return 1 >>= return.(+2) === WH ([1],3) Of course this may break in other cases. The reason is that (apart from reducing explicit recording) I have used the Maybe monad extensively to express "computation that may fail" in existing code, and in the end I would like something which not only handles the possible failure also records history based on this WithHistory monad. 在 2018-11-19 01:34:33,"Dan Burton" 写道: I would recommend against this, since having >>= "record history" breaks monad laws. Particularly, this one: f >>= return === f Instead, why not use a plain old `Writer [Dynamic]` monad and explicitly `tell` whenever you want to add a historical record? import Control.Monad.Trans.Writer (Writer, tell) import Data.Dynamic (Dynamic, toDyn) import Data.Typeable (Typeable) newtype WithHistory b = WH (Writer [Dynamic] b) deriving (Functor, Applicative, Monad) tellHistory :: Typeable a => a -> WithHistory () tellHistory a = WH $ tell [toDyn a] someComputation :: WithHistory Int someComputation = do let x = 1 tellHistory x let y = x + 1 tellHistory y let yStr = show y tellHistory yStr let z = y + 3 tellHistory z return z -- Dan Burton On Sun, Nov 18, 2018 at 10:31 AM ducis wrote: Hi, Anthony, The top-level story is that I am trying to create a monad that somehow records the "intermediate steps" of computation. e.g. something like Prelude> return 1 ([],1) Prelude> return 1 >>= return.(+1) ([1],2) Prelude> return 1 >>= return.(+1)>>=return.(+3) ([2,1],5) (the list has the intermediate steps placed right-to-left so that new steps are appended to the left of the older steps) Of course all "intermediate steps of computation" actually form a graph, but we are frequently focused on, say, the transformation of a parse tree, where we want to take a series of snapshots of one "thing". Since a "lifted function" (e.g. return.(+1)) has in general the type a->m b, there are two ways to deal with input and output being not necessarily equal. The first approach I tried is to only record latest steps starting with the last change of type > newtype WithHistory b = WH ([b], b) and just discard the older steps when the input and output are of different types. > newtype WithHistory b = WH ([b], b) deriving (Show,Eq) > instance Monad WithHistory where > return b = WH ([], b) > (>>=) :: forall a b. WithHistory a -> (a -> WithHistory b) -> WithHistory b > WH (h,a) >>= fm = WH (h1++coerceHistory (a:h),b) > where > WH (h1, b) = fm a > class CoerceHistory a b where > coerceHistory :: [a] -> [b] > instance CoerceHistory a a where > coerceHistory = id > instance CoerceHistory a b where > coerceHistory _ = [] I have got the coerceHistory function to (appear to) work in GHCi *Main> coerceHistory [2::Int] :: [Int] [2] *Main> coerceHistory "c" :: [Int] [] But the Monad instanciation does not really work. GHC(7.6.3) hints for -XIncoherentInstances, which when enabled seems to force the (>>=) to always use the instance of coerceHistory returning [] The second approach is to use [Dynamic] for steps, i.e., > newtype WithHistory b = WH ([Dynamic], b) > instance Monad WithHistory where > return b = WH ([], b) > WH (h,a) >>= fm = WH (h1++forceDynList a++h, b) > where WH (h1, b) = fm a and presumably > class ForceDynList a where forceDynList :: a -> [Dynamic] > instance (Typeable a) => ForceDynList a where forceDynList x = [toDyn x] > instance ForceDynList a where forceDynList x = [] which is far from correct with error "Duplicate instance declarations" Thanks! Ducis -- ----------------------------- At 2018-11-18 20:00:01, haskell-cafe-request at haskell.org wrote: >Send Haskell-Cafe mailing list submissions to > haskell-cafe at haskell.org > >To subscribe or unsubscribe via the World Wide Web, visit > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >or, via email, send a message with subject or body 'help' to > haskell-cafe-request at haskell.org > >You can reach the person managing the list at > haskell-cafe-owner at haskell.org > >When replying, please edit your Subject line so it is more specific >than "Re: Contents of Haskell-Cafe digest..." > > >Today's Topics: > > 1. Timing out a pure evaluation of an expression I did not write > myself (Ryan Reich) > 2. Re: Timing out a pure evaluation of an expression I did not > write myself (Daniel Díaz Casanueva) > 3. Re: Timing out a pure evaluation of an expression I did not > write myself (Daniel Díaz Casanueva) > 4. Re: Timing out a pure evaluation of an expression I did not > write myself (Ryan Reich) > 5. Specialize a function on types of arguments? (ducis) > 6. Re: Specialize a function on types of arguments? (Anthony Clayden) > 7. Re: Timing out a pure evaluation of an expression I did not > write myself (arjenvanweelden at gmail.com) > 8. external git dependency source in .cabal (Fabien R) > > >---------------------------------------------------------------------- > >Message: 1 >Date: Sat, 17 Nov 2018 15:21:53 -0800 >From: Ryan Reich >To: haskell-cafe >Subject: [Haskell-cafe] Timing out a pure evaluation of an expression > I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >I want to time out a pure computation. My experience, and that described >in various previous questions here and elsewhere (the best of which is >https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >is that this doesn't always work: for instance, > >>>> timeout 1 $ evaluate $ let x = 0 : x in last x > >does not time out because, apparently, the fact that the expression >evaluates in constant space (i.e. never allocates) means that it never >yields to the timeout monitor thread that would kill it. > >The solution that is described in the other iterations is to embed >checkpoints in the expression that do allocate, giving the RTS a chance to >switch contexts. However, in my application, the expression is /arbitrary/ >and I do not have the freedom to inject alterations into it. (Don't argue >this point, please. The expression is arbitrary.) > >How can I time out a tight loop like the above? Clearly, it can be done, >because I can, say, alt-tab over to another terminal and kill the process, >which exploits the operating system's more aggressively pre-emptive >scheduling. Is there a solution using bound threads, say 'forkOS' instead >of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >FFI-based workaround? Etc. Keep in mind that notwithstanding that >comment, I don't actually want to kill the whole process, but just the one >evaluation. > >Thanks in advance, >Ryan Reich >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 2 >Date: Sun, 18 Nov 2018 01:51:58 +0100 >From: Daniel Díaz Casanueva >To: ryan.reich at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Hello Ryan. > >Try evaluating the expression to normal form instead of weak head normal >form in your expression. So: > >>>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x > >The function `force` comes from the deepseq package. You can read the docs >here: >http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html > >I hope that helps. > >Best regards, >Daniel > >Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich >: > >> I want to time out a pure computation. My experience, and that described >> in various previous questions here and elsewhere (the best of which is >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >> is that this doesn't always work: for instance, >> >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >> >> does not time out because, apparently, the fact that the expression >> evaluates in constant space (i.e. never allocates) means that it never >> yields to the timeout monitor thread that would kill it. >> >> The solution that is described in the other iterations is to embed >> checkpoints in the expression that do allocate, giving the RTS a chance to >> switch contexts. However, in my application, the expression is /arbitrary/ >> and I do not have the freedom to inject alterations into it. (Don't argue >> this point, please. The expression is arbitrary.) >> >> How can I time out a tight loop like the above? Clearly, it can be done, >> because I can, say, alt-tab over to another terminal and kill the process, >> which exploits the operating system's more aggressively pre-emptive >> scheduling. Is there a solution using bound threads, say 'forkOS' instead >> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >> FFI-based workaround? Etc. Keep in mind that notwithstanding that >> comment, I don't actually want to kill the whole process, but just the one >> evaluation. >> >> Thanks in advance, >> Ryan Reich >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 3 >Date: Sun, 18 Nov 2018 01:55:56 +0100 >From: Daniel Díaz Casanueva >To: ryan.reich at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Actually, after reading the question again, it seems like my response >wasn't quite right. You are not actually building the list. In that case, I >am as confused as you. :) > >Sorry! > >Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < >dhelta.diaz at gmail.com>: > >> Hello Ryan. >> >> Try evaluating the expression to normal form instead of weak head normal >> form in your expression. So: >> >> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x >> >> The function `force` comes from the deepseq package. You can read the docs >> here: >> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html >> >> I hope that helps. >> >> Best regards, >> Daniel >> >> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < >> ryan.reich at gmail.com>: >> >>> I want to time out a pure computation. My experience, and that described >>> in various previous questions here and elsewhere (the best of which is >>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >>> is that this doesn't always work: for instance, >>> >>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >>> >>> does not time out because, apparently, the fact that the expression >>> evaluates in constant space (i.e. never allocates) means that it never >>> yields to the timeout monitor thread that would kill it. >>> >>> The solution that is described in the other iterations is to embed >>> checkpoints in the expression that do allocate, giving the RTS a chance to >>> switch contexts. However, in my application, the expression is /arbitrary/ >>> and I do not have the freedom to inject alterations into it. (Don't argue >>> this point, please. The expression is arbitrary.) >>> >>> How can I time out a tight loop like the above? Clearly, it can be done, >>> because I can, say, alt-tab over to another terminal and kill the process, >>> which exploits the operating system's more aggressively pre-emptive >>> scheduling. Is there a solution using bound threads, say 'forkOS' instead >>> of 'forkIO' in the implementation of 'timeout'? Unix signals? Some >>> FFI-based workaround? Etc. Keep in mind that notwithstanding that >>> comment, I don't actually want to kill the whole process, but just the one >>> evaluation. >>> >>> Thanks in advance, >>> Ryan Reich >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 4 >Date: Sat, 17 Nov 2018 16:57:56 -0800 >From: Ryan Reich >To: dhelta.diaz at gmail.com >Cc: haskell-cafe >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >I was just about to reply with an observation to that effect :) The place >that I'd want to put 'force' is actually inside the 'let' clause, which of >course you can't do just by applying a function. The expression as a whole >is just an Integer. > >On Sat, Nov 17, 2018 at 4:56 PM Daniel Díaz Casanueva >wrote: > >> Actually, after reading the question again, it seems like my response >> wasn't quite right. You are not actually building the list. In that case, I >> am as confused as you. :) >> >> Sorry! >> >> Am So., 18. Nov. 2018 um 01:51 Uhr schrieb Daniel Díaz Casanueva < >> dhelta.diaz at gmail.com>: >> >>> Hello Ryan. >>> >>> Try evaluating the expression to normal form instead of weak head normal >>> form in your expression. So: >>> >>> >>> timeout 1 $ evaluate $ force $ let x = 0 : x in last x >>> >>> The function `force` comes from the deepseq package. You can read the >>> docs here: >>> http://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html >>> >>> I hope that helps. >>> >>> Best regards, >>> Daniel >>> >>> Am So., 18. Nov. 2018 um 00:22 Uhr schrieb Ryan Reich < >>> ryan.reich at gmail.com>: >>> >>>> I want to time out a pure computation. My experience, and that >>>> described in various previous questions here and elsewhere (the best of >>>> which is >>>> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), >>>> is that this doesn't always work: for instance, >>>> >>>> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >>>> >>>> does not time out because, apparently, the fact that the expression >>>> evaluates in constant space (i.e. never allocates) means that it never >>>> yields to the timeout monitor thread that would kill it. >>>> >>>> The solution that is described in the other iterations is to embed >>>> checkpoints in the expression that do allocate, giving the RTS a chance to >>>> switch contexts. However, in my application, the expression is /arbitrary/ >>>> and I do not have the freedom to inject alterations into it. (Don't argue >>>> this point, please. The expression is arbitrary.) >>>> >>>> How can I time out a tight loop like the above? Clearly, it can be >>>> done, because I can, say, alt-tab over to another terminal and kill the >>>> process, which exploits the operating system's more aggressively >>>> pre-emptive scheduling. Is there a solution using bound threads, say >>>> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? Unix >>>> signals? Some FFI-based workaround? Etc. Keep in mind that >>>> notwithstanding that comment, I don't actually want to kill the whole >>>> process, but just the one evaluation. >>>> >>>> Thanks in advance, >>>> Ryan Reich >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >>> >>> >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 5 >Date: Sun, 18 Nov 2018 12:01:25 +0800 (CST) >From: ducis >To: haskell-cafe at haskell.org >Subject: [Haskell-cafe] Specialize a function on types of arguments? >Message-ID: <552773e2.1be5.16724faf3d0.Coremail.ducis_cn at 126.com> >Content-Type: text/plain; charset="gbk" > >Hi, everyone, > >Is it possible to make combine the following "f" and "g" into one function? >f:: a -> b -> b >f x y = y >g:: a -> a -> a >g x y = x > >Or similarly, "eq1" and "eq2" into one function? >eq1 :: (Eq a)=>a->a->Bool >eq1 = (==) >eq2 :: (Eq a,Eq b)=>a->b->Bool >eq2 _ _ = False > >Looks like it would require some typeclasses, but at least in the first case, "a" and "b" should be any types. > >Best! >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 6 >Date: Sun, 18 Nov 2018 17:40:51 +1300 >From: Anthony Clayden >To: haskell-cafe at haskell.org >Subject: Re: [Haskell-cafe] Specialize a function on types of > arguments? >Message-ID: > >Content-Type: text/plain; charset="utf-8" > >Hi Ducis, > >> Is it possible to make combine the following "f" and "g" into one >function? > >"combine" is vague. You perhaps mean: look at the types of the arguments, >and choose one function or the other? > >> Looks like it would require some typeclasses, > >I'll answer the question as put (yes it needs typeclasses), but I can't >help feel there's a backstory, and you might well be doing something that >could be done better, if I knew what you're trying to achieve. Let's take >the second one first > >> "eq1" and "eq2" into one function? >> eq1 :: (Eq a)=>a->a->Bool >> eq1 = (==) >> eq2 :: (Eq a,Eq b)=>a->b->Bool >> eq2 _ _ = False > >class Eqbytype a b where > eqt :: a -> b -> Bool > >instance {-# OVERLAPPING #-} (Eq a) => Eqbytype a a where > eqt = (==) > >instance {-# OVERLAPPABLE #-} Eqbytype a b where > eqt _ _ = False > >Look at the Users Guide for what the OVERLAPPING/OVERLAPPABLE pragmas are doing. > >Note for the first instance I repeated type var `a` in the head, >meaning: pick this instance if the two arguments to the method are of >the same type. > >Note for the second instance, I didn't bother with the `Eq` >constraint, since we can't compare values of distinct types. > > >> f:: a -> b -> b >> f x y = y >> g:: a -> a -> a >> g x y = x >So you want same argument types to drive which argument to pick? Or >you want the return type to drive which argument? That's possible: >look at the definition of class `Read` in the Prelude. Again we can >pick instances depending on a repeated type. But your requirements are >not clear. > > >> but at least in the first case [which I've put second], "a" and "b" should be any types. > >No they can't: as you state it, you require either all three the same, >or the second to be the same as the return type. > >Come back and ask a more focussed question once you've worked through the >above. (And explain why you're asking.) The above code is untested, BTW. > >AntC >-------------- next part -------------- >An HTML attachment was scrubbed... >URL: > >------------------------------ > >Message: 7 >Date: Sun, 18 Nov 2018 09:22:08 +0100 >From: arjenvanweelden at gmail.com >To: haskell-cafe at haskell.org >Subject: Re: [Haskell-cafe] Timing out a pure evaluation of an > expression I did not write myself >Message-ID: <27e9100ff70dd67791ed34e152c58239499bba65.camel at gmail.com> >Content-Type: text/plain; charset="UTF-8" > >On Sat, 2018-11-17 at 15:21 -0800, Ryan Reich wrote: >> I want to time out a pure computation. My experience, and that >> described in various previous questions here and elsewhere (the best >> of which is >> https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html >> ), is that this doesn't always work: for instance, >> >> >>> timeout 1 $ evaluate $ let x = 0 : x in last x >> >> does not time out because, apparently, the fact that the expression >> evaluates in constant space (i.e. never allocates) means that it >> never yields to the timeout monitor thread that would kill it. >> >> The solution that is described in the other iterations is to embed >> checkpoints in the expression that do allocate, giving the RTS a >> chance to switch contexts. However, in my application, the >> expression is /arbitrary/ and I do not have the freedom to inject >> alterations into it. (Don't argue this point, please. The >> expression is arbitrary.) >> >> How can I time out a tight loop like the above? Clearly, it can be >> done, because I can, say, alt-tab over to another terminal and kill >> the process, which exploits the operating system's more aggressively >> pre-emptive scheduling. Is there a solution using bound threads, say >> 'forkOS' instead of 'forkIO' in the implementation of 'timeout'? >> Unix signals? Some FFI-based workaround? Etc. Keep in mind that >> notwithstanding that comment, I don't actually want to kill the whole >> process, but just the one evaluation. >> >> Thanks in advance, >> Ryan Reich >> >If you are using GHC, the -fno-omit-yields compiler option might be of >help, which does not optimize out the allocation check that is also >used for interrupting threads. > >See also: >https://stackoverflow.com/questions/34317730/haskell-timeout-diverging-computation > >Are you using the threaded runtime (GHC option -threaded)? > >hope this helps, Arjen > > > >------------------------------ > >Message: 8 >Date: Sun, 18 Nov 2018 12:53:50 +0100 >From: Fabien R >To: haskell-cafe at haskell.org >Subject: [Haskell-cafe] external git dependency source in .cabal >Message-ID: <660c8ca8-3879-b5e5-52c4-682f6e4be80b at free.fr> >Content-Type: text/plain; charset=utf-8 > >Hello, >I'm trying to reference an external source of a package within a sandbox, using cabal 2.0.0.1: > >source-repository head > type: git > location: > >executable myExe > build-depends: base==4.10.1.0, pack1 -any > >But "cabal -v install --only-dependencies" fails: > >cabal: Encountered missing dependencies: >pack1 -any > >Any hint ? > >-- >Fabien > > >------------------------------ > >Subject: Digest Footer > >_______________________________________________ >Haskell-Cafe mailing list >Haskell-Cafe at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > >------------------------------ > >End of Haskell-Cafe Digest, Vol 183, Issue 14 >********************************************* _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From theedge456 at free.fr Mon Nov 19 10:48:12 2018 From: theedge456 at free.fr (Fabien R) Date: Mon, 19 Nov 2018 11:48:12 +0100 Subject: [Haskell-cafe] external git dependency source in .cabal In-Reply-To: References: <660c8ca8-3879-b5e5-52c4-682f6e4be80b@free.fr> Message-ID: <53a7011e-5042-69ea-3e42-f710ec741708@free.fr> On 18/11/2018 20:34, Vanessa McHale wrote: > Here's an example: > > source-repository-package >     type: git >     location: https://github.com/well-typed/cborg >     tag: 3d274c14ca3077c3a081ba7ad57c5182da65c8c1 >     subdir: cborg > I could not make it work with my version of cabal. So, I ended up with installing the package and referencing it in the sandbox with: cabal sandbox add-source -- Fabien From anthony_clayden at clear.net.nz Mon Nov 19 10:56:41 2018 From: anthony_clayden at clear.net.nz (Anthony Clayden) Date: Mon, 19 Nov 2018 23:56:41 +1300 Subject: [Haskell-cafe] Specialize a function on types of arguments? In-Reply-To: <741530a.492d.1672773c691.Coremail.ducis_cn@126.com> References: <741530a.492d.1672773c691.Coremail.ducis_cn@126.com> Message-ID: On Mon, 19 Nov 2018 at 4:33 AM, ducis wrote: > > The top-level story is that I am trying to create a monad that somehow > records the "intermediate steps" of computation. > Uh-oh. That got into deep water surprisingly quickly. We seem to be a long way from your O.P. already. I'm not sure I can help much/here are some general remarks. Your examples below are using Int and String, but I take it you're really dealing with much more complex types than that(?) -- you mention parse trees. The usual way to stack one type on top of another in steps is with Monad Transformers. At the point of stacking a different type, is that a fresh computation ignoring history? Or is it a computation on type `a` that produces a `b`? I'm not convinced a monad is the right thing here. Perhaps any passing Categoristas could offer an opinion. The reason using a monad feels wrong is because of all the `return`s and especially the `(return . ( f ))`s. I'm also wondering if using a list for "intermediate steps" is worth it: if in general each computation step might produce a different type, just stack on a heterogeneous list (in which some adjacent cells might by coincidence be the same type). See the `'[]` promoted DataKind. Yes, if GHC messages are talking about IncoherentInstances you are in trouble. GHC seems far too eager to suggest them. "Incoherent" is just as bad as it sounds. Almost always you can get the instances to compile but you still can't use them/it shifts the problem to somewhere else in your code which is even harder to diagnose. And it's always possible to rejig the code to avoid IncoherentInstances -- that is, presuming your intended semantics is actually coherent ;-). I think that rather than monad bind `(>>=)` :: m a -> (a -> m b) -> m b`, you want a polymonad bind `(>>?) :: m a -> (a -> m2 b) -> m2 b` in which `m2` stacks a b-history on top of the a-history from `m` (which of course includes history from previous types as well). Now you're in trouble: polymonads currently give typechecking severe indigestion. Contrast that for ordinary monads it's the same `m` all along the chain, any step that fixes the monad (including the expected overall return type) will ripple it through the lot. But it's not as indeterminate as that: you can calculate `m2` given `m`, `b`. And you can back-calculate `m a` given `m2` -- presuming you're using a simple stacking structure. Sounds like a job for Type Families and (if you want to continue using `do` notation) Rebindable syntax. But then beware all the warnings in the Users Guide. AntC > e.g. something like > Prelude> return 1 > ([],1) > Prelude> return 1 >>= return.(+1) > ([1],2) > Prelude> return 1 >>= return.(+1)>>=return.(+3) > ([2,1],5) > (the list has the intermediate steps placed right-to-left so that new > steps are appended to the left of the older steps) > Of course all "intermediate steps of computation" actually form a graph, > but we are frequently focused on, say, > the transformation of a parse tree, where we want to take a series of > snapshots of one "thing". > > Since a "lifted function" (e.g. return.(+1)) has in general the type a->m > b, there are two ways > to deal with input and output being not necessarily equal. > > The first approach I tried is to only record latest steps starting with > the last change of type > > newtype WithHistory b = WH ([b], b) > and just discard the older steps when the input and output are of > different types. > > newtype WithHistory b = WH ([b], b) deriving > (Show,Eq) > > instance Monad WithHistory where > > return b = WH ([], b) > > (>>=) :: forall a b. WithHistory a -> (a -> WithHistory b) -> > WithHistory b > > WH (h,a) >>= fm = WH (h1++coerceHistory (a:h),b) > > where > > WH (h1, b) = fm a > > class CoerceHistory a b where > > coerceHistory :: [a] -> [b] > > instance CoerceHistory a a where > > coerceHistory = id > > instance CoerceHistory a b where > > coerceHistory _ = [] > I have got the coerceHistory function to (appear to) work in GHCi > *Main> coerceHistory [2::Int] :: [Int] > [2] > *Main> coerceHistory "c" :: [Int] > [] > But the Monad instanciation does not really work. > GHC(7.6.3) hints for -XIncoherentInstances, which when > enabled seems to force the (>>=) to always use the instance > of coerceHistory returning [] > > The second approach is to use [Dynamic] for steps, i.e., > > newtype WithHistory b = WH ([Dynamic], b) > > instance Monad WithHistory where > > return b = WH ([], b) > > WH (h,a) >>= fm = WH (h1++forceDynList a++h, b) > > where WH (h1, b) = fm a > and presumably > > class ForceDynList a where > forceDynList :: a -> [Dynamic] > > instance (Typeable a) => ForceDynList a where forceDynList x = [toDyn > x] > > instance ForceDynList a where forceDynList > x = [] > which is far from correct with error "Duplicate instance declarations" > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.reich at gmail.com Mon Nov 19 19:26:17 2018 From: ryan.reich at gmail.com (Ryan Reich) Date: Mon, 19 Nov 2018 11:26:17 -0800 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: Message-ID: I suppose my question concerns the more general question of how to create OS-managed threads in GHC. As I understand it, GHC's concurrency model only exposes its RTS-managed internal threads, which are distributed somehow to OS threads by the scheduler, and this is the source of my timeout problem, because the scheduler never runs. Contrast this with plain Linux C, where we can do something with pthread_create to call a function in an OS-managed thread directly. I would have expected there to be a corresponding operation in GHC Haskell ("bound threads" seem not to be it, as they are still scheduled by the RTS) but it does not appear that there is. Is this because of the need to keep the runtime unified? Because it seems strange that we are prevented from operating truly independent threads. Ryan On Sat, Nov 17, 2018 at 3:21 PM Ryan Reich wrote: > I want to time out a pure computation. My experience, and that described > in various previous questions here and elsewhere (the best of which is > https://mail.haskell.org/pipermail/haskell-cafe/2011-February/088820.html), > is that this doesn't always work: for instance, > > >>> timeout 1 $ evaluate $ let x = 0 : x in last x > > does not time out because, apparently, the fact that the expression > evaluates in constant space (i.e. never allocates) means that it never > yields to the timeout monitor thread that would kill it. > > The solution that is described in the other iterations is to embed > checkpoints in the expression that do allocate, giving the RTS a chance to > switch contexts. However, in my application, the expression is /arbitrary/ > and I do not have the freedom to inject alterations into it. (Don't argue > this point, please. The expression is arbitrary.) > > How can I time out a tight loop like the above? Clearly, it can be done, > because I can, say, alt-tab over to another terminal and kill the process, > which exploits the operating system's more aggressively pre-emptive > scheduling. Is there a solution using bound threads, say 'forkOS' instead > of 'forkIO' in the implementation of 'timeout'? Unix signals? Some > FFI-based workaround? Etc. Keep in mind that notwithstanding that > comment, I don't actually want to kill the whole process, but just the one > evaluation. > > Thanks in advance, > Ryan Reich > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Mon Nov 19 20:26:51 2018 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Mon, 19 Nov 2018 15:26:51 -0500 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: Message-ID: <20181119202651.GH4122@straasha.imrryr.org> On Mon, Nov 19, 2018 at 11:26:17AM -0800, Ryan Reich wrote: > I suppose my question concerns the more general question of how to create > OS-managed threads in GHC. [...] > I would have expected there to > be a corresponding operation in GHC Haskell ("bound threads" seem not to be > it, as they are still scheduled by the RTS) but it does not appear that > there is. Is this because of the need to keep the runtime unified? > Because it seems strange that we are prevented from operating truly > independent threads. I was just reading: https://cs.nyu.edu/~mwalfish/classes/14fa/ref/boehm05threads.pdf which may offer some insight. The runtime needs to be able to provide a consistent memory model to threads. Just running something in an OS thread that's managed by the RTS could make that difficult, and it is not clear how that cooperates with garbage collection. But to your point, when adding threads to your example, I find that the infinite loop then runs concurrently in all the threads, and the timeout never happens. While: Replacing: let x = 0:x in last x with: let ! x = 0 + x in x does make timeout work, so it is not entirely obvious which pure computations can be timed out. -- Viktor. From frank at fstaals.net Mon Nov 19 20:38:15 2018 From: frank at fstaals.net (Frank Staals) Date: Mon, 19 Nov 2018 21:38:15 +0100 Subject: [Haskell-cafe] Help with DataKinds example In-Reply-To: ("Marc =?utf-8?Q?Busqu=C3=A9=22's?= message of "Sun, 18 Nov 2018 18:29:01 +0100 (CET)") References: Message-ID: Marc Busqué writes: > I'm reading Sandy Maguire book Thinking with Types, and I'm stuck > understanding an example about `DataKinds` language extension. > > In the book, it is said that it can be used to prevent at the type level > that non admin users perform some action for which admin privileges are > required. > > So, in the example, having `DataKinds` enabled, we define: > > ``` > data UserType = User | Admin > ``` > > Then, we change User type: > > ``` > data User = User > { userAdminToken :: Maybe (Proxy 'Admin) } > ``` > > And then it is said that we can enforce that sensitive operations are > performed by a user with the admin token: > > ``` > doSensitiveThings :: Proxy 'Admin -> IO () > ``` > > No other language extensions have been explained before in the book, and > I simply don't understand how it is works... > > First, I guess that when writing `data User = ...` we are overriding > `'User` promoted data constructor. Isn't it? The second 'User' type (and constructor) are both different from the 'User' constructor in the UserType type. It may be clearer if we slightly rename these types and the constructors a bit to something like: ``` {-# LANGUAGE DataKinds #-} import Data.Proxy data UserKind = User | Admin data RealUser = RealUser { userAdminToken :: Maybe (Proxy 'Admin) } doSensitiveThings :: Proxy 'Admin -> IO () doSensitiveThings = undefined ``` > Also, I don't understand how I could define a type `Proxy 'Admin`. If > I'm not wrong, `Proxy` should have the kind `UserType -> *`, but I > don't know how to do that. You can define it like: data Proxy (a :: k) = Proxy but that requires the {-# LANGUAGE PolyKinds #-} language extension > Besides that, I would like some guidance in the general idea of the > example, because I'm quite puzzled :) The idea is that to restrict the type of the 'doSensitiveThings' function so that you can only call it if you have "admin powers". To prove that you have those admin powers you have to pass it a value of type 'Proxy Admin'. Let me maybe adapt the example slightly again to make things clearer: ``` {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} data UserKind = User | Admin data RealUser (uk :: UserKind) = RealUser { userName :: String } root :: RealUser 'Admin root = RealUser "root" frank :: RealUser 'User frank = RealUser "frank" doSensitiveThings :: RealUser 'Admin -> IO () doSensitiveThings _ = print "installing packages now ... " -- | this compiles fine: testAllowed = doSensitiveThings root -- | This gives a type error: testNotAllowed = doSensitiveThings frank -- • Couldn't match type ‘'User’ with ‘'Admin’ -- Expected type: RealUser 'Admin -- Actual type: RealUser 'User -- • In the first argument of ‘doSensitiveThings’, namely ‘frank’ -- In the expression: doSensitiveThings frank -- In an equation for ‘testNotAllowed’: -- testNotAllowed = doSensitiveThings frank ``` In the above example, I've "tagged" the RealUser type with a type variable that expresses if our user is a regular user or an Admin, and our 'doSensitiveThings' function can only be called with Users that are admins. I hope this helps -- - Frank From olf at aatal-apotheke.de Mon Nov 19 21:03:53 2018 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Mon, 19 Nov 2018 22:03:53 +0100 Subject: [Haskell-cafe] Specialize a function on types of arguments? Message-ID: <7C2F0D12-BC56-4F75-967F-449B0C0E2E36@aatal-apotheke.de> > > The top-level story is that I am trying to create a monad that somehow > records the "intermediate steps" of computation. > If it is only for knowing where things went wrong, isn't that what the Either monad is for? The semantics of (Either YourErrorType) is that it returns `Right result' when all steps went through, and `Left errmsg' from the first place where something went wrong. You'd have to define YourErrorType to incorporate the relevant error information. If you also want something like a call stack, i.e. a message like "computation failed in step 3 with message: foo" Then you need to stack a state transformer on top, e.g. StateT CallStack (Either YourErrorType) which decodes to CallStack -> Either YourErrorType (resultType,CallStack) An example using mtl transformers: import Control.Monad.State.Strict import Control.Monad.Except type CallStack = (Int,[String]) type YourErrorType = String type M a = StateT CallStack (Except YourError) a fancyFunc :: Show a => (a -> b) -> (a -> M b) fancyFunc f a = do (n,stack) <- get put (n+1,show a : stack) return b fancyMaybe :: Show a => (a -> Maybe b) -> (a -> M b) fancyMaybe f a = do (n,stack) <- get case (f a) of Nothing -> throwError $ "Failed at step "++(show n)++" on input "++(show a) Just b -> do put (n+1,show a : stack) return b runChainOfComputations = runStateT (1,[]) I once wrote a type 'ProvenienceT' which is a bit fancier than the above. It is a monadic EDSL and constructs a graph where nodes are (Markup of) intermediate steps of a computation and where edges are (user-supplied descriptions of) functions. It is inspired by the Javelin software of the 80s which pre-dates Excel spreadsheets. The result can be rendered as html. Can provide code if anyone is interested. Cheers, Olaf From anthony_clayden at clear.net.nz Tue Nov 20 03:03:25 2018 From: anthony_clayden at clear.net.nz (Anthony Clayden) Date: Tue, 20 Nov 2018 16:03:25 +1300 Subject: [Haskell-cafe] Specialize a function on types of arguments? Message-ID: On Mon, 19 Nov 2018 at 21:03, Olaf Klinke wrote: >>* The top-level story is that I am trying to create a monad that somehow* *>*>* records the "intermediate steps" of computation.* >> > If it is only for knowing where things went wrong, ... Thanks Olaf, no I think Ducis wants to stack the whole history of the computation. > If ... Then you need to stack a state transformer on top, Yes a monad transformer might be it. Thank you for the example. As per my previous message, I'm not convinced it needs monads at all. Here's a dumb approach as a straw man, showing that type-changing steps are nothing special (or perhaps I mean type-preserving steps are nothing special ;-). Ducis could explain why this won't do nil = () cons x l = (x, l) start :: a -> (a,()) start x = cons x nil -- i.e. singleton x infixl 0 $>> ($>>) :: (b, _a) -> (b -> c) -> (c, (b, _a)) xs@(x, z) $>> f = cons (f x) xs eg = start 1 $>> (+ 1) $>> (+ 3) $>> double $>> show ===> ("10",(10,(5,(2,(1,()))))) I chose ($>>) to be similar to ($>) from the Control.FPipe package "trivial F#-style pipes for function composition and application". You could use Datakind `'[]` instead of the 'poor man's heterogeneous list' I've used, but that seems over-engineering. AntC -------------- next part -------------- An HTML attachment was scrubbed... URL: From cdsmith at gmail.com Tue Nov 20 18:46:31 2018 From: cdsmith at gmail.com (Chris Smith) Date: Tue, 20 Nov 2018 13:46:31 -0500 Subject: [Haskell-cafe] Feedback on plan for checking code requirements in a GHC plugin Message-ID: Hey everyone, I'm converging on a design for a new feature of CodeWorld, the Haskell-based educational programming environment that I teach with. I'm wondering if anyone has done something like this before. The goal is that when I give an assignment in a class (e.g., "modify this starting code to generalize the repeated pattern using a function"), I want the user to see a checklist of assignment requirements when they run the code. A prototype implementation is here: https://code.world/haskell#PpwpTF1wv3qIvwhohCfvSrQ There are all sorts of possible requirements, such as: "No lines longer than 80 characters", or "there must be a function called foo", or "all top-level definitions must have type signatures", or "your code must define at least 10 top-level variables, and use at least 3 where clauses", or "your definition of var should be equivalent to this one" (see Joachim Breitner's inspection testing work), or even "the function f must satisfy this QuickCheck property". It's been suggested that the requirements language also include the ability to match patterns in the AST, which I think is a good idea. The current prototype uses a pre-compile step that parses the code using haskell-src-exts, and doesn't implement dynamic requirements (runtime-evaluated) at all. My ultimate plan, though, is to send these requirements to GHC via a plugin, then have it evaluate the static ones at compile time, and generate code to check the dynamic ones. Finally, the plugin would add new code to the beginning of main that will invoke a configurable function with the results of the requirement check (hard-coding the static ones, and evaluating dynamic ones on the fly). (In the CodeWorld environment, this function would display the checklist in the web UI, for example.) Has anyone done anything like this before? Any wisdom to share, or ideas to contribute? Thanks, Chris -------------- next part -------------- An HTML attachment was scrubbed... URL: From astrohavoc at gmail.com Wed Nov 21 02:59:00 2018 From: astrohavoc at gmail.com (Shao Cheng) Date: Wed, 21 Nov 2018 10:59:00 +0800 Subject: [Haskell-cafe] Feedback on plan for checking code requirements in a GHC plugin In-Reply-To: References: Message-ID: Hi Chris, For "checking static properties at compile time", you may find [sbvPlugin]( https://hackage.haskell.org/package/sbvPlugin) useful, it supports annotating functions with ANN pragmas that declare properties verifiable by an SMT solver. I haven't used it with ghcjs so not sure if it fits your use case, but probably worth a try. Regards, Shao Cheng On Wed, Nov 21, 2018 at 2:47 AM Chris Smith wrote: > Hey everyone, > > I'm converging on a design for a new feature of CodeWorld, the > Haskell-based educational programming environment that I teach with. I'm > wondering if anyone has done something like this before. > > The goal is that when I give an assignment in a class (e.g., "modify this > starting code to generalize the repeated pattern using a function"), I want > the user to see a checklist of assignment requirements when they run the > code. A prototype implementation is here: > https://code.world/haskell#PpwpTF1wv3qIvwhohCfvSrQ > > There are all sorts of possible requirements, such as: "No lines longer > than 80 characters", or "there must be a function called foo", or "all > top-level definitions must have type signatures", or "your code must define > at least 10 top-level variables, and use at least 3 where clauses", or > "your definition of var should be equivalent to this one" (see Joachim > Breitner's inspection testing work), or even "the function f must satisfy > this QuickCheck property". It's been suggested that the requirements > language also include the ability to match patterns in the AST, which I > think is a good idea. > > The current prototype uses a pre-compile step that parses the code using > haskell-src-exts, and doesn't implement dynamic requirements > (runtime-evaluated) at all. My ultimate plan, though, is to send these > requirements to GHC via a plugin, then have it evaluate the static ones at > compile time, and generate code to check the dynamic ones. Finally, the > plugin would add new code to the beginning of main that will invoke a > configurable function with the results of the requirement check > (hard-coding the static ones, and evaluating dynamic ones on the fly). (In > the CodeWorld environment, this function would display the checklist in the > web UI, for example.) > > Has anyone done anything like this before? Any wisdom to share, or ideas > to contribute? > > Thanks, > Chris > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Wed Nov 21 13:28:07 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Wed, 21 Nov 2018 14:28:07 +0100 Subject: [Haskell-cafe] Feedback on plan for checking code requirements in a GHC plugin Message-ID: > Has anyone done anything like this before? Sort-of. Not with a GHC plugin, but haskell-src-exts to get the AST, and then match with a blueprint for the code (students have to replace "undefined" by some expression). See "How I Teach Functional Programming" (WFLP 2017) https://www.imn.htwk-leipzig.de/~waldmann/talk/ - J.W. From matthewtpickering at gmail.com Wed Nov 21 17:04:43 2018 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Wed, 21 Nov 2018 17:04:43 +0000 Subject: [Haskell-cafe] Feedback on plan for checking code requirements in a GHC plugin In-Reply-To: References: Message-ID: Nothing to add other than this sounds just like the sort of thing that will be easy to implement as a source plugin. You might find my plugins resource page useful: http://mpickering.github.io/plugins.html In particular, this post about how to construct expressions: http://mpickering.github.io/posts/2018-06-11-source-plugins.html Cheers, Matt On Tue, Nov 20, 2018 at 6:47 PM Chris Smith wrote: > > Hey everyone, > > I'm converging on a design for a new feature of CodeWorld, the Haskell-based educational programming environment that I teach with. I'm wondering if anyone has done something like this before. > > The goal is that when I give an assignment in a class (e.g., "modify this starting code to generalize the repeated pattern using a function"), I want the user to see a checklist of assignment requirements when they run the code. A prototype implementation is here: https://code.world/haskell#PpwpTF1wv3qIvwhohCfvSrQ > > There are all sorts of possible requirements, such as: "No lines longer than 80 characters", or "there must be a function called foo", or "all top-level definitions must have type signatures", or "your code must define at least 10 top-level variables, and use at least 3 where clauses", or "your definition of var should be equivalent to this one" (see Joachim Breitner's inspection testing work), or even "the function f must satisfy this QuickCheck property". It's been suggested that the requirements language also include the ability to match patterns in the AST, which I think is a good idea. > > The current prototype uses a pre-compile step that parses the code using haskell-src-exts, and doesn't implement dynamic requirements (runtime-evaluated) at all. My ultimate plan, though, is to send these requirements to GHC via a plugin, then have it evaluate the static ones at compile time, and generate code to check the dynamic ones. Finally, the plugin would add new code to the beginning of main that will invoke a configurable function with the results of the requirement check (hard-coding the static ones, and evaluating dynamic ones on the fly). (In the CodeWorld environment, this function would display the checklist in the web UI, for example.) > > Has anyone done anything like this before? Any wisdom to share, or ideas to contribute? > > Thanks, > Chris > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From olf at aatal-apotheke.de Wed Nov 21 21:01:08 2018 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Wed, 21 Nov 2018 22:01:08 +0100 Subject: [Haskell-cafe] static analysis of a C-like language Message-ID: <1E63A5AE-1463-4C52-85C6-05C015C18E6E@aatal-apotheke.de> Dear Cafe, I want to build a linter for a C-like language. My company uses a UI system that comes with a C-like language that is used to provide functionality to the UI elements. The language is interpreted at runtime. The user, however, has no access to the built-in parser and checking functions. Only a basic syntax check comes with their editor. Therefore many stupid mistakes only show at runtime and can not be tested for statically. The language is in many respects even simpler than C. No structs, no enumerations, only a handful of basic data types and arrays thereof, plus pointers and the usual control flow structures. On the other hand, there are some features that make static analysis near impossible, e.g. the possibility of dynamic registration of variables. Higher-order types are emulated by passing the name of other functions as strings. There is explicit referencing of other sources (#include statements) as well as implicit referencing within UI elements and within the project hierarchy. We want to catch basic programming mistakes - misspelled variables, missing return statements, usage of variables before assignment, wrong number of function arguments/types. A project's code is scattered across multiple files and layers - a function declaration can mask a declaration from the layer below. Therefore, a per-file-linter will not suffice. As a side-effect this may also yield a documentation generator (boy do I miss haddock while working with that), which is also missing in the system. I have never done something like this and will seek help from local CS departments (If you are a CS student in Paderborn or Bielefeld, Germany, get in touch!). My company would be willing to sponsor a Bachelor or Master's thesis project. Ultimately this will be comercialized as an add-on, so anyone who helps will also profit from the result financially. The user community is not large, but includes big names such as Siemens, London Heathrow, the Metros in NYC and Bilbao, and CERN. What kind of expertise shall I look for? Compiler theorists? What information shall I request from the language author? I feel that Haskell might be a good language to represent the AST in. But I am overwhelmed by the numerous AST libraries on hackage. How similar is my problem to what is covered by, say, haskell-src-exts, hlint, alex or syntactic? Can I re-use code from these projects? What solutions are out there for dependency resolution between source files? I suppose for informative error messages I need to decorate each semantic bit with information about - source file and location - what is in scope at that position, plus the source of the symbols in scope What data structures can be used to build and represent this information? Any pointers welcome. Olaf From holgersiegel74 at yahoo.de Thu Nov 22 13:21:38 2018 From: holgersiegel74 at yahoo.de (Holger Siegel) Date: Thu, 22 Nov 2018 14:21:38 +0100 Subject: [Haskell-cafe] static analysis of a C-like language In-Reply-To: <1E63A5AE-1463-4C52-85C6-05C015C18E6E@aatal-apotheke.de> References: <1E63A5AE-1463-4C52-85C6-05C015C18E6E@aatal-apotheke.de> Message-ID: <278a8448-b577-cdfb-51a7-1bcb8dd81dcf@yahoo.de> Hello Olaf, to me that sounds as if you want to do an abstract interpretation with a forward collecting semantics that employs non-relational abstract domains for the primitive data types and summarizes the dimensions of arrays. That is what the Java compiler does when it analyzes whether a variable is 'effectively final' (except that it doesn't even have to summarize arrays for that), and it should suffice for the kind of bugs you want to find. I would start by writing a simple interpreter for the language to be analyzed. That way you fix messy details before they bite you, e.g. the order in which submodules are loaded and initialized. You also get a clear formalization of the semantics, and you can annotate the syntax tree and implement informative error messages for the bugs you want to detect. You don't even need to implement every primitive function - it suffices that they return some random value, provided that the intended return value is one of the possible values. Lifting the interpreter to an abstract interpreter can then be done in a canonical way. Regards, Holger Am 21.11.2018 um 22:01 schrieb Olaf Klinke: > Dear Cafe, > > I want to build a linter for a C-like language. My company uses a UI system that comes with a C-like language that is used to provide functionality to the UI elements. The language is interpreted at runtime. The user, however, has no access to the built-in parser and checking functions. Only a basic syntax check comes with their editor. Therefore many stupid mistakes only show at runtime and can not be tested for statically. > The language is in many respects even simpler than C. No structs, no enumerations, only a handful of basic data types and arrays thereof, plus pointers and the usual control flow structures. On the other hand, there are some features that make static analysis near impossible, e.g. the possibility of dynamic registration of variables. Higher-order types are emulated by passing the name of other functions as strings. There is explicit referencing of other sources (#include statements) as well as implicit referencing within UI elements and within the project hierarchy. > > We want to catch basic programming mistakes - misspelled variables, missing return statements, usage of variables before assignment, wrong number of function arguments/types. A project's code is scattered across multiple files and layers - a function declaration can mask a declaration from the layer below. Therefore, a per-file-linter will not suffice. > As a side-effect this may also yield a documentation generator (boy do I miss haddock while working with that), which is also missing in the system. > > I have never done something like this and will seek help from local CS departments (If you are a CS student in Paderborn or Bielefeld, Germany, get in touch!). My company would be willing to sponsor a Bachelor or Master's thesis project. Ultimately this will be comercialized as an add-on, so anyone who helps will also profit from the result financially. The user community is not large, but includes big names such as Siemens, London Heathrow, the Metros in NYC and Bilbao, and CERN. > > What kind of expertise shall I look for? Compiler theorists? What information shall I request from the language author? I feel that Haskell might be a good language to represent the AST in. But I am overwhelmed by the numerous AST libraries on hackage. > > How similar is my problem to what is covered by, say, haskell-src-exts, hlint, alex or syntactic? Can I re-use code from these projects? > > What solutions are out there for dependency resolution between source files? > > I suppose for informative error messages I need to decorate each semantic bit with information about > - source file and location > - what is in scope at that position, plus the source of the symbols in scope > What data structures can be used to build and represent this information? > > Any pointers welcome. > Olaf > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From siddu.druid at gmail.com Thu Nov 22 13:26:38 2018 From: siddu.druid at gmail.com (Siddharth Bhat) Date: Thu, 22 Nov 2018 18:56:38 +0530 Subject: [Haskell-cafe] static analysis of a C-like language In-Reply-To: <278a8448-b577-cdfb-51a7-1bcb8dd81dcf@yahoo.de> References: <1E63A5AE-1463-4C52-85C6-05C015C18E6E@aatal-apotheke.de> <278a8448-b577-cdfb-51a7-1bcb8dd81dcf@yahoo.de> Message-ID: What is the canonical way to lift an interpreter to an abstract interpreter, while ensuring convergence ---figuring out how and when to widen? Thanks Siddharth On Thu, 22 Nov, 2018, 18:52 Holger Siegel via Haskell-Cafe, < haskell-cafe at haskell.org> wrote: > Hello Olaf, > > to me that sounds as if you want to do an abstract interpretation with a > forward collecting semantics that employs non-relational abstract > domains for the primitive data types and summarizes the dimensions of > arrays. That is what the Java compiler does when it analyzes whether a > variable is 'effectively final' (except that it doesn't even have to > summarize arrays for that), and it should suffice for the kind of bugs > you want to find. > > I would start by writing a simple interpreter for the language to be > analyzed. That way you fix messy details before they bite you, e.g. the > order in which submodules are loaded and initialized. You also get a > clear formalization of the semantics, and you can annotate the syntax > tree and implement informative error messages for the bugs you want to > detect. You don't even need to implement every primitive function - it > suffices that they return some random value, provided that the intended > return value is one of the possible values. Lifting the interpreter to > an abstract interpreter can then be done in a canonical way. > > > Regards, > > Holger > > > Am 21.11.2018 um 22:01 schrieb Olaf Klinke: > > Dear Cafe, > > > > I want to build a linter for a C-like language. My company uses a UI > system that comes with a C-like language that is used to provide > functionality to the UI elements. The language is interpreted at runtime. > The user, however, has no access to the built-in parser and checking > functions. Only a basic syntax check comes with their editor. Therefore > many stupid mistakes only show at runtime and can not be tested for > statically. > > The language is in many respects even simpler than C. No structs, no > enumerations, only a handful of basic data types and arrays thereof, plus > pointers and the usual control flow structures. On the other hand, there > are some features that make static analysis near impossible, e.g. the > possibility of dynamic registration of variables. Higher-order types are > emulated by passing the name of other functions as strings. There is > explicit referencing of other sources (#include statements) as well as > implicit referencing within UI elements and within the project hierarchy. > > > > We want to catch basic programming mistakes - misspelled variables, > missing return statements, usage of variables before assignment, wrong > number of function arguments/types. A project's code is scattered across > multiple files and layers - a function declaration can mask a declaration > from the layer below. Therefore, a per-file-linter will not suffice. > > As a side-effect this may also yield a documentation generator (boy do I > miss haddock while working with that), which is also missing in the system. > > > > I have never done something like this and will seek help from local CS > departments (If you are a CS student in Paderborn or Bielefeld, Germany, > get in touch!). My company would be willing to sponsor a Bachelor or > Master's thesis project. Ultimately this will be comercialized as an > add-on, so anyone who helps will also profit from the result financially. > The user community is not large, but includes big names such as Siemens, > London Heathrow, the Metros in NYC and Bilbao, and CERN. > > > > What kind of expertise shall I look for? Compiler theorists? What > information shall I request from the language author? I feel that Haskell > might be a good language to represent the AST in. But I am overwhelmed by > the numerous AST libraries on hackage. > > > > How similar is my problem to what is covered by, say, haskell-src-exts, > hlint, alex or syntactic? Can I re-use code from these projects? > > > > What solutions are out there for dependency resolution between source > files? > > > > I suppose for informative error messages I need to decorate each > semantic bit with information about > > - source file and location > > - what is in scope at that position, plus the source of the symbols in > scope > > What data structures can be used to build and represent this information? > > > > Any pointers welcome. > > Olaf > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Sending this from my phone, please excuse any typos! -------------- next part -------------- An HTML attachment was scrubbed... URL: From holgersiegel74 at yahoo.de Thu Nov 22 13:55:40 2018 From: holgersiegel74 at yahoo.de (Holger Siegel) Date: Thu, 22 Nov 2018 14:55:40 +0100 Subject: [Haskell-cafe] static analysis of a C-like language In-Reply-To: References: <1E63A5AE-1463-4C52-85C6-05C015C18E6E@aatal-apotheke.de> <278a8448-b577-cdfb-51a7-1bcb8dd81dcf@yahoo.de> Message-ID: <23eea6e0-0f46-e2e0-5829-b72993cbd0fe@yahoo.de> Hello Siddharth, Am 22.11.2018 um 14:26 schrieb Siddharth Bhat: > What is the canonical way to lift an interpreter to an abstract > interpreter, while ensuring convergence ---figuring out how and when > to widen? Yes, exactly. In case of Olaf's imperative language with control structures that would be the entry point of while-loops. Potentially recursive function calls also have to be considered when you move from a per-function analysis to interprocedural analysis. Regards, Holger From ducis_cn at 126.com Fri Nov 23 06:11:29 2018 From: ducis_cn at 126.com (ducis) Date: Fri, 23 Nov 2018 14:11:29 +0800 (CST) Subject: [Haskell-cafe] Is there some way to hack the type system without recompiling GHC? In-Reply-To: References: Message-ID: <1f63bb89.56d5.1673f31d568.Coremail.ducis_cn@126.com> We know that the type system is now a second language where you spec formal requirements and let the compiler solve it, kinda like logic programming. But sometimes I knew something is correct or at least willing to take the risk of runtime errors, but the typechecker is not (yet) able to figure it out. In this case is it possible to somehow insert (regular haskell) code into the typechecker and force the compiler to think some values are of some types, rather than waiting for or inventing some formally correct solution, which may be fundamentally very difficult? -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Fri Nov 23 06:25:14 2018 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 23 Nov 2018 06:25:14 +0000 Subject: [Haskell-cafe] Is there some way to hack the type system without recompiling GHC? In-Reply-To: <1f63bb89.56d5.1673f31d568.Coremail.ducis_cn@126.com> References: <1f63bb89.56d5.1673f31d568.Coremail.ducis_cn@126.com> Message-ID: <20181123062513.pjwztyjeainllz5a@weber> On Fri, Nov 23, 2018 at 02:11:29PM +0800, ducis wrote: > In this case is it possible to somehow insert (regular haskell) code into > the typechecker Are you looking for GHC plugins? https://downloads.haskell.org/~ghc/8.6.2/docs/html/users_guide/extending_ghc.html#compiler-plugins From danburton.email at gmail.com Sat Nov 24 06:23:18 2018 From: danburton.email at gmail.com (Dan Burton) Date: Fri, 23 Nov 2018 23:23:18 -0700 Subject: [Haskell-cafe] Is there some way to hack the type system without recompiling GHC? In-Reply-To: <1f63bb89.56d5.1673f31d568.Coremail.ducis_cn@126.com> References: <1f63bb89.56d5.1673f31d568.Coremail.ducis_cn@126.com> Message-ID: "force the compiler to think some values are of some types" Sounds like a job for unsafeCoerce. On Thu, Nov 22, 2018, 23:12 ducis We know that the type system is now a second language where you spec > formal requirements and let the compiler solve it, kinda like logic > programming. > But sometimes I knew something is correct or at least willing to take the > risk of runtime errors, but the typechecker is not (yet) able to figure it > out. > In this case is it possible to somehow insert (regular haskell) code into > the typechecker and force the compiler to think some values are of some > types, > rather than waiting for or inventing some formally correct solution, which > may be fundamentally very difficult? > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From marc at lamarciana.com Sat Nov 24 07:59:17 2018 From: marc at lamarciana.com (=?ISO-8859-15?Q?Marc_Busqu=E9?=) Date: Sat, 24 Nov 2018 08:59:17 +0100 (CET) Subject: [Haskell-cafe] Help with DataKinds example In-Reply-To: References: Message-ID: Thank you very much for this dedicated explanation, Frank. With your last example, where you are tagging the `RealUser` type with a type of `UserKind`, I have come to appreciate the usefulness of `DataKinds`. And it is really nice. However, I still don't understand the example without those final changes. I copy it again here for more context: ``` {-# LANGUAGE DataKinds #-} import Data.Proxy data UserKind = User | Admin data RealUser = RealUser { userAdminToken :: Maybe (Proxy 'Admin) } doSensitiveThings :: Proxy 'Admin -> IO () doSensitiveThings = undefined ``` How am I supposed to call here `doSensitiveThings`? I need to provide it a value of type `Proxy 'Admin`, but, as fas as I know, promoted data constructors (`'Admin` here) are uninhabited. Thanks, Marc Busqué http://waiting-for-dev.github.io/about/ On Mon, 19 Nov 2018, Frank Staals wrote: > Marc Busqué writes: > >> I'm reading Sandy Maguire book Thinking with Types, and I'm stuck >> understanding an example about `DataKinds` language extension. >> >> In the book, it is said that it can be used to prevent at the type level >> that non admin users perform some action for which admin privileges are >> required. >> >> So, in the example, having `DataKinds` enabled, we define: >> >> ``` >> data UserType = User | Admin >> ``` >> >> Then, we change User type: >> >> ``` >> data User = User >> { userAdminToken :: Maybe (Proxy 'Admin) } >> ``` >> >> And then it is said that we can enforce that sensitive operations are >> performed by a user with the admin token: >> >> ``` >> doSensitiveThings :: Proxy 'Admin -> IO () >> ``` >> >> No other language extensions have been explained before in the book, and >> I simply don't understand how it is works... >> >> First, I guess that when writing `data User = ...` we are overriding >> `'User` promoted data constructor. Isn't it? > > The second 'User' type (and constructor) are both different from the 'User' > constructor in the UserType type. It may be clearer if we slightly > rename these types and the constructors a bit to something like: > > ``` > {-# LANGUAGE DataKinds #-} > > import Data.Proxy > > data UserKind = User | Admin > > data RealUser = RealUser { userAdminToken :: Maybe (Proxy 'Admin) } > > doSensitiveThings :: Proxy 'Admin -> IO () > doSensitiveThings = undefined > ``` > >> Also, I don't understand how I could define a type `Proxy 'Admin`. If >> I'm not wrong, `Proxy` should have the kind `UserType -> *`, but I >> don't know how to do that. > > You can define it like: > > data Proxy (a :: k) = Proxy > > but that requires the {-# LANGUAGE PolyKinds #-} language extension > >> Besides that, I would like some guidance in the general idea of the >> example, because I'm quite puzzled :) > > The idea is that to restrict the type of the 'doSensitiveThings' > function so that you can only call it if you have "admin powers". To > prove that you have those admin powers you have to pass it a value of > type 'Proxy Admin'. > > Let me maybe adapt the example slightly again to make things clearer: > > ``` > {-# LANGUAGE DataKinds #-} > {-# LANGUAGE PolyKinds #-} > data UserKind = User | Admin > > data RealUser (uk :: UserKind) = RealUser { userName :: String } > > root :: RealUser 'Admin > root = RealUser "root" > > frank :: RealUser 'User > frank = RealUser "frank" > > doSensitiveThings :: RealUser 'Admin -> IO () > doSensitiveThings _ = print "installing packages now ... " > > -- | this compiles fine: > testAllowed = doSensitiveThings root > > > -- | This gives a type error: > testNotAllowed = doSensitiveThings frank > -- • Couldn't match type ‘'User’ with ‘'Admin’ > -- Expected type: RealUser 'Admin > -- Actual type: RealUser 'User > -- • In the first argument of ‘doSensitiveThings’, namely ‘frank’ > -- In the expression: doSensitiveThings frank > -- In an equation for ‘testNotAllowed’: > -- testNotAllowed = doSensitiveThings frank > ``` > > In the above example, I've "tagged" the RealUser type with a type > variable that expresses if our user is a regular user or an Admin, and > our 'doSensitiveThings' function can only be called with Users that are > admins. > > I hope this helps > > -- > > - Frank > From javran.c at gmail.com Sat Nov 24 09:36:16 2018 From: javran.c at gmail.com (Javran Cheng) Date: Sat, 24 Nov 2018 01:36:16 -0800 Subject: [Haskell-cafe] Help with DataKinds example In-Reply-To: References: Message-ID: Hi Marc, You can try `doSensitiveThings (Proxy :: Proxy 'Admin)`, recall that we have `data Proxy (a :: k) = Proxy`, it does nothing on value level, but it effectively passes a type (in this case 'Admin) as an argument, I guess that's where the name "Proxy" comes from. Cheers, Javran On Fri, Nov 23, 2018 at 11:59 PM Marc Busqué wrote: > Thank you very much for this dedicated explanation, Frank. > > With your last example, where you are tagging the `RealUser` type with a > type of `UserKind`, I have come to appreciate the usefulness of > `DataKinds`. And it is really nice. > > However, I still don't understand the example without those final > changes. I copy it again here for more context: > > ``` > {-# LANGUAGE DataKinds #-} > > import Data.Proxy > > data UserKind = User | Admin > > data RealUser = RealUser { userAdminToken :: Maybe (Proxy 'Admin) } > > doSensitiveThings :: Proxy 'Admin -> IO () > doSensitiveThings = undefined > ``` > > How am I supposed to call here `doSensitiveThings`? I need to provide it > a value of type `Proxy 'Admin`, but, as fas as I know, promoted data > constructors (`'Admin` here) are uninhabited. > > Thanks, > > Marc Busqué > http://waiting-for-dev.github.io/about/ > > On Mon, 19 Nov 2018, Frank Staals wrote: > > > Marc Busqué writes: > > > >> I'm reading Sandy Maguire book Thinking with Types, and I'm stuck > >> understanding an example about `DataKinds` language extension. > >> > >> In the book, it is said that it can be used to prevent at the type level > >> that non admin users perform some action for which admin privileges are > >> required. > >> > >> So, in the example, having `DataKinds` enabled, we define: > >> > >> ``` > >> data UserType = User | Admin > >> ``` > >> > >> Then, we change User type: > >> > >> ``` > >> data User = User > >> { userAdminToken :: Maybe (Proxy 'Admin) } > >> ``` > >> > >> And then it is said that we can enforce that sensitive operations are > >> performed by a user with the admin token: > >> > >> ``` > >> doSensitiveThings :: Proxy 'Admin -> IO () > >> ``` > >> > >> No other language extensions have been explained before in the book, and > >> I simply don't understand how it is works... > >> > >> First, I guess that when writing `data User = ...` we are overriding > >> `'User` promoted data constructor. Isn't it? > > > > The second 'User' type (and constructor) are both different from the > 'User' > > constructor in the UserType type. It may be clearer if we slightly > > rename these types and the constructors a bit to something like: > > > > ``` > > {-# LANGUAGE DataKinds #-} > > > > import Data.Proxy > > > > data UserKind = User | Admin > > > > data RealUser = RealUser { userAdminToken :: Maybe (Proxy 'Admin) } > > > > doSensitiveThings :: Proxy 'Admin -> IO () > > doSensitiveThings = undefined > > ``` > > > >> Also, I don't understand how I could define a type `Proxy 'Admin`. If > >> I'm not wrong, `Proxy` should have the kind `UserType -> *`, but I > >> don't know how to do that. > > > > You can define it like: > > > > data Proxy (a :: k) = Proxy > > > > but that requires the {-# LANGUAGE PolyKinds #-} language extension > > > >> Besides that, I would like some guidance in the general idea of the > >> example, because I'm quite puzzled :) > > > > The idea is that to restrict the type of the 'doSensitiveThings' > > function so that you can only call it if you have "admin powers". To > > prove that you have those admin powers you have to pass it a value of > > type 'Proxy Admin'. > > > > Let me maybe adapt the example slightly again to make things clearer: > > > > ``` > > {-# LANGUAGE DataKinds #-} > > {-# LANGUAGE PolyKinds #-} > > data UserKind = User | Admin > > > > data RealUser (uk :: UserKind) = RealUser { userName :: String } > > > > root :: RealUser 'Admin > > root = RealUser "root" > > > > frank :: RealUser 'User > > frank = RealUser "frank" > > > > doSensitiveThings :: RealUser 'Admin -> IO () > > doSensitiveThings _ = print "installing packages now ... " > > > > -- | this compiles fine: > > testAllowed = doSensitiveThings root > > > > > > -- | This gives a type error: > > testNotAllowed = doSensitiveThings frank > > -- • Couldn't match type ‘'User’ with ‘'Admin’ > > -- Expected type: RealUser 'Admin > > -- Actual type: RealUser 'User > > -- • In the first argument of ‘doSensitiveThings’, namely ‘frank’ > > -- In the expression: doSensitiveThings frank > > -- In an equation for ‘testNotAllowed’: > > -- testNotAllowed = doSensitiveThings frank > > ``` > > > > In the above example, I've "tagged" the RealUser type with a type > > variable that expresses if our user is a regular user or an Admin, and > > our 'doSensitiveThings' function can only be called with Users that are > > admins. > > > > I hope this helps > > > > -- > > > > - Frank > >_______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Javran (Fang) Cheng -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexandrfedorov at gmail.com Mon Nov 26 14:02:21 2018 From: alexandrfedorov at gmail.com (Alexandr Fedorov) Date: Mon, 26 Nov 2018 18:02:21 +0400 Subject: [Haskell-cafe] Taking over a package bindings-librrd Message-ID: Hello, this package looks abandoned and does not compile on the latest librrd library. Let me clarify this: if MasatakeDaimon can hear this letter, please add me to bindings-librrd maintainers list, i'd be more than happy to help and a taking over is not necessary, but if somehow he still doesn't show up, hackage administrator please consider either adding me as a maintainer, or let me take over this package. -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Mon Nov 26 20:37:10 2018 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Mon, 26 Nov 2018 21:37:10 +0100 Subject: [Haskell-cafe] static analysis of a C-like language Message-ID: > Hello Olaf, > > to me that sounds as if you want to do an abstract interpretation with a > forward collecting semantics that employs non-relational abstract > domains for the primitive data types and summarizes the dimensions of > arrays. ... > I would start by writing a simple interpreter for the language to be > analyzed. That way you fix messy details before they bite you, e.g. the > order in which submodules are loaded and initialized. I was hoping not having to write an interpreter (because the language author wrote a translation to C++ already), but if that is the way to go, I'll do it. As I understand it, the Haskell semantics should contain just enough substance so that the errors I am after will cause hiccups in the Haskell compiler? That is indeed a compelling approach. What this does not address is the question about error reporting: How could a translation to Haskell preserve information about scope, source position and masking? Can I leverage the ghc API for that? Regards, Olaf From carter.schonwald at gmail.com Tue Nov 27 00:13:38 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 26 Nov 2018 19:13:38 -0500 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: <20181119202651.GH4122@straasha.imrryr.org> References: <20181119202651.GH4122@straasha.imrryr.org> Message-ID: so one way to handle no allocation things playing nicely with the scheduler is to compile haskell code with -fno-omit-yields this will generate code which has scheduler yields even in loops which dont allocate cheers! -Carter On Mon, Nov 19, 2018 at 3:27 PM Viktor Dukhovni wrote: > On Mon, Nov 19, 2018 at 11:26:17AM -0800, Ryan Reich wrote: > > > I suppose my question concerns the more general question of how to create > > OS-managed threads in GHC. [...] > > I would have expected there to > > be a corresponding operation in GHC Haskell ("bound threads" seem not to > be > > it, as they are still scheduled by the RTS) but it does not appear that > > there is. Is this because of the need to keep the runtime unified? > > Because it seems strange that we are prevented from operating truly > > independent threads. > > I was just reading: > > https://cs.nyu.edu/~mwalfish/classes/14fa/ref/boehm05threads.pdf > > which may offer some insight. The runtime needs to be able to > provide a consistent memory model to threads. Just running something > in an OS thread that's managed by the RTS could make that difficult, > and it is not clear how that cooperates with garbage collection. > > But to your point, when adding threads to your example, I find that > the infinite loop then runs concurrently in all the threads, and > the timeout never happens. While: > > Replacing: let x = 0:x in last x > with: let ! x = 0 + x in x > > does make timeout work, so it is not entirely obvious which pure > computations can be timed out. > > -- > Viktor. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ramin.honary at cross-compass.com Tue Nov 27 07:45:37 2018 From: ramin.honary at cross-compass.com (Ramin Honary) Date: Tue, 27 Nov 2018 16:45:37 +0900 Subject: [Haskell-cafe] [Job] Cross Compass is currently hiring Haskell developers Message-ID: [Cross Compass](https://www.xcompass.com/en/) is a data science and machine learning consultancy located in Tokyo, Japan. Most of the work is focused on solving problems for clients by making creative use of their data. We currently have a small team of Haskellers working on a deep learning framework implemented in Haskell. We plan to use this framework multiple ways. For example, we have created a web platform for the manufacturing industry to make it easy to generate anomaly detection models for use in a factory. We are hiring Haskell programmers to help create this framework. We are mainly looking for people skilled in either web programming or machine learning. ### The ideal candidate would be similar to the following: - Passionate about functional programming, type-driven development, and modern artificial intelligence, especially deep learning. - Have experience with machine learning/deep learning, either professionally or academically. Be experienced with popular frameworks like Tensorflow, PyTorch, etc. - Have extensive Haskell experience. Be completely comfortable using (or learning) libraries like `lens`, `servant`, `singletons`, etc. Author of popular Haskell libraries. Worked on multiple large applications. - Have experience developing web apps using any of JavaScript, TypeScript, PureScript, Elm, GHCJS, and have created web apps using frameworks like Vue, Angular, React, Halogen, Reflex, or Miso. Ideally with a backend REST API implemented in Haskell. - Able to work full-time (40 hours a week) or **part-time** (20+ hours a week). - Willing to do freelance with us for a few weeks to make sure we are a good match for each other before becoming an permanent employee. - Able to work either on-site or **remote** - In the case of remote, you live in near Japan's timezone (UTC+9) and can fly to the office in Tokyo multiple times per year. (This requirement could be waived for strong candidates.) - Experience as a team-lead, chopping up and assigning tasks to less experienced Haskellers, reviewing PRs, etc. ## Flexible with job requirements We realize there are probably very few people that actually meet all these points. We are flexible, so please feel free to get in touch even if you don't think you meet our ideal requirements. It is possible for us to hire remotely, although we prefer people that are near Japan's timezone (UTC+9) and can fly to the office in Tokyo multiple times per year. We can also sponsor visas for people that want to move to Japan. As stated above, we are also open to applicants who want to do non-full-time work (20+ hours per week). Here are two examples of people we would love to talk to even though they don't meet all of the points above: ### Example 1: - Going to graduate school in Tokyo for machine learning. Very familiar with deep learning. - Beginning Haskeller. Have read through all of Haskell Programming From First Principles (and perhaps [Thinking with Types](https://leanpub.com/thinking-with-types)?), but has no experience working with large applications. - Able to come in to the office 20 to 25 hours a week. ### Example 2: - Living in Australia - Intimately familiar with Haskell, author of multiple popular libraries. - Very competent with web programming. - No experience with machine learning. - Multiple years of experience working remotely. - Able to work full-time. ## Some of the benefits of working at Cross Compass: - Work with passionate Haskellers. You may have seen us either here on [/r/haskell](https://www.reddit.com/r/haskell), or at conferences: - [Hideaki Kawai](https://github.com/kayhide) - [Viktor Kronvall](https://github.com/considerate) - [Ramin Honary](https://github.com/RaminHAL9001) - [Dennis Gosnell](https://functor.tokyo/) - We also work with [Tweag I/O](https://www.tweag.io). Their Haskellers are really top class. - Attend conferences like ICFP, Lambda Jam, etc. We each try to attend a couple conferences a year. - Training. We are planning to have the entire team take the [Guide to Haskell Performance and Optimization](https://www.well-typed.com/services_training_performance_and_optimization/) course from Well-Typed at some point. The lower end of the pay scale is 8 Million Yen (800万円) per year for full-time. I'm not sure what the higher end is. If this sounds interesting, please feel free to email us atrecruit-haskell at cross-compass.com, possibly with your resume and why you think we'd be good for each other. If you want to know more, we would love to take you out to lunch if you're located in Tokyo, or chat with you on Skype if not. -------------- next part -------------- An HTML attachment was scrubbed... URL: From leah at vuxu.org Tue Nov 27 13:11:56 2018 From: leah at vuxu.org (Leah Neukirchen) Date: Tue, 27 Nov 2018 14:11:56 +0100 Subject: [Haskell-cafe] Munich Haskell Meeting, 2018-11-28 @ 19:30 Message-ID: <87o9aapsv7.fsf@vuxu.org> Dear all, This week, our monthly Munich Haskell Meeting will take place again on Wednesday, November 28 at Cafe Puck at 19h30. For details see here: http://muenchen.haskell.bayern/dates.html If you plan to join, please add yourself to this dudle so we can reserve enough seats! It is OK to add yourself to the dudle anonymously or pseudonymously. https://dudle.inf.tu-dresden.de/haskell-munich-nov-2018/ Everybody is welcome! cu, -- Leah Neukirchen http://leah.zone From johannes.waldmann at htwk-leipzig.de Tue Nov 27 17:39:19 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 27 Nov 2018 18:39:19 +0100 Subject: [Haskell-cafe] how to cabal-install so that :doc works? Message-ID: <67d439a6-9e36-67af-7d9c-d344a857532c@htwk-leipzig.de> Dear Cafe - what do I have to put in my global .cabal/config in order to make ghci's new :doc command https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghci-cmd-:doc work after "cabal install "? I thought "documentation: True" should do it but I am invariably getting this: GHCi, version 8.6.2: http://www.haskell.org/ghc/ :? for help Prelude> import Ersatz Prelude Ersatz> :doc solveWith ghc: Can't find any documentation for Ersatz.Solver. This is probably because the module was compiled without '-haddock', but it's also possible that the module contains no documentation. I do have the .cabal/share/doc/x86_64-linux-ghc-8.6.2/ersatz-0.4.4/html directory. The :doc command seems to work for the libraries that come with ghc (documentation in /opt/ghc/ghc-8.6.2/share/doc/ghc-8.6.2/html/ ) - J.W. From carter.schonwald at gmail.com Tue Nov 27 17:47:18 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 27 Nov 2018 12:47:18 -0500 Subject: [Haskell-cafe] how to cabal-install so that :doc works? In-Reply-To: <67d439a6-9e36-67af-7d9c-d344a857532c@htwk-leipzig.de> References: <67d439a6-9e36-67af-7d9c-d344a857532c@htwk-leipzig.de> Message-ID: i always set documentation: True in my ~/.cabal/config file On Tue, Nov 27, 2018 at 12:40 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > Dear Cafe - > > what do I have to put in my global .cabal/config > in order to make ghci's new :doc command > > https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghci-cmd-:doc > work after "cabal install "? > > I thought "documentation: True" should do it > but I am invariably getting this: > > GHCi, version 8.6.2: http://www.haskell.org/ghc/ :? for help > Prelude> import Ersatz > Prelude Ersatz> :doc solveWith > ghc: Can't find any documentation for Ersatz.Solver. > This is probably because the module was compiled without '-haddock', > but it's also possible that the module contains no documentation. > > I do have the .cabal/share/doc/x86_64-linux-ghc-8.6.2/ersatz-0.4.4/html > directory. > > The :doc command seems to work for the libraries that come with ghc > (documentation in /opt/ghc/ghc-8.6.2/share/doc/ghc-8.6.2/html/ ) > > - J.W. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.jakobi at googlemail.com Tue Nov 27 19:13:28 2018 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Tue, 27 Nov 2018 20:13:28 +0100 Subject: [Haskell-cafe] how to cabal-install so that :doc works? In-Reply-To: <67d439a6-9e36-67af-7d9c-d344a857532c@htwk-leipzig.de> References: <67d439a6-9e36-67af-7d9c-d344a857532c@htwk-leipzig.de> Message-ID: Hi Johannes, adding ghc-options: -haddock in ~/.cabal/config works for me. Cheers, Simon Am Di., 27. Nov. 2018 um 18:39 Uhr schrieb Johannes Waldmann < johannes.waldmann at htwk-leipzig.de>: > Dear Cafe - > > what do I have to put in my global .cabal/config > in order to make ghci's new :doc command > > https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghci-cmd-:doc > work after "cabal install "? > > I thought "documentation: True" should do it > but I am invariably getting this: > > GHCi, version 8.6.2: http://www.haskell.org/ghc/ :? for help > Prelude> import Ersatz > Prelude Ersatz> :doc solveWith > ghc: Can't find any documentation for Ersatz.Solver. > This is probably because the module was compiled without '-haddock', > but it's also possible that the module contains no documentation. > > I do have the .cabal/share/doc/x86_64-linux-ghc-8.6.2/ersatz-0.4.4/html > directory. > > The :doc command seems to work for the libraries that come with ghc > (documentation in /opt/ghc/ghc-8.6.2/share/doc/ghc-8.6.2/html/ ) > > - J.W. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Tue Nov 27 19:23:12 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 27 Nov 2018 20:23:12 +0100 Subject: [Haskell-cafe] how to cabal-install so that :doc works? In-Reply-To: References: <67d439a6-9e36-67af-7d9c-d344a857532c@htwk-leipzig.de> Message-ID: >   ghc-options: -haddock > > in ~/.cabal/config works for me. confirmed working. Thanks! - J.W. From johannes.waldmann at htwk-leipzig.de Tue Nov 27 20:18:36 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 27 Nov 2018 21:18:36 +0100 Subject: [Haskell-cafe] haddock (on hackage/stackage) missing references to external libraries Message-ID: <8adfed6a-c7e9-7bc3-0bfc-201d0ed34d3a@htwk-leipzig.de> Dear Cafe, it seems that haddock (as used on hackage) does not link to identifiers from other packages (neither in HTML nor in hyperlinked source). This hurts, especially if a project has several packages that are meant to be used together, but are split for others reasons (modularity, maintenance). Example: This index has an entry for "bpf", with a non-linked module name Csound.Base: https://hackage.haskell.org/package/csound-expression-5.3.2/docs/doc-index-B.html The reason is (I think) that "bpf" is defined elsewhere, but re-exported, and "elsewhere" is in a different package. It is very hard to find the name of this package! (in this case, csound-expression-opcodes) Of course, in no way is this a complaint about Anton's csound-* project. I use it in teaching, and I wonder how could we make documentation more accessible - without extra manual work. Now, :doc of ghc-8.6 works, and :info helps somewhat: :info bpf ... -- Defined in ‘Csound.Typed.Opcode.SignalGenerators’ but it still does not show the name of the package. But at least we know the name of the module to look for. - J.W. From simon.jakobi at googlemail.com Tue Nov 27 20:51:51 2018 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Tue, 27 Nov 2018 21:51:51 +0100 Subject: [Haskell-cafe] haddock (on hackage/stackage) missing references to external libraries In-Reply-To: <8adfed6a-c7e9-7bc3-0bfc-201d0ed34d3a@htwk-leipzig.de> References: <8adfed6a-c7e9-7bc3-0bfc-201d0ed34d3a@htwk-leipzig.de> Message-ID: Hi Johannes, this is https://github.com/haskell/haddock/issues/682 I agree that it should be fixed. Cheers, Simon Am Di., 27. Nov. 2018 um 21:18 Uhr schrieb Johannes Waldmann < johannes.waldmann at htwk-leipzig.de>: > Dear Cafe, > > it seems that haddock (as used on hackage) > does not link to identifiers from other packages > (neither in HTML nor in hyperlinked source). > > This hurts, especially if a project has several packages > that are meant to be used together, but are split > for others reasons (modularity, maintenance). > > Example: This index has an entry for "bpf", > with a non-linked module name Csound.Base: > > https://hackage.haskell.org/package/csound-expression-5.3.2/docs/doc-index-B.html > > The reason is (I think) that "bpf" is defined elsewhere, > but re-exported, and "elsewhere" is in a different package. > > It is very hard to find the name of this package! > (in this case, csound-expression-opcodes) > > Of course, in no way is this a complaint about Anton's > csound-* project. I use it in teaching, and I wonder > how could we make documentation more accessible - > without extra manual work. > > Now, :doc of ghc-8.6 works, and :info helps somewhat: > :info bpf ... > -- Defined in ‘Csound.Typed.Opcode.SignalGenerators’ > but it still does not show the name of the package. > But at least we know the name of the module to look for. > > - J.W. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists0 at freea2a.de Tue Nov 27 22:21:55 2018 From: lists0 at freea2a.de (Puck) Date: Tue, 27 Nov 2018 23:21:55 +0100 Subject: [Haskell-cafe] XText vs DSL in Haskell in mission critical software Message-ID: <20181127232155.663fd651@duin.fritz.box> Hello all, how can I convince my bosses to use existing functional languages for specifying the future embedded softwares from the company instead of using Xtext or other things that firm under the name "model driven development". The softwares are mission critical. A local cooperation is already building an research institute with the goal of "model driven development". Why they do not use plain Haskell, LiquidHaskell and Coq? Neither can I imagine, that Haskell or Coq is so hard to learn, neither can I imagine that they want the developers to dive through handwritten Java extensions for their tool, that can only be analyzed with Java-tools and cannot be proven. Is XText, for example, really so good? Is a Haskell-DSL as a counterpart, not very much fewer dependent on other things, and very much easier to maintain? Thanks for suggestions and arguments Puck From johannes.waldmann at htwk-leipzig.de Tue Nov 27 22:51:29 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 27 Nov 2018 23:51:29 +0100 Subject: [Haskell-cafe] haddock (on hackage/stackage) missing references to external libraries In-Reply-To: References: <8adfed6a-c7e9-7bc3-0bfc-201d0ed34d3a@htwk-leipzig.de> Message-ID: > this is https://github.com/haskell/haddock/issues/682 also https://github.com/haskell/haddock/issues/496 (missing refs in hyperlinked source) - J.W. From johannes.waldmann at htwk-leipzig.de Tue Nov 27 23:21:14 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Wed, 28 Nov 2018 00:21:14 +0100 Subject: [Haskell-cafe] XText vs DSL in Haskell in mission critical software Message-ID: <9d8f9da5-7540-7cc3-e50e-1726051131f1@htwk-leipzig.de> > how can I convince my bosses to use existing functional languages You don't. Instead you have a coffee and read about bosses and software at dilbert.com and hackernews. While the browser refreshes the page, you write a compiler from xtext (or whatever the current buzzword is) to Haskell and back. - J.W. From jo at durchholz.org Wed Nov 28 06:05:41 2018 From: jo at durchholz.org (Joachim Durchholz) Date: Wed, 28 Nov 2018 07:05:41 +0100 Subject: [Haskell-cafe] XText vs DSL in Haskell in mission critical software In-Reply-To: <20181127232155.663fd651@duin.fritz.box> References: <20181127232155.663fd651@duin.fritz.box> Message-ID: <6a09dd22-ad21-dfc4-0a22-ed1a25422946@durchholz.org> Am 27.11.18 um 23:21 schrieb Puck: > Hello all, > > how can I convince my bosses to use existing functional languages for > specifying the future embedded softwares from the company instead of > using Xtext or other things that firm under the name "model driven > development". "Model-driven" is actually fine. It's not defined by tools but by the approach. BTW Xtext is a toolchain for creating a DSL parser. It can be used for model-driven development, in the same sense that a coding toolchain can be used for model-driven development. So I suspect various people misunderstood what "model-driven" actually means. > how can I convince my bosses You do NOT try to convince them unless you already have a standing of providing feedback that they consider useful. Without that, you'd have a hard time convincing anybody, even over small things. You also do NOT try to convince them if they already have spent considerable time thinking about their approach; you'd be demanding that they throw away everything they already invested in the strategy. In that case, you simply take a look at what they're doing. You understand what constraints they are operating under, take these constraints seriously (otherwise they'll just dismiss your feedback as "interesting but irrelevant to the problems I'm currently solving"), and present your approach as helping them overcome limitations - which means you also need to understand the pros and cons of the toolchain that they are currently aiming for. > Why they do not use plain Haskell, LiquidHaskell and Coq? > Neither can I imagine, that Haskell or Coq is so hard to learn, neither > can I imagine that they want the developers to dive through handwritten > Java extensions for their tool, that can only be analyzed with > Java-tools and cannot be proven. You are underestimating the raw cost of learning a new ecosystem. Haskell - the language - is in fact easy to learn. Any experienced programmer can learn a programming language within a few weeks. Learning to use that language *competently* takes months, and learning it well enough to make architectural decision takes years. Integrating a new programmer into an existing project is hard enough. The consensus is that a new hire will be a net loss in the first six months: Contributes very little, but keeps colleagues off their own work because they have to explain stuff to him: Project conventions, architecture and details of the existing codebase, project goals (what's important and what isn't), procedures (git branching conventions, issue tracking, definition of Done, etc. etc. etc.) Learning a new language on top of all that means that a new programmer will take at least two years until she is productive. A programmer costs roughly 50% more than his wages, so even a cheap one at 60k/year will cost the company 200k and a delay of two years; if time to market is a consideration, that's an absolute killer. Oh, and two years means that some competitor will simply outpace your company, if such a competitor with an experienced team already exists. You *might* have a chance to argue against the language-experience barrier if they are 150% confident that the company project exists for longer than two years. They also need to be 150% confident that what you say is true. If you have hard, experience-backed proof that Haskell (or whatever) is giving them faster results, AND they will have to hire programmers anyway, AND you can tell them where to find Haskell programmers, then they will listen. If any of this isn't given: Don't damage your reputation by building an impression of a daydream who doesn't know what he's talking about. Use the experience as a learning opportunity. See what works and what doesn't. See what people can do and what they cannot do. One more thing: If Haskell is *that* much better than Xtext, you should be able to produce better results by coding the stuff in Haskell in your free time. If you succeed, you'll be able to prove that the alternate approach is better (but you should be very cautious about taking that proof to your bosses - by the time you can do that, they will have invested too much in their approach and would lose a lot of money if they switch). If you fail, you have learned something about what kinds of roadblock exist even with better tools. > Is XText, for example, really so good? > Is a Haskell-DSL as a counterpart, not very much fewer dependent on > other things, and very much easier to maintain? I don't think that anything Java-based is so much better than Haskell. However, Java has a great library ecosystem. It has been amazing me at what's available since Maven became a standard repository format; the latest amazement was what they delivered with Apache Kafka (I'm working in a company that processes millions of externally-provided records per day, where near-realtime is one of the important priorities; stuff like Kafka is what grabs our attention). And libraries are what makes an ecosystem viable. Language properties decide what kind of ecosystem starts to exist, but sometimes it's surprisingly trivial properties that have an impact. For Java, I think three decisions were crucial: The decision to have a universal binary format (the JVM bytecode) so compiler variation does not block code reuse (as it has happened in C++); the decision to use DNS domain names as library qualifiers so it's clear who's responsible for placing modules where in the namespace (this is an ongoing problem in almost all languages); the decision to have strict compatibility requirements on implementations, so the code will have identical semantics on all platforms (and they kept improving on that over the first ten years). I'm not sure how good Haskell is in these areas. I have seen some pretty impressive library work in Haskell, so it isn't bad, but the JVM ecosystem is really, really good. You may find that while you can solve problems faster in Haskell, less readymade solutions are available. Doesn't make Java any better, of course (the language itself is pretty meh, it's the Cobol of today: too limited and too verbose to be fun to work with); but the quality of the language itself is just one of several important factors for developer efficiacy. Just my 2c. Regards, Jo From alex at slab.org Wed Nov 28 08:28:59 2018 From: alex at slab.org (Alex McLean) Date: Wed, 28 Nov 2018 08:28:59 +0000 Subject: [Haskell-cafe] Tidal (musical pattern library) refactor - feedback appreciated Message-ID: https://slab.org/tidal-1-0-0-refactor/ -- blog: http://slab.org/ From alex at slab.org Wed Nov 28 08:30:52 2018 From: alex at slab.org (Alex McLean) Date: Wed, 28 Nov 2018 08:30:52 +0000 Subject: [Haskell-cafe] Tidal (musical pattern library) refactor - feedback appreciated References: Message-ID: Sorry for rudeness, I sent that early in error! But the subject and blog post says it all, I'd love some feedback from the Haskell community on the current state of tidalcycles: https://slab.org/tidal-1-0-0-refactor/ All criticism and feedback much appreciated. Best wishes alex On Wed, 28 Nov 2018 at 08:28, Alex McLean wrote: > > https://slab.org/tidal-1-0-0-refactor/ > > -- > blog: http://slab.org/ -- blog: http://slab.org/ From ryan.reich at gmail.com Wed Nov 28 17:39:01 2018 From: ryan.reich at gmail.com (Ryan Reich) Date: Wed, 28 Nov 2018 09:39:01 -0800 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: <20181119202651.GH4122@straasha.imrryr.org> Message-ID: Thanks for the suggestion, which Arjen made also. Unfortunately, it does not appear to help. See this simple program: -- Loop.hs import Control.Exception import System.Timeout main :: IO (Maybe Integer) main = timeout 100000 $ evaluate $ last $ repeat 0 -- end With either GHC invocation "stack exec ghc Loop[ -- -fno-omit-yields]", running ./Loop fails to terminate (it should do so in 0.1s). Based only on the very terse description of that flag in the User's Guide, and its name, I think the problem is simply that GHC doesn't normally *generate* yields in that loop, so there's nothing not to omit. On Mon, Nov 26, 2018 at 4:14 PM Carter Schonwald wrote: > so one way to handle no allocation things playing nicely with the > scheduler is to compile haskell code with -fno-omit-yields > > this will generate code which has scheduler yields even in loops which > dont allocate > > cheers! > -Carter > > On Mon, Nov 19, 2018 at 3:27 PM Viktor Dukhovni > wrote: > >> On Mon, Nov 19, 2018 at 11:26:17AM -0800, Ryan Reich wrote: >> >> > I suppose my question concerns the more general question of how to >> create >> > OS-managed threads in GHC. [...] >> > I would have expected there to >> > be a corresponding operation in GHC Haskell ("bound threads" seem not >> to be >> > it, as they are still scheduled by the RTS) but it does not appear that >> > there is. Is this because of the need to keep the runtime unified? >> > Because it seems strange that we are prevented from operating truly >> > independent threads. >> >> I was just reading: >> >> https://cs.nyu.edu/~mwalfish/classes/14fa/ref/boehm05threads.pdf >> >> which may offer some insight. The runtime needs to be able to >> provide a consistent memory model to threads. Just running something >> in an OS thread that's managed by the RTS could make that difficult, >> and it is not clear how that cooperates with garbage collection. >> >> But to your point, when adding threads to your example, I find that >> the infinite loop then runs concurrently in all the threads, and >> the timeout never happens. While: >> >> Replacing: let x = 0:x in last x >> with: let ! x = 0 + x in x >> >> does make timeout work, so it is not entirely obvious which pure >> computations can be timed out. >> >> -- >> Viktor. >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Thu Nov 29 01:10:21 2018 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Wed, 28 Nov 2018 20:10:21 -0500 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: <20181119202651.GH4122@straasha.imrryr.org> Message-ID: <20181129011021.GB4122@straasha.imrryr.org> On Wed, Nov 28, 2018 at 09:39:01AM -0800, Ryan Reich wrote: > Thanks for the suggestion, which Arjen made also. Unfortunately, it does > not appear to help. See this simple program: > > -- Loop.hs > import Control.Exception > import System.Timeout > > main :: IO (Maybe Integer) > main = timeout 100000 $ evaluate $ last $ repeat 0 > -- end > > With either GHC invocation "stack exec ghc Loop[ -- -fno-omit-yields]", > running ./Loop fails to terminate (it should do so in 0.1s). > > Based only on the very terse description of that flag in the User's Guide, > and its name, I think the problem is simply that GHC doesn't normally > *generate* yields in that loop, so there's nothing not to omit. It times out for me with GHC 8.4.4 on FreeBSD 11.2, and "ghc -O -fno-omit-yields" and does not time out with "ghc -O": $ cat /tmp/foo.hs import Control.Exception import System.Timeout main :: IO (Maybe Integer) main = timeout 1000000 $ evaluate $ last $ repeat 0 $ ghc -O -fno-omit-yields /tmp/foo.hs [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) [Optimisation flags changed] Linking /tmp/foo ... $ time /tmp/foo real 0m1.033s user 0m1.025s sys 0m0.008s $ rm /tmp/foo $ ghc -O /tmp/foo.hs [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) [Optimisation flags changed] Linking /tmp/foo ... $ time /tmp/foo ^C^C real 0m5.864s user 0m5.857s sys 0m0.000s On MacOS X with GHC 7.10.3, it does not time out either way. Perhaps some versions of GHC don't make the timeout possible. -- Viktor. From ryan.reich at gmail.com Thu Nov 29 02:40:20 2018 From: ryan.reich at gmail.com (Ryan Reich) Date: Wed, 28 Nov 2018 18:40:20 -0800 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: <20181129011021.GB4122@straasha.imrryr.org> References: <20181119202651.GH4122@straasha.imrryr.org> <20181129011021.GB4122@straasha.imrryr.org> Message-ID: I expected something like that. I'm all the way back in ghc-8.2.2, but I think what this really shows is that the flag is unreliable and version-dependent. Unfortunately there doesn't seem to be a precise specification of where yield points should appear, and therefore, where they might be not-omitted. On Wed, Nov 28, 2018, 17:10 Viktor Dukhovni On Wed, Nov 28, 2018 at 09:39:01AM -0800, Ryan Reich wrote: > > > Thanks for the suggestion, which Arjen made also. Unfortunately, it does > > not appear to help. See this simple program: > > > > -- Loop.hs > > import Control.Exception > > import System.Timeout > > > > main :: IO (Maybe Integer) > > main = timeout 100000 $ evaluate $ last $ repeat 0 > > -- end > > > > With either GHC invocation "stack exec ghc Loop[ -- -fno-omit-yields]", > > running ./Loop fails to terminate (it should do so in 0.1s). > > > > Based only on the very terse description of that flag in the User's > Guide, > > and its name, I think the problem is simply that GHC doesn't normally > > *generate* yields in that loop, so there's nothing not to omit. > > It times out for me with GHC 8.4.4 on FreeBSD 11.2, and "ghc -O > -fno-omit-yields" > and does not time out with "ghc -O": > > $ cat /tmp/foo.hs > import Control.Exception > import System.Timeout > > main :: IO (Maybe Integer) > main = timeout 1000000 $ evaluate $ last $ repeat 0 > > $ ghc -O -fno-omit-yields /tmp/foo.hs > [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) > [Optimisation flags changed] > Linking /tmp/foo ... > > $ time /tmp/foo > > real 0m1.033s > user 0m1.025s > sys 0m0.008s > > $ rm /tmp/foo > $ ghc -O /tmp/foo.hs > [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) > [Optimisation flags changed] > Linking /tmp/foo ... > > $ time /tmp/foo > ^C^C > > real 0m5.864s > user 0m5.857s > sys 0m0.000s > > On MacOS X with GHC 7.10.3, it does not time out either way. Perhaps > some versions of GHC don't make the timeout possible. > > -- > Viktor. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Thu Nov 29 10:15:49 2018 From: hesselink at gmail.com (Erik Hesselink) Date: Thu, 29 Nov 2018 11:15:49 +0100 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: <20181119202651.GH4122@straasha.imrryr.org> <20181129011021.GB4122@straasha.imrryr.org> Message-ID: Hi Ryan, I'm not quite sure of your use case, but lambdabot/mueval do something like this I think. From a brief look at the source [1] it seems they compute in a separate thread, then in another thread, wait until the timeout then kill the computation thread. Would something like that work for you? Erik [1] https://github.com/gwern/mueval/blob/09b6a7aa5a25c4115442ea2e6ae0c2db557007f8/Mueval/Parallel.hs On Thu, 29 Nov 2018 at 03:41, Ryan Reich wrote: > I expected something like that. I'm all the way back in ghc-8.2.2, but I > think what this really shows is that the flag is unreliable and > version-dependent. Unfortunately there doesn't seem to be a precise > specification of where yield points should appear, and therefore, where > they might be not-omitted. > > On Wed, Nov 28, 2018, 17:10 Viktor Dukhovni >> On Wed, Nov 28, 2018 at 09:39:01AM -0800, Ryan Reich wrote: >> >> > Thanks for the suggestion, which Arjen made also. Unfortunately, it >> does >> > not appear to help. See this simple program: >> > >> > -- Loop.hs >> > import Control.Exception >> > import System.Timeout >> > >> > main :: IO (Maybe Integer) >> > main = timeout 100000 $ evaluate $ last $ repeat 0 >> > -- end >> > >> > With either GHC invocation "stack exec ghc Loop[ -- -fno-omit-yields]", >> > running ./Loop fails to terminate (it should do so in 0.1s). >> > >> > Based only on the very terse description of that flag in the User's >> Guide, >> > and its name, I think the problem is simply that GHC doesn't normally >> > *generate* yields in that loop, so there's nothing not to omit. >> >> It times out for me with GHC 8.4.4 on FreeBSD 11.2, and "ghc -O >> -fno-omit-yields" >> and does not time out with "ghc -O": >> >> $ cat /tmp/foo.hs >> import Control.Exception >> import System.Timeout >> >> main :: IO (Maybe Integer) >> main = timeout 1000000 $ evaluate $ last $ repeat 0 >> >> $ ghc -O -fno-omit-yields /tmp/foo.hs >> [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) >> [Optimisation flags changed] >> Linking /tmp/foo ... >> >> $ time /tmp/foo >> >> real 0m1.033s >> user 0m1.025s >> sys 0m0.008s >> >> $ rm /tmp/foo >> $ ghc -O /tmp/foo.hs >> [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) >> [Optimisation flags changed] >> Linking /tmp/foo ... >> >> $ time /tmp/foo >> ^C^C >> >> real 0m5.864s >> user 0m5.857s >> sys 0m0.000s >> >> On MacOS X with GHC 7.10.3, it does not time out either way. Perhaps >> some versions of GHC don't make the timeout possible. >> >> -- >> Viktor. >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Nov 29 14:24:50 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 29 Nov 2018 09:24:50 -0500 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: <20181119202651.GH4122@straasha.imrryr.org> <20181129011021.GB4122@straasha.imrryr.org> Message-ID: Yeah that’s probably a better approach. On Thu, Nov 29, 2018 at 5:16 AM Erik Hesselink wrote: > Hi Ryan, > > I'm not quite sure of your use case, but lambdabot/mueval do something > like this I think. From a brief look at the source [1] it seems they > compute in a separate thread, then in another thread, wait until the > timeout then kill the computation thread. Would something like that work > for you? > > Erik > > [1] > https://github.com/gwern/mueval/blob/09b6a7aa5a25c4115442ea2e6ae0c2db557007f8/Mueval/Parallel.hs > > On Thu, 29 Nov 2018 at 03:41, Ryan Reich wrote: > >> I expected something like that. I'm all the way back in ghc-8.2.2, but I >> think what this really shows is that the flag is unreliable and >> version-dependent. Unfortunately there doesn't seem to be a precise >> specification of where yield points should appear, and therefore, where >> they might be not-omitted. >> >> On Wed, Nov 28, 2018, 17:10 Viktor Dukhovni > wrote: >> >>> On Wed, Nov 28, 2018 at 09:39:01AM -0800, Ryan Reich wrote: >>> >>> > Thanks for the suggestion, which Arjen made also. Unfortunately, it >>> does >>> > not appear to help. See this simple program: >>> > >>> > -- Loop.hs >>> > import Control.Exception >>> > import System.Timeout >>> > >>> > main :: IO (Maybe Integer) >>> > main = timeout 100000 $ evaluate $ last $ repeat 0 >>> > -- end >>> > >>> > With either GHC invocation "stack exec ghc Loop[ -- -fno-omit-yields]", >>> > running ./Loop fails to terminate (it should do so in 0.1s). >>> > >>> > Based only on the very terse description of that flag in the User's >>> Guide, >>> > and its name, I think the problem is simply that GHC doesn't normally >>> > *generate* yields in that loop, so there's nothing not to omit. >>> >>> It times out for me with GHC 8.4.4 on FreeBSD 11.2, and "ghc -O >>> -fno-omit-yields" >>> and does not time out with "ghc -O": >>> >>> $ cat /tmp/foo.hs >>> import Control.Exception >>> import System.Timeout >>> >>> main :: IO (Maybe Integer) >>> main = timeout 1000000 $ evaluate $ last $ repeat 0 >>> >>> $ ghc -O -fno-omit-yields /tmp/foo.hs >>> [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) >>> [Optimisation flags changed] >>> Linking /tmp/foo ... >>> >>> $ time /tmp/foo >>> >>> real 0m1.033s >>> user 0m1.025s >>> sys 0m0.008s >>> >>> $ rm /tmp/foo >>> $ ghc -O /tmp/foo.hs >>> [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) >>> [Optimisation flags changed] >>> Linking /tmp/foo ... >>> >>> $ time /tmp/foo >>> ^C^C >>> >>> real 0m5.864s >>> user 0m5.857s >>> sys 0m0.000s >>> >>> On MacOS X with GHC 7.10.3, it does not time out either way. Perhaps >>> some versions of GHC don't make the timeout possible. >>> >>> -- >>> Viktor. >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Nov 29 14:26:20 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 29 Nov 2018 09:26:20 -0500 Subject: [Haskell-cafe] Is there some way to hack the type system without recompiling GHC? In-Reply-To: References: <1f63bb89.56d5.1673f31d568.Coremail.ducis_cn@126.com> Message-ID: Which is safe as long as the GC ETC still can walk it correctly! And that you’re not rereferencing an Int as a list of A :) On Sat, Nov 24, 2018 at 1:24 AM Dan Burton wrote: > "force the compiler to think some values are of some types" > > Sounds like a job for unsafeCoerce. > > > On Thu, Nov 22, 2018, 23:12 ducis >> We know that the type system is now a second language where you spec >> formal requirements and let the compiler solve it, kinda like logic >> programming. >> But sometimes I knew something is correct or at least willing to take the >> risk of runtime errors, but the typechecker is not (yet) able to figure it >> out. >> In this case is it possible to somehow insert (regular haskell) code into >> the typechecker and force the compiler to think some values are of some >> types, >> rather than waiting for or inventing some formally correct solution, >> which may be fundamentally very difficult? >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ian at zenhack.net Thu Nov 29 14:28:43 2018 From: ian at zenhack.net (Ian Denhardt) Date: Thu, 29 Nov 2018 09:28:43 -0500 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: <20181119202651.GH4122@straasha.imrryr.org> <20181129011021.GB4122@straasha.imrryr.org> Message-ID: <154350172391.841.8211327085580435976@localhost> That should have the same problem; the exceptions can't be delivered until the target thread reaches a yield. 'timeout' uses the same underlying mechanism. Obvious worrisome question: is it possible to use this to DoS lambdabot/mueval? Quoting Erik Hesselink (2018-11-29 05:15:49) > Hi Ryan, > I'm not quite sure of your use case, but lambdabot/mueval do something > like this I think. From a brief look at the source [1] it seems they > compute in a separate thread, then in another thread, wait until the > timeout then kill the computation thread. Would something like that > work for you? > Erik > [1] > [1]https://github.com/gwern/mueval/blob/09b6a7aa5a25c4115442ea2e6ae0c2d > b557007f8/Mueval/Parallel.hs > > On Thu, 29 Nov 2018 at 03:41, Ryan Reich <[2]ryan.reich at gmail.com> > wrote: > > I expected something like that. I'm all the way back in ghc-8.2.2, but > I think what this really shows is that the flag is unreliable and > version-dependent. Unfortunately there doesn't seem to be a precise > specification of where yield points should appear, and therefore, where > they might be not-omitted. > > On Wed, Nov 28, 2018, 17:10 Viktor Dukhovni <[3]ietf-dane at dukhovni.org > wrote: > > On Wed, Nov 28, 2018 at 09:39:01AM -0800, Ryan Reich wrote: > > Thanks for the suggestion, which Arjen made also.� Unfortunately, > it does > > not appear to help.� See this simple program: > > > > -- Loop.hs > > import Control.Exception > > import System.Timeout > > > > main :: IO (Maybe Integer) > > main = timeout 100000 $ evaluate $ last $ repeat 0 > > -- end > > > > With either GHC invocation "stack exec ghc Loop[ -- > -fno-omit-yields]", > > running ./Loop fails to terminate (it should do so in 0.1s). > > > > Based only on the very terse description of that flag in the > User's Guide, > > and its name, I think the problem is simply that GHC doesn't > normally > > *generate* yields in that loop, so there's nothing not to omit. > It times out for me with GHC 8.4.4 on FreeBSD 11.2, and "ghc -O > -fno-omit-yields" > and does� not time out with "ghc -O": > � � $ cat /tmp/foo.hs > � � import Control.Exception > � � import System.Timeout > � � main :: IO (Maybe Integer) > � � main = timeout 1000000 $ evaluate $ last $ repeat 0 > � � $ ghc -O -fno-omit-yields /tmp/foo.hs > � � [1 of 1] Compiling Main� � � � � � � ( /tmp/foo.hs, > /tmp/foo.o ) [Optimisation flags changed] > � � Linking /tmp/foo ... > � � $ time /tmp/foo > � � real� � 0m1.033s > � � user� � 0m1.025s > � � sys� � � 0m0.008s > � � $ rm /tmp/foo > � � $ ghc -O /tmp/foo.hs > � � [1 of 1] Compiling Main� � � � � � � ( /tmp/foo.hs, > /tmp/foo.o ) [Optimisation flags changed] > � � Linking /tmp/foo ... > � � $ time /tmp/foo > � � ^C^C > � � real� � 0m5.864s > � � user� � 0m5.857s > � � sys� � � 0m0.000s > On MacOS X with GHC 7.10.3, it does not time out either way.� > Perhaps > some versions of GHC don't make the timeout possible. > -- > � � � � Viktor. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > [4]http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > [5]http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > Verweise > > 1. https://github.com/gwern/mueval/blob/09b6a7aa5a25c4115442ea2e6ae0c2db557007f8/Mueval/Parallel.hs > 2. mailto:ryan.reich at gmail.com > 3. mailto:ietf-dane at dukhovni.org > 4. http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > 5. http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe From carter.schonwald at gmail.com Thu Nov 29 14:31:15 2018 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 29 Nov 2018 09:31:15 -0500 Subject: [Haskell-cafe] static analysis of a C-like language In-Reply-To: References: Message-ID: Most parser libraries in Haskell provide facilities for including source information. And then you include in your syntax tree extra fields for those positions. Simple as that The paper : http://david.darais.com/assets/papers/abstracting-definitional-interpreters/adi.pdf Is a great reference for how to add a bunch of program analysis features after you have a working interpreter . Also it’s citations show a bunch of ways you can Add different flavored of anayses On Mon, Nov 26, 2018 at 3:37 PM Olaf Klinke wrote: > > Hello Olaf, > > > > to me that sounds as if you want to do an abstract interpretation with a > > forward collecting semantics that employs non-relational abstract > > domains for the primitive data types and summarizes the dimensions of > > arrays. > ... > > I would start by writing a simple interpreter for the language to be > > analyzed. That way you fix messy details before they bite you, e.g. the > > order in which submodules are loaded and initialized. > > I was hoping not having to write an interpreter (because the language > author wrote a translation to C++ already), but if that is the way to go, > I'll do it. As I understand it, the Haskell semantics should contain just > enough substance so that the errors I am after will cause hiccups in the > Haskell compiler? That is indeed a compelling approach. > What this does not address is the question about error reporting: How > could a translation to Haskell preserve information about scope, source > position and masking? Can I leverage the ghc API for that? > > Regards, > Olaf > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From mattei at oca.eu Thu Nov 29 10:33:45 2018 From: mattei at oca.eu (Damien Mattei) Date: Thu, 29 Nov 2018 11:33:45 +0100 Subject: [Haskell-cafe] HDBC database: error on accent table name Message-ID: <5BFFC089.1070505@oca.eu> Hi, i have this error: *** Exception: SqlError {seState = "", seNativeError = 1064, seErrorMsg = "You have an error in your SQL syntax; check the manual that corresponds to your MariaDB server version for the right syntax to use near 'es where Nom = 'A 20'' at line 1"} when doing this : rows_coordonnees <- quickQuery' conn "select * from sidonie.Coordonnées where Nom = 'A 20'" [] it seems tha the tabel name: Coordonnées that contain an accent is causing serious problem to the parser at some point, if i use a table name without accent it works fine. i'm at the point to rename the table which have great impact on all the project build with many other languages (Scheme) that deal correctly the table name with accent. any idea? to make accent works with haskell. Regards, Damien -- Damien.Mattei at unice.fr, Damien.Mattei at oca.eu, UNS / OCA / CNRS From ryan.reich at gmail.com Thu Nov 29 15:32:31 2018 From: ryan.reich at gmail.com (Ryan Reich) Date: Thu, 29 Nov 2018 07:32:31 -0800 Subject: [Haskell-cafe] Timing out a pure evaluation of an expression I did not write myself In-Reply-To: References: <20181119202651.GH4122@straasha.imrryr.org> <20181129011021.GB4122@straasha.imrryr.org> Message-ID: I did actually construct a workaround where I compute in a separate (forked, via System.Posix) *process *to time it out, then recomputed in the main process to get the value. It's got a significant overhead but I'm not sure yet if that is a real issue. Using just a separate rts thread is how the standard timeout works; if you mean that those guys use a separate OS thread that gets scheduled outside the rts, that would be perfect. I'm just faking that with the fork. On Thu, Nov 29, 2018, 02:16 Erik Hesselink Hi Ryan, > > I'm not quite sure of your use case, but lambdabot/mueval do something > like this I think. From a brief look at the source [1] it seems they > compute in a separate thread, then in another thread, wait until the > timeout then kill the computation thread. Would something like that work > for you? > > Erik > > [1] > https://github.com/gwern/mueval/blob/09b6a7aa5a25c4115442ea2e6ae0c2db557007f8/Mueval/Parallel.hs > > On Thu, 29 Nov 2018 at 03:41, Ryan Reich wrote: > >> I expected something like that. I'm all the way back in ghc-8.2.2, but I >> think what this really shows is that the flag is unreliable and >> version-dependent. Unfortunately there doesn't seem to be a precise >> specification of where yield points should appear, and therefore, where >> they might be not-omitted. >> >> On Wed, Nov 28, 2018, 17:10 Viktor Dukhovni > wrote: >> >>> On Wed, Nov 28, 2018 at 09:39:01AM -0800, Ryan Reich wrote: >>> >>> > Thanks for the suggestion, which Arjen made also. Unfortunately, it >>> does >>> > not appear to help. See this simple program: >>> > >>> > -- Loop.hs >>> > import Control.Exception >>> > import System.Timeout >>> > >>> > main :: IO (Maybe Integer) >>> > main = timeout 100000 $ evaluate $ last $ repeat 0 >>> > -- end >>> > >>> > With either GHC invocation "stack exec ghc Loop[ -- -fno-omit-yields]", >>> > running ./Loop fails to terminate (it should do so in 0.1s). >>> > >>> > Based only on the very terse description of that flag in the User's >>> Guide, >>> > and its name, I think the problem is simply that GHC doesn't normally >>> > *generate* yields in that loop, so there's nothing not to omit. >>> >>> It times out for me with GHC 8.4.4 on FreeBSD 11.2, and "ghc -O >>> -fno-omit-yields" >>> and does not time out with "ghc -O": >>> >>> $ cat /tmp/foo.hs >>> import Control.Exception >>> import System.Timeout >>> >>> main :: IO (Maybe Integer) >>> main = timeout 1000000 $ evaluate $ last $ repeat 0 >>> >>> $ ghc -O -fno-omit-yields /tmp/foo.hs >>> [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) >>> [Optimisation flags changed] >>> Linking /tmp/foo ... >>> >>> $ time /tmp/foo >>> >>> real 0m1.033s >>> user 0m1.025s >>> sys 0m0.008s >>> >>> $ rm /tmp/foo >>> $ ghc -O /tmp/foo.hs >>> [1 of 1] Compiling Main ( /tmp/foo.hs, /tmp/foo.o ) >>> [Optimisation flags changed] >>> Linking /tmp/foo ... >>> >>> $ time /tmp/foo >>> ^C^C >>> >>> real 0m5.864s >>> user 0m5.857s >>> sys 0m0.000s >>> >>> On MacOS X with GHC 7.10.3, it does not time out either way. Perhaps >>> some versions of GHC don't make the timeout possible. >>> >>> -- >>> Viktor. >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Thu Nov 29 18:42:42 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 29 Nov 2018 19:42:42 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields Message-ID: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Dear Cafe, I am surprised by the behaviour of the program below (the interesting property is whether it will output "foo"). Behaviours (plural) actually: it seems to depend on optimisation level, on omit-yields, and on very small changes in the source code: It does print (mostly), when compiled with -O0. It does not, when compiled with -O2. With -O2 -fno-omit-yields, it will print. With -O0 -fno-omit-yields, and when I remove the two newTVar in the beginning, it will mostly not print. How come? These differences already occur with the last two lines replaced by "forever $ return ()", so the STM stuff may be inessential here. But that's the context where I came across the problem. - J.W. import Control.Concurrent.STM import Control.Concurrent ( forkIO ) import Control.Monad ( forever ) import System.IO main = do atomically $ newTVar "bar" atomically $ newTVar False forkIO $ putStrLn "foo" x <- atomically $ newTVar False forever $ atomically $ writeTVar x True From allbery.b at gmail.com Thu Nov 29 18:48:21 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 29 Nov 2018 13:48:21 -0500 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Message-ID: This is undoubtedly nothing more than timing issues. Remember that the main thread exiting will kill the entire process, automatically killing all other threads as side effect. So the question is how much the thread manages to get done before that happens. If you disable output buffering, you may find that "f" or "fo" sometimes gets written before process exit. On Thu, Nov 29, 2018 at 1:43 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > Dear Cafe, > > I am surprised by the behaviour of the program below > (the interesting property is whether it will output "foo"). > > Behaviours (plural) actually: it seems to depend > on optimisation level, on omit-yields, > and on very small changes in the source code: > > It does print (mostly), when compiled with -O0. > It does not, when compiled with -O2. > With -O2 -fno-omit-yields, it will print. > With -O0 -fno-omit-yields, and when I remove the two newTVar > in the beginning, it will mostly not print. > > How come? > > These differences already occur with the > last two lines replaced by "forever $ return ()", > so the STM stuff may be inessential here. > But that's the context where I came across the problem. > > - J.W. > > > import Control.Concurrent.STM > import Control.Concurrent ( forkIO ) > import Control.Monad ( forever ) > import System.IO > > main = do > > atomically $ newTVar "bar" > atomically $ newTVar False > > forkIO $ putStrLn "foo" > > x <- atomically $ newTVar False > forever $ atomically $ writeTVar x True > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Thu Nov 29 18:51:19 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 29 Nov 2018 19:51:19 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Message-ID: On 11/29/18 7:48 PM, Brandon Allbery wrote: > main thread exiting will kill the entire process, The main thread does "forever $ something". The process does not exit (I am not getting the console prompt). I observe that the process either prints and then hangs, or it hangs immediately. - J. From b at chreekat.net Thu Nov 29 19:25:07 2018 From: b at chreekat.net (Bryan Richter) Date: Thu, 29 Nov 2018 21:25:07 +0200 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Message-ID: On Thu, Nov 29, 2018, 20:51 Johannes Waldmann < johannes.waldmann at htwk-leipzig.de wrote: > On 11/29/18 7:48 PM, Brandon Allbery wrote: > > > main thread exiting will kill the entire process, > > The main thread does "forever $ something". > > The process does not exit (I am not getting > the console prompt). I observe that the process > either prints and then hangs, or it hangs immediately. > Printing to the console still isn't a great test to see if something has "run", because of buffering that seems to behave unintuitively in these situations. Maybe try flushing stdout within the forked thread, to ensure the runtime is doing what you think it's doing? -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Nov 29 19:28:14 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 29 Nov 2018 14:28:14 -0500 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Message-ID: I also note that the "forever" is in fact writing to a TVar. I'd be curious as to whether it's retrying for some reason, possibly related to the "lost" TVars confusing the STM machinery. I seem to recall it has some infelicities currently; and I have no idea how (or if) STM retries interact with thread yielding. On Thu, Nov 29, 2018 at 2:25 PM Bryan Richter wrote: > > > On Thu, Nov 29, 2018, 20:51 Johannes Waldmann < > johannes.waldmann at htwk-leipzig.de wrote: > >> On 11/29/18 7:48 PM, Brandon Allbery wrote: >> >> > main thread exiting will kill the entire process, >> >> The main thread does "forever $ something". >> >> The process does not exit (I am not getting >> the console prompt). I observe that the process >> either prints and then hangs, or it hangs immediately. >> > > Printing to the console still isn't a great test to see if something has > "run", because of buffering that seems to behave unintuitively in these > situations. Maybe try flushing stdout within the forked thread, to ensure > the runtime is doing what you think it's doing? > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Thu Nov 29 19:37:35 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 29 Nov 2018 20:37:35 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Message-ID: <88a337f1-e441-555f-5a4d-1d4da04e7a92@htwk-leipzig.de> > ... try flushing stdout within the forked thread, I did. The behaviour is still as described: depends on -O0/2, [no]omit-yield, and small changes in the source. While I agree with the general point - why would I need to hFlush after putStrLn? hGetBuffering stdout tells me it's LineBuffering, and putStrLn does write a line? - J. From allbery.b at gmail.com Thu Nov 29 19:40:07 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 29 Nov 2018 14:40:07 -0500 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: <88a337f1-e441-555f-5a4d-1d4da04e7a92@htwk-leipzig.de> References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> <88a337f1-e441-555f-5a4d-1d4da04e7a92@htwk-leipzig.de> Message-ID: The idea is that putStrLn iterates putChar over the String, then putChar '\n'; so thread scheduling would be more obvious with individual characters being output instead of a single flush triggered by the final putChar. On Thu, Nov 29, 2018 at 2:37 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > > ... try flushing stdout within the forked thread, > > I did. The behaviour is still as described: > depends on -O0/2, [no]omit-yield, > and small changes in the source. > > While I agree with the general point - > why would I need to hFlush after putStrLn? > hGetBuffering stdout tells me it's LineBuffering, > and putStrLn does write a line? > > - J. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Thu Nov 29 19:49:03 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 29 Nov 2018 20:49:03 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> <88a337f1-e441-555f-5a4d-1d4da04e7a92@htwk-leipzig.de> Message-ID: <308a488b-1a15-7af8-eae7-0b691ade5792@htwk-leipzig.de> > so thread scheduling would be more obvious with individual > characters being output instead of a single flush triggered by the final > putChar. Yes but in my example program, there is no contention for stdout, as only one thread is using it. I am inclined to enter this into the GHC issue tracker as it seems there's no obvious explanation, and "lost TVars confusing the STM machinery" was mentioned. Do you mean that this a known thing? Searching the tracker for "lost TVar" does not turn up anything. - J.W. From allbery.b at gmail.com Thu Nov 29 19:53:36 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 29 Nov 2018 14:53:36 -0500 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: <308a488b-1a15-7af8-eae7-0b691ade5792@htwk-leipzig.de> References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> <88a337f1-e441-555f-5a4d-1d4da04e7a92@htwk-leipzig.de> <308a488b-1a15-7af8-eae7-0b691ade5792@htwk-leipzig.de> Message-ID: What does this have to do with contention for stdout? Thread switching is unrelated; seeing individual output operations just gives more hints about when the thread switches happen. And with -fno-omit-yields it presumably can happen when putChar is evaluated, not because of I/O but because of function entry. On Thu, Nov 29, 2018 at 2:49 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > > so thread scheduling would be more obvious with individual > > characters being output instead of a single flush triggered by the final > > putChar. > > Yes but in my example program, there is no contention for stdout, > as only one thread is using it. > > I am inclined to enter this into the GHC issue tracker > as it seems there's no obvious explanation, > and "lost TVars confusing the STM machinery" was mentioned. > Do you mean that this a known thing? Searching the tracker > for "lost TVar" does not turn up anything. > > - J.W. > -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Thu Nov 29 20:28:24 2018 From: svenpanne at gmail.com (Sven Panne) Date: Thu, 29 Nov 2018 21:28:24 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Message-ID: Am Do., 29. Nov. 2018 um 19:43 Uhr schrieb Johannes Waldmann < johannes.waldmann at htwk-leipzig.de>: > I am surprised by the behaviour of the program below > (the interesting property is whether it will output "foo"). > > Behaviours (plural) actually: it seems to depend > on optimisation level, on omit-yields, > and on very small changes in the source code: [...] > IMHO there is nothing very surprising here: You have 2 threads with no synchronization between them whatsoever, so you get what you deserve: Undefined behavior. :-) This is the behavior you get in basically all programming languages/execution environments I know of, *unless* they make a very strong guarantee about their scheduling behavior (whichis very rare, for good reasons). Do we have such a guarantee somewhere in the GHC/base documentation? I don't think so, but if we had, I would be interested to see a reference to that. Cheers, S. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ian at zenhack.net Thu Nov 29 20:52:06 2018 From: ian at zenhack.net (Ian Denhardt) Date: Thu, 29 Nov 2018 15:52:06 -0500 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Message-ID: <154352472677.3857.4052918294025813694@localhost> Quoting Johannes Waldmann (2018-11-29 13:42:42) > These differences already occur with the > last two lines replaced by "forever $ return ()", > so the STM stuff may be inessential here. > But that's the context where I came across the problem. There's another thread right now with a subject line of "Timing out a pure evaluation of an expression I did not write myself," that seems like it might be related: I would expect forever $ return () to not allocate, which would mean it would never hit any yields, and thus never be rescheduled, and hogging the CPU. I've been able to reproduce your results, and if I change the last line to: forever $ do yield atomically $ writeTVar x True ..it always prints -- so the culprit is definitely a failure to yield. -Ian From johannes.waldmann at htwk-leipzig.de Thu Nov 29 20:54:15 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 29 Nov 2018 21:54:15 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> Message-ID: <981d20df-79f0-82e7-d646-aa7750967a4b@htwk-leipzig.de> > IMHO there is nothing very surprising here: You have 2 threads with no > synchronization between them whatsoever, so you get what you deserve: > Undefined behavior. :-) Well, yes. It feels as if the scheduler is mighty unfair here (delaying the printing indefinitely) but apparently it is allowed to do so - mainly since there is no specification that would require otherwise. But then (seconding your question) what guarantees *do* we have? For a single-threaded program, it would certainly not be OK to execute "main = print ()" as "block immediately"? But when we forkIO this, then it can happen? Possibly related: discussion about (state of formal specification of) GHC RTS memory model at https://mail.haskell.org/pipermail/ghc-devs/2018-November/016583.html - J.W. From johannes.waldmann at htwk-leipzig.de Thu Nov 29 21:45:09 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 29 Nov 2018 22:45:09 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: <154352472677.3857.4052918294025813694@localhost> References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> <154352472677.3857.4052918294025813694@localhost> Message-ID: > forever $ do > yield > atomically $ writeTVar x True > > ..it always prints -- so the culprit is definitely a failure to yield. A-ha. So my implicit assumption was that a run of the transaction manager (because "atomically") is also a yield - but this example shows that it isn't. If this is indeed the case, then this deserves to be mentioned in the documentation of Control.Concurrent.STM ? - J.W. From ietf-dane at dukhovni.org Fri Nov 30 02:34:45 2018 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Thu, 29 Nov 2018 21:34:45 -0500 Subject: [Haskell-cafe] GHC 8.6.2 zombie processes? Message-ID: <0A084774-0F65-4862-B38D-9B20880EED92@dukhovni.org> It seems that GHC 8.6.2 does not reap defunct child processes in a timely manner when compiling many modules (e.g. "base" when stack is building a new sandbox). This is especially visible when using LLVM 6.0 whose optimizer is particularly CPU-intensive (read mind-numbingly slow) on my X86_84 FreeBSD system: The process: $ ps -wwwwwww -o pid,etime,args -p 98525 PID ELAPSED COMMAND 98525 55:47 /home/viktor/.local/lib/ghc-8.6.2.20181122/bin/ghc -B/home/viktor/.local/lib/ghc-8.6.2.20181122 --make -fbuilding-cabal-package -O -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi -outputdir .stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build -odir .stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build -hidir .stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build -stubdir .stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build -i -i.stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build -i. -i.stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build/autogen -i.stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build/global-autogen -I.stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build/autogen -I.stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build/global-autogen -I.stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build -I/usr/local/Cellar/postgresql/10.0/include -I/usr/local/include -I/usr/local/opt/icu4c/include -optP-include -optP.stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/build/autogen/cabal_macros.h -this-unit-id Cabal-2.4.1.0-IaB5GUEm19R82R9cEdbB1D -hide-all-packages -Wmissing-home-modules -no-user-package-db -package-db /usr/home/viktor/.stack/snapshots/x86_64-freebsd/nightly-2018-11-28/8.6.2.20181122/pkgdb -package-db .stack-work/dist/x86_64-freebsd/Cabal-2.4.0.1/package.conf.inplace -package-id array-0.5.3.0 -package-id base-4.12.0.0 -package-id binary-0.8.6.0 -package-id bytestring-0.10.8.2 -package-id containers-0.6.0.1 -package-id deepseq-1.4.4.0 -package-id directory-1.3.3.0 -package-id filepath-1.4.2.1 -package-id mtl-2.2.2 -package-id parsec-3.1.13.0 -package-id pretty-1.1.3.6 -package-id process-1.6.3.0 -package-id text-1.2.3.1 -package-id time-1.8.0.2 -package-id transformers-0.5.5.0 -package-id unix-2.7.2.2 -XHaskell2010 Distribution.Backpack Distribution.Backpack.Configure Distribution.Backpack.ComponentsGraph Distribution.Backpack.ConfiguredComponent Distribution.Backpack.DescribeUnitId Distribution.Backpack.FullUnitId Distribution.Backpack.LinkedComponent Distribution.Backpack.ModSubst Distribution.Backpack.ModuleShape generated multiple hundreds of "zombies": $ ps $(pgrep -P 98525) | egrep -c defunct 460 I guess the build taking an hour is far more an issue than a few hundred zombies, but this message is about the zombies. Is this a feature or a bug? -- Viktor. From svenpanne at gmail.com Fri Nov 30 10:05:20 2018 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 30 Nov 2018 11:05:20 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: <154352472677.3857.4052918294025813694@localhost> References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> <154352472677.3857.4052918294025813694@localhost> Message-ID: Am Do., 29. Nov. 2018 um 21:54 Uhr schrieb Ian Denhardt : > [...] I've been able to reproduce your results, and if I change the last > line > to: > > forever $ do > yield > atomically $ writeTVar x True > > ..it always prints -- so the culprit is definitely a failure to yield. > But even that is not enough from a specification POV: After the yield, the same thread might be schedule immediately again, and again, ... Or do we have some specification of the scheduler? I don't think so, but perhaps I'm wrong in this respect. If we have one, it has to state explicitly that the scheduling is fair in the sense that every runnable thread actually runs after a finite amount of time, otherwise you are in undefined land again... The question where scheduling can actually happen is a totally different issue, and I don't know of a specification here, either. In GHC, this seems to be tied to allocations, but this is a bit brittle and unintuitive. To guarantee that you hit a scheduling point after a finite amount of time is easy in principle, e.g. do this on every backwards branch and on every function entry. But this has an associated cost, so we have a tradeoff here. In general, I wouldn't worry too much about the semantics of unsynchronized threads, if you rely on this somehow, you will sooner or later enter a world of pain. Add e.g. thread priorities to the mix, and you will suffer even more, experiencing wonderful things like priority inversion etc. :-P -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Fri Nov 30 10:50:03 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Fri, 30 Nov 2018 11:50:03 +0100 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> <154352472677.3857.4052918294025813694@localhost> Message-ID: Hi, > the same thread might be schedule immediately again, and again, ... Or > do we have some specification of the scheduler? My working assumption is that the scheduler tries to be fair. So all strange behaviour could be explained with the scheduler not running at all, because threads weren't yielding. > The question where scheduling can actually happen is a totally different > issue, and I don't know of a specification here, either. In GHC, this > seems to be tied to allocations, but this is a bit brittle and > unintuitive. Yes, especially if the compiler might (re)move allocations due to some code transformations. Given that, it now feels strange that the following *does* work: main = do forkIO $ do threadDelay 1000000 ; putStrLn "foo" forever $ putStr "" I am seeing the "foo" output. I expect the last line to be non-allocating. But it does still yield? Why? - J.W. From takenobu.hs at gmail.com Fri Nov 30 11:45:45 2018 From: takenobu.hs at gmail.com (Takenobu Tani) Date: Fri, 30 Nov 2018 20:45:45 +0900 Subject: [Haskell-cafe] WebAssembly illustrated Message-ID: Hi cafe, I share this even in this place. WebAssembly illustrated https://takenobu-hs.github.io/downloads/WebAssembly_illustrated.pdf P.S. Haskell has backends such as asterius [1] and dhc [2]. [1]: https://github.com/tweag/asterius [2]: https://github.com/dfinity/dhc Cheers, Takenobu -------------- next part -------------- An HTML attachment was scrubbed... URL: From takenobu.hs at gmail.com Fri Nov 30 13:55:46 2018 From: takenobu.hs at gmail.com (Takenobu Tani) Date: Fri, 30 Nov 2018 22:55:46 +0900 Subject: [Haskell-cafe] WebAssembly illustrated In-Reply-To: References: Message-ID: Hi Sven, Thank you for teaching me. > Also, are you slides free to use? Could you please share the source? Of course you can use it freely :) I also commit the source. (But it is PowerPoint.) Cheers, Takenobu On Fri, Nov 30, 2018 at 9:10 PM Sven Sauleau wrote: > Hi, > > Interesting document, thanks for sharing! > > I opened a clarification issue: [1]. > > Also, are you slides free to use? Could you please share the source? > [1]: https://github.com/takenobu-hs/WebAssembly-illustrated/issues/1 > > Thanks! > Sven > > On 30/11/2018 12:45, Takenobu Tani wrote: > > Hi cafe, > > I share this even in this place. > > WebAssembly illustrated > https://takenobu-hs.github.io/downloads/WebAssembly_illustrated.pdf > > > P.S. > Haskell has backends such as asterius [1] and dhc [2]. > > [1]: https://github.com/tweag/asterius > [2]: https://github.com/dfinity/dhc > > Cheers, > Takenobu > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to:http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ichistmeinname at web.de Fri Nov 30 16:11:49 2018 From: ichistmeinname at web.de (Sandra Dylus) Date: Fri, 30 Nov 2018 17:11:49 +0100 Subject: [Haskell-cafe] Haskell-related summer internship in Germany Message-ID: Our department (PL and compiler construction) again offers a summer internship in 2019 sponsored by DAAD Rise Germany [1]. Undergraduate students enrolled at North American, British and Irish universities are eligible to make an application. We'd be very happy to host a motivated student, who is keen to improve our compiler for the functional logic programming language Curry in terms of performance. For more information you may have a look at our project poster [2]. If you have any questions, feel free to mail any of the contact persons. Please also spread the news to your students and classmates. Cheers, Finn and Sandra [1]: https://www.daad.de/rise/en/rise-germany/ [2]: https://www-ps.informatik.uni-kiel.de/~sad/DAADRise.pdf -------------- next part -------------- An HTML attachment was scrubbed... URL: From ian at zenhack.net Fri Nov 30 18:33:22 2018 From: ian at zenhack.net (Ian Denhardt) Date: Fri, 30 Nov 2018 13:33:22 -0500 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> <154352472677.3857.4052918294025813694@localhost> Message-ID: <154360280286.880.15427652626344269929@localhost> Quoting Johannes Waldmann (2018-11-30 05:50:03) > Given that, it now feels strange that the following *does* work: > > main = do > forkIO $ do threadDelay 1000000 ; putStrLn "foo" > forever $ putStr "" > > I am seeing the "foo" output. I expect the last line > to be non-allocating. But it does still yield? Why? putStr has to acquire a lock on stdout, so that's probably enough to allow the scheduler to run. From allbery.b at gmail.com Fri Nov 30 19:06:01 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 30 Nov 2018 14:06:01 -0500 Subject: [Haskell-cafe] semantics of concurrent program depends on -O level, -f[no-]omit-yields In-Reply-To: <154360280286.880.15427652626344269929@localhost> References: <56feaebc-199d-1337-bf2d-4b68eb4d5d02@htwk-leipzig.de> <154352472677.3857.4052918294025813694@localhost> <154360280286.880.15427652626344269929@localhost> Message-ID: Hm, has that been optimized to output all at once? The implementation I recall is more or less mapM_ putChar, deferring the lock to putChar which never gets invoked because the list is empty. Okay, just checked; it reserves the handle up front, and then the above implementation (albeit directly instead of via mapM_) is used only in the NoBuffering case, using an internal function that doesn't reserve. Which will complicate understanding what's going on, although my suggestion earlier about unbuffering output still applies. On Fri, Nov 30, 2018 at 1:35 PM Ian Denhardt wrote: > Quoting Johannes Waldmann (2018-11-30 05:50:03) > > > Given that, it now feels strange that the following *does* work: > > > > main = do > > forkIO $ do threadDelay 1000000 ; putStrLn "foo" > > forever $ putStr "" > > > > I am seeing the "foo" output. I expect the last line > > to be non-allocating. But it does still yield? Why? > > putStr has to acquire a lock on stdout, so that's probably enough to > allow the scheduler to run. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: