From bryan at haskell.foundation Thu Jun 1 14:55:44 2023 From: bryan at haskell.foundation (Bryan Richter) Date: Thu, 1 Jun 2023 17:55:44 +0300 Subject: [Haskell-cafe] type error when specializing lens zooms in ghc >= 9.0 In-Reply-To: <63cb8f6f43bd4cd385e46493a6176b7cfb6d3aeb.camel@aatal-apotheke.de> References: <3a3ba5c235db4c827a2cfe2ac7abc83dadb41524.camel@aatal-apotheke.de> <63cb8f6f43bd4cd385e46493a6176b7cfb6d3aeb.camel@aatal-apotheke.de> Message-ID: And in case it proves intractable to provide concise, useful error messages, perhaps having entries at https://errors.haskell.org (with examples!) would also be helpful. On Mon, 15 May 2023 at 18:07, Olaf Klinke wrote: > On Fri, 2023-05-12 at 17:13 -0400, Brandon Allbery wrote: > > My first suspicion would be simplified subsumption. Try eta-expanding > them. > > > > Indeed, the eta-expanded versions do compile with GHC >= 9. > Now I remember that I've fallen into a similar trap before [1] (and > Brandon offered the right hint back then, too. Thanks, Brandon!) > So let me re-cap: > (1) Haskell is not a category: there are types a, b, c > and morphisms f :: a -> b, g :: b -> c > such that g.f is not a morphism. > (2) Haskell is not a lambda calculus [2]: There are terms f such that > \x -> f x > belongs to the calculus but f does not. > > Personally, I would already call the situation improved when the > compiler instead of Brandon could tell me the fix. From the discussion > [3]: > > > The most interesting thing I've learned from the lengthy threads, > > along with deficiencies in the testing process for ecosystem > > breakage, is how much absolute confusion there is over how rank-n- > > types work, and the limitations and complexities of algorithms > > pertaining to them. Now that they are in widespread use and on by > > default in ghc, it seems like an important case where user education > > is warranted. > > I'd love to be educated. And I'd be very pleased if helpful compiler > error messages were the first entry point for that, so that I can spare > the patient and helpful Haskell Cafe members some time. > > Olaf > > [1] > https://mail.haskell.org/pipermail/haskell-cafe/2023-February/135903.html > [2] > https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0287-simplify-subsumption.rst#costs-and-drawbacks > [3] https://github.com/ghc-proposals/ghc-proposals/pull/287 > > that apparently I have not managed to form an in > > > On Fri, May 12, 2023 at 5:10 PM Olaf Klinke > wrote: > > > > > > Dear Cafe, > > > > > > I'm an infrequent lens user so please forgive me if the below problem > > > has a trivial solution. > > > > > > For a long time the documentation of Control.Lens.Zoom has been > > > claiming that 'zoom' and 'magnify' can be specialized to the following > > > types. > > > > > > {-# LANGUAGE RankNTypes #-} > > > -- Type error with GHC 9.0.2 or 9.2.7, okay with GHC 8.8.4 > > > import Control.Lens.Zoom (zoom,magnify) > > > import Control.Lens.Type (Lens') > > > import Control.Monad.RWS (RWS) > > > zoomRWS :: Monoid w => Lens' s s' -> RWS r w s' a -> RWS r w s a > > > zoomRWS = zoom > > > magnifyRWS :: Monoid w => Lens' r r' -> RWS r' w s a -> RWS r w s a > > > magnifyRWS = magnify > > > > > > Indeed GHC 8.8.4 compiles this happily (on lens-4.18.1), but 9.0.2 (on > > > lens-5.0.1) throws nearly undecipherable errors, claiming that Lens' > > > can not be matched with some more specialized type involving Magnified > > > and LensLike. > > > The source of Control.Lens.Zoom does not differ substantially between > > > 4.18.1 and 5.0.1 so my guess is it is a type checker issue. Can anyone > > > explain? On which bug tracker should I raise this issue, if it is > > > indeed a valid one? > > > (I pulled the above versions from stackage lts-16.31, -19.5 and -20.20, > > > respectively and compiled with stack.) > > > > > > Thanks > > > Olaf > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Thu Jun 1 21:58:47 2023 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Thu, 01 Jun 2023 23:58:47 +0200 Subject: [Haskell-cafe] type error when specializing lens zooms in ghc >= 9.0 In-Reply-To: References: <3a3ba5c235db4c827a2cfe2ac7abc83dadb41524.camel@aatal-apotheke.de> <63cb8f6f43bd4cd385e46493a6176b7cfb6d3aeb.camel@aatal-apotheke.de> Message-ID: On Thu, 2023-06-01 at 17:55 +0300, Bryan Richter wrote: > And in case it proves intractable to provide concise, useful error > messages, perhaps having entries at https://errors.haskell.org (with > examples!) would also be helpful. > The thing is, the error message is rather general, which was my original complaint. I haven't got a GHC-9.6.1 installation, so what is the error code when compiling the following minimal example? More importantly, how many situations completely unrelated to simplified subsumption produce the same error code? If there are many such situations, then making the errors.haskell.org entry of the error code point to simplified subsumption would mislead too many programmers, wouldn't it? {-# LANGUAGE RankNTypes #-} type Void = forall t. t {-- does compile with ghc < 9 but not with ghc >= 9, error message is of the form Couldn't match type with by specializing universally quantified type variables> --} final :: Void -> () final = (id :: () -> ()) -- eta-expanded version of final, -- does compile with ghc >= 9 finalEta :: Void -> () finalEta x = id x Having produced this example, I do acknowledge that simplified subsumption is an improvement. The fact that ghc 8 did accept the equation final=id is indeed weird. Olaf > On Mon, 15 May 2023 at 18:07, Olaf Klinke wrote: > > > On Fri, 2023-05-12 at 17:13 -0400, Brandon Allbery wrote: > > > My first suspicion would be simplified subsumption. Try eta-expanding > > them. > > > > > > > Indeed, the eta-expanded versions do compile with GHC >= 9. > > Now I remember that I've fallen into a similar trap before [1] (and > > Brandon offered the right hint back then, too. Thanks, Brandon!) > > So let me re-cap: > > (1) Haskell is not a category: there are types a, b, c > >     and morphisms f :: a -> b, g :: b -> c > >     such that g.f is not a morphism. > > (2) Haskell is not a lambda calculus [2]: There are terms f such that > >     \x -> f x > >     belongs to the calculus but f does not. > > > > Personally, I would already call the situation improved when the > > compiler instead of Brandon could tell me the fix. From the discussion > > [3]: > > > > > The most interesting thing I've learned from the lengthy threads, > > > along with deficiencies in the testing process for ecosystem > > > breakage, is how much absolute confusion there is over how rank-n- > > > types work, and the limitations and complexities of algorithms > > > pertaining to them. Now that they are in widespread use and on by > > > default in ghc, it seems like an important case where user education > > > is warranted. > > > > I'd love to be educated. And I'd be very pleased if helpful compiler > > error messages were the first entry point for that, so that I can spare > > the patient and helpful Haskell Cafe members some time. > > > > Olaf > > > > [1] > > https://mail.haskell.org/pipermail/haskell-cafe/2023-February/135903.html > > [2] > > https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0287-simplify-subsumption.rst#costs-and-drawbacks > > [3] https://github.com/ghc-proposals/ghc-proposals/pull/287 > > > > that apparently I have not managed to form an in > > > > > On Fri, May 12, 2023 at 5:10 PM Olaf Klinke > > wrote: > > > > > > > > Dear Cafe, > > > > > > > > I'm an infrequent lens user so please forgive me if the below problem > > > > has a trivial solution. > > > > > > > > For a long time the documentation of Control.Lens.Zoom has been > > > > claiming that 'zoom' and 'magnify' can be specialized to the following > > > > types. > > > > > > > > {-# LANGUAGE RankNTypes #-} > > > > -- Type error with GHC 9.0.2 or 9.2.7, okay with GHC 8.8.4 > > > > import Control.Lens.Zoom (zoom,magnify) > > > > import Control.Lens.Type (Lens') > > > > import Control.Monad.RWS (RWS) > > > > zoomRWS :: Monoid w => Lens' s s' -> RWS r w s' a -> RWS r w s a > > > > zoomRWS = zoom > > > > magnifyRWS :: Monoid w => Lens' r r' -> RWS r' w s a -> RWS r w s a > > > > magnifyRWS = magnify > > > > > > > > Indeed GHC 8.8.4 compiles this happily (on lens-4.18.1), but 9.0.2 (on > > > > lens-5.0.1) throws nearly undecipherable errors, claiming that Lens' > > > > can not be matched with some more specialized type involving Magnified > > > > and LensLike. > > > > The source of Control.Lens.Zoom does not differ substantially between > > > > 4.18.1 and 5.0.1 so my guess is it is a type checker issue. Can anyone > > > > explain? On which bug tracker should I raise this issue, if it is > > > > indeed a valid one? > > > > (I pulled the above versions from stackage lts-16.31, -19.5 and -20.20, > > > > respectively and compiled with stack.) > > > > > > > > Thanks > > > > Olaf > > > > > > > > _______________________________________________ > > > > Haskell-Cafe mailing list > > > > To (un)subscribe, modify options or view archives go to: > > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > Only members subscribed via the mailman list are allowed to post. > > > > > > > > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. From ietf-dane at dukhovni.org Fri Jun 2 00:32:23 2023 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Thu, 1 Jun 2023 20:32:23 -0400 Subject: [Haskell-cafe] type error when specializing lens zooms in ghc >= 9.0 In-Reply-To: References: <3a3ba5c235db4c827a2cfe2ac7abc83dadb41524.camel@aatal-apotheke.de> <63cb8f6f43bd4cd385e46493a6176b7cfb6d3aeb.camel@aatal-apotheke.de> Message-ID: On Thu, Jun 01, 2023 at 11:58:47PM +0200, Olaf Klinke wrote: > The thing is, the error message is rather general, which was my > original complaint. I haven't got a GHC-9.6.1 installation, so what is > the error code when compiling the following minimal example? Essentially the same error text with GHC 9.2.7: foo.hs:13:10: error: • Couldn't match type ‘()’ with ‘forall t. t’ Expected: Void -> () Actual: () -> () • In the expression: id :: () -> () In an equation for ‘final’: final = (id :: () -> ()) | 13 | final = (id :: () -> ()) | ^^^^^^^^^^^^^^ and GHC 9.6.2: foo.hs:13:10: error: [GHC-83865] • Couldn't match type ‘()’ with ‘forall t. t’ Expected: Void -> () Actual: () -> () • In the expression: id :: () -> () In an equation for ‘final’: final = (id :: () -> ()) | 13 | final = (id :: () -> ()) | ^^^^^^^^^^^^^^ -- Viktor. From simon at joyful.com Fri Jun 2 02:18:32 2023 From: simon at joyful.com (Simon Michael) Date: Thu, 1 Jun 2023 16:18:32 -1000 Subject: [Haskell-cafe] ANN: hledger 1.30 Message-ID: <61CD63D5-C606-4E22-AF6A-EA6261283E5D@joyful.com> I'm pleased to announce hledger 1.30 ! Highlights: - Boolean queries - with the new `expr:` query type you can freely combined other queries with AND, OR, NOT and parentheses. - Easier CSV file management - you can now read a CSV .rules file, and let it fetch the data file from a downloads directory, simplifying CSV file management. - Built-in demos - a new `demo` command plays several asciinema casts to demonstrate features. We'll add more of these in future. - hledger-ui has a new Cash accounts screen, and now starts on the Menu screen. - The usual miscellaneous fixes. Thank you release contributors Chris Lemaire and Yehoshua Pesach Wallach. - https://github.com/simonmichael/hledger/releases/1.30 - https://hledger.org/release-notes.html#hledger-1-30 - https://hledger.org/install What is hledger ? - Fast, reliable, free, multicurrency, double-entry, plain text accounting software for unix, mac, windows, and the web - Built around human-readable, version-controllable plain text files - Inspired by and largely compatible with Ledger CLI, convertible to and from Beancount - Written in Haskell for reliability and longevity. For help getting started or more info, see https://hledger.org and join our Matrix/IRC chat or mail list: https://hledger.org/support . Newcomers, experts, contributors, sponsors, feedback are welcome! For more about plain text accounting, see https://plaintextaccounting.org . Live well and prosper, -Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From yann.hamdaoui at gmail.com Fri Jun 2 03:50:13 2023 From: yann.hamdaoui at gmail.com (Yann Hamdaoui) Date: Fri, 2 Jun 2023 05:50:13 +0200 Subject: [Haskell-cafe] [CfP][CONFLANG23] 2nd Workshop on Configuration Languages Message-ID: Dear Haskellers, and maybe more generally programming language enthusiasts, I am happy to announce the 2nd Workshop on Configuration Languages, co-located at SPLASH 23, and focused on the quite peculiar (and thus, exciting!) space of designing configuration languages, and more general configuration and infrastructure management. Cheers, Yann CALL FOR PRESENTATIONS - 2nd Workshop on Configuration Languages 2023 (CONFLANG23) EVENT DETAILS Event: CONFLANG23, colocated at SPLASH 2023 Date: Tuesday 24 October 2023 Submission deadline: Friday 12 July 2023 Location: Cascais, Portugal Website: https://2023.splashcon.org/home/conflang-2023 OVERVIEW CONFLANG is a new workshop on the design, the usage and the tooling of configuration programming languages. CONFLANG aims at uniting language designers, industry practitioners and passionate hobbyists to share knowledge in any form. Topics of interest include, but are not limited to: - Infrastructure and configuration code maintenance and evolution - Specification learning and mining for configurations - Infrastructure and Configuration testing and verification - Infrastructure as Code and configuration repair - New languages for configuration - The application of language security and type theory to program configuration CALL FOR PRESENTATIONS The committee welcomes proposals for presentations: - Traditional talks on any theoretical or practical aspect of the usage, the tooling and the design of configuration languages - Experience and case study talks on the real world usage and deployment of configuration languages - Explorative talks and/or demos on experimenting with configuration languages and related tools SUBMISSION GUIDELINES Please submit an abstract (up to 600 words, excluding title, author names, and bibliography) of your proposed talk using the submission link provided below. - **Format**: 600 words maximum abstract (estimated between 1 and 1,5 pages) as a PDF, excluding title, author names, and bibliography. Any additional material will be considered at the discretion of the PC. - **URL** : https://conflang23.hotcrp.com/ PROGRAM CHAIRS - Yann Hamdaoui (Tweag) - Jürgen Cito (TU Wien and Facebook) - Mark Santolucito (Columbia University) - Marcel van Lohuizen (CUE Lang) -------------- next part -------------- An HTML attachment was scrubbed... URL: From bryan at haskell.foundation Fri Jun 2 08:50:57 2023 From: bryan at haskell.foundation (Bryan Richter) Date: Fri, 2 Jun 2023 11:50:57 +0300 Subject: [Haskell-cafe] type error when specializing lens zooms in ghc >= 9.0 In-Reply-To: References: <3a3ba5c235db4c827a2cfe2ac7abc83dadb41524.camel@aatal-apotheke.de> <63cb8f6f43bd4cd385e46493a6176b7cfb6d3aeb.camel@aatal-apotheke.de> Message-ID: Hm, yikes, I tend to agree this is a very general error message. Here are all the places "83865" shows up in the code base: https://gitlab.haskell.org/search?search=83865&project_id=1&group_id=2&search_code=true&repository_ref=master I opened https://gitlab.haskell.org/ghc/ghc/-/issues/23466 to follow up. Feel free to weigh in. (Contact me if you need an account - spam measures currently include manual approvals for new accounts.) On Fri, 2 Jun 2023 at 03:33, Viktor Dukhovni wrote: > On Thu, Jun 01, 2023 at 11:58:47PM +0200, Olaf Klinke wrote: > > > The thing is, the error message is rather general, which was my > > original complaint. I haven't got a GHC-9.6.1 installation, so what is > > the error code when compiling the following minimal example? > > Essentially the same error text with GHC 9.2.7: > > foo.hs:13:10: error: > • Couldn't match type ‘()’ with ‘forall t. t’ > Expected: Void -> () > Actual: () -> () > • In the expression: id :: () -> () > In an equation for ‘final’: final = (id :: () -> ()) > | > 13 | final = (id :: () -> ()) > | ^^^^^^^^^^^^^^ > > and GHC 9.6.2: > > foo.hs:13:10: error: [GHC-83865] > • Couldn't match type ‘()’ with ‘forall t. t’ > Expected: Void -> () > Actual: () -> () > • In the expression: id :: () -> () > In an equation for ‘final’: final = (id :: () -> ()) > | > 13 | final = (id :: () -> ()) > | ^^^^^^^^^^^^^^ > > -- > Viktor. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From zoran.bosnjak at via.si Fri Jun 2 13:32:47 2023 From: zoran.bosnjak at via.si (Zoran =?utf-8?Q?Bo=C5=A1njak?=) Date: Fri, 2 Jun 2023 13:32:47 +0000 (UTC) Subject: [Haskell-cafe] could not deduce Show compile error Message-ID: <1793282487.9136.1685712767404.JavaMail.zimbra@via.si> Dear haskell cafe members, I would appreciate a suggestion how to fix compile error on this simple test program (I am using ghc 9.0.2). The idea is to have 'data Flow a b' unrestricted and create necessary constraints only when running/interpreting the flow. The problem is obviously an intermediate type 'b' in 'Compose', where the 'Show' instance is not deduced. I have a vague clue that some type families might be necessary to propagate Show constraint, or a type class with associated type family, but I don't know exactly how. --- import Prelude hiding ((.), id) import Control.Category data Flow a b where Id :: Flow a a Compose :: Flow a b -> Flow b c -> Flow a c instance Category Flow where id = Id (.) = flip Compose runFlow :: Show a => Flow a b -> a -> IO b runFlow f x = case f of Id -> print x >> pure x Compose f1 f2 -> runFlow f1 x >>= runFlow f2 main :: IO () main = runFlow (Id >>> Id) () --- The error is: • Could not deduce (Show b1) arising from a use of ‘runFlow’ from the context: Show a bound by the type signature for: runFlow :: forall a b. Show a => Flow a b -> a -> IO b at a02.hs:13:1-42 Possible fix: add (Show b1) to the context of the data constructor ‘Compose’ • In the second argument of ‘(>>=)’, namely ‘runFlow f2’ In the expression: runFlow f1 x >>= runFlow f2 In a case alternative: Compose f1 f2 -> runFlow f1 x >>= runFlow f2 | 16 | Compose f1 f2 -> runFlow f1 x >>= runFlow f2 | ^^^^^^^^^^ kind regards, Zoran From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Fri Jun 2 14:15:02 2023 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 2 Jun 2023 15:15:02 +0100 Subject: [Haskell-cafe] could not deduce Show compile error In-Reply-To: <1793282487.9136.1685712767404.JavaMail.zimbra@via.si> References: <1793282487.9136.1685712767404.JavaMail.zimbra@via.si> Message-ID: `Compose` allows you to join together `Flow a b` and `Flow b c`, regardless of what `b` is, even if it doesn't have a `Show` instance, so how can you possibly show it in the recursive call `runFlow f2`? Changing the definition of `Flow` to data Flow a b where Id :: Flow a a Compose :: Show b => Flow a b -> Flow b c -> Flow a c would allow you to write `runFlow` but then you can't define a `Category` instance, since `(.)` is not allowed to be constrained. Perhaps you want something like this: {-# LANGUAGE GADTs #-} import Control.Category import Prelude hiding (id, (.)) data Flow a b where Id :: Flow a a Compose :: Flow a b -> Flow b c -> Flow a c ShowId :: Show a => Flow a a instance Category Flow where id = Id (.) = flip Compose runFlow :: Flow a b -> a -> IO b runFlow f x = case f of Id -> pure x Compose f1 f2 -> runFlow f1 x >>= runFlow f2 ShowId -> print x >> pure x main :: IO () main = runFlow (ShowId >>> ShowId) () Tom On Fri, Jun 02, 2023 at 01:32:47PM +0000, Zoran Bošnjak wrote: > Dear haskell cafe members, > I would appreciate a suggestion how to fix compile error on this simple test program (I am using ghc 9.0.2). > > The idea is to have 'data Flow a b' unrestricted and create necessary constraints only when running/interpreting the flow. The problem is obviously an intermediate type 'b' in 'Compose', where the 'Show' instance is not deduced. > I have a vague clue that some type families might be necessary to propagate Show constraint, or a type class with associated type family, but I don't > know exactly how. > > --- > > import Prelude hiding ((.), id) > import Control.Category > > data Flow a b where > Id :: Flow a a > Compose :: Flow a b -> Flow b c -> Flow a c > > instance Category Flow where > id = Id > (.) = flip Compose > > runFlow :: Show a => Flow a b -> a -> IO b > runFlow f x = case f of > Id -> print x >> pure x > Compose f1 f2 -> runFlow f1 x >>= runFlow f2 > > main :: IO () > main = runFlow (Id >>> Id) () > > --- > > The error is: > > • Could not deduce (Show b1) arising from a use of ‘runFlow’ > from the context: Show a > bound by the type signature for: > runFlow :: forall a b. Show a => Flow a b -> a -> IO b > at a02.hs:13:1-42 > Possible fix: > add (Show b1) to the context of the data constructor ‘Compose’ > • In the second argument of ‘(>>=)’, namely ‘runFlow f2’ > In the expression: runFlow f1 x >>= runFlow f2 > In a case alternative: Compose f1 f2 -> runFlow f1 x >>= runFlow f2 > | > 16 | Compose f1 f2 -> runFlow f1 x >>= runFlow f2 > | ^^^^^^^^^^ From olf at aatal-apotheke.de Fri Jun 2 14:16:17 2023 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Fri, 02 Jun 2023 16:16:17 +0200 Subject: [Haskell-cafe] type error when specializing lens zooms in ghc >= 9.0 Message-ID: <01f9667743615d6a038411a008b4312751baf72b.camel@aatal-apotheke.de> > Hm, yikes, I tend to agree this is a very general error message. Here > are > all the places "83865" shows up in the code base: > > > https://gitlab.haskell.org/search?search=83865&project_id=1&group_id=2&search_code=true&repository_ref=master > > I opened https://gitlab.haskell.org/ghc/ghc/-/issues/23466 to follow > up. > Feel free to weigh in. (Contact me if you need an account - spam > measures > currently include manual approvals for new accounts.) > Thanks, Bryan. This made me wonder what the current system behind assignment of error codes is. I'd expect five-digit error codes to be *more* specific than the general shape of error message emitted by ghc, but here it is evidently less specific. 82865 stands for the error message constructor TypeEqMismatch [1] which is a record [2] with many fields. In particular, the teq_mismatch_expected and teq_mismatch_actual fields hold structural information: a ForAllTy [3] may hint at simplified subsumption. Thus my proposal would be that error codes are composite values, with one part (as currently implemented) in bijection to the error message constructor and another part determined by a function of the actual error value. This function has to be chosen to provide sufficient abstraction from the actual situation but e.g. differentiate between constructors of the Type type. For example, why don't the cases differentiated by the pretty-printer [4] not own their own error codes? Olaf [1] https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Types/Error/Codes.hs [2] https://hackage.haskell.org/package/ghc-9.6.1/docs/src/GHC.Tc.Errors.Types.html#TypeEqMismatch [3] https://hackage.haskell.org/package/ghc-9.6.1/docs/src/GHC.Core.TyCo.Rep.html#ForAllTy [4] https://hackage.haskell.org/package/ghc-9.6.1/docs/src/GHC.Tc.Errors.Ppr.html#pprMismatchMsg From lemming at henning-thielemann.de Fri Jun 2 14:21:02 2023 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 2 Jun 2023 16:21:02 +0200 (CEST) Subject: [Haskell-cafe] could not deduce Show compile error In-Reply-To: <1793282487.9136.1685712767404.JavaMail.zimbra@via.si> References: <1793282487.9136.1685712767404.JavaMail.zimbra@via.si> Message-ID: On Fri, 2 Jun 2023, Zoran Bošnjak wrote: > import Prelude hiding ((.), id) > import Control.Category > > data Flow a b where > Id :: Flow a a > Compose :: Flow a b -> Flow b c -> Flow a c type variable 'b' of Compose is not visible outside Flow. Thus you cannot get later in runFlow, but you have to embed the Show constraint in the Compose constructor like so: Compose :: (Show b) => Flow a b -> Flow b c -> Flow a c But this in turn means, you can compose only Flows where the interim type 'b' is an instance of Show. To avoid this you would need an additional type parameter to Flow with a constraint kind constructor or an existentially quantified type, that holds all the constraints you need for your current application. I think it should be like so: type family FlowConstraints constr a data FlowAny type instance FlowConstraints FlowAny a = () data FlowShow type instance FlowConstraints FlowShow a = (Show a) data Flow constr a b where Id :: Flow a a Compose :: (FlowConstraints constr b) => Flow a b -> Flow b c -> Flow a c or alternatively: data family FlowConstraints constr a data FlowAny data instance FlowConstraints FlowAby a = FlowAnyConstraint data FlowShow data instance FlowConstraints FlowShow a = (Show a) => FlowShowConstraint data Flow constr a b where Id :: Flow a a Compose :: (FlowConstraints constr b) => Flow a b -> Flow b c -> Flow a c In this case you have to match on FlowAnyConstraint or FlowShowConstraint in runFlow in order to get back the required constraints. In any case, the constraints must already be available at construction with Compose. Thus you will not be able to use Compose in a Category instance. From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Fri Jun 2 14:29:16 2023 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 2 Jun 2023 15:29:16 +0100 Subject: [Haskell-cafe] could not deduce Show compile error In-Reply-To: References: <1793282487.9136.1685712767404.JavaMail.zimbra@via.si> Message-ID: Sorry for the wonky formatting. Here is a corrected version: {-# LANGUAGE GADTs #-} import Control.Category import Prelude hiding (id, (.)) data Flow a b where Id :: Flow a a Compose :: Flow a b -> Flow b c -> Flow a c ShowId :: Show a => Flow a a instance Category Flow where id = Id (.) = flip Compose runFlow :: Flow a b -> a -> IO b runFlow f x = case f of Id -> pure x Compose f1 f2 -> runFlow f1 x >>= runFlow f2 ShowId -> print x >> pure x main :: IO () main = runFlow (ShowId >>> ShowId) () On Fri, Jun 02, 2023 at 03:15:02PM +0100, Tom Ellis wrote: > `Compose` allows you to join together `Flow a b` and `Flow b c`, > regardless of what `b` is, even if it doesn't have a `Show` instance, > so how can you possibly show it in the recursive call `runFlow f2`? > > Changing the definition of `Flow` to > > data Flow a b where > Id :: Flow a a > Compose :: Show b => Flow a b -> Flow b c -> Flow a c > > would allow you to write `runFlow` but then you can't define a > `Category` instance, since `(.)` is not allowed to be constrained. > > Perhaps you want something like this: > > {-# LANGUAGE GADTs #-} > > import Control.Category > import Prelude hiding (id, (.)) > > data Flow a b where > Id :: Flow a a > Compose :: Flow a b -> Flow b c -> Flow a c > ShowId :: Show a => Flow a a > > instance Category Flow where > id = Id > (.) = flip Compose > > runFlow :: Flow a b -> a -> IO b > runFlow f x = case f of > Id -> pure x > Compose f1 f2 -> runFlow f1 x >>= runFlow f2 > ShowId -> print x >> pure x > > main :: IO () > main = runFlow (ShowId >>> ShowId) () > > Tom > > On Fri, Jun 02, 2023 at 01:32:47PM +0000, Zoran Bošnjak wrote: > > Dear haskell cafe members, > > I would appreciate a suggestion how to fix compile error on this simple test program (I am using ghc 9.0.2). > > > > The idea is to have 'data Flow a b' unrestricted and create necessary constraints only when running/interpreting the flow. The problem is obviously an intermediate type 'b' in 'Compose', where the 'Show' instance is not deduced. > > I have a vague clue that some type families might be necessary to propagate Show constraint, or a type class with associated type family, but I don't > > know exactly how. > > > > --- > > > > import Prelude hiding ((.), id) > > import Control.Category > > > > data Flow a b where > > Id :: Flow a a > > Compose :: Flow a b -> Flow b c -> Flow a c > > > > instance Category Flow where > > id = Id > > (.) = flip Compose > > > > runFlow :: Show a => Flow a b -> a -> IO b > > runFlow f x = case f of > > Id -> print x >> pure x > > Compose f1 f2 -> runFlow f1 x >>= runFlow f2 > > > > main :: IO () > > main = runFlow (Id >>> Id) () > > > > --- > > > > The error is: > > > > • Could not deduce (Show b1) arising from a use of ‘runFlow’ > > from the context: Show a > > bound by the type signature for: > > runFlow :: forall a b. Show a => Flow a b -> a -> IO b > > at a02.hs:13:1-42 > > Possible fix: > > add (Show b1) to the context of the data constructor ‘Compose’ > > • In the second argument of ‘(>>=)’, namely ‘runFlow f2’ > > In the expression: runFlow f1 x >>= runFlow f2 > > In a case alternative: Compose f1 f2 -> runFlow f1 x >>= runFlow f2 > > | > > 16 | Compose f1 f2 -> runFlow f1 x >>= runFlow f2 > > | ^^^^^^^^^^ > _______________________________________________ > 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 simon at joyful.com Fri Jun 2 21:01:36 2023 From: simon at joyful.com (Simon Michael) Date: Fri, 2 Jun 2023 11:01:36 -1000 Subject: [Haskell-cafe] [hledger] ANN: hledger 1.30 In-Reply-To: References: <61CD63D5-C606-4E22-AF6A-EA6261283E5D@joyful.com> Message-ID: <1ED1F2A7-2FBE-49AB-BB11-0DA928744701@joyful.com> > On Jun 2, 2023, at 00:55, Henning Thielemann wrote: > > I can build with GHC-8.8.4, but with GHC-8.10 and later I get: > > > Hledger/Cli/Commands/Demo.hs:63:3: error: > • Exception when trying to run compile-time code: > /ram/cabal/tmp/src-191030/hledger-1.30/embeddedfiles/add.cast: openFile: does not exist (No such file or directory) > Code: embedFileRelative "embeddedfiles/add.cast" > • In the untyped splice: > $(embedFileRelative "embeddedfiles/add.cast") > | > 63 | $(embedFileRelative "embeddedfiles/add.cast"), -- https://asciinema.org/a/567935 The easiest way to start a journal (add) > | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Thanks for the report; I have released hledger-1.30.1 on Hackage to fix this. From kindaro at gmail.com Sun Jun 4 15:19:29 2023 From: kindaro at gmail.com (Ignat Insarov) Date: Sun, 4 Jun 2023 18:19:29 +0300 Subject: [Haskell-cafe] Course materials to help me teach Software Engineering with Haskell? Message-ID: Hello café! I am looking for some kind of lesson plans, lecture notes or other inspiring materials that would help me construct an advanced course in Software Engineering with Haskell — or other pure functional technologies — with the aim to teach this art to myself and others to the highest level of excellence. I know there is a choice of published books with «Haskell» in the title, and I shall draw from them. However, I am not super happy about any of the books I looked into so far, because they are so concrete. They would pick a bunch of best practices and some well known libraries and write about that in excruciating detail. It seems a published book cannot afford to say anything abstract or outlandish. Assorti lecture notes I could find on the Internet are more diverse and fresh, but I have not found many and whichever I found are all somewhat beginner level, they talk about Haskell's syntax and evaluation more than about Software Engineering overall. The stuff I wish to see would be like: * Continuation passing style. * Recursion schemes. * Polynomial functors. * The nature of `IO`. * Evaluation of Haskell on a graph machine. * The expression problem. In short, stuff that transcends specific libraries and concrete code. In the ideal, I wish there was a literature review that refers to foundational research. I do not expect ready-made perfection; please send me whatever you think would help, even your brief thoughts and wishes. From jm at memorici.de Sun Jun 4 17:10:52 2023 From: jm at memorici.de (Jons Mostovojs) Date: Sun, 4 Jun 2023 18:10:52 +0100 Subject: [Haskell-cafe] Course materials to help me teach Software Engineering with Haskell? In-Reply-To: References: Message-ID: Here's one that is really good. Made in the company I have co-founded, but I'm genuinely a huge fan of this course. https://github.com/jagajaga/FP-Course-ITMO On Sun, 4 Jun 2023, 16:20 Ignat Insarov, wrote: > Hello café! > > I am looking for some kind of lesson plans, lecture notes or other > inspiring materials that would help me construct an advanced course in > Software Engineering with Haskell — or other pure functional > technologies — with the aim to teach this art to myself and others to > the highest level of excellence. > > I know there is a choice of published books with «Haskell» in the > title, and I shall draw from them. However, I am not super happy about > any of the books I looked into so far, because they are so concrete. > They would pick a bunch of best practices and some well known > libraries and write about that in excruciating detail. It seems a > published book cannot afford to say anything abstract or outlandish. > > Assorti lecture notes I could find on the Internet are more diverse > and fresh, but I have not found many and whichever I found are all > somewhat beginner level, they talk about Haskell's syntax and > evaluation more than about Software Engineering overall. > > The stuff I wish to see would be like: > > * Continuation passing style. > * Recursion schemes. > * Polynomial functors. > * The nature of `IO`. > * Evaluation of Haskell on a graph machine. > * The expression problem. > > In short, stuff that transcends specific libraries and concrete code. > > In the ideal, I wish there was a literature review that refers to > foundational research. > > I do not expect ready-made perfection; please send me whatever you > think would help, even your brief thoughts and wishes. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.gl.scott at gmail.com Mon Jun 5 11:47:24 2023 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Mon, 5 Jun 2023 07:47:24 -0400 Subject: [Haskell-cafe] Final Call for Talks: Haskell Implementors' Workshop 2023 Message-ID: The 2023 Haskell Implementors' Workshop deadline is just under one month away. We are looking forward to your talk submissions. Best, Ryan ================================== ACM SIGPLAN Haskell Implementors' Workshop https://icfp23.sigplan.org/home/hiw-2023 Seattle, Washington, United States, September 4, 2023 Co-located with ICFP 2023 https://icfp23.sigplan.org/ Important dates --------------- Deadline: July 4, 2023 (AoE) Notification: August 4, 2023 Workshop: September 4, 2023 The 15th Haskell Implementors' Workshop is to be held alongside ICFP 2023 this year in Seattle. 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 to 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 short 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 2023. 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 are encouraged to attend the workshop -- we need your feedback to keep the Haskell ecosystem thriving. Students working with Haskell are especially 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, optimisation 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://icfphiw23.hotcrp.com until July 4 (anywhere on earth). We will also have a lightning talks session. These have been very well received in recent years, and we aim to increase the time available to them. Lightning talks should 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. Program Committee ----------------- * Gergő Érdi (Standard Chartered Bank) * Sebastian Graf (Karlsruhe Institute of Technology) * Wen Kokke (University of Strathclyde) * Ryan Scott (Galois, Inc.) * Rebecca Skinner (Mercury) * Li-yao Xia (University of Edinburgh) Contact ------- * Ryan Scott -------------- next part -------------- An HTML attachment was scrubbed... URL: From Graham.Hutton at nottingham.ac.uk Mon Jun 5 14:30:35 2023 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Mon, 5 Jun 2023 14:30:35 +0000 Subject: [Haskell-cafe] Journal of Functional Programming - Call for PhD Abstracts Message-ID: Dear all, If you or one of your students recently completed a PhD (or Habilitation) in the area of functional programming, please submit the dissertation abstract for publication in JFP. Simple process, no refereeing, open access, 200+ published to date, deadline 30th June 2023. Please share! Best wishes, Graham Hutton ============================================================ CALL FOR PHD ABSTRACTS Journal of Functional Programming Deadline: 30th June 2023 http://tinyurl.com/jfp-phd-abstracts ============================================================ PREAMBLE: Many students complete PhDs in functional programming each year. As a service to the community, twice per year the Journal of Functional Programming publishes the abstracts from PhD dissertations completed during the previous year. The abstracts are made freely available on the JFP website, i.e. not behind any paywall. They do not require any transfer of copyright, merely a license from the author. A dissertation is eligible for inclusion if parts of it have or could have appeared in JFP, that is, if it is in the general area of functional programming. The abstracts are not reviewed. Please submit dissertation abstracts according to the instructions below. We welcome submissions from both the student and the advisor/supervisor although we encourage them to coordinate. Habilitation dissertations are also eligible for inclusion. ============================================================ SUBMISSION: Please submit the following information to Graham Hutton by 30th June 2023. o Dissertation title: (including any subtitle) o Student: (full name) o Awarding institution: (full name and country) o Date of award: (month and year; depending on the institution, this may be the date of the viva, corrections being approved, graduation ceremony, or otherwise) o Advisor/supervisor: (full names) o Dissertation URL: (please provide a permanently accessible link to the dissertation if you have one, such as to an institutional repository or other public archive; links to personal web pages should be considered a last resort) o Dissertation abstract: (plain text, maximum 350 words; you may use \emph{...} for emphasis, but we prefer no other markup or formatting; if your original abstract exceeds the word limit, please submit an abridged version within the limit) Please do not submit a copy of the dissertation itself, as this is not required. JFP reserves the right to decline to publish abstracts that are not deemed appropriate. ============================================================ PHD ABSTRACT EDITOR: Graham Hutton School of Computer Science University of Nottingham Nottingham NG8 1BB United Kingdom ============================================================ This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please contact the sender and delete the email and attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. Email communications with the University of Nottingham may be monitored where permitted by law. From dyaitskov at gmail.com Tue Jun 6 16:30:00 2023 From: dyaitskov at gmail.com (Daneel Yaitskov) Date: Tue, 6 Jun 2023 12:30:00 -0400 Subject: [Haskell-cafe] Multicolumn aggregate in Beam Message-ID: Hi, I am using beam library in my project and trying to express a query with a several aggregating subqueries: select (select * from t order by ts desc limit 1), (select * from t order by ts asc limit 1), (select count(*) from t) as nnn I figured out how to do multiple columns: userDataTableDigestQ :: UserTable -> SqlSelect Postgres (UserDataTable, UserDataTable) userDataTableDigestQ ut = select ag where al = all_ (userDataTableRef $ usertableName ut) ag = subselect_ $ aggregate_ (BF.bimap group_ group_) ((,) <$> limit_ 1 (orderBy_ (asc_ . userdatatableTs) al) <*> limit_ 1 (orderBy_ (desc_ . userdatatableTs) al)) but mixing group_ and count_ produces a very long type error Is there other sql-backend agnostic Haskell library which could express the query above? -- Best regards, Daniil Iaitskov -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Fri Jun 16 11:11:27 2023 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 16 Jun 2023 12:11:27 +0100 Subject: [Haskell-cafe] Best way to implement "scoped exceptions"? In-Reply-To: References: Message-ID: On Thu, Dec 29, 2022 at 03:41:22PM +0000, Tom Ellis wrote: > On Thu, Dec 29, 2022 at 01:31:47PM +0000, Li-yao Xia wrote: > > The recently implemented Delimited Continuation Primops proposal[1] features > > tagged prompts. That seems like just what you are looking for. > > > > [1]: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0313-delimited-continuation-primops.rst > > Very interesting, thanks! My initial attempt at implementing scoped > exceptions using the delimited continuation primops was bad: > > withScopedExceptionBad :: > ((e -> IO (Either e r)) -> IO r) -> IO (Either e r) > withScopedExceptionBad body = do > promptTag <- newPromptTag > prompt promptTag $ do > l <- control0 promptTag $ \myThrow -> do > r <- body (myThrow . pure) > pure (Right r) > pure (Left l) > > It was very head-scratching trying to work out how it should be > implemented. Then with the help of a gist by sebfisch[1] I managed > it: > > withScopedException :: > ((forall a. e -> IO a) -> IO r) -> IO (Either e r) > withScopedException body = do > promptTag <- newPromptTag > prompt promptTag $ do > r <- body (\e -> control0 promptTag (\_ -> pure (Left e))) > pure (Right r) > > Surprisingly to me, for scoped exceptions, the handler passed to > control0 should *ignore* its argument. That's because its argument > allows it to escape from the call to control0, but we want to escape > from the call to prompt. This is very powerful and mind-bending stuff > and allows me to do exactly what I wanted. Inspired by Alexis King's excellent talk recently at ZuriHac I reimplemented this in a more general way. https://www.youtube.com/watch?v=aaApZhfisbs ZuriHac 2023 — Alexis King — Delimited Continuations, Demystified "withScopedEffect" allows to use any handler you like for the "effect". withScopedEffect :: (a -> (IO b -> IO r) -> IO r) -> ((a -> IO b) -> IO r) -> IO r withScopedEffect handler body = do promptTag <- newPromptTag prompt promptTag (body (\e -> control0 promptTag (\k -> handler e (prompt promptTag . k)))) withScopedException :: ((e -> IO Void) -> IO r) -> IO (Either e r) withScopedException body = withScopedEffect (\e _ -> pure (Left e)) (fmap Right . body) Tom From me at alcidesfonseca.com Fri Jun 16 22:15:04 2023 From: me at alcidesfonseca.com (Alcides Fonseca) Date: Fri, 16 Jun 2023 23:15:04 +0100 Subject: [Haskell-cafe] SPLASH 2023 - Second Combined Call for Contributions Message-ID: ====================================================================== Second Combined Call For Contributions ACM Conference on Systems, Programming, Languages, and Applications: Software for Humanity (SPLASH'23) October 22-27, 2023, Cascais, Portugal https://2023.splashcon.org ====================================================================== SPLASH - The ACM SIGPLAN conference on Systems, Programming, Languages, and Applications: Software for Humanity embraces all aspects of software construction and delivery, to make it the premier conference on the applications of programming languages - at the intersection of programming languages and software engineering. Follow the registration space on the SPLASH website to attend this fantastic line-up of events - we aim to open for registration on July 20. ====================================================================== OUTLINE OF THE SECOND COMBINED CALL FOR CONTRIBUTIONS: SPLASH upcoming deadlines: * Posters (deadline: 15 Aug) * SPLASH-E (deadline: 27 Jul) * Doctoral Symposium (deadline: 7 Jul) * Student Research Competition (deadline: 14 Jul) * Programming Languages Mentoring Workshop (PLMW) (deadline: 24 Jul) SPLASH Workshops (submission deadline: 12 Jul): * CONFLANG * FTSCS * HATRA * IWACO * LIVE * PAINT * PLF * REBELS * ST30 SPLASH Co-located Events: * DLS (Deadline: 28 Jun) * GPCE (Deadline: 7 July) * MPLR (Deadline: 26 Jun) ====================================================================== SPLASH - The ACM SIGPLAN conference on Systems, Programming, Languages, and Applications: Software for Humanity embraces all aspects of software construction and delivery, to make it the premier conference on the applications of programming languages - at the intersection of programming languages and software engineering. SPLASH 2023 aims to signify the reopening of the world and being able to meet your international colleagues in person. ** Co-located Events ** **** Dynamic Languages Symposium (DLS) **** The Dynamic Languages Symposium (DLS) is the premier forum for researchers and practitioners to share research and experience on all aspects of dynamic languages. After two decades of dynamic language research and DLS, it is time to reflect and look forward to what the next two decades will bring. This year's DLS will therefore be a special DLS focusing on the Future of Dynamic Languages. To do the notion of "symposium" justice, we will actively invite speakers to present their opinions on where Dynamic Languages might be, will be, or should be going in the next twenty years. Paper Submission Deadline: 28 Jun 2023 Details: https://2023.splashcon.org/home/dls-2023 **** Generative Programming: Concepts & Experiences (GPCE)**** ACM SIGPLAN International Conference on Generative Programming: Concepts & Experiences (GPCE) is a venue for researchers and practitioners interested in techniques that use program generation, domain-specific languages, and component deployment to increase programmer productivity, improve software quality, and shorten the time-to-market of software products. In addition to exploring cutting-edge techniques of generative software, our goal is to foster further cross-fertilization between the software engineering and the programming languages research communities. Abstract Submission Deadline: 3 Jul 2023 Paper Submission Deadline: 7 Jul 2023 Details: https://2023.splashcon.org/home/gpce-2023 **** Managed Programming Languages & Runtimes (MPLR)**** The 20th International Conference on Managed Programming Languages & Runtimes (MPLR'23, formerly ManLang, originally PPPJ) is a premier forum for presenting and discussing novel results in all aspects of managed programming languages and runtime systems, which serve as building blocks for some of the most important computing systems around, ranging from small-scale (embedded and real-time systems) to large-scale (cloud-computing and big-data platforms) and anything in between (mobile, IoT, and wearable applications). Paper/Abstract Submission Deadline: 26 Jun 2023 Details: https://2023.splashcon.org/home/mplr-2023 **** Posters **** The SPLASH Posters track provides an excellent forum for authors to present their recent or ongoing projects in an interactive setting, and receive feedback from the community. We invite submissions covering any aspect of programming, systems, languages and applications. The goal of the poster session is to encourage and facilitate small groups of individuals interested in a technical area to gather and interact. It is held early in the conference, to promote continued discussion among interested parties. Submission Deadline: 15 Aug 2023 **** SPLASH-E **** SPLASH-E is a symposium, started in 2013, for software and languages (SE/PL) researchers with activities and interests around computing education. Some build pedagogically-oriented languages or tools; some think about pedagogic challenges around SE/PL courses; some bring computing to non-CS communities; some pursue human studies and educational research. At SPLASH-E, we share our educational ideas and challenges centered in software/languages, as well as our best ideas for advancing such work. SPLASH-E strives to bring together researchers and those with educational interests that arise from software ideas or concerns. Archival Submission Deadline: 27 Jul 2023 ** Student Research Competition (SRC) ** The ACM Student Research Competition (SRC) offers a unique opportunity for undergraduate and graduate students to present their research to a panel of judges and conference attendees at SPLASH. The SRC provides visibility and exposes up-and-coming researchers to computer science research and the research community. This competition also gives students an opportunity to discuss their research with experts in their field, get feedback, and sharpen their communication and networking skills. Abstract Submission Deadline: 14 Jul 2023 ** Programming Languages Mentoring Workshop (PLMW) ** The SPLASH Programming Languages Mentoring Workshop encourages graduate students (PhD and MSc) and senior undergraduate students to pursue research in programming languages. This workshop will provide mentoring sessions on how to prepare for and thrive in graduate school and in a research career, focusing both on cutting-edge research topics and practical advice. The workshop brings together leading researchers and junior students in an inclusive environment in order to help welcome newcomers to our field of programming languages research. The workshop will show students the many paths that they might take to enter and contribute to our research community. Application Submission Deadline: 24 Jul 2023 ** Workshops ** **** CONFLANG **** CONFLANG is a workshop on the design, the theory, the practice and the future evolution of configuration languages. It aims to gather the emerging community in this area in order to engage in fruitful interactions, to share ideas, results, opinions, and experiences on languages for configuration. Correct configuration is an actual industrial problem, and would greatly benefit from existing and ongoing academic research. Dually, this is a space with new challenges to overcome and new directions to explore, which is a great opportunity to confront new ideas with large-scale production. **** FTSCS **** The aim of this workshop is to bring together researchers and engineers who are interested in the application of formal and semi-formal methods to improve the quality of safety-critical computer systems. FTSCS strives to promote research and development of formal methods and tools for industrial applications, and is particularly interested in industrial applications of formal methods. Specific topics include, but are not limited to: case studies and experience reports on the use of formal methods for analyzing safety-critical systems, including avionics, automotive, medical, railway, and other kinds of safety-critical and QoS-critical systems; methods, techniques and tools to support automated analysis, certification, debugging, etc., of safety/QoS-critical systems; analysis methods that address the limitations of formal methods in industry (usability, scalability, etc.); formal analysis support for modeling languages used in industry, such as AADL, Ptolemy, SysML, SCADE, Modelica, etc.; code generation from validated models. The workshop will provide a platform for discussions and the exchange of innovative ideas, so submissions on work in progress are encouraged. **** HATRA **** Programming language designers seek to provide strong tools to help developers reason about their programs. For example, the formal methods community seeks to enable developers to prove correctness properties of their code, and type system designers seek to exclude classes of undesirable behavior from programs. The security community creates tools to help developers achieve their security goals. In order to make these approaches as effective as possible for developers, recent work has integrated approaches from human-computer interaction research into programming language design. This workshop brings together programming languages, software engineering, security, and human-computer interaction researchers to investigate methods for making languages that provide stronger safety properties more effective for programmers and software engineers. We have two goals: (1) to provide a venue for discussion and feedback on early-stage approaches that might enable people to be more effective at achieving stronger safety properties in their programs; (2) to facilitate discussion about relevant topics of participant interest. **** IWACO **** Many techniques have been introduced to describe and reason about stateful programs, and to restrict, analyze, and prevent aliases. These include various forms of ownership types, capabilities, separation logic, linear logic, uniqueness, sharing control, escape analysis, argument independence, read-only references, linear references, effect systems, and access control mechanisms. These tools have found their way into type systems, compilers and interpreters, runtime systems and bug-finding tools. Their immediate practical relevance is self-evident from the popularity of Rust, a programming language built around reasoning about aliasing and ownership to enable static memory management and data race freedom, voted the "most beloved" language in the annual Stack Overflow Developer Survey seven times in a row. IWACO'23 will focus on these techniques, on how they can be used to reason about stateful (sequential or concurrent) programs, and how they have been applied to programming languages. In particular, we will consider papers on: models, type systems and other formal systems, programming language mechanisms, analysis and design techniques, patterns and notations for expressing ownership, aliasing, capabilities, uniqueness, and related topics; empirical studies of programs or experience reports from programming systems designed with these techniques in mind; programming logics that deal with aliasing and/or shared state, or use ownership, capabilities or resourcing; applications of capabilities, ownership and other similar type systems in low-level systems such as programming languages runtimes, virtual machines, or compilers; and optimization techniques, analysis algorithms, libraries, applications, and novel approaches exploiting ownership, aliasing, capabilities, uniqueness, and related topics. **** LIVE **** Programming is cognitively demanding, and too difficult. LIVE is a workshop exploring new user interfaces that improve the immediacy, usability, and learnability of programming. Whereas PL research traditionally focuses on programs, LIVE focuses more on the activity of programming. Our goal is to provide a supportive venue where early-stage work receives constructive criticism. Whether graduate students or tenured faculty, researchers need a forum to discuss new ideas and get helpful feedback from their peers. Towards that end, we will allot about ten minutes for discussion after every presentation. **** PAINT **** Programming environments that integrate tools, notations, and abstractions into a holistic user experience can provide programmers with better support for what they want to achieve. These programming environments can create an engaging place to do new forms of informational work - resulting in enjoyable, creative, and productive experiences with programming. In the workshop on Programming Abstractions and Interactive Notations, Tools, and Environments (PAINT), we want to discuss programming environments that support users in working with and creating notations and abstractions that matter to them. We are interested in the relationship between people centric notations and general-purpose programming languages and environments. How do we reflect the various experiences, needs, and priorities of the many people involved in programming — whether they call it that or not? **** PLF **** Applications supporting multi-device are ubiquitous. While most of the distributed applications that we see nowadays are cloud-based, avoiding the cloud can lead to privacy and performance benefits for users and operational and cost benefits for companies and developers. Following this idea, Local-First Software runs and stores its data locally while still allowing collaboration, thus retaining the benefits of existing collaborative applications without depending on the cloud. Many specific solutions already exist: operational transformation, client-side databases with eventually consistent replication based on CRDTs, and even synchronization as a service provided by commercial offerings, and a vast selection of UI design libraries. However, these solutions are not integrated with the programming languages that applications are developed in. Language based solutions related to distribution such as type systems describing protocols, reliable actor runtimes, data processing, machine learning, etc., are designed and optimized for the cloud not for a loosely connected set of cooperating devices. This workshop aims at bringing the issue to the attention of the PL community, and accelerating the development of suitable solutions for this area. **** REBELS **** Reactive programming and event-based programming are two closely related programming styles that are becoming ever more important with the advent of advanced HPC technology and the ever increasing requirement for our applications to run on the web or on collaborating mobile devices. A number of publications on middleware and language design — so-called reactive and event-based languages and systems (REBLS) — have already seen the light, but the field still raises several questions. For example, the interaction with mainstream language concepts is poorly understood, implementation technology is in its infancy and modularity mechanisms are almost totally lacking. Moreover, large applications are still to be developed and patterns and tools for developing reactive applications is an area that is vastly unexplored. This workshop will gather researchers in reactive and event-based languages and systems. The goal of the workshop is to exchange new technical research results and to define better the field by coming up with taxonomies and overviews of the existing work. **** ST30 **** Session types are a type-theoretic approach to specifying communication protocols so that they can be verified by type-checking. This year marks 30 years since the first paper on session types, by Kohei Honda at CONCUR 1993. Since then the topic has attracted increasing interest, and a substantial community and literature have developed. Google Scholar lists almost 400 articles with "session types" in the title, and most programming language conferences now include several papers on session types each year. In terms of the technical focus, there have been continuing theoretical developments (notably the generalisation from two-party to multi-party session types by Honda, Yoshida and Carbone in 2008, and the development of a Curry-Howard correspondence with linear logic by Caires and Pfenning in 2010) and a variety of implementations of session types as programming language extensions or libraries, covering (among others) Haskell, OCaml, Java, Scala, Rust, Python, C#, Go. ST30 is a workshop to celebrate the 30th anniversary of session types by bringing together the community for a day of talks and technical discussion. ====================================================================== Be part of these fantastic events! ====================================================================== Organizing Committee General Chair: Vasco T. Vasconcelos (University of Lisbon) OOPSLA Review Committee Chair: Mira Mezini (TU Darmstadt) OOPSLA Publications Co-Chair: Ragnar Mogk (TU Darmstadt) OOPSLA Artifact Evaluation Co-Chair: Benjamin Greenman (Brown University) OOPSLA Artifact Evaluation Co-Chair: Guillaume Baudart (INRIA) DLS General Chair: Stefan Marr (University of Kent) GPCE General Chair: Bernhard Rumpe (RWTH Aachen University) GPCE PC Chair: Amir Shaikhha (University of Edinburgh) LOPSTR PC Chair: Robert Glück (University of Copenhagen, Denmark) LOPSTR PC Chair: Bishoksan Kafle (IMDEA) MPLR General Chair: Rodrigo Bruno (University of Lisbon) MPLR PC Chair: Elliot Moss (University of Massachusetts Amherst) PPDP PC Chair: Santiago Escobar (Universitat Politècnica de València ) SAS Co-Chair: Manuel Hermenegildo (Technical University of Madrid & IMDEA) SAS Co-Chair: José Morales (IMDEA) SAS Artifact Evaluation Chair: Marc Chevalier (Snyk) SLE Chair: João Saraiva (University of Minho) SLE PC Co-Chair: Thomas Degueule (CNRS, LaBRI) SLE PC Co-Chair: Elizabeth Scott (Royal Holloway University of London) Onward! Papers Chair: Tijs van der Storm (CWI & University of Groningen) Onward! Essays Chair: Robert Hirschfeld (University of Potsdam; Hasso Plattner Institute) SPLASH-E Co-Chair: Molly Feldman (Oberlin College) Posters Co-Chair: Xujie Si (University of Toronto) Workshops Co-Chair: Mehdi Bagherzadeh (Oakland University) Workshops Co-Chair: Amin Alipour (University of Houston) Hybridisation Co-Chair: Youyou Cong (Tokyo Institute of Technology) Hybridisation Co-Chair: Jonathan Immanuel Brachthäuser (University of Tübingen) Video Co-Chair: Guilherme Espada (University of Lisbon) Video Co-Chair: Apoorv Ingle (University of Iowa) Publicity Chair, Web Co-Chair: Andreea Costea (National University Of Singapore) Publicity Chair, Web Co-Chair: Alcides Fonseca (University of Lisbon) PLMW Co-Chair: Molly Feldman (Oberlin College) PLMW Co-Chair: Youyou Cong (Tokyo Institute of Technology) PLMW Co-Chair: João Ferreira (University of Lisbon) Sponsoring Co-Chair: Bor-Yuh Evan Chang (University of Colorado Boulder & Amazon) Sponsoring Co-Chair: Nicolas Wu (Imperial College London) Student Research Competition Co-Chair: Xujie Si (McGill University, Canada) Local Organizer Chair: Andreia Mordido (University of Lisbon) SIGPLAN Conference Manager: Neringa Young -------------- next part -------------- An HTML attachment was scrubbed... URL: From ifl21.publicity at gmail.com Mon Jun 19 09:08:36 2023 From: ifl21.publicity at gmail.com (Pieter Koopman) Date: Mon, 19 Jun 2023 02:08:36 -0700 Subject: [Haskell-cafe] IFL23 2nd Call for papers Message-ID: Important Dates Draft Paper Submission Deadline 31st July, 2023 Notification of Acceptance for Presentation 1st August, 2023 Early Registration Deadline 11th August, 2023 Late Registration Deadline 23rd August, 2023 IFL Symposium 29th - 31st August, 2023 Submission of Papers for Peer-Reviewed Proceedings 24th November, 2023 Notification of Acceptance 2nd February, 2024 Camera-ready Version 8th March, 2024 SCOPE AND TOPICS 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. You can find more information about the symposium on its oficial website . IFL 2023 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. See the call for papers in text format . Areas of interest 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 PAPER SUBMISSIONS Following IFL tradition, IFL 2023 will use a post-symposium review process to produce the formal proceedings. Before the symposium, authors submit draft papers. These draft papers will be screened by the program chair to make sure that they are within the scope of IFL. The draft papers will be made available to all participants at the symposium. Each draft paper is presented by one of the authors at the symposium. Notice that it is a requirement that accepted draft papers are presented physically at the symposium. After the symposium every presenter is invited to submit a full paper, incorporating feedback from discussions at the symposium. Work submitted to IFL may not be simultaneously submitted to other venues; submissions must adhere to ACM SIGPLAN's republication policy. 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 for the formal proceedings. As in previous years, we will try to have the papers that are accepted for the formal proceedings published in the International Conference Proceedings Series of the ACM Digital Library. This possibility will be confirmed as soon as possible. Reviewing is single blind. There will be at least 3 reviews per paper. For the camera-ready version the authors can make minor revisions which are accepted without further reviewing. Papers must use the ACM two columns conference format, which can be found here . (For LaTeX users, start your document with \documentclass[sigconf,screen,review]{acmart}.) All contributions must be written in English. Note that this format has a rather long but limited list of packages that can be used. Please make sure that your document adheres to this list. The page limit for papers is twelve pages (excluding references). Only papers that were presented at the IFL 2023 Symposium will be considered for publication. LOCATION IFL 2023 will be held physically in Braga, Portugal. For more information, click here . [image: beacon] -------------- next part -------------- An HTML attachment was scrubbed... URL: From ty.wang at btq.com Tue Jun 20 03:02:43 2023 From: ty.wang at btq.com (Ting Wang) Date: Tue, 20 Jun 2023 11:02:43 +0800 Subject: [Haskell-cafe] Keelung Compiler is now open source! Message-ID: Hello developers, We are thrilled to announce that Keelung is now 100% open source! By making it transparent under the Apache 2.0 license, we aim to increase accessibility and foster contributions from the community. The Keelung Compiler transforms programs written in Keelung, a new domain-specific language (DSL) designed to make fast, private, and secure applications, into constraint systems for proof generation and verification. It includes an interpreter for program execution during development and a solver for generating witnesses in constraint systems. Anticipate a more powerful Keelung! Upcoming updates include seamless Keelung-Haskell integration and unsigned integers with limitless bit-widths. Cheers, BTQ team Blog post: https://www.btq.com/blog/keelung-compiler-is-now-open-source Discord: https://discord.gg/j5rMMZ3nVh Keelung Language repo: https://github.com/btq-ag/keelung Keelung Compiler repo: https://github.com/btq-ag/keelung-compiler -------------- next part -------------- An HTML attachment was scrubbed... URL: From val.saven at gmail.com Fri Jun 23 05:37:34 2023 From: val.saven at gmail.com (Val Saven) Date: Fri, 23 Jun 2023 12:37:34 +0700 Subject: [Haskell-cafe] wiki-account-request Message-ID: Hi! I would like to create an account for https://wiki.haskell.org with the username ValSaven. Thanks in advance. -------------- next part -------------- An HTML attachment was scrubbed... URL: From leah at vuxu.org Sun Jun 25 20:10:38 2023 From: leah at vuxu.org (Leah Neukirchen) Date: Sun, 25 Jun 2023 22:10:38 +0200 Subject: [Haskell-cafe] Munich Haskell Meeting, 2023-06-27 @ 19:30 Message-ID: <87bkh3b8w1.fsf@vuxu.org> Dear all, Next week, our monthly Munich Haskell Meeting will take place again on Tuesday, June 27 at Augustiner-Gaststätte Rumpler at 19h30. For details see here: http://muenchen.haskell.bayern/dates.html If you plan to join, please add yourself to this nuudel so we can reserve enough seats! It is OK to add yourself to the nuudel anonymously or pseudonymously. https://nuudel.digitalcourage.de/sPH3fnJ1Jrx61Iky Everybody is welcome! cu, -- Leah Neukirchen https://leahneukirchen.org/ From icfp.publicity at googlemail.com Tue Jun 27 05:19:24 2023 From: icfp.publicity at googlemail.com (ICFP Publicity) Date: Tue, 27 Jun 2023 13:19:24 +0800 Subject: [Haskell-cafe] ICFP 2023: Call for Volunteers (Deadline: 30 June!) Message-ID: ICFP 2023 CALL FOR VOLUNTEERS 28th ACM SIGPLAN International Conference on Functional Programming https://icfp23.sigplan.org/track/icfp-2023-volunteers Sign up to be a Volunteer and help us make ICFP 2023 a unique experience for all attendants! ICFP 2023 is pleased to offer a number of opportunities for volunteers, who are vital to the efficient operation and continued success of the conference each year. The volunteer program is a chance for people from around the world to participate in the conferences whilst assisting us in preparing and running the event. The Volunteer Program helps more people attend the ICFP conference by covering conference fees, including access to the banquet (but not travel or lodging expenses) in exchange for a fixed number of work hours (usually from 12 to 15) helping with the conference organization. ## How to apply Please apply using this form (https://forms.gle/27pzbztJq5PVCZeW9). The deadline is June 30th ## Eligibility Everyone is welcome to apply. Priority is given to junior members of our community, e.g. full- or part-time students of computer science and related fields. ## Expectation Applicants must be available for at least four (4) full days between September 4th and September 9th, 2023, and will be expected to provide a total of 12-15 hours of volunteering work in that time. The skills, talents, and dedication of our Volunteers contribute to the overall quality of the conference. The Volunteer role this year will mainly involve working with the organizers to prepare for the conference by providing technical assistance to attendees, managing online Q&A and poster sessions, and supporting active communication in our online environment. ## Compensation * A Complimentary Conference Registration, offering access to all open sessions (i.e., parallel paper presentations, demonstrations, and workshops) and conference proceedings. * Free lunches and refreshments during breaks. * Volunteer garments. * Free admission to all social events. Please note that volunteers are responsible for their own travel and accommodation arrangements. If you need additional travel funding, please consider SIGPLAN PAC Funding (http://www.sigplan.org/PAC/) and PLMW (https://icfp23.sigplan.org/track/plmw-icfp-2023). From bryan at haskell.foundation Tue Jun 27 06:06:33 2023 From: bryan at haskell.foundation (Bryan Richter) Date: Tue, 27 Jun 2023 09:06:33 +0300 Subject: [Haskell-cafe] type error when specializing lens zooms in ghc >= 9.0 In-Reply-To: <01f9667743615d6a038411a008b4312751baf72b.camel@aatal-apotheke.de> References: <01f9667743615d6a038411a008b4312751baf72b.camel@aatal-apotheke.de> Message-ID: Hi Olaf, I don't know the precise background to the current system for assignment of error codes, but I do know that there is ongoing work to provide more structure to errors. These instances of overly-general codes (and hypothetically some that may be overly-specific) are artifacts of a rather young process. I added some of your suggestions to the ticket. On Fri, 2 Jun 2023 at 17:16, Olaf Klinke wrote: > > Hm, yikes, I tend to agree this is a very general error message. Here > > are > > all the places "83865" shows up in the code base: > > > > > > > https://gitlab.haskell.org/search?search=83865&project_id=1&group_id=2&search_code=true&repository_ref=master > > > > I opened https://gitlab.haskell.org/ghc/ghc/-/issues/23466 to follow > > up. > > Feel free to weigh in. (Contact me if you need an account - spam > > measures > > currently include manual approvals for new accounts.) > > > > Thanks, Bryan. > > This made me wonder what the current system behind assignment of error > codes is. I'd expect five-digit error codes to be *more* specific than > the general shape of error message emitted by ghc, but here it is > evidently less specific. 82865 stands for the error message constructor > TypeEqMismatch [1] which is a record [2] with many fields. In > particular, the teq_mismatch_expected and teq_mismatch_actual fields > hold structural information: a ForAllTy [3] may hint at simplified > subsumption. > > Thus my proposal would be that error codes are composite values, with > one part (as currently implemented) in bijection to the error message > constructor and another part determined by a function of the actual > error value. This function has to be chosen to provide sufficient > abstraction from the actual situation but e.g. differentiate between > constructors of the Type type. For example, why don't the cases > differentiated by the pretty-printer [4] not own their own error codes? > > Olaf > > [1] > https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Types/Error/Codes.hs > [2] > https://hackage.haskell.org/package/ghc-9.6.1/docs/src/GHC.Tc.Errors.Types.html#TypeEqMismatch > [3] > https://hackage.haskell.org/package/ghc-9.6.1/docs/src/GHC.Core.TyCo.Rep.html#ForAllTy > [4] > https://hackage.haskell.org/package/ghc-9.6.1/docs/src/GHC.Tc.Errors.Ppr.html#pprMismatchMsg > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From zoran.bosnjak at via.si Fri Jun 30 18:00:03 2023 From: zoran.bosnjak at via.si (Zoran =?utf-8?Q?Bo=C5=A1njak?=) Date: Fri, 30 Jun 2023 18:00:03 +0000 (UTC) Subject: [Haskell-cafe] servant streaming question Message-ID: <1583064132.3146.1688148003211.JavaMail.zimbra@via.si> Hi all, I would like to reuse some streaming functions from the turtle package in the context of the servant streaming handler. Relevant references: https://hackage.haskell.org/package/turtle-1.6.1/docs/Turtle-Shell.html https://hackage.haskell.org/package/turtle-1.6.1/docs/Turtle-Prelude.html https://hackage.haskell.org/package/servant-0.20/docs/Servant-Types-SourceT.html As a simple example: Turtle.Prelude.ls function represents stream of FilePaths (directory listing of some path) ls :: FilePath -> Shell FilePath Servant streaming is based around SourceT IO a, for example: type ListFiles = "ls" :> StreamGet NewlineFraming PlainText (SourceT IO FilePath) The problem is that the streaming (Shell a) is not exactly the same as servant's (SourceT IO a). But as far as I understand, they both represent "stream of values of type 'a'". My question is: Is a generic conversion function possible? Something like: shellToSource :: forall a. Shell a -> SourceIO a shellToSource = ?? ... such that I could reuse the 'ls' and write a streaming servant handler like this: listFilesHandler :: Handler (SourceIO FilePath) listFilesHandler = pure $ shellToSource $ Turtle.Prelude.ls "somePath" Appreciate any suggestion. regards, Zoran