From manny at fpcomplete.com Mon Jun 3 13:56:45 2019 From: manny at fpcomplete.com (Emanuel Borsboom) Date: Mon, 3 Jun 2019 06:56:45 -0700 Subject: [Haskell-cafe] ANN: stack-2.1 second release candidate Message-ID: Announcing the second release candidate for Stack 2.1! This is the version that will be released one week from now if there aren't any major issues discovered, so please give it a try. You can download bindists for Linux, macOS, and Windows from https://github.com/commercialhaskell/stack/releases/tag/v2.1.0.3 **Changes since v2.1.0.1** Other enhancements: * Add `--docker-mount-mode` option to set the Docker volume mount mode for performance tuning on macOS. Bug fixes: * Fix regression where `stack --docker` would quit after 20 seconds on macOS. From icfp.publicity at googlemail.com Mon Jun 3 16:03:53 2019 From: icfp.publicity at googlemail.com (Sam Tobin-Hochstadt) Date: Mon, 03 Jun 2019 12:03:53 -0400 Subject: [Haskell-cafe] Second Call for Submissions: ICFP Student Research Competition Message-ID: <5cf544e9cf261_78b42ab427c125b891461@homer.mail> ICFP 2019 Student Research Competition Call for Submissions ICFP invites students to participate in the Student Research Competition in order to present their research and get feedback from prominent members of the programming language research community. Please submit your extended abstracts through the submission website. ### Important dates Submissions due: 14 Jun 2019 (Friday) https://icfp19src.hotcrp.com Notification: 28 Jun 2019 (Friday) Conference: 18 August (Sunday) - 23 August (Friday) Each submission (referred to as "abstract" below) should include the student author’s name and e-mail address; institutional affiliation; research advisor’s name; ACM student member number; category (undergraduate or graduate); research title; and an extended abstract addressing the following: * Problem and Motivation: Clearly state the problem being addressed and explain the reasons for seeking a solution to this problem. * Background and Related Work: Describe the specialized (but pertinent) background necessary to appreciate the work in the context of ICFP areas of interest. Include references to the literature where appropriate, and briefly explain where your work departs from that done by others. * Approach and Uniqueness: Describe your approach in addressing the problem and clearly state how your approach is novel. * Results and Contributions: Clearly show how the results of your work contribute to programming language design and implementation in particular and to computer science in general; explain the significance of those results. * Submissions must be original research that is not already published at ICFP or another conference or journal. One of the goals of the SRC is to give students feedback on ongoing, unpublished work. Furthermore, the abstract must be authored solely by the student. If the work is collaborative with others and*or part of a larger group project, the abstract should make clear what the student’s role was and should focus on that portion of the work. * 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 https://www.acm.org/publications/authors/submissions. For authors using LaTeX, a lighter-weight package, including only the essential files, is available from http://sigplan.org/Resources/Author/#acmart-format. The submission must not exceed 3 pages in PDF format. Reference lists do not count towards the 3-page limit. Further information is available at the ICFP SRC website: https://icfp19.sigplan.org/track/icfp-2019-Student-Research-Competition ICFP Student Research Competition Chair: William J. Bowman (University of British Columbia) From qdunkan at gmail.com Tue Jun 4 06:17:05 2019 From: qdunkan at gmail.com (Evan Laforge) Date: Mon, 3 Jun 2019 23:17:05 -0700 Subject: [Haskell-cafe] conduit/pipes/streaming and prompt cleanup Message-ID: I'm using the 'streaming' library and realized it doesn't close files in a timely way for the way I'm using it, and in fact can't, due to how the library works. I know conduit has put a lot of thought into closing resources in a timely way, so I did an experiment to see what it does, but as far as I can tell, conduit has the same problem. Maybe I'm doing it wrong? The situation is that I'm opening multiple files and mixing their output. I want to close the inputs as soon as I'm done with them. But I can get done with them earlier than the end of the file. Since all of these libraries are based on pulling from downstream, if you don't pull all the way to the end, the close at the end doesn't happen, and has to wait until runResourceT returns, which is too late. I remember long ago reading Oleg's original iteratee paper, and it seems like he called out this problem with pull-based iterators, that the iterator doesn't know when its caller is done with it, so it can't close files on time. Here's a conduit version that I think illustrates the situation: import qualified Conduit as C import Conduit ((.|)) import qualified Control.Monad.Trans as Trans import qualified System.IO as IO main :: IO () main = C.runResourceT $ C.runConduit pipe pipe :: C.ConduitM a c (C.ResourceT IO) () pipe = fileLines "TODO" .| (C.takeC 3 >> C.yield "***") .| C.mapM_C (Trans.liftIO . putStrLn) fileLines :: C.MonadResource m => FilePath -> C.ConduitT i String m () fileLines fname = C.bracketP (IO.openFile fname IO.ReadMode) close handleLines handleLines :: Trans.MonadIO m => IO.Handle -> C.ConduitT i String m () handleLines hdl = loop where loop = do eof <- Trans.liftIO $ IO.hIsEOF hdl if eof then return () else do line <- Trans.liftIO $ IO.hGetLine hdl C.yield line loop close :: IO.Handle -> IO () close hdl = IO.hClose hdl >> putStrLn "=== close" This prints the first three lines of TOOD, then ***, and then "=== close", where the close should go before the ***s. As far as I can see, conduit can't do this any more than 'streaming' can, because 'C.takeC' is just some awaits and yields, with no indication that the final await is more special than any other await. I think what would be necessary to solve this is that combinators like 'take' have to be able to tell the stream to close, and that has to propagate back up to each producer that has registered a cleanup. Of course this renders the stream invalid, so it's not safe to have any other references to the stream around, but I guess streams are stateful in general so that's always true. Maybe I could accumulate the finalizers in the stream data type and have combinators like 'take' call it as soon as they've taken their last. What I actually wound up doing was make a 'takeClose' that also takes a 'close' action to run when its done with the stream. It's not exactly general but I'm not writing a library so I don't need general. Is there some kind of standard or built-in solution for this situation? I know others have given a lot more thought to streaming than I have, so surely this issue has come up. I know there is a lot of talk about "prompt finalisation" and streams vs. pipes vs. conduit, and talk about brackets and whatnot, but despite reading various documents (https://hackage.haskell.org/package/streaming-with, http://www.haskellforall.com/2013/01/pipes-safe-10-resource-management-and.html, etc.) I still don't really understand what they're talking about. It seems like they're really about reliable cleanup when there are exceptions, not really about prompt cleanup. Certainly pipes-safe doesn't do prompt cleanup, at least not the kind I'm talking about. From simons at nospf.cryp.to Tue Jun 4 12:15:59 2019 From: simons at nospf.cryp.to (Peter Simons) Date: Tue, 04 Jun 2019 14:15:59 +0200 Subject: [Haskell-cafe] How to define classy lenses for polymorphic types that involve singletons? Message-ID: <8736kp35s0.fsf@write-only.cryp.to> Hi, I am trying to combine the lens library's 'makeClassy' feature with a type that's polymorphic over a singleton type: > {-# LANGUAGE DataKinds, FlexibleInstances, FunctionalDependencies, GADTs, > KindSignatures, RankNTypes, TemplateHaskell, TypeFamilies > #-} > > import Control.Lens > import Data.Singletons > import Data.Singletons.TH > > data Sex = Male | Female > deriving (Show, Eq, Ord, Bounded, Enum) > > genSingletons [''Sex] > > data Person (sex :: Sex) = Person { _name :: String, _email :: String } > deriving (Show, Eq) > > makeClassy ''Person Lens generates a class definition that looks sensible to me: class HasPerson a (sex :: Sex) | a -> sex where person :: Lens' a (Person sex) email :: Lens' a String name :: Lens' a String {-# MINIMAL person #-} Furthermore, I also need a type SomePerson to hide the phantom type so that I can store people of different sexes in the same container, i.e. [SomePerson]: > data SomePerson where > SomePerson :: Sing sex -> Person sex -> SomePerson > > fromPerson :: SingI sex => Person sex -> SomePerson > fromPerson p = SomePerson Sing p > > toPerson :: SomePerson -> (forall sex. Sex -> Person sex -> a) -> a > toPerson (SomePerson s p) f = f (fromSing s) p Here is where I've run into trouble. In theory, I should be able to make SomePerson an instance of HasPerson, define person :: Lens' SomePerson (Person sex) to access the Person type inside of it, and that would allow me to use 'name' and 'email' for SomePerson just the same as for Person. However, it seems impossible to define that function because it leaks the universally quantified 'sex', so function does not type-check. I have a somewhat awkward work-around that translates lenses on Person to SomePerson > somePerson :: (forall sex. Lens' (Person sex) a) -> Lens' SomePerson a > somePerson l = lens (\(SomePerson _ p) -> view l p) > (\(SomePerson s p) x -> SomePerson s (set l x p)) and that allows me to define: > type SomePerson' (sex :: Sex) = SomePerson > > instance HasPerson (SomePerson' sex) sex where > person = undefined -- cannot type check because 'sex' would leak > name = somePerson name > email = somePerson email I'm not particularly happy with that solution, though. Is there maybe a way to make this work such that I can avoid defining 'name' and 'email' manually? Or is there a clever alternative way to define HasPerson such a 'person' method for SomePerson is possible? Best regards Peter From lysxia at gmail.com Tue Jun 4 12:43:36 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Tue, 4 Jun 2019 08:43:36 -0400 Subject: [Haskell-cafe] How to define classy lenses for polymorphic types that involve singletons? In-Reply-To: <8736kp35s0.fsf@write-only.cryp.to> References: <8736kp35s0.fsf@write-only.cryp.to> Message-ID: <1bf7878b-72a2-e940-33b8-14cb0b83ccb3@gmail.com> Hi Peter, > In theory, I should be able to make > SomePerson an instance of HasPerson, define > > person :: Lens' SomePerson (Person sex) I wonder what you mean by that, since you highlight the issue just after. Another way to look at the problem is that this type is implicitly universally quantified (unless that's not what you had in mind): person :: forall sex. Lens' SomePerson (Person sex) which can thus be specialized to person :: Lens' SomePerson (Person Male) person :: Lens' SomePerson (Person Female) Those two lenses tell us that any `SomePerson` contains both a `Male` and `Female` person, while the definition of `SomePerson` contains only one. So the types alone reveal a design flaw, and any attempt to inhabit them is thus doomed. Perhaps you could flip the dependency between `SomePerson` and `Person`. Move the singleton to a new field of Person, and generalize it so you can not only instantiate it with a singleton, but also an existentially quantified singleton: data Person' (s :: Type) = Person' { _sex :: s, _name, _email :: String } type Person (sex :: Sex) = Person' (SSex sex) type SomePerson = Person' SomeSex Cheers, Li-yao On 6/4/19 8:15 AM, Peter Simons wrote: > Hi, > > I am trying to combine the lens library's 'makeClassy' feature with a > type that's polymorphic over a singleton type: > >> {-# LANGUAGE DataKinds, FlexibleInstances, FunctionalDependencies, GADTs, >> KindSignatures, RankNTypes, TemplateHaskell, TypeFamilies >> #-} >> >> import Control.Lens >> import Data.Singletons >> import Data.Singletons.TH >> >> data Sex = Male | Female >> deriving (Show, Eq, Ord, Bounded, Enum) >> >> genSingletons [''Sex] >> >> data Person (sex :: Sex) = Person { _name :: String, _email :: String } >> deriving (Show, Eq) >> >> makeClassy ''Person > > Lens generates a class definition that looks sensible to me: > > class HasPerson a (sex :: Sex) | a -> sex where > person :: Lens' a (Person sex) > email :: Lens' a String > name :: Lens' a String > {-# MINIMAL person #-} > > Furthermore, I also need a type SomePerson to hide the phantom type so > that I can store people of different sexes in the same container, i.e. > [SomePerson]: > >> data SomePerson where >> SomePerson :: Sing sex -> Person sex -> SomePerson >> >> fromPerson :: SingI sex => Person sex -> SomePerson >> fromPerson p = SomePerson Sing p >> >> toPerson :: SomePerson -> (forall sex. Sex -> Person sex -> a) -> a >> toPerson (SomePerson s p) f = f (fromSing s) p > > Here is where I've run into trouble. In theory, I should be able to make > SomePerson an instance of HasPerson, define > > person :: Lens' SomePerson (Person sex) > > to access the Person type inside of it, and that would allow me to use > 'name' and 'email' for SomePerson just the same as for Person. However, > it seems impossible to define that function because it leaks the > universally quantified 'sex', so function does not type-check. > > I have a somewhat awkward work-around that translates lenses on Person > to SomePerson > >> somePerson :: (forall sex. Lens' (Person sex) a) -> Lens' SomePerson a >> somePerson l = lens (\(SomePerson _ p) -> view l p) >> (\(SomePerson s p) x -> SomePerson s (set l x p)) > > and that allows me to define: > >> type SomePerson' (sex :: Sex) = SomePerson >> >> instance HasPerson (SomePerson' sex) sex where >> person = undefined -- cannot type check because 'sex' would leak >> name = somePerson name >> email = somePerson email > > I'm not particularly happy with that solution, though. Is there maybe a > way to make this work such that I can avoid defining 'name' and 'email' > manually? Or is there a clever alternative way to define HasPerson such > a 'person' method for SomePerson is possible? > > Best regards > Peter > > _______________________________________________ > 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 michael at snoyman.com Tue Jun 4 13:45:11 2019 From: michael at snoyman.com (Michael Snoyman) Date: Tue, 4 Jun 2019 07:45:11 -0600 Subject: [Haskell-cafe] conduit/pipes/streaming and prompt cleanup In-Reply-To: References: Message-ID: I think you're seeing the fact that conduit no longer has finalizers, see: https://www.snoyman.com/blog/2018/01/drop-conduits-finalizers Though I don't think your example proves the point. You know that the code following `takeC 3` will never `await`, but there's no way for the conduit library to know that. Instead, if you wanted to demonstrate the limitation of removing finalizers you'd need to rewrite your code to this: pipe :: C.ConduitM a c (C.ResourceT IO) () pipe = ((fileLines "TODO" .| C.takeC 3) >> C.yield "***") .| C.mapM_C (Trans.liftIO . putStrLn) Here, we can immediately see the `fileLines` is not going to be `await`ed from again once `takeC 3` is complete, and yet without finalizers the close is still delayed. However, now that I've done that slight rewrite, we can make a further rewrite to leverage the bracket pattern and get back prompt finalization: pipe :: C.ConduitM a c (C.ResourceT IO) () pipe = ((withFileLines "TODO" (C.takeC 3)) >> C.yield "***") .| C.mapM_C (Trans.liftIO . putStrLn) withFileLines :: C.MonadResource m => FilePath -> C.ConduitT String o m r -> C.ConduitT i o m r withFileLines fname inner = C.bracketP (IO.openFile fname IO.ReadMode) close (\h -> handleLines h .| inner) On Tue, Jun 4, 2019 at 12:17 AM Evan Laforge wrote: > I'm using the 'streaming' library and realized it doesn't close files in a > timely way for the way I'm using it, and in fact can't, due to how the > library > works. I know conduit has put a lot of thought into closing resources in a > timely way, so I did an experiment to see what it does, but as far as I can > tell, conduit has the same problem. Maybe I'm doing it wrong? > > The situation is that I'm opening multiple files and mixing their output. > I want to close the inputs as soon as I'm done with them. But I can get > done with them earlier than the end of the file. Since all of these > libraries > are based on pulling from downstream, if you don't pull all the way to the > end, > the close at the end doesn't happen, and has to wait until runResourceT > returns, which is too late. I remember long ago reading Oleg's original > iteratee paper, and it seems like he called out this problem with > pull-based > iterators, that the iterator doesn't know when its caller is done with it, > so > it can't close files on time. > > Here's a conduit version that I think illustrates the situation: > > import qualified Conduit as C > import Conduit ((.|)) > import qualified Control.Monad.Trans as Trans > import qualified System.IO as IO > > main :: IO () > main = C.runResourceT $ C.runConduit pipe > > pipe :: C.ConduitM a c (C.ResourceT IO) () > pipe = fileLines "TODO" .| (C.takeC 3 >> C.yield "***") > .| C.mapM_C (Trans.liftIO . putStrLn) > > fileLines :: C.MonadResource m => FilePath -> C.ConduitT i String m () > fileLines fname = C.bracketP (IO.openFile fname IO.ReadMode) close > handleLines > > handleLines :: Trans.MonadIO m => IO.Handle -> C.ConduitT i String m () > handleLines hdl = loop > where > loop = do > eof <- Trans.liftIO $ IO.hIsEOF hdl > if eof then return () else do > line <- Trans.liftIO $ IO.hGetLine hdl > C.yield line > loop > > close :: IO.Handle -> IO () > close hdl = IO.hClose hdl >> putStrLn "=== close" > > This prints the first three lines of TOOD, then ***, and then "=== close", > where the close should go before the ***s. > > As far as I can see, conduit can't do this any more than 'streaming' can, > because 'C.takeC' is just some awaits and yields, with no indication that > the final await is more special than any other await. > > I think what would be necessary to solve this is that combinators like > 'take' > have to be able to tell the stream to close, and that has to propagate > back up > to each producer that has registered a cleanup. Of course this renders the > stream invalid, so it's not safe to have any other references to the stream > around, but I guess streams are stateful in general so that's always true. > Maybe I could accumulate the finalizers in the stream data type and have > combinators like 'take' call it as soon as they've taken their last. What > I actually wound up doing was make a 'takeClose' that also takes a 'close' > action to run when its done with the stream. It's not exactly general but > I'm > not writing a library so I don't need general. > > Is there some kind of standard or built-in solution for this situation? > I know others have given a lot more thought to streaming than I have, > so surely this issue has come up. > > I know there is a lot of talk about "prompt finalisation" and streams vs. > pipes vs. conduit, and talk about brackets and whatnot, but despite reading > various documents (https://hackage.haskell.org/package/streaming-with, > > http://www.haskellforall.com/2013/01/pipes-safe-10-resource-management-and.html > , > etc.) I still don't really understand what they're talking about. > It seems like they're really about reliable cleanup when there are > exceptions, not really about prompt cleanup. Certainly pipes-safe doesn't > do > prompt cleanup, at least not the kind I'm talking about. > _______________________________________________ > 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 michael at orlitzky.com Wed Jun 5 00:46:08 2019 From: michael at orlitzky.com (Michael Orlitzky) Date: Tue, 4 Jun 2019 20:46:08 -0400 Subject: [Haskell-cafe] Looking for a paper In-Reply-To: <9BBD5F52-13B3-4B66-A927-EE7A954E86F2@ouroborus.net> References: <08980c64-9195-6b48-7f6f-54a58f81bfcb@orlitzky.com> <9BBD5F52-13B3-4B66-A927-EE7A954E86F2@ouroborus.net> Message-ID: <999e0849-3564-99cc-c1d4-b4f09db6cd25@orlitzky.com> On 5/1/19 9:45 AM, Ben Lippmeier wrote: > > Check out: > > A useful lambda-notation. > Fairouz Kamareddine, Rob Nederpelt. > Theoretical Computer Science 115 (1996) 85-109 > > They use “item notation”, and argue that maybe function application isn’t what we should be writing to begin with. > 500+ pages of TaPL later, I can read this =) Their item notation goes a bit further than function application because it encompasses the typed lambda calculi: * Item notation has to handle inline function definitions like (lambda x. 2*x) y (apply the doubling function to "y") * Item notation needs to account for the type annotations in lambda abstractions, such as lambda x:T. f x (declare the argument "x" is of type "T") But, the main idea of item notation is simple: 1. Values, types, and kinds are left alone. 2. Type annotations are handled in a way that is irrelevant for my next few paragraphs. 3. The function application "f x" is translated to "(x delta)f" (These translations are actually performed recursively on terms, but the idea should be clear). The interesting one is #3, because in Dijkstra-dot notation we would write "f x" as "f.x", to mean "apply f to the argument x". The item notation, on the other hand, uses (x delta)f to mean, essentially, "feed x to the function f as an argument." They've used a delta instead of a dot (the dot is taken in the lambda calculus), but the idea is similar. If we were to reverse the Dijkstra-dot notation and write "x.f" to indicate the application of "f" to "x", then we recover the same idea. Doing so has some other benefits -- it makes diagrams easier to read, especially if you write (f;g) for the composition of g and f: x.(f;g) <===> feed x to f, then feed its result to g Older algebra books often adopt this convention modulo the dot, writing for example "xA" for the application of "A" to "x". (When these are vectors/matrices, you can explain away the heresy by defining R^n to consist of row vectors.) And in the presence of anonymous functions -- namely, lambda abstractions -- the item notation paper makes good arguments for this preference. In any case, parentheses are the worst possible choice, and I do find it interesting that the same ideas keep reappearing. Thanks for the reference. From raoknz at gmail.com Wed Jun 5 02:21:20 2019 From: raoknz at gmail.com (Richard O'Keefe) Date: Wed, 5 Jun 2019 14:21:20 +1200 Subject: [Haskell-cafe] Looking for a paper In-Reply-To: <9BBD5F52-13B3-4B66-A927-EE7A954E86F2@ouroborus.net> References: <08980c64-9195-6b48-7f6f-54a58f81bfcb@orlitzky.com> <9BBD5F52-13B3-4B66-A927-EE7A954E86F2@ouroborus.net> Message-ID: Could it possibly be Dijkstra's mid-2000 essay on notation? https://www.cs.utexas.edu/users/EWD/transcriptions/EWD13xx/EWD1300.html Dijkstra used f.x and a programming language I used in the 80s that was designed in the 60s used x.f and that worked very nicely with thinking of record fields as functions. F# of course has both f x and x |> f, where |> has caught on as $ did not. On Thu, 2 May 2019 at 01:45, Ben Lippmeier wrote: > > > > On 10 Apr 2019, at 12:00 am, Michael Orlitzky > wrote: > > > > Everyone knows that parentheses suck for function application. > > > > But I'm looking for a CS paper that argues that function application > > should have its own explicit syntax in a functional programming > > language. I believe, in the paper, that a dot "." was used, but this > > would be analogous to Haskell's "$" function, except that it would be > > made part of the language definition. > > > > I think it came up on this mailing list (where else would I have seen > > it?), and if anyone remembers the name or author I'd be grateful. > > > Hi Michael, long time.. > > Check out: > > A useful lambda-notation. > Fairouz Kamareddine, Rob Nederpelt. > Theoretical Computer Science 115 (1996) 85-109 > > They use “item notation”, and argue that maybe function application isn’t > what we should be writing to begin with. > > Ben. > > > > > > _______________________________________________ > 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 qdunkan at gmail.com Wed Jun 5 02:37:28 2019 From: qdunkan at gmail.com (Evan Laforge) Date: Tue, 4 Jun 2019 19:37:28 -0700 Subject: [Haskell-cafe] conduit/pipes/streaming and prompt cleanup In-Reply-To: References: Message-ID: Hi, thanks for the response! > I think you're seeing the fact that conduit no longer has finalizers, see: > > https://www.snoyman.com/blog/2018/01/drop-conduits-finalizers > > Though I don't think your example proves the point. You know that the code > following `takeC 3` will never `await`, but there's no way for the conduit > library to know that. Instead, if you wanted to demonstrate the limitation of > removing finalizers you'd need to rewrite your code to this: The way I was looking at it, the problem is just that: takeC will never await again, but doesn't tell anyone about that, so conduit can't know it. This is why I was thinking of giving it such a way, by notifying upstream explicitly. I can see how that's an unsatisfying solution, because it means that all functions that cut off the input have to say so explicitly, and forgetting to do that in any one of them will lead to a leak. The bracket pattern encodes the scope of the open file into the shape of the expression, and if I can fit my program into that shape then I get automatic finalization, which is nicer. The question then is can I fit it into that shape? If not then it's at least a data point that you were asking for on the blog post. If I can, but only for conduit and not for streaming, then it's a demonstration of a difference of expressiveness between the two, which is interesting. The complicating factor is that I'm streaming multiple overlapping files, which are all demanded by a single sink. So it's not the concatenation that (>>) does. E.g. mainLoop (events :: [(Int, FilePath)]) = loop 0 [] events where loop now running events = do let (toStart, notYet) = span ((<=now) . fst) events starting <- mapM startStream toStart chunks <- mapMaybeM await (running ++ starting) yield (mix chunks) loop (now+n) (running ++ starting) notYet startStream = takeC 3 . fileLines There's some missing stuff to drop streams that ran out, and stop the loop once events and streams run out, but you get the idea. I can't figure out where the (>>) would go that would terminate one of those streams, or even what "terminate" actually means, if it's not something that takeC does explicitly. From Dominique.Devriese at vub.be Wed Jun 5 06:25:22 2019 From: Dominique.Devriese at vub.be (Dominique DEVRIESE) Date: Wed, 5 Jun 2019 06:25:22 +0000 Subject: [Haskell-cafe] Looking for a paper In-Reply-To: References: <08980c64-9195-6b48-7f6f-54a58f81bfcb@orlitzky.com> <9BBD5F52-13B3-4B66-A927-EE7A954E86F2@ouroborus.net> Message-ID: Richard, Op wo 5 jun. 2019 om 04:22 schreef Richard O'Keefe >: a programming language I used in the 80s that was designed in the 60s used x.f and that worked very nicely with thinking of record fields as functions. Interesting. At some point, there was some discussion on doing the same in GHC, but the idea does not seem to have been looked into further. https://mail.haskell.org/pipermail/glasgow-haskell-users/2013-June/024018.html Do you have a reference for this old language that used x.f? Thanks, Dominique -------------- next part -------------- An HTML attachment was scrubbed... URL: From diaz.carrete at gmail.com Wed Jun 5 20:29:48 2019 From: diaz.carrete at gmail.com (=?UTF-8?B?RGFuaWVsIETDrWF6?=) Date: Wed, 5 Jun 2019 22:29:48 +0200 Subject: [Haskell-cafe] conduit/pipes/streaming and prompt cleanup - using a decorator In-Reply-To: References: Message-ID: I tried to tackle this problem in my "streaming-bracketed" library http://hackage.haskell.org/package/streaming-bracketed, by using a "decorator" that wraps regular streams, as opposed to having a resource-aware base monad. When lifting take-like functions to the decorator, new deallocation actions are inserted. On Tue, Jun 4, 2019 at 2:53 PM wrote: > I'm using the 'streaming' library and realized it doesn't close files in a > timely way for the way I'm using it, and in fact can't, due to how the > library > works. I know conduit has put a lot of thought into closing resources in a > timely way, so I did an experiment to see what it does, but as far as I can > tell, conduit has the same problem. Maybe I'm doing it wrong? > > The situation is that I'm opening multiple files and mixing their output. > I want to close the inputs as soon as I'm done with them. But I can get > done with them earlier than the end of the file. Since all of these > libraries > are based on pulling from downstream, if you don't pull all the way to the > end, > the close at the end doesn't happen, and has to wait until runResourceT > returns, which is too late. I remember long ago reading Oleg's original > iteratee paper, and it seems like he called out this problem with > pull-based > iterators, that the iterator doesn't know when its caller is done with it, > so > it can't close files on time. > > Here's a conduit version that I think illustrates the situation: > > import qualified Conduit as C > import Conduit ((.|)) > import qualified Control.Monad.Trans as Trans > import qualified System.IO as IO > > main :: IO () > main = C.runResourceT $ C.runConduit pipe > > pipe :: C.ConduitM a c (C.ResourceT IO) () > pipe = fileLines "TODO" .| (C.takeC 3 >> C.yield "***") > .| C.mapM_C (Trans.liftIO . putStrLn) > > fileLines :: C.MonadResource m => FilePath -> C.ConduitT i String m () > fileLines fname = C.bracketP (IO.openFile fname IO.ReadMode) close > handleLines > > handleLines :: Trans.MonadIO m => IO.Handle -> C.ConduitT i String m () > handleLines hdl = loop > where > loop = do > eof <- Trans.liftIO $ IO.hIsEOF hdl > if eof then return () else do > line <- Trans.liftIO $ IO.hGetLine hdl > C.yield line > loop > > close :: IO.Handle -> IO () > close hdl = IO.hClose hdl >> putStrLn "=== close" > > This prints the first three lines of TOOD, then ***, and then "=== close", > where the close should go before the ***s. > > As far as I can see, conduit can't do this any more than 'streaming' can, > because 'C.takeC' is just some awaits and yields, with no indication that > the final await is more special than any other await. > > I think what would be necessary to solve this is that combinators like > 'take' > have to be able to tell the stream to close, and that has to propagate > back up > to each producer that has registered a cleanup. Of course this renders the > stream invalid, so it's not safe to have any other references to the stream > around, but I guess streams are stateful in general so that's always true. > Maybe I could accumulate the finalizers in the stream data type and have > combinators like 'take' call it as soon as they've taken their last. What > I actually wound up doing was make a 'takeClose' that also takes a 'close' > action to run when its done with the stream. It's not exactly general but > I'm > not writing a library so I don't need general. > > Is there some kind of standard or built-in solution for this situation? > I know others have given a lot more thought to streaming than I have, > so surely this issue has come up. > > I know there is a lot of talk about "prompt finalisation" and streams vs. > pipes vs. conduit, and talk about brackets and whatnot, but despite reading > various documents (https://hackage.haskell.org/package/streaming-with, > > http://www.haskellforall.com/2013/01/pipes-safe-10-resource-management-and.html > , > etc.) I still don't really understand what they're talking about. > It seems like they're really about reliable cleanup when there are > exceptions, not really about prompt cleanup. Certainly pipes-safe doesn't > do > prompt cleanup, at least not the kind I'm talking about. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From publicityifl at gmail.com Fri Jun 7 09:12:12 2019 From: publicityifl at gmail.com (Jurriaan Hage) Date: Fri, 7 Jun 2019 02:12:12 -0700 Subject: [Haskell-cafe] Final call for regular papers for IFL 2019 (Implementation and Application of Functional Languages) Message-ID: Hello, Please, find below the call for papers for IFL 2019. With respect to the previous call, the deadline for submitting regular papers has been changed to June 15th. Please forward these to anyone you think may be interested. Apologies for any duplicates you may receive. best regards, Jurriaan Hage Publicity Chair of IFL --- ================================================================================ IFL 2019 31st Symposium on Implementation and Application of Functional Languages National University of Singapore September 25th-27th, 2019 http://2019.iflconference.org ================================================================================ ### Scope The goal of the IFL symposia is to bring together researchers actively engaged in the implementation and application of functional and function-based programming languages. IFL 2019 will be a venue for researchers to present and discuss new ideas and concepts, work in progress, and publication-ripe results related to the implementation and application of functional languages and function-based programming. Topics of interest to IFL include, but are not limited to: - language concepts - type systems, type checking, type inferencing - compilation techniques - staged compilation - run-time function specialization - run-time code generation - partial evaluation - (abstract) interpretation - metaprogramming - generic programming - automatic program generation - array processing - concurrent/parallel programming - concurrent/parallel program execution - embedded systems - web applications - (embedded) domain specific languages - security - novel memory management techniques - run-time profiling performance measurements - debugging and tracing - virtual/abstract machine architectures - validation, verification of functional programs - tools and programming techniques - (industrial) applications ### Keynote Speaker * Olivier Danvy, Yale-NUS College ### Submissions and peer-review Differently from previous editions of IFL, IFL 2019 solicits two kinds of submissions: * Regular papers (12 pages including references) * Draft papers for presentations ('weak' limit between 8 and 15 pages) Regular papers will undergo a rigorous review by the program committee, and will be evaluated according to their correctness, novelty, originality, relevance, significance, and clarity. A set of regular papers will be conditionally accepted for publication. Authors of conditionally accepted papers will be provided with committee reviews along with a set of mandatory revisions. Regular papers not accepted for publication will be considered as draft papers, at the request of the author. Draft papers will be screened to make sure that they are within the scope of IFL, and will be accepted for presentation or rejected accordingly. Prior to the symposium: Authors of conditionally accepted papers and accepted presentations will submit a pre-proceedings version of their work that will appear in the draft proceedings distributed at the symposium. The draft proceedings does not constitute a formal publication. We require that at least one of the authors present the work at IFL 2019. After the symposium: Authors of conditionally accepted papers will submit a revised versions of their paper for the formal post-proceedings. The program committee will assess whether the mandatory revisions have been adequately addressed by the authors and thereby determines the final accept/reject status of the paper. Our interest is to ultimately accept all conditionally accepted papers. If you are an author of a conditionally accepted paper, please make sure that you address all the concerns of the reviewers. Authors of accepted presentations will be given the opportunity to incorporate the feedback from discussions at the symposium and will be invited to submit a revised full article for the formal post-proceedings. The program committee will evaluate these submissions according to their correctness, novelty, originality, relevance, significance, and clarity, and will thereby determine whether the paper is accepted or rejected. ### Publication The formal proceedings will appear in the International Conference Proceedings Series of the ACM Digital Library. At no time may work submitted to IFL be simultaneously submitted to other venues; submissions must adhere to ACM SIGPLAN's republication policy: http://www.sigplan.org/Resources/Policies/Republication ### Important dates Submission of regular papers: June 15, 2019 Submission of draft papers: July 15, 2019 Regular and draft papers notification: August 1, 2019 Deadline for early registration: August 15, 2019 Submission of pre-proceedings version: September 15, 2019 IFL Symposium: September 25-27, 2019 Submission of papers for post-proceedings: November 30, 2019 Notification of acceptance: January 31, 2020 Camera-ready version: February 29, 2020 ### Submission details All contributions must be written in English. Papers must use the ACM two columns conference format, which can be found at: http://www.acm.org/publications/proceedings-template Authors submit through EasyChair: https://easychair.org/conferences/?conf=ifl2019 ### Peter Landin Prize The Peter Landin Prize is awarded to the best paper presented at the symposium every year. The honored article is selected by the program committee based on the submissions received for the formal review process. The prize carries a cash award equivalent to 150 Euros. ### Organization and Program committee Chairs: Jurrien Stutterheim (Standard Chartered Bank Singapore), Wei Ngan Chin (National University of Singapore) Program Committee: - Olaf Chitil, University of Kent - Clemens Grelck, University of Amsterdam - Daisuke Kimura, Toho University - Pieter Koopman, Radboud University - Tamas Kozsik, Eotvos Lorand University - Roman Leschinskiy, Facebook - Ben Lippmeier, The University of New South Wales - Marco T. Morazan, Seton Hall University - Sven-Bodo Scholz, Heriot-Watt University - Tom Schrijvers, Katholieke Universiteit Leuven - Alejandro Serrano, Utrecht University - Tony Sloane, Macquarie University - Simon Thompson, University of Kent - Marcos Viera, Universidad de la Republica - Wei Ngan Chin, NUS - Jurrien Stutterheim, Standard Chartered Bank ### Venue The 31st IFL is organized by the National University of Singapore. Singapore is located in the heart of South-East Asia, and the city itself is extremely well connected by trains and taxis. See the website for more information on the venue. ### Acknowledgments This call-for-papers is an adaptation and evolution of content from previous instances of IFL. We are grateful to prior organizers for their work, which is reused here. A part of IFL 2019 format and CFP language that describes conditionally accepted papers has been adapted from call-for-papers of OOPSLA conferences. -------------- next part -------------- An HTML attachment was scrubbed... URL: From nikivazou at gmail.com Sat Jun 8 09:15:28 2019 From: nikivazou at gmail.com (Niki Vazou) Date: Sat, 8 Jun 2019 11:15:28 +0200 Subject: [Haskell-cafe] HiW'19: Call for Talks Message-ID: Hey all, Haskell Implementors Workshop is calling for talk proposals. Co-located with ICFP it is an ideal place to describe a Haskell library, a Haskell extension, works-in-progress, demo a new Haskell-related tool, or even propose future lines of Haskell development. Deadline is June 28th. Call for Talks The 11th Haskell Implementors’ Workshop is to be held alongside ICFP 2019 this year in Berlin. It is a forum for people involved in the design and development of Haskell implementations, tools, libraries, and supporting infrastructure, to share their work and discuss future directions and collaborations with others. Talks and/or demos are proposed by submitting an abstract, and selected by a small program committee. There will be no published proceedings. The workshop will be informal and interactive, with open spaces in the timetable and room for ad-hoc discussion, demos and lightning talks. Scope and Target Audience It is important to distinguish the Haskell Implementors’ Workshop from the Haskell Symposium which is also co-located with ICFP 2019. The Haskell Symposium is for the publication of Haskell-related research. In contrast, the Haskell Implementors’ Workshop will have no proceedings – although we will aim to make talk videos, slides and presented data available with the consent of the speakers. The Implementors’ Workshop is an ideal place to describe a Haskell extension, describe works-in-progress, demo a new Haskell-related tool, or even propose future lines of Haskell development. Members of the wider Haskell community encouraged to attend the workshop – we need your feedback to keep the Haskell ecosystem thriving. Students working with Haskell are specially encouraged to share their work. The scope covers any of the following topics. There may be some topics that people feel we’ve missed, so by all means submit a proposal even if it doesn’t fit exactly into one of these buckets: - Compilation techniques - Language features and extensions - Type system implementation - Concurrency and parallelism: language design and implementation - Performance, optimization and benchmarking - Virtual machines and run-time systems - Libraries and tools for development or deployment Talks We invite proposals from potential speakers for talks and demonstrations. We are aiming for 20-minute talks with 5 minutes for questions and changeovers. We want to hear from people writing compilers, tools, or libraries, people with cool ideas for directions in which we should take the platform, proposals for new features to be implemented, and half-baked crazy ideas. Please submit a talk title and abstract of no more than 300 words. Submissions can be made via HotCRP at https://icfp-hiw19.hotcrp.com/ until June 28th (anywhere on earth). We will also have lightning talks session. These have been very well received in recent years, and we aim to increase the time available to them. Lightning talks be ~7mins and are scheduled on the day of the workshop. Suggested topics for lightning talks are to present a single idea, a work-in-progress project, a problem to intrigue and perplex Haskell implementors, or simply to ask for feedback and collaborators. Invited Speakers - Lennart Augustsson & Satnam Singh Program Committee - Jose Calderon (Galois, Inc) - Jasper Van der Jeugt (Fugue) - Niki Vazou (IMDEA Software Institute) - Ningning Xie (The University of Hong King) - Brent Yorgey (Hendrix College) Best, Niki Vazou -------------- next part -------------- An HTML attachment was scrubbed... URL: From qdunkan at gmail.com Mon Jun 10 00:50:38 2019 From: qdunkan at gmail.com (Evan Laforge) Date: Sun, 9 Jun 2019 17:50:38 -0700 Subject: [Haskell-cafe] conduit/pipes/streaming and prompt cleanup - using a decorator In-Reply-To: References: Message-ID: On Wed, Jun 5, 2019 at 1:30 PM Daniel Díaz wrote: > > I tried to tackle this problem in my "streaming-bracketed" library http://hackage.haskell.org/package/streaming-bracketed, by using a "decorator" that wraps regular streams, as opposed to having a resource-aware base monad. > > When lifting take-like functions to the decorator, new deallocation actions are inserted. Oops, I didn't notice this response, sorry! I did look at streaming-bracketed, but I think it doesn't apply in my case, because the file lifespans are overlapping, not nested. If I understand correctly, that's the case where you need something like resourcet, and brackets won't do. In the end, I just gave 'take' a finalizer argument. Not exactly general purpose but it solved my problem. From Graham.Hutton at nottingham.ac.uk Mon Jun 10 13:38:00 2019 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Mon, 10 Jun 2019 13:38:00 +0000 Subject: [Haskell-cafe] Assistant/Associate Professorships in Nottingham Message-ID: Dear all, As part of a strategic expansion, the School of Computer Science at the University of Nottingham is seeking to make multiple new appointments at the Assistant or Associate Professor level: https://tinyurl.com/y4qfdqps https://tinyurl.com/y2uw6tsa Applications in the area of the Functional Programming (FP) lab are strongly encouraged! The FP lab is keen to receive applications from candidates with an excellent publication record (e.g. papers in leading venues such as LICS, POPL, ICFP, JFP, TOPLAS, etc) and the ability to secure external funding to support their research. Further information about the FP lab is available from: https://tinyurl.com/y2ekdkqa The deadline for applications is Monday 8th July 2019. The advert mentions some specific research areas, but the positions are open to applicants from any area of Computer Science. -- Graham Hutton and Thorsten Altenkirch 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 K.Bleijenberg at lijbrandt.nl Tue Jun 11 10:57:11 2019 From: K.Bleijenberg at lijbrandt.nl (Kees Bleijenberg) Date: Tue, 11 Jun 2019 12:57:11 +0200 Subject: [Haskell-cafe] creating dll fails: missing references Message-ID: <000601d52044$6b950190$42bf04b0$@lijbrandt.nl> HI all, I try to create a dll with ghc (ver 8.6.5) on Windows 7 64 bits. I 'am using the dll with loadLibrary in a cpp program in Visual Studio. I create the dll with: ghc Vogels.hs ghc -c StartEnd.c ghc --make -static -shared -fPIC Vogels.o StartEnd.o -o Vogels.dll StartEnd.o defines HsStart and HsEnd to initialize and close the Haskell runtime. This works. I can create the dll and use the dll in VS. But, if I replace in Vogels.hs the line b=True with b <- doesFileExist vogelsFn, creating the dll fails with error message: Vogels.o:fake:(.text+0x35c): undefined reference to `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileEx ist_closure' Vogels.o:fake:(.text+0x37d): undefined reference to `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileEx ist_closure' Vogels.o:fake:(.data+0xd0): undefined reference to `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileEx ist_closure' It looks like GHC can't find the Directory package. I've installed this package. What can I do about it and how can I find out the dependencies in a *.hs or *.o file? Almost all documentation about dll's is about Linux or about using dll's in Haskell. Kees {-# LANGUAGE BlockArguments #-} {-# LANGUAGE ForeignFunctionInterface #-} module Vogels ( loadVogels ) where import System.Directory import Foreign.Ptr import Foreign.Storable import Foreign.C.String loadVogels :: String -> IO (Either String String) loadVogels vogelsFn = do -- b <- doesFileExist vogelsFn let b=True if b then return $ Left $ "Can\'t find " ++ vogelsFn else do txt <- readFile vogelsFn return $ Right txt loadVogelsFFI :: Ptr Int -> CString -> IO CString loadVogelsFFI messageKind vogelsFnFFI = do vogelsFn <- peekCString vogelsFnFFI eitherRes <- loadVogels vogelsFn case eitherRes of Left errMsg -> do poke messageKind 1 newCString errMsg Right txt -> do poke messageKind 0 newCString txt foreign export ccall loadVogelsFFI :: Ptr Int -> CString -> IO CString --- Dit e-mailbericht is gecontroleerd op virussen met Avast antivirussoftware. https://www.avast.com/antivirus -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Tue Jun 11 12:29:01 2019 From: lonetiger at gmail.com (Phyx) Date: Tue, 11 Jun 2019 13:29:01 +0100 Subject: [Haskell-cafe] creating dll fails: missing references In-Reply-To: <000601d52044$6b950190$42bf04b0$@lijbrandt.nl> References: <000601d52044$6b950190$42bf04b0$@lijbrandt.nl> Message-ID: You're calling gcc my hand, which means you have to tell it which packages your source need. Pass it "-package directory" and it should work. Tamar Sent from my Mobile On Tue, Jun 11, 2019, 11:57 Kees Bleijenberg wrote: > HI all, > > > > I try to create a dll with ghc (ver 8.6.5) on Windows 7 64 bits. I ‘am > using the dll with loadLibrary in a cpp program in Visual Studio. I create > the dll with: > > ghc Vogels.hs > > ghc -c StartEnd.c > > ghc --make -static -shared -fPIC Vogels.o StartEnd.o -o Vogels.dll > > > > StartEnd.o defines HsStart and HsEnd to initialize and close the Haskell > runtime. > > > > This works. I can create the dll and use the dll in VS. > > But, if I replace in Vogels.hs the line b=True with b <- doesFileExist > vogelsFn, creating the dll fails with error message: > > Vogels.o:fake:(.text+0x35c): undefined reference to > `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileExist_closure' > > > Vogels.o:fake:(.text+0x37d): undefined reference to > `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileExist_closure' > > > Vogels.o:fake:(.data+0xd0): undefined reference to > `directoryzm1zi3zi3zi2zmB9tglvOQ6L9Cf7zzVEJ1S6t_SystemziDirectory_doesFileExist_closure' > > > > > It looks like GHC can’t find the Directory package. I’ve installed this > package. What can I do about it and how can I find out the dependencies in > a *.hs or *.o file? Almost all documentation about dll’s is about Linux or > about using dll’s in Haskell. > > > > Kees > > > > > {-# LANGUAGE BlockArguments #-} > > {-# LANGUAGE ForeignFunctionInterface #-} > > module Vogels ( > > loadVogels > > ) where > > > > import System.Directory > > import Foreign.Ptr > > import Foreign.Storable > > import Foreign.C.String > > > > loadVogels :: String -> IO (Either String String) > > loadVogels vogelsFn = do > > -- b <- doesFileExist vogelsFn > > let b=True > > if b > > then return $ Left $ "Can\'t find " ++ vogelsFn > > else do > > txt <- readFile vogelsFn > > return $ Right txt > > > > loadVogelsFFI :: Ptr Int -> CString -> IO CString > > loadVogelsFFI messageKind vogelsFnFFI = do > > vogelsFn <- peekCString vogelsFnFFI > > eitherRes <- loadVogels vogelsFn > > case eitherRes of > > Left errMsg -> do > > poke messageKind 1 > > newCString errMsg > > Right txt -> do > > poke messageKind 0 > > newCString txt > > > > foreign export ccall loadVogelsFFI :: Ptr Int -> CString -> IO CString > > > Virusvrij. > www.avast.com > > <#m_-6065090672777258572_DAB4FAD8-2DD7-40BB-A1B8-4E2AA1F9FDF2> > _______________________________________________ > 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 mail at changlinli.com Tue Jun 11 23:52:45 2019 From: mail at changlinli.com (Changlin Li) Date: Tue, 11 Jun 2019 19:52:45 -0400 Subject: [Haskell-cafe] Is there any place with nightly/master builds of GHC? Message-ID: I'm interested in benchmarking GHC compile times (that is how long it takes GHC to compile a given file) on a more granular basis than official releases. It would be nice to save myself the hassle of re-building GHC across many different commits if there already was some archive of GHC builds (e.g. from master), even if it's a rolling archive over a short time window (e.g. per-week). Changlin From gershomb at gmail.com Wed Jun 12 03:55:14 2019 From: gershomb at gmail.com (Gershom B) Date: Tue, 11 Jun 2019 23:55:14 -0400 Subject: [Haskell-cafe] Final Call for Participation: Compose Conference [NYC, Jun 22- 23 2019] Message-ID: =============================================== Final Call for Participation Compose Conference 2019 Mon June 24 - Tue June 25 2019 (Unconference on Sat Jun 22 - Sun Jun 23) New York, NY Deadline for registration: June 14 at 11pm EST. http://www.composeconference.org/2019 =============================================== The practice and craft of functional programming :: Conference Compose is a conference for typed functional programmers, focused specifically on Haskell, OCaml, F#, SML, and related technologies. Typed functional programming has been taken up widely, by industry and hobbyists alike. For many of us it has renewed our belief that code should be beautiful, and that programming can be as enjoyable as it is practical. Compose is about bringing together functional programmers of all levels of skill and experience — from technical leads to novices, and from long-time hackers to students just getting started. It will feature a two days of great and wide-ranging talks * Invited Keynotes Donya Quick - Making Algorithmic Music David Spivak - Compositional Graphical Logic * Accepted Talks and Tutorials Kenny Foner - Functors of the World, Unite! Phillip Carter - The anatomy of the F# tools for Visual Studio Sebastien Mondet - Genspio: Generating Shell Phrases In OCaml Justin Le - Applicative Regular Expressions using the Free Alternative Gaetano Checinski - Buckaroo SAT - Solving a partially revealed SAT problem for Package Management Richard Feldman - From Rails to Elm and Haskell Samuel Gélineau - Stuck macros: deterministically interleaving macro-expansion and typechecking Vaibhav Sagar - Yes, IHaskell Can Do That! Fintan Halpenny - Bowl Full of Lentils Aditya Siram - A Tase Of ATS Ward Wheeler, Alex Washburn, Callan McGill - Phylogenetic Software in Haskell Igor Trindade Oliveira - Type Driven Secure Enclave Development using Idris David Christiansen - Bidirectional Type Checking Chris Smith - Teaching the intersection of mathematics and functional programming Brandon Kase - Fast Accumulation on Streams James Koppel - The Best Refactoring You’ve Never Heard Of Allister Beharry - Using Dependent Types in an F# DSL for Linear Algebra Diego Balseiro - Bridge Haskell and ReasonML in Production * Full abstracts: http://www.composeconference.org/2019/program * Conference Registration: https://www.eventbrite.com/e/new-york-compose-2019-tickets-56751182314 * Unconference Registration: https://www.eventbrite.com/e/new-york-compose-unconference-2019-tickets-60389859696 * Follow @composeconf on twitter for news: https://twitter.com/composeconf * On freenode irc, chat with fellow attendees at #composeconference * Corporate sponsorships are welcome. Current sponsors list forthcoming. * Policies (diversity and anti-harassment): http://www.composeconference.org/conduct * Email us with any questions at info at composeconference.org * Please forward this announcement to interested parties and lists. From iricanaycan at gmail.com Wed Jun 12 04:20:54 2019 From: iricanaycan at gmail.com (Aycan iRiCAN) Date: Tue, 11 Jun 2019 21:20:54 -0700 Subject: [Haskell-cafe] Is there any place with nightly/master builds of GHC? In-Reply-To: References: Message-ID: You may want to take a look at Nix package manager's CI server: https://hydra.nixos.org/job/nixos/staging/nixpkgs.haskell.compiler.ghcHEAD.x86_64-linux/all Yoiu can easily install any ghcHead package from this binary archive, choose a successful build, and then you can press Help button under actions, you'll get a oneliner like this: nix-env -i /nix/store/kphss7kzd8lbqdxm7pnghcvk2wmzc6b3-ghc-8.5.20180118 --option binary-caches https://cache.nixos.org It's not a very granular archive but can be useful. > On Jun 11, 2019, at 4:52 PM, Changlin Li wrote: > > I'm interested in benchmarking GHC compile times (that is how long it takes GHC to compile a given file) on a more granular basis than official releases. It would be nice to save myself the hassle of re-building GHC across many different commits if there already was some archive of GHC builds (e.g. from master), even if it's a rolling archive over a short time window (e.g. per-week). > > Changlin > > _______________________________________________ > 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 matthewtpickering at gmail.com Wed Jun 12 07:37:51 2019 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Wed, 12 Jun 2019 08:37:51 +0100 Subject: [Haskell-cafe] Is there any place with nightly/master builds of GHC? In-Reply-To: References: Message-ID: All commits are built for many platforms on master. The bindists are saved for a week by default. You can download and install the suitable one for your platform. https://gitlab.haskell.org/ghc/ghc/commits/master I have also written some convenience scripts for downloading and installing them if you use nix. http://mpickering.github.io/posts/2019-06-11-ghc-artefact.html On Wed, Jun 12, 2019 at 12:53 AM Changlin Li wrote: > > I'm interested in benchmarking GHC compile times (that is how long it > takes GHC to compile a given file) on a more granular basis than > official releases. It would be nice to save myself the hassle of > re-building GHC across many different commits if there already was some > archive of GHC builds (e.g. from master), even if it's a rolling archive > over a short time window (e.g. per-week). > > Changlin > > _______________________________________________ > 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 mail at changlinli.com Wed Jun 12 18:27:18 2019 From: mail at changlinli.com (Changlin Li) Date: Wed, 12 Jun 2019 14:27:18 -0400 Subject: [Haskell-cafe] Is there any place with nightly/master builds of GHC? In-Reply-To: References: Message-ID: <1d04ce66-034f-7ed4-9aae-0eb743669346@changlinli.com> Great thank you! I'm still not wholly familiar with the GitLab CI UI and missed the link to build artifacts. On 6/12/19 3:37 AM, Matthew Pickering wrote: > All commits are built for many platforms on master. The bindists are > saved for a week by default. You can download and install the suitable > one for your platform. > > https://gitlab.haskell.org/ghc/ghc/commits/master > > I have also written some convenience scripts for downloading and > installing them if you use nix. > > http://mpickering.github.io/posts/2019-06-11-ghc-artefact.html > > On Wed, Jun 12, 2019 at 12:53 AM Changlin Li wrote: >> I'm interested in benchmarking GHC compile times (that is how long it >> takes GHC to compile a given file) on a more granular basis than >> official releases. It would be nice to save myself the hassle of >> re-building GHC across many different commits if there already was some >> archive of GHC builds (e.g. from master), even if it's a rolling archive >> over a short time window (e.g. per-week). >> >> Changlin >> >> _______________________________________________ >> 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 mail at joachim-breitner.de Wed Jun 12 20:20:32 2019 From: mail at joachim-breitner.de (Joachim Breitner) Date: Wed, 12 Jun 2019 22:20:32 +0200 Subject: [Haskell-cafe] Request for Nominations to the GHC Steering Committee Message-ID: <90af96bdb996b5ab7e826281cbb6a5b10653538b.camel@joachim-breitner.de> Dear Haskell community, the GHC Steering committee is seeking nominations for two or three new member. The committee scrutinizes, nitpicks, improves, weights and eventually accepts or rejects proposals that extend or change the language supported by GHC and other (public-facing) aspects of GHC. Our processes are described at https://github.com/ghc-proposals/ghc-proposals which is also the GitHub repository where proposals are proposed. We are looking for a member who has the ability * to understand such language extension proposals, * to find holes and missing corner cases in the specifications, * foresee the interaction with other language features and specifications, * comment constructively and improve the proposals, * judge the cost/benefit ratio and * finally come to a justifiable conclusion. We look for committee members who have some of these properties: * have substantial experience in writing Haskell applications or libraries, which they can use to inform judgements about the utility or otherwise of proposed features, * have made active contributions to the Haskell community, for some time, * have expertise in language design and implementation, in either Haskell or related languages, which they can share with us. The committee’s work requires a small, but non-trivial amount of time, especially when you are assigned a proposal for shepherding. We estimate the workload to be around 2 hours per week, and our process works best if members usually respond to technical emails within 1-2 weeks (within days is even better). Please keep that in mind if your email inbox is already overflowing. The GHC developers themselves are already well represented already. We seek Haskell _users_ more than GHC hackers. There is no shortage of people who are eager to get fancy new features into the language, both in the committee and the wider community. But each new feature imposes a cost, to implement, to learn, (particularly) through its unexpected interaction with other features. We need to strike a balance, one that encourages innovation (as GHC always has) while still making Haskell attractive for real-world production use and for teaching. We therefore explicitly invite “conservative” members of the community to join the committee. To make a nomination, please send an email to me (as the committee secretary) at mail at joachim-breitner.de until June 23th. I will distribute the nominations among the committee, and we will keep the nominations and our deliberations private. We explicitly encourage self-nominations. You can nominate others, but please obtain their explicit consent to do so. (We don’t want to choose someone who turns out to be unable to serve.) On behalf of the committee, Joachim Breitner -- Joachim Breitner mail at joachim-breitner.de http://www.joachim-breitner.de/ -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 833 bytes Desc: This is a digitally signed message part URL: From boris at d12frosted.io Thu Jun 13 05:36:33 2019 From: boris at d12frosted.io (Boris) Date: Thu, 13 Jun 2019 05:36:33 +0000 Subject: [Haskell-cafe] How to fix ambiguous type variable? Message-ID: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> Hi everyone, I was playing around with some tests and run into code that looks really similar to the following function someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (read . show . read $ s) == v But obviously, it's not clear what instance to use in the right-most read and the show functions. So it doesn't compile. Out of curiosity, is it possible to make this function compile? I've struggled some time and could not find an answer by myself, so here I am. Thanks in advance! Cheers, boris at d12frosted.io From sandeep at sras.me Thu Jun 13 05:45:23 2019 From: sandeep at sras.me (Sandeep.C.R) Date: Thu, 13 Jun 2019 11:15:23 +0530 Subject: [Haskell-cafe] How to fix ambiguous type variable? In-Reply-To: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> References: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> Message-ID: <29d7d478-523c-9b3e-c8f0-5b481a942f02@sras.me> This seems to work for me... someCheck :: forall a . (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (read . show . (read :: String -> a) $ s) == v Probably requires 'ScopedTypeVariables'... On 13/06/19 11:06 AM, Boris wrote: > someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool > someCheck s v = (read . show . read $ s) == v From ietf-dane at dukhovni.org Thu Jun 13 06:45:57 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Thu, 13 Jun 2019 02:45:57 -0400 Subject: [Haskell-cafe] How to fix ambiguous type variable? In-Reply-To: <29d7d478-523c-9b3e-c8f0-5b481a942f02@sras.me> References: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> <29d7d478-523c-9b3e-c8f0-5b481a942f02@sras.me> Message-ID: <20190613064557.GJ33899@straasha.imrryr.org> On Thu, Jun 13, 2019 at 11:15:23AM +0530, Sandeep.C.R via Haskell-Cafe wrote: > This seems to work for me... > > someCheck :: forall a. (Show a, Read a, Eq a) => String -> a -> Bool > someCheck s v = (read . show . (read :: String -> a) $ s) == v > > Probably requires 'ScopedTypeVariables'... Yes. Another variant is: {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck s (v :: a) = (read . show $ read @a s) == v which amounts to the same thing, but is perhaps simpler. For fun, with GHC 8.6 and "BlockArguments" we can drop some parentheses: {-# LANGUAGE BlockArguments #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} someCheck :: forall a. (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = v == do read $ show $ read @a s -- Viktor. From marian.jancar at gmx.com Thu Jun 13 07:50:01 2019 From: marian.jancar at gmx.com (Marian Jancar) Date: Thu, 13 Jun 2019 08:50:01 +0100 Subject: [Haskell-cafe] How to fix ambiguous type variable? In-Reply-To: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> References: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> Message-ID: <31e4e74b-ef47-4107-525d-cbbf3e6785aa@gmx.com> On 6/13/19 6:36 AM, Boris wrote: > someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool > someCheck s v = (read . show . read $ s) == v someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck s v = (r . show . r $ s) == v where r = read I believe you do intend to use the same read in both cases anyway, and letting a different read to slip in would be a bug. Marian From boris at d12frosted.io Thu Jun 13 08:25:40 2019 From: boris at d12frosted.io (Boris) Date: Thu, 13 Jun 2019 08:25:40 +0000 Subject: [Haskell-cafe] How to fix ambiguous type variable? In-Reply-To: <29d7d478-523c-9b3e-c8f0-5b481a942f02@sras.me> References: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> <29d7d478-523c-9b3e-c8f0-5b481a942f02@sras.me> Message-ID: Hi everyone! Thank you for your quick and (as always) helpful responses! -------------------------------------------------------------------------------- Sandeep, > This seems to work for me... > > someCheck :: forall a . (Show a, Read a, Eq a) => String -> a -> Bool > > someCheck s v = (read . show . (read :: String -> a) $ s) == v > > Probably requires 'ScopedTypeVariables'... I clearly tried using `forall a`, but without `ScopedTypeVariables`. That's the missing thing. Thank you very much! -------------------------------------------------------------------------------- Viktor, thank you for providing even more options! I was looking for something like `TypeApplications`! -------------------------------------------------------------------------------- Marian, Agree, a good point. And actually, your variant works without any extensions. Cheers, boris at d12frosted.io ‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Thursday, June 13, 2019 8:45 AM, Sandeep.C.R via Haskell-Cafe wrote: > This seems to work for me... > > someCheck :: forall a . (Show a, Read a, Eq a) => String -> a -> Bool > > someCheck s v = (read . show . (read :: String -> a) $ s) == v > > Probably requires 'ScopedTypeVariables'... > > On 13/06/19 11:06 AM, Boris wrote: > > > someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool > > someCheck s v = (read . show . read $ s) == v > > 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 ietf-dane at dukhovni.org Thu Jun 13 08:46:25 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Thu, 13 Jun 2019 04:46:25 -0400 Subject: [Haskell-cafe] How to fix ambiguous type variable? In-Reply-To: References: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> <29d7d478-523c-9b3e-c8f0-5b481a942f02@sras.me> Message-ID: <9E454664-7031-408B-A5FF-605C919F345B@dukhovni.org> > On Jun 13, 2019, at 4:25 AM, Boris wrote: > > Agree, a good point. And actually, your variant works without any extensions. Well, in a sense it is working with an "extension", just one that happens to be on by default and is required in Haskell 98. Namely, what makes it work is the "MonomorphismRestriction". If you specify: {-# LANGUAGE NoMonomorphismRestriction #-} then the example stops working. I like the posted example as an exceptionally clear illustration of the MonomorphismRestriction. -- Viktor. From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Thu Jun 13 09:53:15 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 13 Jun 2019 10:53:15 +0100 Subject: [Haskell-cafe] How to fix ambiguous type variable? In-Reply-To: <9E454664-7031-408B-A5FF-605C919F345B@dukhovni.org> References: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> <29d7d478-523c-9b3e-c8f0-5b481a942f02@sras.me> <9E454664-7031-408B-A5FF-605C919F345B@dukhovni.org> Message-ID: <20190613095315.2o36vhlkf3zywdcr@weber> On Thu, Jun 13, 2019 at 04:46:25AM -0400, Viktor Dukhovni wrote: > > On Jun 13, 2019, at 4:25 AM, Boris wrote: > > > > Agree, a good point. And actually, your variant works without any extensions. > > Well, in a sense it is working with an "extension", just one that > happens to be on by default and is required in Haskell 98. Namely, > what makes it work is the "MonomorphismRestriction". If you specify: > > {-# LANGUAGE NoMonomorphismRestriction #-} > > then the example stops working. I like the posted example as an > exceptionally clear illustration of the MonomorphismRestriction. And for the record, this version requires no extension nor unextension: {-# LANGUAGE NoMonomorphismRestriction #-} module Check where someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool someCheck = someCheck' read where someCheck' r s v = (r . show . r $ s) == v From boris at d12frosted.io Thu Jun 13 10:59:13 2019 From: boris at d12frosted.io (Boris) Date: Thu, 13 Jun 2019 10:59:13 +0000 Subject: [Haskell-cafe] How to fix ambiguous type variable? In-Reply-To: <20190613095315.2o36vhlkf3zywdcr@weber> References: <3G4RhIp3xgWTIjCedh213BU36GCdXYuDrv13sV7dXVrEO1agCAaDwBBBzALIVQpfox2kep6M2tabyg3Rw-wLpBe4X41pP1rU6g4EzouG-ks=@d12frosted.io> <29d7d478-523c-9b3e-c8f0-5b481a942f02@sras.me> <9E454664-7031-408B-A5FF-605C919F345B@dukhovni.org> <20190613095315.2o36vhlkf3zywdcr@weber> Message-ID: Tom, Haha, nice. Now we have someCheck defined for so many scenarios. I like it. Didn't expect to get so many answers ;) Thanks everyone! Cheers, boris at d12frosted.io ‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Thursday, June 13, 2019 12:53 PM, Tom Ellis wrote: > On Thu, Jun 13, 2019 at 04:46:25AM -0400, Viktor Dukhovni wrote: > > > > On Jun 13, 2019, at 4:25 AM, Boris boris at d12frosted.io wrote: > > > Agree, a good point. And actually, your variant works without any extensions. > > > > Well, in a sense it is working with an "extension", just one that > > happens to be on by default and is required in Haskell 98. Namely, > > what makes it work is the "MonomorphismRestriction". If you specify: > > {-# LANGUAGE NoMonomorphismRestriction #-} > > then the example stops working. I like the posted example as an > > exceptionally clear illustration of the MonomorphismRestriction. > > And for the record, this version requires no extension nor unextension: > > {-# LANGUAGE NoMonomorphismRestriction #-} > > module Check where > > someCheck :: (Show a, Read a, Eq a) => String -> a -> Bool > > someCheck = someCheck' read > where someCheck' r s v = (r . show . r $ s) == v > > > 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 manny at fpcomplete.com Thu Jun 13 18:48:25 2019 From: manny at fpcomplete.com (Emanuel Borsboom) Date: Thu, 13 Jun 2019 11:48:25 -0700 Subject: [Haskell-cafe] ANN: stack-2.1.1 release Message-ID: Announcing the first release in the stack-2.1 series! You can download bindists for all supported platforms from https://github.com/commercialhaskell/stack/releases/tag/v2.1.1 The Stack 2 release represents a series of significant changes to how Stack works internally. For the vast majority of cases, these changes are backwards compatible, in that existing projects will continue to build in the same way with Stack 2 as they did with Stack 1. The large version bump is due to the fundamental internal changes to cache handling, database storage (using SQLite in place of binary files), implicit snapshots (which greatly improve the precompiled cache), and moving to Pantry. We have also removed some less used features, as listed in the release notes below. **Changes since v1.9.3** Major changes: * Switch over to pantry for managing packages. This is a major change to Stack's internals, and affects user-visible behavior in a few places. Some highlights: * Drop support for multiple package indices and legacy `00-index.tar` style indices. See [#4137](https://github.com/commercialhaskell/stack/issues/4137). * Support for archives and repos in the `packages` section has been removed. Instead, you must use `extra-deps` for such dependencies. `packages` now only supports local filepaths. * Add support for Git repositories containing (recursive) submodules. * Addition of new configuration options for specifying a "pantry tree" key, which provides more reproducibility around builds, and (in the future) will be used for more efficient package content downloads. You can also specify package name and version for more efficient config parsing. * __NOTE__ The new `stack freeze` command provides support for automatically generating this additional information. * Package contents and metadata are stored in an SQLite database in place of files on the filesystem. The `pantry` library can be used for interacting with these contents. * Internally, Stack has changed many datatypes, including moving to Cabal's definition of many data types. As a result of such changes, existing cache files will in general be invalidated, resulting in Stack needing to rebuild many previously cached builds in the new version. Sorry :(. * A new command, `stack freeze` has been added which outputs project and snapshot definitions with dependencies pinned to their exact versions. * The `ignore-revision-mismatch` setting is no longer needed, and has been removed. * Overriding GHC boot packages results in any other GHC boot packages depending on it being no longer available as a dependency, such packages need to be added explicitly when needed. See [#4510] (https://github.com/commercialhaskell/stack/issues/4510). * Cabal solver integration was not updated to support newer `cabal-install` versions so `stack solver` command was removed as well as a related option `--solver` from `stack new` and `stack init`. * Upgrade to Cabal 2.4 * Note that, in this process, the behavior of file globbing has been modified to match that of Cabal. In particular, this means that for Cabal spec versions less than 2.4, `*.txt` will match `foo.txt`, but not `foo.2.txt`. * Remove the `stack image` command. With the advent of Docker multistage builds, this functionality is no longer useful. For an example, please see [Building Haskell Apps with Docker](https://www.fpcomplete.com/blog/2017/12/building-haskell-apps-with-docker). * Support building GHC from source (experimental) * Stack now supports building and installing GHC from source. The built GHC is uniquely identified by a commit id and an Hadrian "flavour" (Hadrian is the newer GHC build system), hence `compiler` can be set to use a GHC built from source with `ghc-git-COMMIT-FLAVOUR` * `stack.yaml` now supports a `configure-options`, which are passed directly to the `configure` step in the Cabal build process. See [#1438](https://github.com/commercialhaskell/stack/issues/1438) * Remove support for building GHCJS itself. Future releases of Stack may remove GHCJS support entirely. * Support for lock files for pinning exact project dependency versions Behavior changes: * `stack.yaml` now supports `snapshot`: a synonym for `resolver`. See [#4256](https://github.com/commercialhaskell/stack/issues/4256) * `stack script` now passes `-i -idir` in to the `ghc` invocation. This makes it so that the script can import local modules, and fixes an issue where `.hs` files in the current directory could affect interpretation of the script. See [#4538](https://github.com/commercialhaskell/stack/pull/4538) * When using `stack script`, custom snapshot files will be resolved relative to the directory containing the script. * Remove the deprecated `--upgrade-cabal` flag to `stack setup`. * Support the `drop-packages` field in `stack.yaml` * Remove the GPG signing code during uploads. The GPG signatures have never been used yet, and there are no plans to implement signature verification. * Remove the `--plain` option for the `exec` family of commands * Always use the `--exact-configuration` Cabal configuration option when building (should mostly be a non-user-visible enhancement). * No longer supports Cabal versions older than `1.19.2`. This means projects using snapshots earlier than `lts-3.0` or `nightly-2015-05-05` will no longer build. * Remove the `stack docker cleanup` command. Docker itself now has [`docker image prune`](https://docs.docker.com/engine/reference/commandline/image_prune/) and [`docker container prune`](https://docs.docker.com/engine/reference/commandline/container_prune/), which you can use instead. * Interleaved output is now turned on by default, see [#4702](https://github.com/commercialhaskell/stack/issues/4702). In addition, the `packagename> ` prefix is no longer included in interelaved mode when only building a single target. * The `-fhide-source-paths` GHC option is now enabled by default and can be disabled via the `hide-source-paths` configuration option in `stack.yaml`. See [#3784](https://github.com/commercialhaskell/stack/issues/3784) * Stack will reconfigure a package if you modify your `PATH` environment variable. See [#3138](https://github.com/commercialhaskell/stack/issues/3138). * For GHC 8.4 and later, disable the "shadowed dependencies" workaround. This means that Stack will no longer have to force reconfigures as often. See [#3554](https://github.com/commercialhaskell/stack/issues/3554). * When building a package, Stack takes a lock on the dist directory in use to avoid multiple runs of Stack from trampling each others' files. See [#2730](https://github.com/commercialhaskell/stack/issues/2730). * Stack will check occassionally if there is a new version available and prompt the user to upgrade. This will not incur any additional network traffic, as it will piggy-back on the existing Hackage index updates. You can set `recommend-stack-upgrade: false` to bypass this. See [#1681](https://github.com/commercialhaskell/stack/issues/1681). * `stack list-dependencies` has been removed in favour of `stack ls dependencies`. * The new default for `--docker-auto-pull` is enabled. See [#3332](https://github.com/commercialhaskell/stack/issues/3332). Other enhancements: * Support MX Linux in get-stack.sh. Fixes [#4769](https://github.com/commercialhaskell/stack/issues/4769). * Defer loading up of files for local packages. This allows us to get plan construction errors much faster, and avoid some unnecessary work when only building a subset of packages. This is especially useful for the curator use case. * Existing global option `--color=WHEN` is now also available as a non-project-specific yaml configuration parameter `color:`. * Adopt the standard proposed at http://no-color.org/, that color should not be added by default if the `NO_COLOR` environment variable is present. * New command `stack ls stack-colors` lists the styles and the associated 'ANSI' control character sequences that stack uses to color some of its output. See `stack ls stack-colors --help` for more information. * New global option `--stack-colors=STYLES`, also available as a non-project-specific yaml configuration parameter, allows a stack user to redefine the default styles that stack uses to color some of its output. See `stack --help` for more information. * British English spelling of 'color' (colour) accepted as an alias for `--color`, `--stack-colors`, `stack ls stack-colors` at the command line and for `color:` and `stack-colors:` in yaml configuration files. * New build option `--ddump-dir`. (See [#4225](https://github.com/commercialhaskell/stack/issues/4225)) * Stack parses and respects the `preferred-versions` information from Hackage for choosing latest version of a package in some cases, e.g. `stack unpack packagename`. * The components output in the `The main module to load is ambiguous` message now include package names so they can be more easily copy-pasted. * Git repos are shared across multiple projects. See [#3551](https://github.com/commercialhaskell/stack/issues/3551) * Use en_US.UTF-8 locale by default in pure Nix mode so programs won't crash because of Unicode in their output [#4095](https://github.com/commercialhaskell/stack/issues/4095) * Add `--tree` to `ls dependencies` to list dependencies as tree. [#4101](https://github.com/commercialhaskell/stack/issues/4101) * Add `--pedantic` to `ghci` to run with `-Wall` and `-Werror` [#4463](https://github.com/commercialhaskell/stack/issues/4463) * Add `--cabal-files` flag to `stack ide targets` command. * Add `--stdout` flag to all `stack ide` subcommands. * Use batches when unregistering packages with `ghc-pkg`. (See [#2662](https://github.com/commercialhaskell/stack/issues/2662)) * `get-stack` script now works on Windows CI machines of Appveyor, Travis and Azure Pipelines. See [#4535](https://github.com/commercialhaskell/stack/issues/4535)/ * Show snapshot being used when `stack ghci` is invoked outside of a project directory. See [#3651](https://github.com/commercialhaskell/stack/issues/3651) * The script interpreter now accepts a `--extra-dep` flag for adding packages not present in the snapshot. Currently, this only works with packages from Hackage, not Git repos or archives. * When using the script interpreter with `--optimize` or `--compile`, Stack will perform an optimization of checking whether a newer executable exists, making reruns significantly faster. There's a downside to this, however: if you have a multifile script, and change one of the dependency modules, Stack will not automatically detect and recompile. * `stack clean` will delete the entire `.stack-work/dist` directory, not just the relevant subdirectory for the current GHC version. See [#4480](https://github.com/commercialhaskell/stack/issues/4480). * Add `stack purge` as a shortcut for `stack clean --full`. See [#3863](https://github.com/commercialhaskell/stack/issues/3863). * Both `stack dot` and `stack ls dependencies` accept a `--global-hints` flag to bypass the need for an installed GHC. See [#4390](https://github.com/commercialhaskell/stack/issues/4390). * Add the `stack config env` command for getting shell script environment variables. See [#620](https://github.com/commercialhaskell/stack/issues/620). * Less verbose output from `stack setup` on Windows. See [#1212](https://github.com/commercialhaskell/stack/issues/1212). * Add an optional `ignore-expiry` flag to the `hackage-security` section of the `~/.stack/config.yaml`. It allows to disable timestamp expiration verification just like `cabal --ignore-expiry` does. The flag is not enabled by default so that the default functionality is not changed. * Include default values for most command line flags in the `--help` output. See [#893](https://github.com/commercialhaskell/stack/issues/893). * Set the `GHC_ENVIRONMENT` environment variable to specify dependency packages explicitly when running test. This is done to prevent ambiguous module name errors in `doctest` tests. * `get-stack` script now works on Windows CI machines of Appveyor, Travis and Azure Pipelines. See [#4535](https://github.com/commercialhaskell/stack/issues/4535) * Warn when a Docker image does not include a `PATH` environment variable. See [#2472](https://github.com/commercialhaskell/stack/issues/2742) * When using `system-ghc: true`, Stack will now find the appropriate GHC installation based on the version suffix, allowing you to more easily switch between various system-installed GHCs. See [#2433](https://github.com/commercialhaskell/stack/issues/2433). * `stack init` will now support create a `stack.yaml` file without any local packages. See [#2465](https://github.com/commercialhaskell/stack/issues/2465) * Store caches in SQLite database instead of files. * No longer use "global" Docker image database (`docker.db`). * User config files are respected for the script command. See [#3705](https://github.com/commercialhaskell/stack/issues/3705), [#3887](https://github.com/commercialhaskell/stack/issues/3887). * Set the `GHC_ENVIRONMENT` environment variable to `-` to tell GHC to ignore any such files when GHC is new enough (>= 8.4.4), otherwise simply unset the variable. This allows Stack to have control of package databases when running commands like `stack exec ghci`, even in the presence of implicit environment files created by `cabal new-build`. See [#4706](https://github.com/commercialhaskell/stack/issues/4706). * Use a database cache table to speed up discovery of installed GHCs * You can specify multiple `--test-arguments` options. See [#2226](https://github.com/commercialhaskell/stack/issues/2226) * Windows terminal width detection is now done. See [#3588](https://github.com/commercialhaskell/stack/issues/3588) * On Windows, informs users if the 'programs' path contains a space character and further warns users if that path does not have an alternative short ('8 dot 3') name, referencing the `local-programs-path` configuration option. See [#4726](https://github.com/commercialhaskell/stack/issues/4726) * Add `--docker-mount-mode` option to set the Docker volume mount mode for performance tuning on macOS. Bug fixes: * Ignore duplicate files for a single module when a Haskell module was generated from a preprocessor file. See [#4076](https://github.com/commercialhaskell/stack/issues/4076). * Only track down components in current directory if there are no hs-source-dirs found. This eliminates a number of false-positive warnings, similar to [#4076](https://github.com/commercialhaskell/stack/issues/4076). * Handle a change in GHC's hi-dump format around `addDependentFile`, which now includes a hash. See [yesodweb/yesod#1551](https://github.com/yesodweb/yesod/issues/1551) * Fix `subdirs` for git repos in `extra-deps` to match whole directory names. Also fixes for `subdirs: .`. See [#4292](https://github.com/commercialhaskell/stack/issues/4292) * Fix for git packages to update submodules to the correct state. See [#4314](https://github.com/commercialhaskell/stack/pull/4314) * Add `--cabal-files` flag to `stack ide targets` command. * Don't download ghc when using `stack clean`. * Support loading in GHCi definitions from symlinked C files. Without this patch, Stack will try to find object files in the directory pointed to by symlinks, while GCC will produce the object files in the original directory. See [#4402](https://github.com/commercialhaskell/stack/pull/4402) * Fix handling of GitHub and URL templates on Windows. See [commercialhaskell/stack#4394](https://github.com/commercialhaskell/stack/issues/4394) * Fix `--file-watch` not responding to file modifications when running inside docker on Mac. See [#4506](https://github.com/commercialhaskell/stack/issues/4506) * Using `--ghc-options` with `stack script --compile` now works. * Ensure the detailed-0.9 type tests work. See [#4453](https://github.com/commercialhaskell/stack/issues/4453). * Extra include and lib dirs are now order-dependent. See [#4527](https://github.com/commercialhaskell/stack/issues/4527). * Apply GHC options when building a `Setup.hs` file. See [#4526](https://github.com/commercialhaskell/stack/issues/4526). * Stack handles ABI changes in FreeBSD 12 by differentiating that version from previous. * Help text for the `templates` subcommand now reflects behaviour in stack 1.9 — that it downloads and shows a help file, rather than listing available templates. * Fix detection of aarch64 platform (this broke when we upgraded to a newer Cabal version). * Docker: fix detecting and pulling missing images with `--docker-auto-pull`, see [#4598](https://github.com/commercialhaskell/stack/issues/4598) * Hackage credentials are not world-readable. See [#2159](https://github.com/commercialhaskell/stack/issues/2159). * Warnings are dumped from logs even when color is enabled. See [#2997](https://github.com/commercialhaskell/stack/issues/2997) * `stack init` will now work for cabal files with sublibraries. See [#4408](https://github.com/commercialhaskell/stack/issues/4408) * When the Cabal spec version is newer than the global Cabal version, build against the snapshot's Cabal library. See [#4488](https://github.com/commercialhaskell/stack/issues/4488) * Docker: fix detection of expected subprocess failures. This fixes downloading a compatible `stack` executable when the host `stack` is not compatible with the Docker image (on Linux), and doesn't show an unnecessary extra error when the in-container re-exec'ed `stack` exits with failure. * The `stack ghci` command's `--ghc-options` flag now parses multiple options. See [#3315](https://github.com/commercialhaskell/stack/issues/3315). **Thanks to all our contributors for this release:** * Adam Bergmark * Akshay Mankar * Aleksey Kozin * ALeX Kazik * Alexey Kozin * Alexey Kuleshevich * Anders Kaseorg * Anders Kiel Hovgaard * Artyom Kazak * Bastian Krol * Björn Gohla * Brad Neimann * Brandon Chinn * Colin Woodbury * Cthulhu.Den * dadepo * Daniel Gröber * David Baynard * David Spies * David Vollbracht * dbaynard * Emanuel Borsboom * favonia * flip111 * Florjan Bartol * Gleb Popov * Hussein Ait-Lahcen * Isumi Feng * Janfel * Jurijs Oniscuks * Kayla Ngan * Kirill Zaborsky * Magicloud * Matt Audesse * Mauricio Fierro * Michael Sloan * Michael Snoyman * Mihai Maruseac * Mike Pilgrem * Neil Mitchell * NeonGraal * Niklas Hambüchen * penteract * Phil de Joux * Raghu Kaippully * Sibi * Sibi Prabakaran * Simon Hengel * skapazzo * Sylvain HENRY * Sylvain Henry * Taekyung * Timothy Clem * Tom Sydney Kerckhove * Valery V. Vorotyntsev * Vance Palacio * waddlaw * 欧阳泽 From michelle at galois.com Thu Jun 13 20:10:02 2019 From: michelle at galois.com (Michelle Keppler) Date: Thu, 13 Jun 2019 16:10:02 -0400 Subject: [Haskell-cafe] Posting Request Message-ID: Hello, Could you please post the following to the Haskell Cafe email? Galois is hiring for a variety of roles Including but not limited to: Software Engineers/Researchers, Project Managers, Hardware Engineers, and a Software Integration Engineer. We collaborate with organizations like NASA, DARPA, and AWS to explore blue sky ideas and turn them into usable technology. Some of the things we’ve worked on in the past: Formal methods, static analysis, cryptographic algorithms, abstract interpretation, type theory, formal verification, reinforcement learning, autonomous systems assurance, communication security, cyber-deception for network defense, DDoS defense, provable hardware security, and statistical anomaly detection for detecting advanced persistent threats. We think working here is awesome; see lifeatgalois.com . Thank you, Michelle Keppler -- Michelle Keppler Human Resources Partner michelle at galois.com 571-510-0659 *I* *galois* *I * *GALOIS, INC.* 901 N Stuart Street *I* Suite 501 *I* Arlington, VA 22203 www.galois.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sat Jun 15 16:20:26 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 15 Jun 2019 17:20:26 +0100 Subject: [Haskell-cafe] Deprecation cycle for classes Message-ID: <20190615162026.m2zqb5g4uboefick@weber> I am unsure how to change the name of a class in a library whilst providing a safe deprecation cycle for the users of the library. Suppose I have version 1 of my library with a class -- Version 1 class Foo a where foo :: a and I want to migrate it to version 3 as follows, but with a deprecation cycle provided by version 2 that allows code to work with either version 1 and 2, or 2 and 3. -- Version 3 class Bar a where bar :: a Then I can try to write version 2 as -- Version 2 {-# ConstraintKinds #-} class Foo a where bar :: a bar = foo foo :: a foo = bar type Bar = Foo This satisfies the following conditions: Users of versions 1 and 2 can use * The constraint Foo * The method foo * The class Foo and method foo for implementing their own instances User of versions 2 and 3 can use * The constraint Bar * The method bar * The method bar for implementing their own instances but they cannot jointly use * The *class* Bar for implementing their own instances (since Bar is not a class, just a Constraint) Is there any way I can write a version 2 that allows users to implement instances that work with both version 2 and version 3? Thanks, Tom From ben at well-typed.com Sat Jun 15 19:35:54 2019 From: ben at well-typed.com (Ben Gamari) Date: Sat, 15 Jun 2019 15:35:54 -0400 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.8.1-alpha2 is now available Message-ID: <874l4qzlny.fsf@smart-cactus.org> Hello everyone, The GHC team is pleased to announce the second and likely last alpha release of GHC 8.8.1. The source distribution, binary distributions, and documentation are available at https://downloads.haskell.org/~ghc/8.8.1-alpha2 A draft of the release notes is also available [1]. This release is the culmination of over 3000 commits by over one hundred contributors and has several new features and numerous bug fixes relative to GHC 8.6: * Profiling now works correctly on 64-bit Windows (although still may be problematic on 32-bit Windows due to platform limitations; see #15934) * A new code layout algorithm for amd64's native code generator * The introduction of a late lambda-lifting pass which may reduce allocations significantly for some programs. * Further work on Trees That Grow, enabling improved code re-use of the Haskell AST in tooling * More locations where users can write `forall` (GHC Proposal #0007) * Further work on the Hadrian build system This release brings a number of fixes since alpha 1: * A number of linker fixes (#16779, #16784) * The process, binary, Cabal, time, terminfo libraries have all been bumped to their final release versions * A regression rendering TemplateHaskell unusable in cross-compiled configurations has been fixed (#16331) * A regression causing compiler panics on compilation of some programs has been fixed (#16449) * -Wmissing-home-modules now handles hs-boot files correctly (#16551) * A regression causing some programs to fail at runtime has been fixed (#16066) Due to on-going work on our release and testing infrastructure this cycle is proceeding at a pace significantly slower than expected. However, we anticipate that this investment will allow us to release a more reliable, easier-to-install compiler on the planned six-month release cadence in the future. As always, if anything looks amiss do let us know. Happy compiling! Cheers, - Ben [1] https://downloads.haskell.org/ghc/8.8.1-alpha2/docs/html/users_guide/8.8.1-notes.html -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From jack at jackkelly.name Sat Jun 15 23:59:27 2019 From: jack at jackkelly.name (Jack Kelly) Date: Sun, 16 Jun 2019 09:59:27 +1000 Subject: [Haskell-cafe] Deprecation cycle for classes In-Reply-To: <20190615162026.m2zqb5g4uboefick@weber> (Tom Ellis's message of "Sat, 15 Jun 2019 17:20:26 +0100") References: <20190615162026.m2zqb5g4uboefick@weber> Message-ID: <878su2h02o.fsf@jackkelly.name> Tom Ellis writes: > I am unsure how to change the name of a class in a library whilst providing > a safe deprecation cycle for the users of the library. Suppose I have > version 1 of my library with a class > > -- Version 1 > class Foo a where > foo :: a > > and I want to migrate it to version 3 as follows, but with a deprecation > cycle provided by version 2 that allows code to work with either version 1 > and 2, or 2 and 3. > > -- Version 3 > class Bar a where > bar :: a What if you inserted Bar as a superclass of Foo in V2? -- Version 1 class Foo a where foo :: a -- Version 2 {-# DEPRECATED Foo "it's going away in V3" #-} class Bar a => Foo a where foo :: a class Bar a where bar :: a -- Version 3 class Bar a where bar :: a Users of version 1 can use Foo/foo/... When they upgrade to version 2, they get forced to write a Bar instance, get warned that Foo is going away, and they can use the class Bar to implement their own instances. Users of version 3 can only use Bar/bar/... Does that help? -- Jack From ietf-dane at dukhovni.org Sun Jun 16 03:51:33 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sat, 15 Jun 2019 23:51:33 -0400 Subject: [Haskell-cafe] Deprecation cycle for classes In-Reply-To: <20190615162026.m2zqb5g4uboefick@weber> References: <20190615162026.m2zqb5g4uboefick@weber> Message-ID: <5CB56925-498C-4967-A14C-CCB2AE7496F2@dukhovni.org> > On Jun 15, 2019, at 12:20 PM, Tom Ellis wrote: > > I am unsure how to change the name of a class in a library whilst providing > a safe deprecation cycle for the users of the library. Suppose I have > version 1 of my library with a class Is this perhaps essentially: https://gitlab.haskell.org/ghc/ghc/issues/7543 -- Viktor. From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Jun 16 06:39:35 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 16 Jun 2019 07:39:35 +0100 Subject: [Haskell-cafe] Deprecation cycle for classes In-Reply-To: <878su2h02o.fsf@jackkelly.name> References: <20190615162026.m2zqb5g4uboefick@weber> <878su2h02o.fsf@jackkelly.name> Message-ID: <20190616063935.kea7da7p2q3zz2zs@weber> On Sun, Jun 16, 2019 at 09:59:27AM +1000, Jack Kelly wrote: > Tom Ellis writes: > > > I am unsure how to change the name of a class in a library whilst providing > > a safe deprecation cycle for the users of the library. Suppose I have > > version 1 of my library with a class > > > > -- Version 1 > > class Foo a where > > foo :: a > > > > and I want to migrate it to version 3 as follows, but with a deprecation > > cycle provided by version 2 that allows code to work with either version 1 > > and 2, or 2 and 3. > > > > -- Version 3 > > class Bar a where > > bar :: a > > What if you inserted Bar as a superclass of Foo in V2? > > -- Version 1 > class Foo a where > foo :: a > > -- Version 2 > {-# DEPRECATED Foo "it's going away in V3" #-} > class Bar a => Foo a where > foo :: a > > class Bar a where > bar :: a > > -- Version 3 > class Bar a where > bar :: a > > Users of version 1 can use Foo/foo/... > > When they upgrade to version 2, they get forced to write a Bar instance, > get warned that Foo is going away, and they can use the class Bar to > implement their own instances. Unfortunately I don't think this scheme allows the user to write code that is compatible with version 1 and version 2 at the same time. From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sun Jun 16 07:02:20 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 16 Jun 2019 08:02:20 +0100 Subject: [Haskell-cafe] Deprecation cycle for classes In-Reply-To: <5CB56925-498C-4967-A14C-CCB2AE7496F2@dukhovni.org> References: <20190615162026.m2zqb5g4uboefick@weber> <5CB56925-498C-4967-A14C-CCB2AE7496F2@dukhovni.org> Message-ID: <20190616070220.f6ucp3aem7bt44v3@weber> On Sat, Jun 15, 2019 at 11:51:33PM -0400, Viktor Dukhovni wrote: > > On Jun 15, 2019, at 12:20 PM, Tom Ellis wrote: > > > > I am unsure how to change the name of a class in a library whilst providing > > a safe deprecation cycle for the users of the library. Suppose I have > > version 1 of my library with a class > > Is this perhaps essentially: > > https://gitlab.haskell.org/ghc/ghc/issues/7543 It's closely related and indeed option 2 that Edward Yang proposes below would allow me to do what I want: "Allow instance declarations on constraint synonyms, but only if after desugaring the synonym, you end up with a single class head." https://gitlab.haskell.org/ghc/ghc/issues/13267 From ietf-dane at dukhovni.org Sun Jun 16 07:13:45 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sun, 16 Jun 2019 03:13:45 -0400 Subject: [Haskell-cafe] Deprecation cycle for classes In-Reply-To: <20190616070220.f6ucp3aem7bt44v3@weber> References: <20190615162026.m2zqb5g4uboefick@weber> <5CB56925-498C-4967-A14C-CCB2AE7496F2@dukhovni.org> <20190616070220.f6ucp3aem7bt44v3@weber> Message-ID: <20190616071345.GC84864@straasha.imrryr.org> On Sun, Jun 16, 2019 at 08:02:20AM +0100, Tom Ellis wrote: > On Sat, Jun 15, 2019 at 11:51:33PM -0400, Viktor Dukhovni wrote: > > > On Jun 15, 2019, at 12:20 PM, Tom Ellis wrote: > > > > > > I am unsure how to change the name of a class in a library whilst providing > > > a safe deprecation cycle for the users of the library. Suppose I have > > > version 1 of my library with a class > > > > Is this perhaps essentially: > > > > https://gitlab.haskell.org/ghc/ghc/issues/7543 > > It's closely related and indeed option 2 that Edward Yang proposes below > would allow me to do what I want: > > "Allow instance declarations on constraint synonyms, but only if after > desugaring the synonym, you end up with a single class head." > > https://gitlab.haskell.org/ghc/ghc/issues/13267 Your motivation sounds quite reasonable, though the issues appear to be difficult, maybe if you ask again there'll be a different answer this time? -- Viktor. From matthewtpickering at gmail.com Mon Jun 17 10:24:16 2019 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Mon, 17 Jun 2019 11:24:16 +0100 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.8.1-alpha2 is now available In-Reply-To: <874l4qzlny.fsf@smart-cactus.org> References: <874l4qzlny.fsf@smart-cactus.org> Message-ID: There seems to be no debian8 bindist which is different from every release at least back to ghc-8.0.1. On Sat, Jun 15, 2019 at 8:36 PM Ben Gamari wrote: > > Hello everyone, > > The GHC team is pleased to announce the second and likely last alpha > release of GHC 8.8.1. The source distribution, binary distributions, and > documentation are available at > > https://downloads.haskell.org/~ghc/8.8.1-alpha2 > > A draft of the release notes is also available [1]. > > This release is the culmination of over 3000 commits by over one hundred > contributors and has several new features and numerous bug fixes > relative to GHC 8.6: > > * Profiling now works correctly on 64-bit Windows (although still may > be problematic on 32-bit Windows due to platform limitations; see > #15934) > > * A new code layout algorithm for amd64's native code generator > > * The introduction of a late lambda-lifting pass which may reduce > allocations significantly for some programs. > > * Further work on Trees That Grow, enabling improved code re-use of the > Haskell AST in tooling > > * More locations where users can write `forall` (GHC Proposal #0007) > > * Further work on the Hadrian build system > > This release brings a number of fixes since alpha 1: > > * A number of linker fixes (#16779, #16784) > > * The process, binary, Cabal, time, terminfo libraries have all been > bumped to their final release versions > > * A regression rendering TemplateHaskell unusable in cross-compiled > configurations has been fixed (#16331) > > * A regression causing compiler panics on compilation of some programs > has been fixed (#16449) > > * -Wmissing-home-modules now handles hs-boot files correctly (#16551) > > * A regression causing some programs to fail at runtime has been fixed > (#16066) > > Due to on-going work on our release and testing infrastructure this > cycle is proceeding at a pace significantly slower than expected. > However, we anticipate that this investment will allow us to release a > more reliable, easier-to-install compiler on the planned six-month > release cadence in the future. > > As always, if anything looks amiss do let us know. > > Happy compiling! > > Cheers, > > - Ben > > [1] https://downloads.haskell.org/ghc/8.8.1-alpha2/docs/html/users_guide/8.8.1-notes.html > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From ben at well-typed.com Mon Jun 17 12:23:09 2019 From: ben at well-typed.com (Ben Gamari) Date: Mon, 17 Jun 2019 08:23:09 -0400 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.8.1-alpha2 is now available In-Reply-To: References: <874l4qzlny.fsf@smart-cactus.org> Message-ID: That is true and this will be fixed for the release candidate. However Debian 8 is now no longer Debian's current stable release so I wasn't prioritizing this issue. If the lack of a Debian 8 distribution is preventing anyone from testing please let me know. Cheers, - Ben On June 17, 2019 6:24:16 AM EDT, Matthew Pickering wrote: >There seems to be no debian8 bindist which is different from every >release at least back to ghc-8.0.1. > >On Sat, Jun 15, 2019 at 8:36 PM Ben Gamari wrote: >> >> Hello everyone, >> >> The GHC team is pleased to announce the second and likely last alpha >> release of GHC 8.8.1. The source distribution, binary distributions, >and >> documentation are available at >> >> https://downloads.haskell.org/~ghc/8.8.1-alpha2 >> >> A draft of the release notes is also available [1]. >> >> This release is the culmination of over 3000 commits by over one >hundred >> contributors and has several new features and numerous bug fixes >> relative to GHC 8.6: >> >> * Profiling now works correctly on 64-bit Windows (although still >may >> be problematic on 32-bit Windows due to platform limitations; see >> #15934) >> >> * A new code layout algorithm for amd64's native code generator >> >> * The introduction of a late lambda-lifting pass which may reduce >> allocations significantly for some programs. >> >> * Further work on Trees That Grow, enabling improved code re-use of >the >> Haskell AST in tooling >> >> * More locations where users can write `forall` (GHC Proposal #0007) >> >> * Further work on the Hadrian build system >> >> This release brings a number of fixes since alpha 1: >> >> * A number of linker fixes (#16779, #16784) >> >> * The process, binary, Cabal, time, terminfo libraries have all been >> bumped to their final release versions >> >> * A regression rendering TemplateHaskell unusable in cross-compiled >> configurations has been fixed (#16331) >> >> * A regression causing compiler panics on compilation of some >programs >> has been fixed (#16449) >> >> * -Wmissing-home-modules now handles hs-boot files correctly >(#16551) >> >> * A regression causing some programs to fail at runtime has been >fixed >> (#16066) >> >> Due to on-going work on our release and testing infrastructure this >> cycle is proceeding at a pace significantly slower than expected. >> However, we anticipate that this investment will allow us to release >a >> more reliable, easier-to-install compiler on the planned six-month >> release cadence in the future. >> >> As always, if anything looks amiss do let us know. >> >> Happy compiling! >> >> Cheers, >> >> - Ben >> >> [1] >https://downloads.haskell.org/ghc/8.8.1-alpha2/docs/html/users_guide/8.8.1-notes.html >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -- Sent from my Android device with K-9 Mail. Please excuse my brevity. -------------- next part -------------- An HTML attachment was scrubbed... URL: From dennis.raddle at gmail.com Mon Jun 17 20:55:30 2019 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Mon, 17 Jun 2019 13:55:30 -0700 Subject: [Haskell-cafe] functional languages - pretty good for students! Message-ID: I've been doing computer science tutoring for a few years in languages like Java and Python. I started teaching a 10th grade student Elm recently. I'd like to use Haskell at some point, but because he likes websites and games, Elm seemed more apropos. What I'm discovering is that a functional language like Elm is fairly natural to him and he's learning quickly! Our lessons prior to Elm (including Python, Java, and JavaScript at this point) are extracurricular and he hasn't put much study in-between lessons, so his progress has been slow. I don't think he's developed many "programming muscles." But now, his progress in Elm is faster. One factor, I think, is how concise functional code is. He hasn't developed much "programmer's eye" up to now (by which I mean scanning a lot of code quickly) but Elm, being much shorter, is easier for him to grasp at a glance. He also thinks the algebraic data model is cool. He sees how it's related to classes and subclasses, but he appreciates how relatively simple it is. Mike -------------- next part -------------- An HTML attachment was scrubbed... URL: From nadine.and.henry at pobox.com Tue Jun 18 03:42:45 2019 From: nadine.and.henry at pobox.com (Henry Laxen) Date: Mon, 17 Jun 2019 22:42:45 -0500 Subject: [Haskell-cafe] Lenses and Nested Maps Message-ID: <23816.23989.345264.924722@gargle.gargle.HOWL> Hi Cafe, Suppose I have: s :: Map String (Map Int Char) s = M.fromList [("alice", M.fromList [(5,'a')]), ("bob", M.fromList [(6,'b')])] Is there any way to modify the 'b' entry easily using lenses? Thanks in advance. Best wishes, Henry Laxen From david.feuer at gmail.com Tue Jun 18 03:55:23 2019 From: david.feuer at gmail.com (David Feuer) Date: Mon, 17 Jun 2019 23:55:23 -0400 Subject: [Haskell-cafe] Lenses and Nested Maps In-Reply-To: <23816.23989.345264.924722@gargle.gargle.HOWL> References: <23816.23989.345264.924722@gargle.gargle.HOWL> Message-ID: The main lensy tools for maps are the At and Ixed classes, both found in Control.Lens.At. On Mon, Jun 17, 2019, 11:45 PM Henry Laxen wrote: > Hi Cafe, > > Suppose I have: > > s :: Map String (Map Int Char) > s = M.fromList [("alice", M.fromList [(5,'a')]), ("bob", M.fromList > [(6,'b')])] > > Is there any way to modify the 'b' entry easily using lenses? > > Thanks in advance. > Best wishes, > Henry Laxen > > _______________________________________________ > 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 mgsloan at gmail.com Tue Jun 18 03:55:11 2019 From: mgsloan at gmail.com (Michael Sloan) Date: Mon, 17 Jun 2019 21:55:11 -0600 Subject: [Haskell-cafe] Lenses and Nested Maps In-Reply-To: <23816.23989.345264.924722@gargle.gargle.HOWL> References: <23816.23989.345264.924722@gargle.gargle.HOWL> Message-ID: Hi Henry, Yes, the "ix" function traverses into particular keys of map-like structures https://www.stackage.org/haddock/lts-13.25/lens-4.17.1/Control-Lens-At.html#v:ix So, (s & ix "bob" . ix 6 .~ 'c') will yield a modified Map with 'b' changed to 'c'. -Michael On Mon, Jun 17, 2019 at 9:45 PM Henry Laxen wrote: > > Hi Cafe, > > Suppose I have: > > s :: Map String (Map Int Char) > s = M.fromList [("alice", M.fromList [(5,'a')]), ("bob", M.fromList [(6,'b')])] > > Is there any way to modify the 'b' entry easily using lenses? > > Thanks in advance. > Best wishes, > Henry Laxen > > _______________________________________________ > 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 jack at jackkelly.name Tue Jun 18 03:56:40 2019 From: jack at jackkelly.name (Jack Kelly) Date: Tue, 18 Jun 2019 13:56:40 +1000 Subject: [Haskell-cafe] Lenses and Nested Maps In-Reply-To: <23816.23989.345264.924722@gargle.gargle.HOWL> (Henry Laxen's message of "Mon, 17 Jun 2019 22:42:45 -0500") References: <23816.23989.345264.924722@gargle.gargle.HOWL> Message-ID: <8736k7tukn.fsf@jackkelly.name> Henry Laxen writes: > s :: Map String (Map Int Char) > s = M.fromList [("alice", M.fromList [(5,'a')]), ("bob", M.fromList [(6,'b')])] `ix` will give you a `Traversal` that targets a given key. If it's not present in the map, you get a `Traversal` that hits no targets. t :: Map String (Map Int Char) t = s & ix "bob" . ix 6 %~ succ *Main> t fromList [("alice",fromList [(5,'a')]),("bob",fromList [(6,'c')])] If you want more control (to set or delete values, for instance), the `at` function gives you a lens that views a `Maybe`. Writing `Just` into the lens creates the value at the key, and writing `Nothing` into the lens removes the value at the key. The `(?~)` operator, and the `_Just` prism may be useful to you if you use `at`. HTH, -- Jack From simons at nospf.cryp.to Tue Jun 18 07:01:57 2019 From: simons at nospf.cryp.to (Peter Simons) Date: Tue, 18 Jun 2019 09:01:57 +0200 Subject: [Haskell-cafe] How to define classy lenses for polymorphic types that involve singletons? References: <8736kp35s0.fsf@write-only.cryp.to> <1bf7878b-72a2-e940-33b8-14cb0b83ccb3@gmail.com> Message-ID: <87pnnbml5m.fsf@write-only.cryp.to> Hi Li-yao, >> In theory, I should be able to make SomePerson an >> instance of HasPerson, define >> >> person :: Lens' SomePerson (Person sex) > > I wonder what you mean by that, since you highlight > the issue just after. what I meant is that defining that instance is the intended purpose of the HasPerson type class. That entire construct exists so that -- in theory -- I can make SomePerson an instance of it and use it exactly the same way as I would use a 'Person'. It's just that the theory doesn't work out. I can't make SomePerson an instance of HasPerson even though it clearly *has* a Person inside that I *can* access. Now, I understand why SomePerson cannot be an instance of HasPerson. What I wonder is whether there is maybe a way to define HasPerson such that I *can* make SomePerson and instance of it and use it like I would use a Person type as far as the lenses are concerned. I have outlined one such solution in my posting, but that solution feels awkward because it requires quite a bit of glue code. So, I was hoping that someone could point me to a better way to define the *class* in order to make it applicable to SomePerson in the way HasPerson is intended to be used. Best regards, Peter From pea at pea.sh Wed Jun 19 01:53:55 2019 From: pea at pea.sh (Ashlynn Anderson) Date: Tue, 18 Jun 2019 21:53:55 -0400 Subject: [Haskell-cafe] functional languages - pretty good for students! In-Reply-To: References: Message-ID: >What I'm discovering is that a functional language like >Elm >is fairly natural to him and he's learning quickly! This is something I've wondered about a lot and is very interesting to hear actual results on (despite it just being in regards to one student) Despite the connections often drawn between programming and mathematics, imperative programming requires a fairly different model of thinking than most mathematics I'd argue, so I've always believed that if properly presented, functional programming would be simpler to pick up and possibly even lead to more understandable code down the line even when working in imperative languages. Of course, the mathematical density of Haskell concepts themselves is a problem, but it's interesting to hear how easily your student has picked up a "beginner-focused" functional language like Elm as opposed to other "easy languages" that are more imperative. Ashlynn -------------- next part -------------- An HTML attachment was scrubbed... URL: From evan at evan-borden.com Wed Jun 19 16:28:49 2019 From: evan at evan-borden.com (Evan Borden) Date: Wed, 19 Jun 2019 11:28:49 -0500 Subject: [Haskell-cafe] ANN brittany-0.12.0.0 Message-ID: Hello, I am happy to announce the release of brittany version 0.12.0.0. This version includes a number of fantastic improvements from many excellent contributors. Additionally brittany will soon be added back to stackage. In the meantime it can be built with the stack.yaml in its source or with cabal v2-build. https://hackage.haskell.org/package/brittany-0.12.0.0 Contributors ============ * Benjamin Kovach @5outh * Doug Beardsley @mightybyte * Evan Borden @eborden * Lennart Spitzner @lspitzner * Matt Noonan @moatt-noonan * Phil Hazelden @ChickenProp * Rupert Horlick @ruhatch * Sergey Vinokurov @sergv New Collaborators ================= You may be wondering why I am sending this message instead of Lennart. Taylor Fausak and I are taking on some of the maintenance for brittany. We will hopefully lift some of the burden from Lennart so he can remain the guiding light and driving force behind the project. Changes ========== This release includes many bug fixes, additional support for a number of syntactic constructs and a few layouting modifications. For full details check the change log on github: https://github.com/lspitzner/brittany/blob/master/ChangeLog.md Again thank you to brittany's fantastic contributors for helping making this release happen. -- Evan From evan at evan-borden.com Thu Jun 20 03:15:10 2019 From: evan at evan-borden.com (Evan Borden) Date: Wed, 19 Jun 2019 22:15:10 -0500 Subject: [Haskell-cafe] ANN: network-3.1.0.1 Message-ID: Hello, I'm happy to announce the release of network-3.1.0.1. This release includes a few maintenance changes. http://hackage.haskell.org/package/network-3.1.0.1 Contributors ============ * Evan Borden @eborden * Jack Kelly @endgame * Kazu Yamamoto @kazu-yamamoto * Leif Metcalf @leifmetcalf Changes ======= You can view the changes on github. https://github.com/haskell/network/releases/tag/v3.1.0.1 Thank you to network's contributors for their continued support. -- Evan Borden From nikivazou at gmail.com Fri Jun 21 09:48:38 2019 From: nikivazou at gmail.com (Niki Vazou) Date: Fri, 21 Jun 2019 11:48:38 +0200 Subject: [Haskell-cafe] HiW'19: Second Call for Talks In-Reply-To: References: Message-ID: Hey all, A second reminder to submit your talk proposals to HiW. Submission deadline is in one week. Call for Talks The 11th Haskell Implementors’ Workshop is to be held alongside ICFP 2019 this year in Berlin. It is a forum for people involved in the design and development of Haskell implementations, tools, libraries, and supporting infrastructure, to share their work and discuss future directions and collaborations with others. Talks and/or demos are proposed by submitting an abstract, and selected by a small program committee. There will be no published proceedings. The workshop will be informal and interactive, with open spaces in the timetable and room for ad-hoc discussion, demos and lightning talks. Scope and Target Audience It is important to distinguish the Haskell Implementors’ Workshop from the Haskell Symposium which is also co-located with ICFP 2019. The Haskell Symposium is for the publication of Haskell-related research. In contrast, the Haskell Implementors’ Workshop will have no proceedings – although we will aim to make talk videos, slides and presented data available with the consent of the speakers. The Implementors’ Workshop is an ideal place to describe a Haskell extension, describe works-in-progress, demo a new Haskell-related tool, or even propose future lines of Haskell development. Members of the wider Haskell community encouraged to attend the workshop – we need your feedback to keep the Haskell ecosystem thriving. Students working with Haskell are specially encouraged to share their work. The scope covers any of the following topics. There may be some topics that people feel we’ve missed, so by all means submit a proposal even if it doesn’t fit exactly into one of these buckets: - Compilation techniques - Language features and extensions - Type system implementation - Concurrency and parallelism: language design and implementation - Performance, optimization and benchmarking - Virtual machines and run-time systems - Libraries and tools for development or deployment Talks We invite proposals from potential speakers for talks and demonstrations. We are aiming for 20-minute talks with 5 minutes for questions and changeovers. We want to hear from people writing compilers, tools, or libraries, people with cool ideas for directions in which we should take the platform, proposals for new features to be implemented, and half-baked crazy ideas. Please submit a talk title and abstract of no more than 300 words. Submissions can be made via HotCRP at https://icfp-hiw19.hotcrp.com/ until June 28th (anywhere on earth). We will also have lightning talks session. These have been very well received in recent years, and we aim to increase the time available to them. Lightning talks be ~7mins and are scheduled on the day of the workshop. Suggested topics for lightning talks are to present a single idea, a work-in-progress project, a problem to intrigue and perplex Haskell implementors, or simply to ask for feedback and collaborators. Invited Speakers - Lennart Augustsson & Satnam Singh Program Committee - Jose Calderon (Galois, Inc) - Jasper Van der Jeugt (Fugue) - Niki Vazou (IMDEA Software Institute) - Ningning Xie (The University of Hong King) - Brent Yorgey (Hendrix College) Best, Niki Vazou -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Sat Jun 22 15:01:01 2019 From: ben at well-typed.com (Ben Gamari) Date: Sat, 22 Jun 2019 11:01:01 -0400 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.8.1-alpha2 is now available In-Reply-To: References: <874l4qzlny.fsf@smart-cactus.org> Message-ID: <877e9dy89j.fsf@smart-cactus.org> George Colpitts writes: > Will 8.8.1 use llvm 7.0.1? I don't see it mentioned in the release notes. > Yes, this release will target LLVM 7. I'll add a mention to the release notes. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From leah at vuxu.org Sun Jun 23 14:52:51 2019 From: leah at vuxu.org (Leah Neukirchen) Date: Sun, 23 Jun 2019 16:52:51 +0200 Subject: [Haskell-cafe] Munich Haskell Meeting, 2019-06-25 @ 19:30 Message-ID: <87blyo8ibg.fsf@vuxu.org> Dear all, Next week, our monthly Munich Haskell Meeting will take place again on Tuesday, June 25 at **Hirschgarten (self-service area)** at 19h30. The weather should be nice! 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-jun-2019/ Everybody is welcome! cu, -- Leah Neukirchen https://leahneukirchen.org/ From DekuDekuplex at Yahoo.com Sun Jun 23 17:20:11 2019 From: DekuDekuplex at Yahoo.com (Benjamin L. Russell) Date: Mon, 24 Jun 2019 02:20:11 +0900 Subject: [Haskell-cafe] How long does it take to add an entry to https://www.haskell.org/community/? Message-ID: Twenty-three days ago, I added an entry to the list of Haskell communities at https://www.haskell.org/community/ and submitted a pull request to have the page (https://github.com/haskell-infra/www.haskell.org/blob/master/community.markdown) updated; however, the page still has not been updated. In addition, it seems that there are 3 other pull requests for the same page by other users that have also not been applied, the earliest of which dates from March 16. How long does it take to add an entry to https://www.haskell.org/community/? (I'm assuming that submitting a pull request to "Update community.markdown" on Github is the correct procedure for those users without write access to the page.) -- Benjamin L. Russell -- Benjamin L. Russell / DekuDekuplex at Yahoo dot com http://dekudekuplex.wordpress.com/ Computer Science Document Translator/Editor "Furuike ya, kawazu tobikomu mizu no oto." -- Matsuo Basho^ From icfp.publicity at googlemail.com Mon Jun 24 21:13:21 2019 From: icfp.publicity at googlemail.com (Sam Tobin-Hochstadt) Date: Mon, 24 Jun 2019 17:13:21 -0400 Subject: [Haskell-cafe] Call for Participation: ICFP 2019 Message-ID: <5d113cf1e98_25202adb8252c5b428cf@homer.mail> ===================================================================== Call for Participation ICFP 2019 24th ACM SIGPLAN International Conference on Functional Programming and affiliated events August 18 - August 23, 2019 Berlin, Germany http://icfp19.sigplan.org/ Early Registration until July 18! ===================================================================== ICFP provides a forum for researchers and developers to hear about the latest work on the design, implementations, principles, and uses of functional programming. The conference covers the entire spectrum of work, from practice to theory, including its peripheries. This year, ICFP is co-located with BOBKonf! * Overview and affiliated events: http://icfp19.sigplan.org/home * Program: http://icfp19.sigplan.org/program/program-icfp-2019 * Accepted papers: http://icfp19.sigplan.org/track/icfp-2019-papers * Registration is available via: https://regmaster4.com/2019conf/ICFP19/register.php Early registration ends 18 July, 2019. * Programming contest: https://icfpcontest2019.github.io/ * Student Research Competition: https://icfp19.sigplan.org/track/icfp-2019-Student-Research-Competition * Follow us on Twitter for the latest news: http://twitter.com/icfp_conference In addition to BOBKonf (8/21), there are several events co-located with ICFP: * Erlang Workshop (8/18) * Functional Art, Music, Modeling and Design (8/23) * Functional High-Performance and Numerical Computing (8/18) * Haskell Implementors' Workshop (8/23) * Haskell Symposium (8/22-8/23) * miniKanren Workshop (8/22) * ML Family Workshop (8/22) * OCaml Workshop (8/23) * Programming Languages Mentoring Workshop (8/18) * Scheme Workshop (8/18) * Type-Driven Development (8/18) ### 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 Tue Jun 25 10:43:03 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 25 Jun 2019 12:43:03 +0200 Subject: [Haskell-cafe] extra semi-colons Message-ID: Dear Cafe, why does ghc accept the extra semi-colon in case () of { () -> (); } or even case () of { ;;; () -> () ;;; } Yes I understand that semicolons like this are introduce by the layout rule L ( : ts) (m : ms) = ; : (L ts (m : ms)) if m = n https://www.haskell.org/onlinereport/haskell2010/haskellch10.html#x17-17800010.3 and it's convenient to ignore extra ones. But it's not in the grammar? alts → alt1 ; … ; altn (n ≥ 1) https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-460003.13 - J. From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Tue Jun 25 13:47:29 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Tue, 25 Jun 2019 14:47:29 +0100 Subject: [Haskell-cafe] extra semi-colons In-Reply-To: References: Message-ID: <20190625134729.k5iuwobg6kdst4ir@weber> On Tue, Jun 25, 2019 at 12:43:03PM +0200, Johannes Waldmann wrote: > But it's not in the grammar? > > alts → alt1 ; … ; altn (n ≥ 1) > > https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-460003.13 The rule "alt" allows "(empty alternative)" From bernardobruno at gmail.com Tue Jun 25 14:45:27 2019 From: bernardobruno at gmail.com (Bruno Bernardo) Date: Tue, 25 Jun 2019 16:45:27 +0200 Subject: [Haskell-cafe] (Extended deadline) Formal Methods 2019 - 1st Workshop on Formal Methods for Blockchains, CFP Message-ID: [ Please distribute, apologies for multiple postings. ] ========================================================== 1st Workshop on Formal Methods for Blockchains (FMBC) 2019 https://sites.google.com/view/fmbc/home Porto, Portugal, October 11 Part of the 3rd World Congress on Formal Methods http://formalmethods2019.inesctec.pt/ ------------------------------------------------------------- IMPORTANT DATES -------------------------------- Abstract submission: June 30, 2019 (extended) Full paper submission: July 7, 2019 (extended) Notification: July 31, 2019 Camera-ready: September 2, 2019 Conference: October 11, 2019 -------------------------------- -------------------------------- TOPICS OF INTEREST -------------------------------- Blockchains are decentralized transactional ledgers that rely on cryptographic hash functions for guaranteeing the integrity of the stored data. Participants on the network reach agreement on what valid transactions are through consensus algorithms. Blockchains may also provide support for Smart Contracts. Smart Contracts are scripts of an ad-hoc programming language that are stored in the blockchain and that run on the network. They can interact with the ledger’s data and update its state. These scripts can express the logic of possibly complex contracts between users of the blockchain. Thus, Smart Contracts can facilitate the economic activity of blockchain participants. With the emergence and increasing popularity of cryptocurrencies such as Bitcoin and Ethereum, it is now of utmost importance to have strong guarantees of the behavior of blockchain so ware. These guarantees can be brought by using Formal Methods. Indeed, Blockchain software encompasses many topics of computer science where using Formal Methods techniques and tools are relevant: consensus algorithms to ensure the liveness and the security of the data on the chain, programming languages specifically designed to write smart contracts, cryptographic protocols, such as zero-knowledge proofs, used to ensure privacy, etc. This workshop is a forum to identify theoretical and practical approaches of formal methods for blockchain technology. Topics include, but are not limited to: * Design and implementation of Smart Contract languages * Formal models of blockchain applications or concepts * Formal methods for consensus protocols * Formal methods for blockchain-specific cryptographic primitives or   protocols Formal languages for Smart * Verification of Smart Contracts -------------------------------- -------------------------------- SUBMISSION -------------------------------- Submit original manuscripts (not published or considered elsewhere) with a maximum of twelve pages (regular papers), six pages (short papers), and two pages (extended abstract) describing new and emerging ideas or summarizing existing work). Each paper should include a title and the name and affiliation of each author. Authors of selected extended-abstracts are invited to give a short lightning talk of up to 15 minutes. At least one author of an accepted paper is expected to present the paper at the workshop as a registered participant. All accepted contributions will be reviewed once more by the program committee after the workshop and before being included in the post-proceedings. submission link https://easychair.org/conferences/?conf=fmbc19 -------------------------------- -------------------------------- PROCEEDINGS -------------------------------- All submissions will be peer-reviewed by at least three members of the program committee for quality and relevance. Accepted regular papers (full and short papers) will be included in the FM workshop post-proceedings, published as a volume of the Lecture Notes in Computer Science (LNCS) by Springer. -------------------------------- -------------------------------- INVITED SPEAKER --------------------------------------------------------------------------------------------------------- Ilya Sergey - Associate Professor at Yale-NUS College and NUS School of Computing, (Singapore). --------------------------------------------------------------------------------------------------------- -------------------------------- -------------------------------- PROGRAM committee -------------------------------- Program Chairs Bruno Bernardo (bruno at nomadic-labs.com ) Néstor Cataño (nestor.catano at gmail.com ) Diego Marmsoler (diego.marmsoler at tum.de ) Program Committee Pietro Abate (Nomadic Labs, France) Ijaz Ahmed (University of Madeira, Portuga) Jonathan Aldrich (Carnegie Mellon University, USA) Bernhard Beckert (Karlsruhe Institute of Technology, Germany) Bruno Bernardo (Nomadic Labs, France) Sukriti Bhattacharya (LIST, Luxembourg) Néstor Cataño (Universidad del Norte, Colombia) Maria Christakis (MPI-SWS, Germany) Léa-Zaynah Dargaye (CEA LIST, France) Georges Gonthier (Inria, France) Neville Grech (University of Athens, Greece / University of Malta, Malta) Davide Grossi (University of Groningen, Netherlands) Sorren Hanvey (Liverpool John Moores University, UK) Andreas Lochbihler (Digital Asset, Swiss) Diego Marmsoler (Technische Universitat Munchen, Germany) Anastasia Mavridou (NASA Ames, USA) Simão Melo de Sousa (Universidade da Beira Interior, Portugal) Fabio Mogavero (Università degli Studi di Napoli, Italy) Peter Csaba Ölveczky (University of Oslo, Norway) Karl Palmskog (University of Texas at Austin, USA) Vincent Rahli (University of Luxembourg, Luxembourg) Steve Reeves (University of Waikato, New Zealand) Camilo Rueda (Pontificia Universidad Javeriana, Colombia) Claudio Russo (Dfinity Foundation, USA) Jorge Sousa Pinto (Universidade do Minho, Portugal) Bas Spitters (Aarhus University, Denmark) Christoph Sprenger (ETH, Zürich) Mark Staples (Data61, Australia) Philip Wadler (University of Edinburgh / IOHK, UK) Xi Wu (The University of Queensland, Australia) Santiago Zanella-Beguelin (Microsoft Research Cambridge, UK) -------------------------------- -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Wed Jun 26 06:24:54 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Wed, 26 Jun 2019 02:24:54 -0400 Subject: [Haskell-cafe] Unexpected result from Data.Compact.inCompact? Message-ID: <20190626062454.GC84864@straasha.imrryr.org> I am seeing surprising results from 'inCompact' after 'compact'. It seems there are additional limitations on what can be compacted, with 'compact' not throwing a 'CompactionFailed' exception in some cases, and yet not compacting the value. Is this expected? When the below is compiled and run: {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Data.Compact import qualified Data.ByteString.Short as S import qualified Data.Map.Strict as M fib :: [Int] fib = 0:1:zipWith (+) fib (tail fib) u = if M.lookup 3 m == Just 2 then () else undefined f3 = head $ drop 3 fib m = M.fromList $ zip [0..9] fib main :: IO () main = do test "explicit ()" () test "computed ()" u test "explicit Int" (42 :: Int) test "computed Int" f3 test "empty string" ("" :: String) test "non-empty string" ("some string" :: String) test "empty short bytestring" S.empty test "non-empty short bytestring" (S.toShort "some bytestring") test "explict empty map" (M.empty :: M.Map Int Int) test "computed fib table" m where test :: String -> a -> IO () test msg val = do putStr (msg ++ ": ") c <- compact val inCompact c (getCompact c) >>= print it outputs: explicit (): False computed (): False explicit Int: False computed Int: True empty string: False non-empty string: True empty short bytestring: True non-empty short bytestring: True explict empty map: False computed fib table: True but the documentation promises: getCompact :: Compact a -> a # Retrieve a direct pointer to the value pointed at by a Compact reference. If you have used compactAdd, there may be multiple Compact references into the same compact region. Upholds the property: inCompact c (getCompact c) == True so when 'compact' does not bottom, I'd expect 'True'. -- Viktor. From trent.shipley at gmail.com Wed Jun 26 06:51:16 2019 From: trent.shipley at gmail.com (trent shipley) Date: Tue, 25 Jun 2019 23:51:16 -0700 Subject: [Haskell-cafe] OT: CLR and JVM Message-ID: Is there a typed, functional language with mature versions on Microsoft's CLR and the JVM? A JVM OCaml to go with F# would be ideal. Trent -------------- next part -------------- An HTML attachment was scrubbed... URL: From lanablack at amok.cc Wed Jun 26 11:24:54 2019 From: lanablack at amok.cc (Lana Black) Date: Wed, 26 Jun 2019 11:24:54 +0000 Subject: [Haskell-cafe] Reshaping arrays in accelerate Message-ID: <42199765-6f8c-e8aa-0498-0215350ae5eb@amok.cc> Hello cafe, Is there a generic way to reshape an array in accelerate[1] assuming the number of dimensions remains constant? For example, given a matrix, is there a way to add or, more importantly, remove several rows or columns? It seems to me that the API is lacking in this case, but I hope I'm wrong. Thank you. [1]: https://hackage.haskell.org/package/accelerate-1.2.0.1/ From bertram.felgenhauer at googlemail.com Wed Jun 26 16:08:26 2019 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Wed, 26 Jun 2019 18:08:26 +0200 Subject: [Haskell-cafe] Unexpected result from Data.Compact.inCompact? In-Reply-To: <20190626062454.GC84864@straasha.imrryr.org> References: <20190626062454.GC84864@straasha.imrryr.org> Message-ID: <20190626160826.GA1704@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Viktor Dukhovni wrote: > I am seeing surprising results from 'inCompact' after 'compact'. > It seems there are additional limitations on what can be compacted, > with 'compact' not throwing a 'CompactionFailed' exception in some > cases, and yet not compacting the value. Is this expected? This seems to be a documentation problem. `compact` forces and copies /most/ of the data, but there are some exceptions: - data that is already compacted is not copied (this does not happen in your example, I think) - statically allocated data is not copied either. This includes nullary constructors like (), [], or Data.Map.Internal.Tip (the empty map) as well as many statically known values like 42 :: Int See also shouldCompact(), https://github.com/ghc/ghc/blob/master/rts/sm/CNF.c#L615 which is called several times in stg_compactAddWorkerzh, https://github.com/ghc/ghc/blob/master/rts/Compact.cmm#L50 Cheers, Bertram From johannes.waldmann at htwk-leipzig.de Wed Jun 26 19:07:50 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Wed, 26 Jun 2019 21:07:50 +0200 Subject: [Haskell-cafe] extra semi-colons Message-ID: <12364059-304f-d9f5-e9fa-374898be41af@htwk-leipzig.de> > The rule "alt" allows "(empty alternative)" Ah, yes. But no? The standard says > A case expression must have at least one alternative > and each alternative must have at least one body. Should this be "each non-empty alternative must have ..."? I think the intention is to allow case () of () | False -> () | True -> () (one alternative, two bodies) but to disallow case () of () (one alternative, no body) - J. From allbery.b at gmail.com Wed Jun 26 19:09:45 2019 From: allbery.b at gmail.com (Brandon Allbery) Date: Wed, 26 Jun 2019 15:09:45 -0400 Subject: [Haskell-cafe] extra semi-colons In-Reply-To: <12364059-304f-d9f5-e9fa-374898be41af@htwk-leipzig.de> References: <12364059-304f-d9f5-e9fa-374898be41af@htwk-leipzig.de> Message-ID: As of at least recently, empty cases are entirely permitted (and used for e.g. Void / nullary types). On Wed, Jun 26, 2019 at 3:08 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > > The rule "alt" allows "(empty alternative)" > > Ah, yes. But no? The standard says > > > A case expression must have at least one alternative > > and each alternative must have at least one body. > > Should this be "each non-empty alternative must have ..."? > > I think the intention is to allow > > case () of () | False -> () | True -> () > > (one alternative, two bodies) but to disallow > > case () of () > > (one alternative, no body) > > - 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 Wed Jun 26 19:19:48 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Wed, 26 Jun 2019 21:19:48 +0200 Subject: [Haskell-cafe] extra semi-colons In-Reply-To: References: <12364059-304f-d9f5-e9fa-374898be41af@htwk-leipzig.de> Message-ID: <205e91d3-8c5a-2902-295c-8965330b7572@htwk-leipzig.de> On 6/26/19 9:09 PM, Brandon Allbery wrote: > As of at least recently, empty cases are entirely permitted Yes I know, but this is not about "empty case" (= no alternative?), but about one (or more) empty alternatives (that are accepted without -XEmptyCase ). I admit it's not related to any practical problem. It came up in the following way: a student who compared ghc's behaviour to that of a purpose-built parser for case expressions that I wrote for my e-Learning/testing system. And I thought - well, the Standard certainly should explain ghc's behaviour, but I have a hard time parsing it. More nit-picking: while "case () of { }" prompts the "Use EmptyCase" hint, "case () of { ; }" is a parse error (no hint), with or without -XEmptyCase. - J From trevor.mcdonell at gmail.com Thu Jun 27 14:35:38 2019 From: trevor.mcdonell at gmail.com (Trevor McDonell) Date: Thu, 27 Jun 2019 16:35:38 +0200 Subject: [Haskell-cafe] Reshaping arrays in accelerate In-Reply-To: <42199765-6f8c-e8aa-0498-0215350ae5eb@amok.cc> References: <42199765-6f8c-e8aa-0498-0215350ae5eb@amok.cc> Message-ID: Hi Lana, The `reshape` operation in Accelerate just changes the extent of an array without changing the underlying data. But, for example, the following will select only the the given (by index) rows of a matrix: selectRows :: Elt e => Acc (Vector Int) -> Acc (Matrix e) -> Acc (Matrix e) selectRows rs xs = let Z :. rows = unlift (shape rs) cols = indexHead (shape xs) in generate (index2 rows cols) (\ix -> let Z :. r :. c = unlift ix in xs ! index2 (rs!!r) c) We could generalise this to other dimensions as well; I'd probably use lenses for that. I'm not really sure if this fits what you're looking for, so I'd be interested to hear more about what you're trying to achieve. In general I'm happy to add common utility functions like this to the API; you're welcome to make feature requests via the GitHub issue tracker as well: https://github.com/AccelerateHS/accelerate/issues Cheers, -Trev On Wed, 26 Jun 2019 at 13:25, Lana Black wrote: > Hello cafe, > > Is there a generic way to reshape an array in accelerate[1] assuming the > number of dimensions remains constant? For example, given a matrix, is > there a way to add or, more importantly, remove several rows or columns? > > It seems to me that the API is lacking in this case, but I hope I'm wrong. > > Thank you. > > [1]: https://hackage.haskell.org/package/accelerate-1.2.0.1/ > _______________________________________________ > 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 selinger at mathstat.dal.ca Thu Jun 27 21:19:03 2019 From: selinger at mathstat.dal.ca (Peter Selinger) Date: Thu, 27 Jun 2019 18:19:03 -0300 (ADT) Subject: [Haskell-cafe] Intention to take over package "quipper" Message-ID: <20190627211903.CB058140633@chase.mathstat.dal.ca> I am writing, as recommended at https://wiki.haskell.org/Taking_over_a_package, to announce my intention to take over the "quipper" package on Hackage. I have contacted the author (miniBill, aka Leonardo Taglialegne) in February 2019, and again this Tuesday, with no response. I am one of the authors of Quipper, and the code in miniBill's "quipper" package was actually written by me and my coauthors. Since the package is both outdated and incomplete, and he is not maintaining it, we would like to assume ownership of the package. Thanks, -- Peter From brucker at spamfence.net Sat Jun 29 20:00:58 2019 From: brucker at spamfence.net (Achim D. Brucker) Date: Sat, 29 Jun 2019 21:00:58 +0100 Subject: [Haskell-cafe] Call For Papers: Workshop in OCL and Textual Modeling (OCL 2019) Message-ID: <20190629200058.ihsitsw75ckxbwdi@ananogawa.home.brucker.ch> CALL FOR PAPERS 19th International Workshop on OCL and Textual Modeling Co-located with MODELS 2019 ACM/IEEE 22nd International Conference on Model Driven Engineering Languages and System, September 15-20, 2019, Munich, Germany http://oclworkshop.github.io The goal of this workshop is to create a forum where researchers and practitioners interested in building models using OCL or other kinds of textual languages (e.g., OCL, textual MOF, Epsilon, or Alloy) can directly interact, report advances, share results, identify tools for language development, and discuss appropriate standards. In particular, the workshop will encourage discussions for achieving synergy from different modeling language concepts and modeling language use. The close interaction will enable researchers and practitioners to identify common interests and options for potential cooperation. ## Topics of interest Topics of interest include (but are not limited to): - Mappings between textual modeling languages and other languages/formalisms - Mathematical models and/or formal semantics for textual modeling languages - Algorithms, evaluation strategies and optimizations in the context of textual modeling languages for: - validation, verification, and testing, - model transformation and code generation, - meta-modeling and DSLs, and - query and constraint specifications - Alternative graphical/textual notations for textual modeling languages - Evolution, transformation and simplification of textual modeling expressions - Libraries, templates and patterns for textual modeling languages - Tools that support textual modeling languages (e.g., verification of OCL formulae, runtime monitoring of invariants) - Model-driven security using textual modeling languages - Complexity results for textual modeling languages - Quality models and benchmarks for comparing and evaluating textual modeling tools and algorithms - Successful applications of textual modeling languages - Case studies on industrial applications of textual modeling languages - Experience reports: - usage of textual modeling languages and tools in complex domains, - usability of textual modeling languages and tools for end-users - Empirical studies about the benefits and drawbacks of textual modeling languages - Innovative textual modeling tools - Comparison, evaluation and integration of modeling languages - Correlation between modeling languages and modeling tasks We particularly encourage submissions describing applications and case studies of textual modeling as well as test suites and benchmark collections for evaluating textual modeling tools. ## Submissions Four types of submissions will be considered: * Presentation only submission (not included in the workshop proceedings), e.g., for already published work. Authors should submit a short (1 page) abstract of their presentation. * Short papers (between 5 and 7 pages) describing new ideas or position papers. * Tool papers (between 5 and 7 pages) describing tools supporting textual modeling tools * Full papers (between 10 and 14 pages). All submissions should follow the LNCS format guidelines and should be uploaded to [EasyChair](https://easychair.org/conferences/?conf=ocl2019). Accepted papers will be published online in [CEUR](http://www.ceur-ws.org). ## Important Dates - Submission of papers: 14 Jul 2019 - Notification: 25 Aug 2019 - Pre-Workshop CRC: 9 Sep 2019 - Post-Workshop CRC: 5 Oct 2019 -- Prof. Achim Brucker | Chair in Cybersecurity & Head of Group | University of Exeter https://www.brucker.ch | https://logicalhacking.com/blog @adbrucker | @logicalhacking