From groups7 at alexn.org Wed Jan 2 00:44:25 2019 From: groups7 at alexn.org (Alexandru Nedelcu) Date: Wed, 02 Jan 2019 02:44:25 +0200 Subject: [Haskell-cafe] MVar considered harmful In-Reply-To: References: Message-ID: <7C1EC6E1-C402-4F64-9782-36A285FE22A7@alexn.org> Hello, I’m the author of the `MVar` implementation in Cats-Effect. > Recently I had an interesting discussion on MVars with cats-effect > library > designers. Cats-effect brings MVar synchronization primitive along > with > other IO stuff to the Scala programming language. I tried to persuade > them > to include some Control.Concurrent.MVar’s functions to the library > but has > failed completely. Moreover, now I think that MVar is a poor choice > for > basic synchronization primitive. I believe `MVar` is a superb choice for synchronisation, because it behaves like a blocking queue, which in computer science is a pretty fundamental tool. It is true that in Cats-Effect an `MVar` might not be a primitive, but as I explained in that thread, on top of the JVM the real primitives are the low level building blocks like `AtomicReference`. > 1. It’s complex. Each MVar has 2 state transitions, each may block. Blocking is a feature. If you have to build that logic via `Ref` (`IORef`), you’d have to model the state machine by yourself and that’s complexity being pushed to the user. > 2. It does not play well in presence of asynchronous exceptions. More > specifically, `take` and `put` operations should be balanced (each > `take` > must be followed by `put`) The `take` followed by a `put` rule is only for your “modify” use-case. The problem is that a `modify` function that’s described via `take` + `put` is not an atomic operation and this is a problem, but only if any of the actors accessing the `MVar` are doing so in a different order. This isn’t a problem for other use-cases tough. > this force programmer to mask asynchronous > exceptions during the MVar acquisition and since `take` function may > block, > this will delay task cancelation. I don’t have much experience with Haskell’s async exceptions, but if you mean that `take` must be executed as `uncancelable`, via `bracket`, then this is a problem that we can fix in Cats-Effect 2.x, as mentioned in that thread. > What could be the sensible alternative? Guy from the cats-effect > suggested > me IVar + atomic reference (IORef). This pattern separates concern of > blocking (synchronization) from the atomic mutation. So everything can > be > represented as atomic reference with IVar inside. Just look at this > beautiful mutex implementation > https://github.com/ovotech/fs2-kafka/blob/master/src/main/scala/fs2/kafka/internal/Synchronized.scala As I said above, most things on top of the JVM can be implemented via an `AtomicReference` due to its memory model and this is no exception. But it’s not elegant, or simple ;-) > (By ”beautiful” I mean approach itself of course, but not the > Scala’s > syntax. Scala is one of most ugliest girls after C++ I was forced to > date > with by my employer for money. Thankfully he didn’t force me to do > the same > things with her grandma Java). That’s unnecessary and TBH a turnoff. Cheers, -- Alexandru Nedelcu https://alexn.org -------------- next part -------------- An HTML attachment was scrubbed... URL: From groups7 at alexn.org Wed Jan 2 01:04:34 2019 From: groups7 at alexn.org (Alexandru Nedelcu) Date: Wed, 02 Jan 2019 03:04:34 +0200 Subject: [Haskell-cafe] MVar considered harmful In-Reply-To: <7C1EC6E1-C402-4F64-9782-36A285FE22A7@alexn.org> References: <7C1EC6E1-C402-4F64-9782-36A285FE22A7@alexn.org> Message-ID: And one more thing, you mentioned the `Synchronized` implementation at: https://github.com/ovotech/fs2-kafka/blob/master/src/main/scala/fs2/kafka/internal/Synchronized.scala N.B. I happen to believe this is harmful because: 1. Mutexes are in general bad, a solution of last resort, because it prevents threads from making progress in case the scheduler pauses the OS thread that holds the lock; for this reason we want non-blocking, even wait-free algorithms, whenever possible 2. This implementation itself has performance characteristics that are less than ideal — could be much better as it could use platform intrinsics for spin-locking and it could be biased for single threaded uses On point number 2, this is important because it shows that `Ref` isn’t very adequate to build `Synchronized`. On point number 1 … this extends to `MVar` usage too. If you have blocking behaviour in a way that prevents threads from making progress, such solutions don’t scale and it doesn’t matter how you build it (`MVar` or `IORef` or whatever), it’s still going to be a bottleneck. -- Alexandru Nedelcu https://alexn.org On 2 Jan 2019, at 2:44, Alexandru Nedelcu wrote: > Hello, > > I’m the author of the `MVar` implementation in Cats-Effect. > >> Recently I had an interesting discussion on MVars with cats-effect >> library >> designers. Cats-effect brings MVar synchronization primitive along >> with >> other IO stuff to the Scala programming language. I tried to persuade >> them >> to include some Control.Concurrent.MVar’s functions to the library >> but has >> failed completely. Moreover, now I think that MVar is a poor choice >> for >> basic synchronization primitive. > > I believe `MVar` is a superb choice for synchronisation, because it > behaves like a blocking queue, which in computer science is a pretty > fundamental tool. > > It is true that in Cats-Effect an `MVar` might not be a primitive, but > as I explained in that thread, on top of the JVM the real primitives > are the low level building blocks like `AtomicReference`. > >> 1. It’s complex. Each MVar has 2 state transitions, each may block. > > Blocking is a feature. If you have to build that logic via `Ref` > (`IORef`), you’d have to model the state machine by yourself and > that’s complexity being pushed to the user. > >> 2. It does not play well in presence of asynchronous exceptions. More >> specifically, `take` and `put` operations should be balanced (each >> `take` >> must be followed by `put`) > > The `take` followed by a `put` rule is only for your “modify” > use-case. > > The problem is that a `modify` function that’s described via `take` > + `put` is not an atomic operation and this is a problem, but only if > any of the actors accessing the `MVar` are doing so in a different > order. > > This isn’t a problem for other use-cases tough. > >> this force programmer to mask asynchronous >> exceptions during the MVar acquisition and since `take` function may >> block, >> this will delay task cancelation. > > I don’t have much experience with Haskell’s async exceptions, but > if you mean that `take` must be executed as `uncancelable`, via > `bracket`, then this is a problem that we can fix in Cats-Effect 2.x, > as mentioned in that thread. > >> What could be the sensible alternative? Guy from the cats-effect >> suggested >> me IVar + atomic reference (IORef). This pattern separates concern of >> blocking (synchronization) from the atomic mutation. So everything >> can be >> represented as atomic reference with IVar inside. Just look at this >> beautiful mutex implementation >> https://github.com/ovotech/fs2-kafka/blob/master/src/main/scala/fs2/kafka/internal/Synchronized.scala > > As I said above, most things on top of the JVM can be implemented via > an `AtomicReference` due to its memory model and this is no exception. > > But it’s not elegant, or simple ;-) > >> (By ”beautiful” I mean approach itself of course, but not the >> Scala’s >> syntax. Scala is one of most ugliest girls after C++ I was forced to >> date >> with by my employer for money. Thankfully he didn’t force me to do >> the same >> things with her grandma Java). > > That’s unnecessary and TBH a turnoff. > > Cheers, > > -- > Alexandru Nedelcu > https://alexn.org -------------- next part -------------- An HTML attachment was scrubbed... URL: From V.Liepelt at kent.ac.uk Wed Jan 2 09:47:15 2019 From: V.Liepelt at kent.ac.uk (V.Liepelt) Date: Wed, 2 Jan 2019 09:47:15 +0000 Subject: [Haskell-cafe] Ord methods too strict? Message-ID: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> I am surprised to find that `False <= undefined = undefined`. What justifies (<=) to be strict in both arguments? Vilem From V.Liepelt at kent.ac.uk Wed Jan 2 11:31:38 2019 From: V.Liepelt at kent.ac.uk (V.Liepelt) Date: Wed, 2 Jan 2019 11:31:38 +0000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> Message-ID: <91F22511-496E-40B7-91C5-AB7B60853B38@kent.ac.uk> More concretely, it's likely that Ord Bool is defined via `compare`, which is necessarily strict in both arguments. Yes, this did come to mind. In general a non-strict `compare` would only make sense for `()`. One of the relationships implied by the Ord typeclass is: a <= b = True iff compare a b = EQ \/ compare a b = LT So wouldn’t it make sense to define `compare` in terms of the “weaker” relations? It seems very unhaskelly to do the unnecessary work of evaluating the second argument to a relation when we already know what the result should be. Vilem On 2 Jan 2019, at 10:29, Isaac Elliott > wrote: One of the relationships implied by the Ord typeclass is: a <= b = True iff compare a b = EQ \/ compare a b = LT If we write an alternative definition of (<=) that is only strict in its first argument: False <= _ = True True <= x = x Then it's impossible to write `compare` in a way that's consistent with that relation. More concretely, it's likely that Ord Bool is defined via `compare`, which is necessarily strict in both arguments. On Wed, 2 Jan. 2019, 7:47 pm V.Liepelt, > wrote: I am surprised to find that `False <= undefined = undefined`. What justifies (<=) to be strict in both arguments? Vilem _______________________________________________ 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 tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Wed Jan 2 11:37:23 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Wed, 2 Jan 2019 11:37:23 +0000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> Message-ID: <20190102113723.f7ggsrm55ezhr26x@weber> On Wed, Jan 02, 2019 at 09:47:15AM +0000, V.Liepelt wrote: > I am surprised to find that `False <= undefined = undefined`. > > What justifies (<=) to be strict in both arguments? The implementation of the Ord instance for Bool is derived, as you can see here: https://www.stackage.org/haddock/lts-12.1/ghc-prim-0.5.2.0/src/GHC-Classes.html#Ord As for the justification, perhaps it's too much of a special case for only one value of an enumeration to compare to undefined without crashing, and perhaps it inhibits optimisation opportunities. Tom From V.Liepelt at kent.ac.uk Wed Jan 2 11:49:40 2019 From: V.Liepelt at kent.ac.uk (V.Liepelt) Date: Wed, 2 Jan 2019 11:49:40 +0000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: <20190102113723.f7ggsrm55ezhr26x@weber> References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> Message-ID: > The implementation of the Ord instance for Bool is derived So my argument would be—doesn’t this mean that we need to do cleverer deriving or at least have a hand-written instance? > As for the justification, perhaps it's too much of a special case for only > one value of an enumeration to compare to undefined without crashing This is not just about crashing. (I’m using `undefined` as a way of making strictness explicit.) `False >= veryExpensiveComputation` should return `True` immediately without any unnecessary computation. Also it doesn’t seem like a special case: this makes sense for any partially ordered Type with a top and/or bottom element. > perhaps it inhibits optimisation opportunities. That doesn’t seem very likely to me, I would rather think the contrary (see above): doing unnecessary work can hardly make a program run faster. V > On 2 Jan 2019, at 11:37, Tom Ellis wrote: > > On Wed, Jan 02, 2019 at 09:47:15AM +0000, V.Liepelt wrote: >> I am surprised to find that `False <= undefined = undefined`. >> >> What justifies (<=) to be strict in both arguments? > > The implementation of the Ord instance for Bool is derived, as you can see > here: > > https://www.stackage.org/haddock/lts-12.1/ghc-prim-0.5.2.0/src/GHC-Classes.html#Ord > > As for the justification, perhaps it's too much of a special case for only > one value of an enumeration to compare to undefined without crashing, and > perhaps it inhibits optimisation opportunities. > > Tom > _______________________________________________ > 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 V.Liepelt at kent.ac.uk Wed Jan 2 12:34:58 2019 From: V.Liepelt at kent.ac.uk (V.Liepelt) Date: Wed, 2 Jan 2019 12:34:58 +0000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> Message-ID: <90E11DAC-EFB9-4A72-B60A-2DFF27D742C4@kent.ac.uk> False <= _ = True _ <= y = y Yeah, that’s what I was thinking (in fact this is how I hit this in the first place—I was using `(<=)` as a quick and dirty logical implication operator and was surprised to hit `undefined` even though the precondition was False!) Note that even with this definition, "undefined <= True = undefined" so strictness is now not symmetric. Isn’t “asymmetry” the whole point of laziness? Consider `(||)`. Note "fromEnum" here is zero cost, and there is no branch. Checking the left hand branch for false first would require a branch that would possibly hit performance. This probably isn't worth slowing down this function just so it's lazy in it's right argument (but as a gotcha now, still strict in it's left argument). Yes, comparison on constants may happen to be faster on a concrete architecture. Thanks, I hadn’t considered this. However this assumes that both arguments are already evaluated, which of course will require branching unless you happen to know the second argument at compile time, for which case we might want to have a rewrite rule for the more efficient implementation. But it feels wrong to make architectural considerations leak into the standard library when this isn’t really necessary. V On 2 Jan 2019, at 12:09, Clinton Mead > wrote: How would you define Ord on Bools? Like so? False <= _ = True _ <= y = y Note that even with this definition, "undefined <= True = undefined" so strictness is now not symmetric. Also, as bool are implemented as just an int of some sort (presumably 0 and 1), the strict definition allows the following implementation in effect: x <= y = fromEnum x <= fromEnum y Note "fromEnum" here is zero cost, and there is no branch. Checking the left hand branch for false first would require a branch that would possibly hit performance. This probably isn't worth slowing down this function just so it's lazy in it's right argument (but as a gotcha now, still strict in it's left argument). On Wed, Jan 2, 2019 at 10:50 PM V.Liepelt > wrote: > The implementation of the Ord instance for Bool is derived So my argument would be—doesn’t this mean that we need to do cleverer deriving or at least have a hand-written instance? > As for the justification, perhaps it's too much of a special case for only > one value of an enumeration to compare to undefined without crashing This is not just about crashing. (I’m using `undefined` as a way of making strictness explicit.) `False >= veryExpensiveComputation` should return `True` immediately without any unnecessary computation. Also it doesn’t seem like a special case: this makes sense for any partially ordered Type with a top and/or bottom element. > perhaps it inhibits optimisation opportunities. That doesn’t seem very likely to me, I would rather think the contrary (see above): doing unnecessary work can hardly make a program run faster. V > On 2 Jan 2019, at 11:37, Tom Ellis > wrote: > > On Wed, Jan 02, 2019 at 09:47:15AM +0000, V.Liepelt wrote: >> I am surprised to find that `False <= undefined = undefined`. >> >> What justifies (<=) to be strict in both arguments? > > The implementation of the Ord instance for Bool is derived, as you can see > here: > > https://www.stackage.org/haddock/lts-12.1/ghc-prim-0.5.2.0/src/GHC-Classes.html#Ord > > As for the justification, perhaps it's too much of a special case for only > one value of an enumeration to compare to undefined without crashing, and > perhaps it inhibits optimisation opportunities. > > Tom > _______________________________________________ > 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 tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Wed Jan 2 14:42:10 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Wed, 2 Jan 2019 14:42:10 +0000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> Message-ID: <20190102144210.zllt2qi5yaix2uyh@weber> On Wed, Jan 02, 2019 at 11:49:40AM +0000, V.Liepelt wrote: > > As for the justification, perhaps it's too much of a special case for only > > one value of an enumeration to compare to undefined without crashing > > Also it doesn’t seem like a special case: this makes sense for any > partially ordered Type with a top and/or bottom element. I mean that for any data type data E of C1 | C2 | ... you are preposing that the (<=) of the derived Ord instance would have a special case for C1. From svenpanne at gmail.com Wed Jan 2 19:06:08 2019 From: svenpanne at gmail.com (Sven Panne) Date: Wed, 2 Jan 2019 20:06:08 +0100 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: <20190102144210.zllt2qi5yaix2uyh@weber> References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> <20190102144210.zllt2qi5yaix2uyh@weber> Message-ID: Am Mi., 2. Jan. 2019 um 15:42 Uhr schrieb Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk>: > I mean that for any data type > > data E of C1 | C2 | ... > > you are preposing that the (<=) of the derived Ord instance would have a > special case for C1. > ... and another special case for (>=) for the last enumeration value. And a very special version for one-element enumerations. And what about (<) and (>)? And derived (==) for one-element enumerations? And, and, and... :-P Putting on the language lawyer hat: The Haskell Report explicitly states that Bool's Ord instance is derived (section 6.1.1), and section 11.1 explicitly states that all derived operations for Eq and Ord are strict in both arguments. Consequently, Implementing Ord for Bool in a lazier way would violate the specification. I would say that the the way the report specifies this is a good thing: Coming up with special cases is a bad design principle, consistency almost always trumps anything else (the human brain is notoriously small). Furthermore, laziness is not always a good thing, it could lead to space leaks, so e.g. making Bool's Ord operations lazier would definitely make various people very unhappy sooner or later. :-) -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Wed Jan 2 21:51:25 2019 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Wed, 2 Jan 2019 22:51:25 +0100 Subject: [Haskell-cafe] Ord methods too strict? Message-ID: Information-theoretically 'compare' must be stricter than <= because is gives more information: It decides equality, which <= doesn't. Therefore compare must be strict in both arguments. What follows is an argument that there can not be a lazy implementation of <= that behaves like logical implication. We try to model <= after the logical implication operator. Order-theoretically, the binary operation (<=) should be antitone in the first and monotone in the second argument. The preceding sentence only makes sense once we define a mathematical order on the semantics of Bool. Let's declare the "logical" order False < undefined < True. I give a formal justification in Appendix A below. Arrange all nine combinations of type (Bool,Bool) in a 3x3 grid where the first dimension is descending and the second dimension is ascending in the logical order. Now we consider: (undefined,True) must map to True because (True,True) maps to True and descending in the first argument means ascending in the result. (False,undefined) must map to True because (False,False) maps to True and ascending in the second argument means ascending in the result. Further we require (True,False) mapping to False. But now we're in trouble: A function giving the above three return values requires ambiguous choice, which we don't have available in pure, sequential Haskell, q.e.d. It's the same reason why we can't have (&&) or (||) operators which behave symmetrically w.r.t. the logical order. Olaf ========== Appendix A Let R be a binary relation on a set A. The Egli-Milner-lifting of R is a binary relation on the powerset of A. Among several possible liftings, it is the one with the most pleasing properties [1, Theorem 2.12]. Identify the "undefined" value of a type A with the maximal element of the powerset of A, which expresses that "undefined" may evaluate to anything. In Haskell terms: {-# LANGUAGE Rank2Types #-} module RelationLifting where import Prelude hiding (undefined) type Relation a = a -> a -> Bool type Lifting = forall a. Relation a -> Relation [a] egliMilner :: Lifting egliMilner r xs ys = hoare && smyth where hoare = all (\x -> any (\y -> r x y) ys) xs smyth = all (\y -> any (\x -> r x y) xs) ys true, false, undefined :: [Bool] true = [True] false = [False] undefined = [False,True] RelationLifting> egliMilner (<=) false undefined True RelationLifting> egliMilner (<=) undefined true True [1] https://www.cs.le.ac.uk/people/akurz/Papers/kv-relation-lifting.pdf From damien.mattei at gmail.com Wed Jan 2 08:17:03 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Wed, 2 Jan 2019 09:17:03 +0100 Subject: [Haskell-cafe] Maybe type filtered In-Reply-To: References: Message-ID: i repost because it seems that the first post of the year in haskell cafe ailing list has been lost! i cant't see in the archive of january neither december.... so here it is again: On Tue, Jan 1, 2019 at 10:25 AM Damien Mattei wrote: > i had filtered a [Maybe Text] type to remove Nothing from the list and now > i want to put the result in a [Text] type but the compiler complains about > the incompatible type : > > (bd_rows_WDS :: [Only (Maybe Text)]) <- query conn qry_head_WDS (Only > (name::String)) > > -- remove the records having N°BD NULL > let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> > case a of > Nothing -> False > Just a -> True) > bd_rows_WDS > > Prelude> :load UpdateSidonie > [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) > > UpdateSidonie.hs:282:33: error: > • Couldn't match type ‘Maybe Text’ with ‘Text’ > Expected type: [Only Text] > Actual type: [Only (Maybe Text)] > • In the expression: > Prelude.filter > (\ (Only a) > -> case a of > Nothing -> False > Just a -> True) > bd_rows_WDS > In a pattern binding: > fltWDS :: [Only Text] > = Prelude.filter > (\ (Only a) > -> case a of > Nothing -> False > Just a -> True) > bd_rows_WDS > In the expression: > do conn <- connect > defaultConnectInfo > {connectHost = "moita", connectUser = "mattei", > connectPassword = "sidonie2", connectDatabase = > "sidonie"} > (rows :: [(Text, Double)]) <- query_ > conn > "SELECT Nom,distance FROM > AngularDistance WHERE distance > 0.000278" > (names :: [Only Text]) <- query_ > conn > "SELECT Nom FROM AngularDistance > WHERE distance > 0.000278" > let resLstNames = Prelude.map fromOnly names > .... > | > 282 | let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> > | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... > Failed, no modules loaded. > > how can id do the type conversion,now i'm sure there is no more Nothing > values? > -------------- next part -------------- An HTML attachment was scrubbed... URL: From damien.mattei at gmail.com Tue Jan 1 09:25:29 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Tue, 1 Jan 2019 10:25:29 +0100 Subject: [Haskell-cafe] Maybe type filtered Message-ID: i had filtered a [Maybe Text] type to remove Nothing from the list and now i want to put the result in a [Text] type but the compiler complains about the incompatible type : (bd_rows_WDS :: [Only (Maybe Text)]) <- query conn qry_head_WDS (Only (name::String)) -- remove the records having N°BD NULL let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS Prelude> :load UpdateSidonie [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) UpdateSidonie.hs:282:33: error: • Couldn't match type ‘Maybe Text’ with ‘Text’ Expected type: [Only Text] Actual type: [Only (Maybe Text)] • In the expression: Prelude.filter (\ (Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS In a pattern binding: fltWDS :: [Only Text] = Prelude.filter (\ (Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS In the expression: do conn <- connect defaultConnectInfo {connectHost = "moita", connectUser = "mattei", connectPassword = "sidonie2", connectDatabase = "sidonie"} (rows :: [(Text, Double)]) <- query_ conn "SELECT Nom,distance FROM AngularDistance WHERE distance > 0.000278" (names :: [Only Text]) <- query_ conn "SELECT Nom FROM AngularDistance WHERE distance > 0.000278" let resLstNames = Prelude.map fromOnly names .... | 282 | let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... Failed, no modules loaded. how can id do the type conversion,now i'm sure there is no more Nothing values? -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Thu Jan 3 03:53:00 2019 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Thu, 3 Jan 2019 13:53:00 +1000 Subject: [Haskell-cafe] Maybe type filtered In-Reply-To: References: Message-ID: That's because you still have "Just a" values. Try mapMaybe from Data.Maybe instead. On mobile; please excuse any tpyos. On Thu, 3 Jan. 2019, 1:29 pm Damien Mattei i repost because it seems that the first post of the year in haskell cafe > ailing list has been lost! i cant't see in the archive of january neither > december.... > so here it is again: > > On Tue, Jan 1, 2019 at 10:25 AM Damien Mattei > wrote: > >> i had filtered a [Maybe Text] type to remove Nothing from the list and >> now i want to put the result in a [Text] type but the compiler complains >> about the incompatible type : >> >> (bd_rows_WDS :: [Only (Maybe Text)]) <- query conn qry_head_WDS (Only >> (name::String)) >> >> -- remove the records having N°BD NULL >> let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> >> case a of >> Nothing -> False >> Just a -> True) >> bd_rows_WDS >> >> Prelude> :load UpdateSidonie >> [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) >> >> UpdateSidonie.hs:282:33: error: >> • Couldn't match type ‘Maybe Text’ with ‘Text’ >> Expected type: [Only Text] >> Actual type: [Only (Maybe Text)] >> • In the expression: >> Prelude.filter >> (\ (Only a) >> -> case a of >> Nothing -> False >> Just a -> True) >> bd_rows_WDS >> In a pattern binding: >> fltWDS :: [Only Text] >> = Prelude.filter >> (\ (Only a) >> -> case a of >> Nothing -> False >> Just a -> True) >> bd_rows_WDS >> In the expression: >> do conn <- connect >> defaultConnectInfo >> {connectHost = "moita", connectUser = "mattei", >> connectPassword = "sidonie2", connectDatabase = >> "sidonie"} >> (rows :: [(Text, Double)]) <- query_ >> conn >> "SELECT Nom,distance FROM >> AngularDistance WHERE distance > 0.000278" >> (names :: [Only Text]) <- query_ >> conn >> "SELECT Nom FROM AngularDistance >> WHERE distance > 0.000278" >> let resLstNames = Prelude.map fromOnly names >> .... >> | >> 282 | let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> >> | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... >> Failed, no modules loaded. >> >> how can id do the type conversion,now i'm sure there is no more Nothing >> values? >> > _______________________________________________ > 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 damien.mattei at gmail.com Wed Jan 2 13:45:47 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Wed, 2 Jan 2019 14:45:47 +0100 Subject: [Haskell-cafe] Maybe type filtered to remove Nothing Message-ID: i had filtered a [Maybe Text] type to remove Nothing from the list and now i want to put the result in a [Text] type but the compiler complains about the incompatible type : (bd_rows_WDS :: [Only (Maybe Text)]) <- query conn qry_head_WDS (Only (name::String)) -- remove the records having N°BD NULL let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS Prelude> :load UpdateSidonie [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) UpdateSidonie.hs:282:33: error: • Couldn't match type ‘Maybe Text’ with ‘Text’ Expected type: [Only Text] Actual type: [Only (Maybe Text)] • In the expression: Prelude.filter (\ (Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS In a pattern binding: fltWDS :: [Only Text] = Prelude.filter (\ (Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS In the expression: do conn <- connect defaultConnectInfo {connectHost = "moita", connectUser = "mattei", connectPassword = "sidonie2", connectDatabase = "sidonie"} (rows :: [(Text, Double)]) <- query_ conn "SELECT Nom,distance FROM AngularDistance WHERE distance > 0.000278" (names :: [Only Text]) <- query_ conn "SELECT Nom FROM AngularDistance WHERE distance > 0.000278" let resLstNames = Prelude.map fromOnly names .... | 282 | let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... Failed, no modules loaded. how can id do the type conversion,now i'm sure there is no more Nothing values? -------------- next part -------------- An HTML attachment was scrubbed... URL: From mpevnev at gmail.com Tue Jan 1 14:33:39 2019 From: mpevnev at gmail.com (Michail Pevnev) Date: Tue, 1 Jan 2019 17:33:39 +0300 Subject: [Haskell-cafe] Left and right monadic folds Message-ID: <20190101143339.oqklkuxgov4cov4f@MishkaPC> Hello everyone. Recently I've run into a situation where a monadic fold seems like an interesting option. However, I'm not particularly sure how to choose which fold - left or right - to use. For non-monadic folds the rule of thumb is 'avoid foldl, use foldr for infinite things and foldl' for performance'. What are the guidelines for the monadic ones? The fact that 'foldlM' is implemented (in base-4.12.0-0) using 'foldr' and 'foldrM' uses 'foldl' (also, non-strict foldl, which is worrying) adds somewhat to my confusion. I've played a bit with folding Eithers, and foldlM seems to work somewhat intuitively (breaks on the first Left, as is usual for Either), and also accepts infinite lists (which makes sense, given it's a foldr): import Data.Foldable main :: IO () main = do print $ sumNonNegative $ [1, 2, -4] ++ [5..] sumNonNegative :: [Int] -> Either String Int sumNonNegative = foldlM foo 0 foo :: Int -> Int -> Either String Int foo acc x | x >= 0 = Right $ x + acc | otherwise = Left $ "Negative number: " ++ show x This prints out "Negative number: -4". Odd things begin when I edit the above to use foldrM. It doesn't terminate on an infinite list, which is expected from a disguised foldl. But given several negative numbers in the input, it prints out the last one, seemingly turning the usual behaviour of Either on its head. It seems its foldl heritage results in applying side-effects (in case of Either, erroring out with a Left) in reverse order. Do I get this right and is this the general behaviour of foldrM for any monad? -- Michail. From lysxia at gmail.com Wed Jan 2 16:18:41 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Wed, 2 Jan 2019 17:18:41 +0100 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default Message-ID: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Hello Café, I would like to propose making haddock keep instance lists collapsed by default. Some discussion is in order since it would significantly affect the documentation of many packages on Hackage. Feel free to reply here or on the related Github thread: https://github.com/haskell/haddock/issues/698 1. Instance lists take a lot of screen estate For a motivating example, I can point to the Prelude we all love. https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html We are immediately welcomed by half a page of instances of Bool, which is not quite bad, but classes have the most impressive instance lists, as you may see when you reach Eq. Many packages, even commonly used ones, have the same issue. For an extreme example, see the scrollbar jump when you fold the instance list of Apply in singletons. https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply 2. Current workarounds They can be collapsed manually one by one, and we can jump to the middle of a module with the table of contents, but scrolling up from the bottom of an instance list is still a chore. Of course, instance lists also contain quite important information. Would it become too easy to miss if it were hidden by default? Would a more fine-grained alternative be better? Regards, Li-yao From damien.mattei at gmail.com Wed Jan 2 18:38:24 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Wed, 2 Jan 2019 19:38:24 +0100 Subject: [Haskell-cafe] remove Maybe Message-ID: i had filtered a [Maybe Text] type to remove Nothing from the list and now i want to put the result in a [Text] type but the compiler complains about the incompatible type : (bd_rows_WDS :: [Only (Maybe Text)]) <- query conn qry_head_WDS (Only (name::String)) -- remove the records having N°BD NULL let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS Prelude> :load UpdateSidonie [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) UpdateSidonie.hs:282:33: error: • Couldn't match type ‘Maybe Text’ with ‘Text’ Expected type: [Only Text] Actual type: [Only (Maybe Text)] • In the expression: Prelude.filter (\ (Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS In a pattern binding: fltWDS :: [Only Text] = Prelude.filter (\ (Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS In the expression: do conn <- connect defaultConnectInfo {connectHost = "moita", connectUser = "mattei", connectPassword = "sidonie2", connectDatabase = "sidonie"} (rows :: [(Text, Double)]) <- query_ conn "SELECT Nom,distance FROM AngularDistance WHERE distance > 0.000278" (names :: [Only Text]) <- query_ conn "SELECT Nom FROM AngularDistance WHERE distance > 0.000278" let resLstNames = Prelude.map fromOnly names .... | 282 | let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... Failed, no modules loaded. how can id do the type conversion,now i'm sure there is no more Nothing values? -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Thu Jan 3 04:29:32 2019 From: bob at redivi.com (Bob Ippolito) Date: Wed, 2 Jan 2019 20:29:32 -0800 Subject: [Haskell-cafe] remove Maybe In-Reply-To: References: Message-ID: One way to figure out how to solve this problem is to search Hoogle for the type of function you’re looking for, in this case: [Maybe a] -> [a] https://www.haskell.org/hoogle/?hoogle=%5BMaybe+a%5D+-%3E+a You’ll find that such a function exists in Data.Maybe and it is named catMaybes. No need to filter out Nothing separately, this function will do it. On Wed, Jan 2, 2019 at 20:08 Damien Mattei wrote: > i had filtered a [Maybe Text] type to remove Nothing from the list and now > i want to put the result in a [Text] type but the compiler complains about > the incompatible type : > > (bd_rows_WDS :: [Only (Maybe Text)]) <- query conn qry_head_WDS (Only > (name::String)) > > -- remove the records having N°BD NULL > let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> > case a of > Nothing -> False > Just a -> True) > bd_rows_WDS > > Prelude> :load UpdateSidonie > [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) > > UpdateSidonie.hs:282:33: error: > • Couldn't match type ‘Maybe Text’ with ‘Text’ > Expected type: [Only Text] > Actual type: [Only (Maybe Text)] > • In the expression: > Prelude.filter > (\ (Only a) > -> case a of > Nothing -> False > Just a -> True) > bd_rows_WDS > In a pattern binding: > fltWDS :: [Only Text] > = Prelude.filter > (\ (Only a) > -> case a of > Nothing -> False > Just a -> True) > bd_rows_WDS > In the expression: > do conn <- connect > defaultConnectInfo > {connectHost = "moita", connectUser = "mattei", > connectPassword = "sidonie2", connectDatabase = > "sidonie"} > (rows :: [(Text, Double)]) <- query_ > conn > "SELECT Nom,distance FROM > AngularDistance WHERE distance > 0.000278" > (names :: [Only Text]) <- query_ > conn > "SELECT Nom FROM AngularDistance > WHERE distance > 0.000278" > let resLstNames = Prelude.map fromOnly names > .... > | > 282 | let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> > | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^... > Failed, no modules loaded. > > how can id do the type conversion,now i'm sure there is no more Nothing > values? > > _______________________________________________ > 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 clintonmead at gmail.com Wed Jan 2 12:09:43 2019 From: clintonmead at gmail.com (Clinton Mead) Date: Wed, 2 Jan 2019 23:09:43 +1100 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> Message-ID: How would you define Ord on Bools? Like so? False <= _ = True _ <= y = y Note that even with this definition, "undefined <= True = undefined" so strictness is now not symmetric. Also, as bool are implemented as just an int of some sort (presumably 0 and 1), the strict definition allows the following implementation in effect: x <= y = fromEnum x <= fromEnum y Note "fromEnum" here is zero cost, and there is no branch. Checking the left hand branch for false first would require a branch that would possibly hit performance. This probably isn't worth slowing down this function just so it's lazy in it's right argument (but as a gotcha now, still strict in it's left argument). On Wed, Jan 2, 2019 at 10:50 PM V.Liepelt wrote: > > The implementation of the Ord instance for Bool is derived > > So my argument would be—doesn’t this mean that we need to do cleverer > deriving or at least have a hand-written instance? > > > As for the justification, perhaps it's too much of a special case for > only > > one value of an enumeration to compare to undefined without crashing > > This is not just about crashing. (I’m using `undefined` as a way of making > strictness explicit.) `False >= veryExpensiveComputation` should return > `True` immediately without any unnecessary computation. > > Also it doesn’t seem like a special case: this makes sense for any > partially ordered Type with a top and/or bottom element. > > > perhaps it inhibits optimisation opportunities. > > That doesn’t seem very likely to me, I would rather think the contrary > (see above): doing unnecessary work can hardly make a program run faster. > > V > > > On 2 Jan 2019, at 11:37, Tom Ellis < > tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > > > > On Wed, Jan 02, 2019 at 09:47:15AM +0000, V.Liepelt wrote: > >> I am surprised to find that `False <= undefined = undefined`. > >> > >> What justifies (<=) to be strict in both arguments? > > > > The implementation of the Ord instance for Bool is derived, as you can > see > > here: > > > > > https://www.stackage.org/haddock/lts-12.1/ghc-prim-0.5.2.0/src/GHC-Classes.html#Ord > > > > As for the justification, perhaps it's too much of a special case for > only > > one value of an enumeration to compare to undefined without crashing, and > > perhaps it inhibits optimisation opportunities. > > > > Tom > > _______________________________________________ > > 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 isaace71295 at gmail.com Wed Jan 2 10:29:51 2019 From: isaace71295 at gmail.com (Isaac Elliott) Date: Wed, 2 Jan 2019 20:29:51 +1000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> Message-ID: One of the relationships implied by the Ord typeclass is: a <= b = True iff compare a b = EQ \/ compare a b = LT If we write an alternative definition of (<=) that is only strict in its first argument: False <= _ = True True <= x = x Then it's impossible to write `compare` in a way that's consistent with that relation. More concretely, it's likely that Ord Bool is defined via `compare`, which is necessarily strict in both arguments. On Wed, 2 Jan. 2019, 7:47 pm V.Liepelt, wrote: > I am surprised to find that `False <= undefined = undefined`. > > What justifies (<=) to be strict in both arguments? > > Vilem > _______________________________________________ > 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 lysxia at gmail.com Wed Jan 2 15:06:57 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Wed, 2 Jan 2019 16:06:57 +0100 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: <90E11DAC-EFB9-4A72-B60A-2DFF27D742C4@kent.ac.uk> References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> <90E11DAC-EFB9-4A72-B60A-2DFF27D742C4@kent.ac.uk> Message-ID: <47cce08d-9ab1-9f8d-f581-1a0dcf3cd459@gmail.com> Hi Vilem, > This is not just about crashing. (I’m using `undefined` as a way of > making strictness explicit.) `False >= veryExpensiveComputation` > should return `True` immediately without any unnecessary computation. There is also an opposite situation, where evaluating the second argument allows us to free a lot of memory, as that argument would otherwise remain a thunk with references to many things. > Also it doesn’t seem like a special case: this makes sense for any partially ordered Type with a top and/or bottom element. That may be acceptable with Bool because its values are small. But to compare two pairs `(a,b) <= (x,y)` we would have to first traverse `(a,b)` to decide whether it's the smallest element, before evaluating the second argument to WHNF and comparing component-wise. Besides the extra complexity (both in code and in run time), this would not be less strict than the current default, since the first argument could get completely evaluated before even looking at the second one: `(False, _|_) <= (True, True) = _|_` (currently, this is `True`). We also would not know whether the type (a, b) has a smallest element without stronger constraints than (Ord a, Ord b), so this optimization is really only practically feasible for types with a nullary first constructor. Li-yao From ian at zenhack.net Thu Jan 3 05:23:58 2019 From: ian at zenhack.net (Ian Denhardt) Date: Thu, 03 Jan 2019 00:23:58 -0500 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: <154649303875.15528.13203831716285449397@localhost.localdomain> Quoting Li-yao Xia (2019-01-02 11:18:41) > For a motivating example, I can point to the Prelude we all love. > > https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html > > We are immediately welcomed by half a page of instances of Bool, which > is not quite bad, but classes have the most impressive instance lists, > as you may see when you reach Eq. > > Many packages, even commonly used ones, have the same issue. For an > extreme example, see the scrollbar jump when you fold the instance > list of Apply in singletons. > > https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply Another example where this gets a little ridiculous is my capnp package, which defines a few type classes with instances for most types in the generated code, e.g: https://hackage.haskell.org/package/capnp-0.3.0.0/docs/Data-Capnp-Classes.html It's not quite as absurd as the singletons package, but from eyeballing the size of my scrollbar I'd guess that the instance lists are 80-90% of that page. > Of course, instance lists also contain quite important information. > Would it become too easy to miss if it were hidden by default? Would a > more fine-grained alternative be better? Personally I rarely use them. It was mentioned on the Github issue/pr as well, but I think a collapse/expand all would be a good idea. My personal inclination would be to have it collapsed by default, though I feel less strongly about this. -Ian From ryan.reich at gmail.com Thu Jan 3 05:50:32 2019 From: ryan.reich at gmail.com (Ryan Reich) Date: Wed, 2 Jan 2019 21:50:32 -0800 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: I think this is a great idea. I do wonder, however, if it might exacerbate a kind of meta-documentation problem that I, at least, had when I was more of a beginner: it was not clear to me that most of a type's API is implicit in its instances of many standard classes, and specialized functions for things like mapping or folding or appending may not even be present in the rest of the module. Obviously this is something that every Haskeller needs to learn, but it was an issue for me even when the instance lists were present for me to gloss over. Perhaps Haddock could, rather than establishing this as a new default, provide a "collapse all" and "expand all" set of functions at the top of the page? On Wed, Jan 2, 2019 at 8:03 PM Li-yao Xia wrote: > Hello Café, > > I would like to propose making haddock keep instance lists collapsed by > default. Some discussion is in order since it would significantly affect > the documentation of many packages on Hackage. > > Feel free to reply here or on the related Github thread: > https://github.com/haskell/haddock/issues/698 > > 1. Instance lists take a lot of screen estate > > For a motivating example, I can point to the Prelude we all love. > > https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html > > We are immediately welcomed by half a page of instances of Bool, which > is not quite bad, but classes have the most impressive instance lists, > as you may see when you reach Eq. > > Many packages, even commonly used ones, have the same issue. For an > extreme example, see the scrollbar jump when you fold the instance list > of Apply in singletons. > > > https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply > > 2. Current workarounds > > They can be collapsed manually one by one, and we can jump to the middle > of a module with the table of contents, but scrolling up from the bottom > of an instance list is still a chore. > > Of course, instance lists also contain quite important information. > Would it become too easy to miss if it were hidden by default? Would a > more fine-grained alternative be better? > > Regards, > Li-yao > _______________________________________________ > 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 oleg.grenrus at iki.fi Thu Jan 3 07:23:16 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Thu, 3 Jan 2019 09:23:16 +0200 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: How about a compromise: show dozen or so instances with "show rest" link-toggle. That would work very nicely, if we could control which instances (e.g. instances with haddocks) should be shown. E.g. in `servant` *a lot* of docs & examples are in instance haddocks, so making them hidden will make documentation strictly worse. - Oleg > On 3 Jan 2019, at 7.50, Ryan Reich wrote: > > I think this is a great idea. I do wonder, however, if it might exacerbate a kind of meta-documentation problem that I, at least, had when I was more of a beginner: it was not clear to me that most of a type's API is implicit in its instances of many standard classes, and specialized functions for things like mapping or folding or appending may not even be present in the rest of the module. Obviously this is something that every Haskeller needs to learn, but it was an issue for me even when the instance lists were present for me to gloss over. > > Perhaps Haddock could, rather than establishing this as a new default, provide a "collapse all" and "expand all" set of functions at the top of the page? > >> On Wed, Jan 2, 2019 at 8:03 PM Li-yao Xia wrote: >> Hello Café, >> >> I would like to propose making haddock keep instance lists collapsed by >> default. Some discussion is in order since it would significantly affect >> the documentation of many packages on Hackage. >> >> Feel free to reply here or on the related Github thread: >> https://github.com/haskell/haddock/issues/698 >> >> 1. Instance lists take a lot of screen estate >> >> For a motivating example, I can point to the Prelude we all love. >> >> https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html >> >> We are immediately welcomed by half a page of instances of Bool, which >> is not quite bad, but classes have the most impressive instance lists, >> as you may see when you reach Eq. >> >> Many packages, even commonly used ones, have the same issue. For an >> extreme example, see the scrollbar jump when you fold the instance list >> of Apply in singletons. >> >> https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply >> >> 2. Current workarounds >> >> They can be collapsed manually one by one, and we can jump to the middle >> of a module with the table of contents, but scrolling up from the bottom >> of an instance list is still a chore. >> >> Of course, instance lists also contain quite important information. >> Would it become too easy to miss if it were hidden by default? Would a >> more fine-grained alternative be better? >> >> Regards, >> Li-yao >> _______________________________________________ >> 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 ganesh at earth.li Thu Jan 3 07:43:25 2019 From: ganesh at earth.li (Ganesh Sittampalam) Date: Thu, 3 Jan 2019 07:43:25 +0000 Subject: [Haskell-cafe] Maybe type filtered to remove Nothing In-Reply-To: References: Message-ID: <32cc4d05-c9ff-da92-e395-f453db0b7ee6@earth.li> On 02/01/2019 13:45, Damien Mattei wrote: > i had filtered a [Maybe Text] type to remove Nothing from the list and > now i want to put the result in a [Text] type but the compiler complains > about the incompatible type : As you've seen, filter removes values but doesn't change the type. If you did have [Maybe Text] you could use the library function catMaybes :: [Maybe a] -> [a] to both do the filtering and change the types. > (bd_rows_WDS :: [Only (Maybe Text)]) <- query conn qry_head_WDS (Only > (name::String)) > > -- remove the records having N°BD NULL > let fltWDS :: [Only Text] = Prelude.filter (\(Only a) -> > case a of > Nothing -> False > Just a -> True) > bd_rows_WDS But in your case you actually have [Only (Maybe Text)] rather than [Maybe Text] so catMaybes won't work. One option is to use a list comprehension instead: let fltWDS = [Only a | Only (Just a) <- bd_rows_WDS] Cheers, Ganesh From jon.fairbairn at cl.cam.ac.uk Thu Jan 3 10:33:02 2019 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Thu, 03 Jan 2019 10:33:02 +0000 Subject: [Haskell-cafe] Maybe type filtered References: Message-ID: Ivan Lazar Miljenovic writes: > That's because you still have "Just a" values. Try mapMaybe from Data.Maybe > instead. Sounds like a job for catMaybes from Data.Maybe catMaybes [Nothing, Just "foo"] ==> ["foo"] -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From neil_mayhew at users.sourceforge.net Thu Jan 3 14:53:45 2019 From: neil_mayhew at users.sourceforge.net (Neil Mayhew) Date: Thu, 3 Jan 2019 07:53:45 -0700 Subject: [Haskell-cafe] Maybe type filtered to remove Nothing In-Reply-To: <32cc4d05-c9ff-da92-e395-f453db0b7ee6@earth.li> References: <32cc4d05-c9ff-da92-e395-f453db0b7ee6@earth.li> Message-ID: On 2019-01-03 12:43 AM, Ganesh Sittampalam wrote: > If you did have [Maybe Text] you could use the library function > >   catMaybes :: [Maybe a] -> [a] > > to both do the filtering and change the types. > > ... > > But in your case you actually have [Only (Maybe Text)] rather than > [Maybe Text] so catMaybes won't work. One option is to use a list > comprehension instead: > > let fltWDS = [Only a | Only (Just a) <- bd_rows_WDS] It probably would be helpful to remove the Only wrapper at this stage, so this might be even better: let fltWDS = [a | Only (Just a) <- bd_rows_WDS] The way to do it with catMaybes would be to map with fromOnly first: let fltWDS = catMaybes (map fromOnly bd_rows_WDS) As Ganesh shows, there's no need for a type annotation after you've done the query, because the compiler can infer the type [Text] from the types of the functions that are used. The annotations are necessary with query only because it's polymorphic and can work with a wide variety of types. -------------- next part -------------- An HTML attachment was scrubbed... URL: From b.a.w.spitters at gmail.com Thu Jan 3 15:55:55 2019 From: b.a.w.spitters at gmail.com (Bas Spitters) Date: Thu, 3 Jan 2019 16:55:55 +0100 Subject: [Haskell-cafe] Concordium is hiring Message-ID: Concordium is the first ID/KYC ready blockchain network. Concordium focuses strongly on software quality and uses languages such as haskell, rust and Coq. There are a number of positions available at the offices in either Aarhus, Zurich, London and Marbella. In exceptional cases is off-site work possible. There is a preference for people with a relevant PhD or master's degree. https://www.concordium.com/careers/ In particular, the Concordium Aarhus office has a strong background in functional programming and type theory, and is looking to strengthen this team. There is a tight collaboration with the scientists at the Concordium Blockchain Research Center at Aarhus University. The center is also advertising several PhD and postdoc positions. https://www.iacr.org/jobs/#1717 From nathan.collins at gmail.com Thu Jan 3 18:35:31 2019 From: nathan.collins at gmail.com (Nathan Collins) Date: Thu, 3 Jan 2019 10:35:31 -0800 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: * I think collapsing instances by default is a great idea! +1 * Examples are already collapsed by default, and I think instances should be treated the same way. Re the concern that this would make the Servant docs worse, for me it would just be a matter of knowing to expand the instance docs when I'm interested in the corresponding class, the same way I expand the examples only where I'm interested. Here's an example of instance docs in Servant: http://hackage.haskell.org/package/servant-0.15/docs/Servant-API.html#t:FromHttpApiData. Until I'm interested in the FromHttpApiData class, I don't personally want to see that long list of instances with some examples. Also, in my experience, having lots of docs/examples on the instances like this is not very common. Here's an instance of examples being collapsed by default to good effect in the Prelude docs for Either: https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html#t:Either * Having a "collapse all/expand all" toggle at the top of the page would be nice, but if the default is not "collapsed" then I'd want a way to make that my personal default. I don't know much about web development, but my impression is that we could use a cookie and some simple JavaScript [1] to make "collapse by default" a per-user preference, say by remembering the last state of the hypothetical "collapse all/expand all" toggle button at the top. Haddock already uses JavaScript, so I expect this would be a small addition. Cheers, -nathan [1] https://developer.mozilla.org/en-US/docs/Web/API/document/cookie On Wed, Jan 2, 2019 at 11:23 PM Oleg Grenrus wrote: > > How about a compromise: show dozen or so instances with "show rest" link-toggle. That would work very nicely, if we could control which instances (e.g. instances with haddocks) should be shown. > > E.g. in `servant` *a lot* of docs & examples are in instance haddocks, so making them hidden will make documentation strictly worse. > > - Oleg > > On 3 Jan 2019, at 7.50, Ryan Reich wrote: > > I think this is a great idea. I do wonder, however, if it might exacerbate a kind of meta-documentation problem that I, at least, had when I was more of a beginner: it was not clear to me that most of a type's API is implicit in its instances of many standard classes, and specialized functions for things like mapping or folding or appending may not even be present in the rest of the module. Obviously this is something that every Haskeller needs to learn, but it was an issue for me even when the instance lists were present for me to gloss over. > > Perhaps Haddock could, rather than establishing this as a new default, provide a "collapse all" and "expand all" set of functions at the top of the page? > > On Wed, Jan 2, 2019 at 8:03 PM Li-yao Xia wrote: >> >> Hello Café, >> >> I would like to propose making haddock keep instance lists collapsed by >> default. Some discussion is in order since it would significantly affect >> the documentation of many packages on Hackage. >> >> Feel free to reply here or on the related Github thread: >> https://github.com/haskell/haddock/issues/698 >> >> 1. Instance lists take a lot of screen estate >> >> For a motivating example, I can point to the Prelude we all love. >> >> https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html >> >> We are immediately welcomed by half a page of instances of Bool, which >> is not quite bad, but classes have the most impressive instance lists, >> as you may see when you reach Eq. >> >> Many packages, even commonly used ones, have the same issue. For an >> extreme example, see the scrollbar jump when you fold the instance list >> of Apply in singletons. >> >> https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply >> >> 2. Current workarounds >> >> They can be collapsed manually one by one, and we can jump to the middle >> of a module with the table of contents, but scrolling up from the bottom >> of an instance list is still a chore. >> >> Of course, instance lists also contain quite important information. >> Would it become too easy to miss if it were hidden by default? Would a >> more fine-grained alternative be better? >> >> Regards, >> Li-yao >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From george at wils.online Fri Jan 4 00:30:28 2019 From: george at wils.online (George Wilson) Date: Fri, 4 Jan 2019 10:30:28 +1000 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: Type class instances are an essential part of a data type's API in Haskell so I'm against hiding them by default. A toggle to collapse all instance blocks on a page would be fine. Cheers, George On Fri, 4 Jan 2019 at 04:36, Nathan Collins wrote: > > * I think collapsing instances by default is a great idea! +1 > > * Examples are already collapsed by default, and I think instances > should be treated the same way. > > Re the concern that this would make the Servant docs worse, for me it > would just be a matter of knowing to expand the instance docs when I'm > interested in the corresponding class, the same way I expand the > examples only where I'm interested. > > Here's an example of instance docs in Servant: > http://hackage.haskell.org/package/servant-0.15/docs/Servant-API.html#t:FromHttpApiData. > Until I'm interested in the FromHttpApiData class, I don't personally > want to see that long list of instances with some examples. Also, in > my experience, having lots of docs/examples on the instances like this > is not very common. > > Here's an instance of examples being collapsed by default to good > effect in the Prelude docs for Either: > https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html#t:Either > > * Having a "collapse all/expand all" toggle at the top of the page > would be nice, but if the default is not "collapsed" then I'd want a > way to make that my personal default. > > I don't know much about web development, but my impression is that we > could use a cookie and some simple JavaScript [1] to make "collapse by > default" a per-user preference, say by remembering the last state of > the hypothetical "collapse all/expand all" toggle button at the top. > Haddock already uses JavaScript, so I expect this would be a small > addition. > > Cheers, > > -nathan > > [1] https://developer.mozilla.org/en-US/docs/Web/API/document/cookie > > On Wed, Jan 2, 2019 at 11:23 PM Oleg Grenrus wrote: > > > > How about a compromise: show dozen or so instances with "show rest" link-toggle. That would work very nicely, if we could control which instances (e.g. instances with haddocks) should be shown. > > > > E.g. in `servant` *a lot* of docs & examples are in instance haddocks, so making them hidden will make documentation strictly worse. > > > > - Oleg > > > > On 3 Jan 2019, at 7.50, Ryan Reich wrote: > > > > I think this is a great idea. I do wonder, however, if it might exacerbate a kind of meta-documentation problem that I, at least, had when I was more of a beginner: it was not clear to me that most of a type's API is implicit in its instances of many standard classes, and specialized functions for things like mapping or folding or appending may not even be present in the rest of the module. Obviously this is something that every Haskeller needs to learn, but it was an issue for me even when the instance lists were present for me to gloss over. > > > > Perhaps Haddock could, rather than establishing this as a new default, provide a "collapse all" and "expand all" set of functions at the top of the page? > > > > On Wed, Jan 2, 2019 at 8:03 PM Li-yao Xia wrote: > >> > >> Hello Café, > >> > >> I would like to propose making haddock keep instance lists collapsed by > >> default. Some discussion is in order since it would significantly affect > >> the documentation of many packages on Hackage. > >> > >> Feel free to reply here or on the related Github thread: > >> https://github.com/haskell/haddock/issues/698 > >> > >> 1. Instance lists take a lot of screen estate > >> > >> For a motivating example, I can point to the Prelude we all love. > >> > >> https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html > >> > >> We are immediately welcomed by half a page of instances of Bool, which > >> is not quite bad, but classes have the most impressive instance lists, > >> as you may see when you reach Eq. > >> > >> Many packages, even commonly used ones, have the same issue. For an > >> extreme example, see the scrollbar jump when you fold the instance list > >> of Apply in singletons. > >> > >> https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply > >> > >> 2. Current workarounds > >> > >> They can be collapsed manually one by one, and we can jump to the middle > >> of a module with the table of contents, but scrolling up from the bottom > >> of an instance list is still a chore. > >> > >> Of course, instance lists also contain quite important information. > >> Would it become too easy to miss if it were hidden by default? Would a > >> more fine-grained alternative be better? > >> > >> Regards, > >> Li-yao > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> To (un)subscribe, modify options or view archives go to: > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >> Only members subscribed via the mailman list are allowed to post. > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > 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 allbery.b at gmail.com Fri Jan 4 00:45:46 2019 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 3 Jan 2019 19:45:46 -0500 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: They're essential, but they're also at minimum an impediment to navigation and to some extent comprehension of a haddock. Arguably what we really need is a better way to present them, but until then collapsed by default is reasonable. On Thu, Jan 3, 2019 at 7:31 PM George Wilson wrote: > Type class instances are an essential part of a data type's API in > Haskell so I'm against hiding them by default. A toggle to collapse > all instance blocks on a page would be fine. > > Cheers, > George > > On Fri, 4 Jan 2019 at 04:36, Nathan Collins > wrote: > > > > * I think collapsing instances by default is a great idea! +1 > > > > * Examples are already collapsed by default, and I think instances > > should be treated the same way. > > > > Re the concern that this would make the Servant docs worse, for me it > > would just be a matter of knowing to expand the instance docs when I'm > > interested in the corresponding class, the same way I expand the > > examples only where I'm interested. > > > > Here's an example of instance docs in Servant: > > > http://hackage.haskell.org/package/servant-0.15/docs/Servant-API.html#t:FromHttpApiData > . > > Until I'm interested in the FromHttpApiData class, I don't personally > > want to see that long list of instances with some examples. Also, in > > my experience, having lots of docs/examples on the instances like this > > is not very common. > > > > Here's an instance of examples being collapsed by default to good > > effect in the Prelude docs for Either: > > > https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html#t:Either > > > > * Having a "collapse all/expand all" toggle at the top of the page > > would be nice, but if the default is not "collapsed" then I'd want a > > way to make that my personal default. > > > > I don't know much about web development, but my impression is that we > > could use a cookie and some simple JavaScript [1] to make "collapse by > > default" a per-user preference, say by remembering the last state of > > the hypothetical "collapse all/expand all" toggle button at the top. > > Haddock already uses JavaScript, so I expect this would be a small > > addition. > > > > Cheers, > > > > -nathan > > > > [1] https://developer.mozilla.org/en-US/docs/Web/API/document/cookie > > > > On Wed, Jan 2, 2019 at 11:23 PM Oleg Grenrus > wrote: > > > > > > How about a compromise: show dozen or so instances with "show rest" > link-toggle. That would work very nicely, if we could control which > instances (e.g. instances with haddocks) should be shown. > > > > > > E.g. in `servant` *a lot* of docs & examples are in instance haddocks, > so making them hidden will make documentation strictly worse. > > > > > > - Oleg > > > > > > On 3 Jan 2019, at 7.50, Ryan Reich wrote: > > > > > > I think this is a great idea. I do wonder, however, if it might > exacerbate a kind of meta-documentation problem that I, at least, had when > I was more of a beginner: it was not clear to me that most of a type's API > is implicit in its instances of many standard classes, and specialized > functions for things like mapping or folding or appending may not even be > present in the rest of the module. Obviously this is something that every > Haskeller needs to learn, but it was an issue for me even when the instance > lists were present for me to gloss over. > > > > > > Perhaps Haddock could, rather than establishing this as a new default, > provide a "collapse all" and "expand all" set of functions at the top of > the page? > > > > > > On Wed, Jan 2, 2019 at 8:03 PM Li-yao Xia wrote: > > >> > > >> Hello Café, > > >> > > >> I would like to propose making haddock keep instance lists collapsed > by > > >> default. Some discussion is in order since it would significantly > affect > > >> the documentation of many packages on Hackage. > > >> > > >> Feel free to reply here or on the related Github thread: > > >> https://github.com/haskell/haddock/issues/698 > > >> > > >> 1. Instance lists take a lot of screen estate > > >> > > >> For a motivating example, I can point to the Prelude we all love. > > >> > > >> https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html > > >> > > >> We are immediately welcomed by half a page of instances of Bool, which > > >> is not quite bad, but classes have the most impressive instance lists, > > >> as you may see when you reach Eq. > > >> > > >> Many packages, even commonly used ones, have the same issue. For an > > >> extreme example, see the scrollbar jump when you fold the instance > list > > >> of Apply in singletons. > > >> > > >> > https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply > > >> > > >> 2. Current workarounds > > >> > > >> They can be collapsed manually one by one, and we can jump to the > middle > > >> of a module with the table of contents, but scrolling up from the > bottom > > >> of an instance list is still a chore. > > >> > > >> Of course, instance lists also contain quite important information. > > >> Would it become too easy to miss if it were hidden by default? Would a > > >> more fine-grained alternative be better? > > >> > > >> Regards, > > >> Li-yao > > >> _______________________________________________ > > >> Haskell-Cafe mailing list > > >> To (un)subscribe, modify options or view archives go to: > > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > >> Only members subscribed via the mailman list are allowed to post. > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From cdsmith at gmail.com Fri Jan 4 00:49:26 2019 From: cdsmith at gmail.com (Chris Smith) Date: Thu, 3 Jan 2019 19:49:26 -0500 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: I'm sympathetic to the notion that instances are an important part of the API. On the other hand, it's hard to argue against how much more usable the documentation becomes when all the page-long instance lists are collapsed. I wonder if there's a compromise possible: in the collapsed form, the instance list could still show a list of the applicable class names, but all on one line instead of a page-long table. Then it's just a click away to get from there to the details (instance context, source link, etc.) that are shown now. On Thu, Jan 3, 2019 at 7:31 PM George Wilson wrote: > Type class instances are an essential part of a data type's API in > Haskell so I'm against hiding them by default. A toggle to collapse > all instance blocks on a page would be fine. > > Cheers, > George > > On Fri, 4 Jan 2019 at 04:36, Nathan Collins > wrote: > > > > * I think collapsing instances by default is a great idea! +1 > > > > * Examples are already collapsed by default, and I think instances > > should be treated the same way. > > > > Re the concern that this would make the Servant docs worse, for me it > > would just be a matter of knowing to expand the instance docs when I'm > > interested in the corresponding class, the same way I expand the > > examples only where I'm interested. > > > > Here's an example of instance docs in Servant: > > > http://hackage.haskell.org/package/servant-0.15/docs/Servant-API.html#t:FromHttpApiData > . > > Until I'm interested in the FromHttpApiData class, I don't personally > > want to see that long list of instances with some examples. Also, in > > my experience, having lots of docs/examples on the instances like this > > is not very common. > > > > Here's an instance of examples being collapsed by default to good > > effect in the Prelude docs for Either: > > > https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html#t:Either > > > > * Having a "collapse all/expand all" toggle at the top of the page > > would be nice, but if the default is not "collapsed" then I'd want a > > way to make that my personal default. > > > > I don't know much about web development, but my impression is that we > > could use a cookie and some simple JavaScript [1] to make "collapse by > > default" a per-user preference, say by remembering the last state of > > the hypothetical "collapse all/expand all" toggle button at the top. > > Haddock already uses JavaScript, so I expect this would be a small > > addition. > > > > Cheers, > > > > -nathan > > > > [1] https://developer.mozilla.org/en-US/docs/Web/API/document/cookie > > > > On Wed, Jan 2, 2019 at 11:23 PM Oleg Grenrus > wrote: > > > > > > How about a compromise: show dozen or so instances with "show rest" > link-toggle. That would work very nicely, if we could control which > instances (e.g. instances with haddocks) should be shown. > > > > > > E.g. in `servant` *a lot* of docs & examples are in instance haddocks, > so making them hidden will make documentation strictly worse. > > > > > > - Oleg > > > > > > On 3 Jan 2019, at 7.50, Ryan Reich wrote: > > > > > > I think this is a great idea. I do wonder, however, if it might > exacerbate a kind of meta-documentation problem that I, at least, had when > I was more of a beginner: it was not clear to me that most of a type's API > is implicit in its instances of many standard classes, and specialized > functions for things like mapping or folding or appending may not even be > present in the rest of the module. Obviously this is something that every > Haskeller needs to learn, but it was an issue for me even when the instance > lists were present for me to gloss over. > > > > > > Perhaps Haddock could, rather than establishing this as a new default, > provide a "collapse all" and "expand all" set of functions at the top of > the page? > > > > > > On Wed, Jan 2, 2019 at 8:03 PM Li-yao Xia wrote: > > >> > > >> Hello Café, > > >> > > >> I would like to propose making haddock keep instance lists collapsed > by > > >> default. Some discussion is in order since it would significantly > affect > > >> the documentation of many packages on Hackage. > > >> > > >> Feel free to reply here or on the related Github thread: > > >> https://github.com/haskell/haddock/issues/698 > > >> > > >> 1. Instance lists take a lot of screen estate > > >> > > >> For a motivating example, I can point to the Prelude we all love. > > >> > > >> https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html > > >> > > >> We are immediately welcomed by half a page of instances of Bool, which > > >> is not quite bad, but classes have the most impressive instance lists, > > >> as you may see when you reach Eq. > > >> > > >> Many packages, even commonly used ones, have the same issue. For an > > >> extreme example, see the scrollbar jump when you fold the instance > list > > >> of Apply in singletons. > > >> > > >> > https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply > > >> > > >> 2. Current workarounds > > >> > > >> They can be collapsed manually one by one, and we can jump to the > middle > > >> of a module with the table of contents, but scrolling up from the > bottom > > >> of an instance list is still a chore. > > >> > > >> Of course, instance lists also contain quite important information. > > >> Would it become too easy to miss if it were hidden by default? Would a > > >> more fine-grained alternative be better? > > >> > > >> Regards, > > >> Li-yao > > >> _______________________________________________ > > >> Haskell-Cafe mailing list > > >> To (un)subscribe, modify options or view archives go to: > > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > >> Only members subscribed via the mailman list are allowed to post. > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > > 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 akcheung at cs.washington.edu Fri Jan 4 00:49:35 2019 From: akcheung at cs.washington.edu (Alvin Cheung) Date: Thu, 3 Jan 2019 16:49:35 -0800 Subject: [Haskell-cafe] Call for papers: DBPL 2019 Message-ID: <55dcd5d5-55a9-1a67-3441-e78b726d313a@cs.washington.edu> The 17th International Symposium on Database Programming Languages https://pldi19.sigplan.org/track/dbpl-2019-papers Phoenix, Arizona, USA June 23, 2019 hosted as part of PLDI 2019 Call for Papers For over 25 years, DBPL has established itself as the principal venue for publishing and discussing new ideas at the intersection of databases and programming languages. Many key contributions in query languages for object-oriented data, persistent databases, nested relational data, and semistructured data, as well as fundamental ideas in types for query languages, were first announced at DBPL. Today, this creative research area is broadening into a subfield of data-centric computation, currently scattered among a range of venues. DBPL is an established destination for such new ideas and solicits submissions from researchers in databases, programming languages or any other community interested in the design, implementation or foundations of data-centric computation. Scope ----- DBPL solicits practical and theoretical papers in all topics at the intersection of databases and programming languages. Papers emphasizing new topics or emerging areas are especially welcome. Suggested, but not exclusive, topics of interest for submissions include: - Compiling Query Languages to Modern Hardware - Data-Centric Programming Abstractions, Comprehensions, Monads - Data Integration, Exchange, and Interoperability - Data Synchronization and Bidirectional Transformations - Declarative Data Centers (e.g., distributed query processing, serverless computing platforms, social computing platforms, etc) - Emerging and Nontraditional Data Models - Language-Based Security in Data Management - Language-Integrated Query Mechanisms - Managing Uncertain and Imprecise Information - Metaprogramming and Heterogeneous Staged Computation - Programming Language Support for Data-Centric Programming (e.g., databases, web programming, machine learning, etc) - Query Compilation and In-memory Databases - Query Language Design and Implementation - Query Transformation and Optimization - Schema Mapping and Metadata Management - Semantics and Verification of Database Systems - Stream Data Processing and Query Languages - Type and Effect Systems for Data-Centric Programming Author Guidelines ----------------- Prospective authors are invited to submit full papers in English presenting original research. Submitted papers must be unpublished and not submitted for publication elsewhere. Submissions should be no more than 10 pages long, excluding references, in the two-column ACM proceedings format, following PLDI’s formatting requirements (https://pldi19.sigplan.org/track/pldi-2019-papers#Call-for-Papers). Each submission should begin with a succinct statement of the problem and a summary of the main results. Authors may provide more details to substantiate the main claims of the paper by including a clearly marked appendix at the end of the submission, which is not included in the page limit and is read at the discretion of the committee. At least one author of each accepted paper must attend the symposium to present their work. Short papers of at most 4 pages (same format as long papers) describing work in progress, demos, research challenges or visions are also welcome. Accepted short papers may be included or excluded from the formal proceedings, whichever the author(s) prefer. Full and short papers are both due on the deadline, February 15, 2019. Instructions on how to submit will be posted on the symposium website noted above. Review is single-blind, so authors do not need to anonymize their submissions. PC submissions are allowed, except for the co-chairs. Important Dates --------------- - Paper Submission: February 15, 2019 - Notification: March 29, 2019 - Final versions due: April 16, 2019 - Symposium: June 23, 2019 Proceedings ----------- Accepted papers will appear as part of the PLDI Proceedings for DBPL 2019. Program Committee ----------------- *Program Co-Chairs* Alvin Cheung, University of Washington Kim Nguyễn, Université Paris-Sud *Program Committee* William Cook, University of Texas at Austin Vasiliki Kalavri, ETH Harshad Kasture, Oracle Oleg Kiselyov, University of Tsukuba Sam Lindley, University of Edinburgh Tiark Rompf, Purdue University Stefanie Scherzinger, OTH Regensberg Amir Shaikhha, EPFL / University of Oxford Avi Shinnar, IBM Guido Wachsmuth, Oracle Melanie Wu, Pomona College History ------- The 17th Symposium on Data Base Programming Languages (DBPL 2019) continues the tradition of excellence initiated by its predecessors in Roscoff, Finistere (1987), Salishan, Oregon (1989), Nafplion, Argolida (1991), Manhattan, New York (1993), Gubbio, Umbria (1995), Estes Park, Colorado (1997), Kinloch Rannoch, Scotland (1999), Marino, Rome (2001), Potsdam, Germany (2003), Trondheim, Norway (2005), Vienna, Austria (2007), Lyon, France (2009), Seattle, Washington (2011), Riva del Garda, Italy (2013), Pittsburgh, Pennsylvania (2015), Munich, Germany (2017). DBPL was affiliated with VLDB from 1999-2013 and in 2017. In 2015, it is affiliated with SPLASH for the first time and in 2019, it is affiliated with PLDI for the first time. From ietf-dane at dukhovni.org Fri Jan 4 01:57:26 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Thu, 3 Jan 2019 20:57:26 -0500 Subject: [Haskell-cafe] Left and right monadic folds In-Reply-To: <20190101143339.oqklkuxgov4cov4f@MishkaPC> References: <20190101143339.oqklkuxgov4cov4f@MishkaPC> Message-ID: <20190104015726.GD79754@straasha.imrryr.org> On Tue, Jan 01, 2019 at 05:33:39PM +0300, Michail Pevnev wrote: > Recently I've run into a situation where a monadic fold seems like an > interesting option. However, I'm not particularly sure how to choose which fold > - left or right - to use. > > Odd things begin when I edit the above to use foldrM. It doesn't terminate on > an infinite list, which is expected from a disguised foldl. But given several > negative numbers in the input, it prints out the last one, seemingly turning > the usual behaviour of Either on its head. It seems its foldl heritage results > in applying side-effects (in case of Either, erroring out with a Left) in > reverse order. Do I get this right and is this the general behaviour of foldrM > for any monad? Short version: Yes, because expanding the definitions one gets: foldlM f z0 xs = (\z -> flip f x1 z >>= ... >>= flip f xn) z0 foldrM f z0 xs = (\z -> f xn z >>= ... >>= f x1) z0 $ ghci λ> import Data.Foldable λ> let f a b = let s = "("++a++", "++b++")" in putStrLn s >> return s λ> foldlM f "z" ["a", "b", "c"] >> return () (z, a) ((z, a), b) (((z, a), b), c) λ> foldrM f "z" ["a", "b", "c"] >> return () (c, z) (b, (c, z)) (a, (b, (c, z))) Longer version, if we define: -- Kleisli composition (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c f >=> g = \a -> f a >>= g -- K is for Kleisli newtype K m a b = K { runK :: a -> m b } -- newtype wrapped composition kcomp :: Monad m => K m a b -> K m b c -> K m a c (K f) `kcomp` (K g) = K $ f >=> g -- K m a a is Monoid under Kleisli composition instance Monad m => Monoid (K m a a) where mempty = K return mappend f g = f `kcomp` g Expanding the definitions of foldrM, it is not too hard to see that: foldrM f z0 [] = return z0 foldrM f z0 xs = (\z -> f xn z >>= ... >>= f x1) z0 = (runK (f xn) >=> ... >=> runK (f x1)) z0 = runK (foldMap f' (reverse xs)) z0 where f' = K . f Thus foldrM is just a foldMap of some Kleisli compositions of the (f x_i) in reverse order. It is right associative, and the side-effects happen in right-to-left order. foldrM is strict in the length of the list. While on the other hand foldlM is foldlM f z0 [] = return z0 foldlM f z0 xs = (\z -> flip f x1 z >>= ... >>= flip f x1) z0 = (runK (flip f x1) >=> ... >=> runK (flip f xn)) z0 = runK (foldMap f' xs) z0 where f' = K . flip f So foldlM is just a foldMap of some Kleisli compositions of the (flip f x_i) in natural order. foldlM is left associative, and the side-effects happen in left-to-right order. If the monad's (>>=) operator is lazy in its right argument, the computation may short-circuit after traversing only an initial segment of the possibly infinite list. -- Viktor. From a.pelenitsyn at gmail.com Fri Jan 4 10:26:57 2019 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Fri, 4 Jan 2019 13:26:57 +0300 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: I like Chris' idea about inline list by default, with the ability to a) get the whole list in old format, b) hide the stuff completely. -- Best, Artem On Fri, 4 Jan 2019 at 03:50 Chris Smith wrote: > I'm sympathetic to the notion that instances are an important part of the > API. On the other hand, it's hard to argue against how much more usable > the documentation becomes when all the page-long instance lists are > collapsed. I wonder if there's a compromise possible: in the collapsed > form, the instance list could still show a list of the applicable class > names, but all on one line instead of a page-long table. Then it's just a > click away to get from there to the details (instance context, source link, > etc.) that are shown now. > > On Thu, Jan 3, 2019 at 7:31 PM George Wilson wrote: > >> Type class instances are an essential part of a data type's API in >> Haskell so I'm against hiding them by default. A toggle to collapse >> all instance blocks on a page would be fine. >> >> Cheers, >> George >> >> On Fri, 4 Jan 2019 at 04:36, Nathan Collins >> wrote: >> > >> > * I think collapsing instances by default is a great idea! +1 >> > >> > * Examples are already collapsed by default, and I think instances >> > should be treated the same way. >> > >> > Re the concern that this would make the Servant docs worse, for me it >> > would just be a matter of knowing to expand the instance docs when I'm >> > interested in the corresponding class, the same way I expand the >> > examples only where I'm interested. >> > >> > Here's an example of instance docs in Servant: >> > >> http://hackage.haskell.org/package/servant-0.15/docs/Servant-API.html#t:FromHttpApiData >> . >> > Until I'm interested in the FromHttpApiData class, I don't personally >> > want to see that long list of instances with some examples. Also, in >> > my experience, having lots of docs/examples on the instances like this >> > is not very common. >> > >> > Here's an instance of examples being collapsed by default to good >> > effect in the Prelude docs for Either: >> > >> https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html#t:Either >> > >> > * Having a "collapse all/expand all" toggle at the top of the page >> > would be nice, but if the default is not "collapsed" then I'd want a >> > way to make that my personal default. >> > >> > I don't know much about web development, but my impression is that we >> > could use a cookie and some simple JavaScript [1] to make "collapse by >> > default" a per-user preference, say by remembering the last state of >> > the hypothetical "collapse all/expand all" toggle button at the top. >> > Haddock already uses JavaScript, so I expect this would be a small >> > addition. >> > >> > Cheers, >> > >> > -nathan >> > >> > [1] https://developer.mozilla.org/en-US/docs/Web/API/document/cookie >> > >> > On Wed, Jan 2, 2019 at 11:23 PM Oleg Grenrus >> wrote: >> > > >> > > How about a compromise: show dozen or so instances with "show rest" >> link-toggle. That would work very nicely, if we could control which >> instances (e.g. instances with haddocks) should be shown. >> > > >> > > E.g. in `servant` *a lot* of docs & examples are in instance >> haddocks, so making them hidden will make documentation strictly worse. >> > > >> > > - Oleg >> > > >> > > On 3 Jan 2019, at 7.50, Ryan Reich wrote: >> > > >> > > I think this is a great idea. I do wonder, however, if it might >> exacerbate a kind of meta-documentation problem that I, at least, had when >> I was more of a beginner: it was not clear to me that most of a type's API >> is implicit in its instances of many standard classes, and specialized >> functions for things like mapping or folding or appending may not even be >> present in the rest of the module. Obviously this is something that every >> Haskeller needs to learn, but it was an issue for me even when the instance >> lists were present for me to gloss over. >> > > >> > > Perhaps Haddock could, rather than establishing this as a new >> default, provide a "collapse all" and "expand all" set of functions at the >> top of the page? >> > > >> > > On Wed, Jan 2, 2019 at 8:03 PM Li-yao Xia wrote: >> > >> >> > >> Hello Café, >> > >> >> > >> I would like to propose making haddock keep instance lists collapsed >> by >> > >> default. Some discussion is in order since it would significantly >> affect >> > >> the documentation of many packages on Hackage. >> > >> >> > >> Feel free to reply here or on the related Github thread: >> > >> https://github.com/haskell/haddock/issues/698 >> > >> >> > >> 1. Instance lists take a lot of screen estate >> > >> >> > >> For a motivating example, I can point to the Prelude we all love. >> > >> >> > >> https://hackage.haskell.org/package/base-4.12.0.0/docs/Prelude.html >> > >> >> > >> We are immediately welcomed by half a page of instances of Bool, >> which >> > >> is not quite bad, but classes have the most impressive instance >> lists, >> > >> as you may see when you reach Eq. >> > >> >> > >> Many packages, even commonly used ones, have the same issue. For an >> > >> extreme example, see the scrollbar jump when you fold the instance >> list >> > >> of Apply in singletons. >> > >> >> > >> >> https://hackage.haskell.org/package/singletons-2.5.1/docs/Data-Singletons.html#t:Apply >> > >> >> > >> 2. Current workarounds >> > >> >> > >> They can be collapsed manually one by one, and we can jump to the >> middle >> > >> of a module with the table of contents, but scrolling up from the >> bottom >> > >> of an instance list is still a chore. >> > >> >> > >> Of course, instance lists also contain quite important information. >> > >> Would it become too easy to miss if it were hidden by default? Would >> a >> > >> more fine-grained alternative be better? >> > >> >> > >> Regards, >> > >> Li-yao >> > >> _______________________________________________ >> > >> Haskell-Cafe mailing list >> > >> To (un)subscribe, modify options or view archives go to: >> > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > >> Only members subscribed via the mailman list are allowed to post. >> > > >> > > _______________________________________________ >> > > Haskell-Cafe mailing list >> > > To (un)subscribe, modify options or view archives go to: >> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > Only members subscribed via the mailman list are allowed to post. >> > > >> > > _______________________________________________ >> > > Haskell-Cafe mailing list >> > > To (un)subscribe, modify options or view archives go to: >> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > Only members subscribed via the mailman list are allowed to post. >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > To (un)subscribe, modify options or view archives go to: >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > Only members subscribed via the mailman list are allowed to post. >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lysxia at gmail.com Fri Jan 4 11:55:08 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Fri, 4 Jan 2019 12:55:08 +0100 Subject: [Haskell-cafe] RFC: in haddock, collapse instances by default In-Reply-To: References: <5c17f57c-c175-7d26-469d-f2cde9d205a4@gmail.com> Message-ID: <4b8a4586-c07e-7062-aa72-37bc32cebc17@gmail.com> Thanks everyone for the response! To summarize the discussion: - There is general agreement that the current default can be problematic, but switching it the other way around doesn't seem unequivocally good either. To add to that counterpoint, I must admit that mtl and time are examples where the instance lists are arguably quite essential to understand those libraries, and for familiar users they aren't that uncomfortably long. In that case, a safer solution seems to keep the current default to not surprise users that are already happy with the current state of things, but add a new option to change the default, to address the cases where they are indeed a problem. - A button to fold/unfold all instance lists seems like an unanimously good idea. * Perhaps the same feature for collapsible examples would be similarly useful. * We can record users preferences. In fact, it appears Haddock already records which instance lists are folded. I am currently interested in implementing the features mentioned above. - There were also suggestions to make the presentation of instance lists more compact, rather than entirely hide them. I am in favor of them, but of course that is more work to flesh out and implement. * Show only some instances (for example, those that have comments attached). * List the relevant classes/types on a single line (rather than the whole instance heads, that are somewhat redundant), with the option to switch to the current display for more details. It seems reasonable to leave these as future tasks, and interested parties are free to discuss and take them on any time. Regards, Li-yao From V.Liepelt at kent.ac.uk Fri Jan 4 15:45:38 2019 From: V.Liepelt at kent.ac.uk (V.Liepelt) Date: Fri, 4 Jan 2019 15:45:38 +0000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: <47cce08d-9ab1-9f8d-f581-1a0dcf3cd459@gmail.com> References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> <90E11DAC-EFB9-4A72-B60A-2DFF27D742C4@kent.ac.uk> <47cce08d-9ab1-9f8d-f581-1a0dcf3cd459@gmail.com> Message-ID: Hi Li-yao, Thanks for you interesting thoughts. There is also an opposite situation, where evaluating the second argument allows us to free a lot of memory, as that argument would otherwise remain a thunk with references to many things. Good point, but this is one of the tradeoffs with laziness. In the case of GHC, will the runtime not eventually free the memory of the second argument and everything it points to? It surely must do this one way or another since otherwise laziness would mean that while a process is running it will keep leaking space. But to compare two pairs `(a,b) <= (x,y)` we would have to first traverse `(a,b)` to decide whether it's the smallest element, before evaluating the second argument to WHNF and comparing component-wise. Besides the extra complexity (both in code and in run time), this would not be less strict than the current default, since the first argument could get completely evaluated before even looking at the second one: `(False, _|_) <= (True, True) = _|_` (currently, this is `True`). So with the laziest possible implementation (below—do check for accuracy, I might have missed something) these are the cases where the result is defined for Bool and undefined for Lazy Bool: (F,u) <= (T,F) (F,u) <= (T,T) (F,u) <= (T,u) vs. (undefined for Bool and defined for Lazy Bool) (F,F) <= (F,u) (F,F) <= (u,F) (F,F) <= (u,T) (F,F) <= (u,u) (T,F) <= (T,u) So it does seem that we can make it marginally more lazy overall. I’m not saying we should, I was just genuinely surprised that Ord is strict. Definitions: F <= _ = T T <= q = q F < q = q T < _ = F (p, q) == (r, s) = p == r /\ q == s (F, F) <= _ = T (p, q) <= (r, s) = p < r \/ p == r /\ q <= s (T, T) < _ = F We also would not know whether the type (a, b) has a smallest element without stronger constraints than (Ord a, Ord b), so this optimization is really only practically feasible for types with a nullary first constructor. Hm, perhaps we are thinking about this in different ways. From the definition above, we don’t need any stronger constraints than Ord. Best, Vilem On 2 Jan 2019, at 15:06, Li-yao Xia > wrote: Hi Vilem, > This is not just about crashing. (I’m using `undefined` as a way of > making strictness explicit.) `False >= veryExpensiveComputation` > should return `True` immediately without any unnecessary computation. There is also an opposite situation, where evaluating the second argument allows us to free a lot of memory, as that argument would otherwise remain a thunk with references to many things. > Also it doesn’t seem like a special case: this makes sense for any partially ordered Type with a top and/or bottom element. That may be acceptable with Bool because its values are small. But to compare two pairs `(a,b) <= (x,y)` we would have to first traverse `(a,b)` to decide whether it's the smallest element, before evaluating the second argument to WHNF and comparing component-wise. Besides the extra complexity (both in code and in run time), this would not be less strict than the current default, since the first argument could get completely evaluated before even looking at the second one: `(False, _|_) <= (True, True) = _|_` (currently, this is `True`). We also would not know whether the type (a, b) has a smallest element without stronger constraints than (Ord a, Ord b), so this optimization is really only practically feasible for types with a nullary first constructor. Li-yao -------------- next part -------------- An HTML attachment was scrubbed... URL: From V.Liepelt at kent.ac.uk Fri Jan 4 15:49:57 2019 From: V.Liepelt at kent.ac.uk (V.Liepelt) Date: Fri, 4 Jan 2019 15:49:57 +0000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: References: Message-ID: Hi Olaf, these are great thoughts, but are we talking about the same thing? I was merely wondering why Ord methods are strict. Best, Vilem > On 2 Jan 2019, at 21:51, Olaf Klinke wrote: > > Information-theoretically 'compare' must be stricter than <= because is gives more information: It decides equality, which <= doesn't. Therefore compare must be strict in both arguments. What follows is an argument that there can not be a lazy implementation of <= that behaves like logical implication. > > We try to model <= after the logical implication operator. Order-theoretically, the binary operation (<=) should be antitone in the first and monotone in the second argument. The preceding sentence only makes sense once we define a mathematical order on the semantics of Bool. Let's declare the "logical" order > > False < undefined < True. > > I give a formal justification in Appendix A below. Arrange all nine combinations of type (Bool,Bool) in a 3x3 grid where the first dimension is descending and the second dimension is ascending in the logical order. Now we consider: > > (undefined,True) must map to True > because (True,True) maps to True and descending in the first argument means ascending in the result. > > (False,undefined) must map to True > because (False,False) maps to True and ascending in the second argument means ascending in the result. > > Further we require (True,False) mapping to False. > > But now we're in trouble: A function giving the above three return values requires ambiguous choice, which we don't have available in pure, sequential Haskell, q.e.d. It's the same reason why we can't have (&&) or (||) operators which behave symmetrically w.r.t. the logical order. > > Olaf > > ========== > Appendix A > > Let R be a binary relation on a set A. The Egli-Milner-lifting of R is a binary relation on the powerset of A. Among several possible liftings, it is the one with the most pleasing properties [1, Theorem 2.12]. Identify the "undefined" value of a type A with the maximal element of the powerset of A, which expresses that "undefined" may evaluate to anything. In Haskell terms: > > {-# LANGUAGE Rank2Types #-} > module RelationLifting where > import Prelude hiding (undefined) > type Relation a = a -> a -> Bool > type Lifting = forall a. Relation a -> Relation [a] > egliMilner :: Lifting > egliMilner r xs ys = hoare && smyth where > hoare = all (\x -> any (\y -> r x y) ys) xs > smyth = all (\y -> any (\x -> r x y) xs) ys > true, false, undefined :: [Bool] > true = [True] > false = [False] > undefined = [False,True] > > RelationLifting> egliMilner (<=) false undefined > True > RelationLifting> egliMilner (<=) undefined true > True > > [1] https://www.cs.le.ac.uk/people/akurz/Papers/kv-relation-lifting.pdf > From V.Liepelt at kent.ac.uk Fri Jan 4 15:55:46 2019 From: V.Liepelt at kent.ac.uk (V.Liepelt) Date: Fri, 4 Jan 2019 15:55:46 +0000 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> <20190102144210.zllt2qi5yaix2uyh@weber> Message-ID: <63AD0161-BD1D-439D-AC99-F33DF2692D6B@kent.ac.uk> Hi Sven, […] section 11.1 [of the Haskell 2010 Report] explicitly states that all derived operations for Eq and Ord are strict in both arguments. Good idea to look at the Report. Unfortunately it doesn’t give any reasoning as to why this choice was made. Best, Vilem On 2 Jan 2019, at 19:06, Sven Panne > wrote: Am Mi., 2. Jan. 2019 um 15:42 Uhr schrieb Tom Ellis >: I mean that for any data type data E of C1 | C2 | ... you are preposing that the (<=) of the derived Ord instance would have a special case for C1. ... and another special case for (>=) for the last enumeration value. And a very special version for one-element enumerations. And what about (<) and (>)? And derived (==) for one-element enumerations? And, and, and... :-P Putting on the language lawyer hat: The Haskell Report explicitly states that Bool's Ord instance is derived (section 6.1.1), and section 11.1 explicitly states that all derived operations for Eq and Ord are strict in both arguments. Consequently, Implementing Ord for Bool in a lazier way would violate the specification. I would say that the the way the report specifies this is a good thing: Coming up with special cases is a bad design principle, consistency almost always trumps anything else (the human brain is notoriously small). Furthermore, laziness is not always a good thing, it could lead to space leaks, so e.g. making Bool's Ord operations lazier would definitely make various people very unhappy sooner or later. :-) _______________________________________________ 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 svenpanne at gmail.com Fri Jan 4 16:37:46 2019 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 4 Jan 2019 17:37:46 +0100 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: <63AD0161-BD1D-439D-AC99-F33DF2692D6B@kent.ac.uk> References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> <20190102144210.zllt2qi5yaix2uyh@weber> <63AD0161-BD1D-439D-AC99-F33DF2692D6B@kent.ac.uk> Message-ID: Am Fr., 4. Jan. 2019 um 16:55 Uhr schrieb V.Liepelt : > Hi Sven, > > […] section 11.1 [of the Haskell 2010 Report] explicitly states that all > derived operations for Eq and Ord are strict in both arguments. > > > Good idea to look at the Report. Unfortunately it doesn’t give any > reasoning as to *why* this choice was made. > As I said: Consistency. (Well, I didn't write the report, but this seems to be the most obvious reason.) -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Fri Jan 4 16:47:28 2019 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 4 Jan 2019 17:47:28 +0100 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> <90E11DAC-EFB9-4A72-B60A-2DFF27D742C4@kent.ac.uk> <47cce08d-9ab1-9f8d-f581-1a0dcf3cd459@gmail.com> Message-ID: Am Fr., 4. Jan. 2019 um 16:46 Uhr schrieb V.Liepelt : > [...] Good point, but this is one of the tradeoffs with laziness. In the > case of GHC, will the runtime not eventually free the memory of the second > argument and everything it points to? It surely must do this one way or > another since otherwise laziness would mean that while a process is running > it will keep leaking space. > You *will* leak space if you keep an unevaluated argument around for a long time, there is nothing any implementation can really do about it: It can't know for sure if you will eventually throw away that argument or (partially) evaluate it. Sometimes the optimizer (e.g. via strictness analysis) can help, but not in the general case. So making an argument lazier is not a no-brainer, quite the opposite... -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Fri Jan 4 17:00:17 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Fri, 4 Jan 2019 12:00:17 -0500 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> <90E11DAC-EFB9-4A72-B60A-2DFF27D742C4@kent.ac.uk> <47cce08d-9ab1-9f8d-f581-1a0dcf3cd459@gmail.com> Message-ID: <73FEBEC3-3C45-4214-88F2-138CFD3A1DBE@dukhovni.org> > On Jan 4, 2019, at 11:47 AM, Sven Panne wrote: > > You *will* leak space if you keep an unevaluated argument around for a long time, there is nothing any implementation can really do about it: It can't know for sure if you will eventually throw away that argument or (partially) evaluate it. Sometimes the optimizer (e.g. via strictness analysis) can help, but not in the general case. So making an argument lazier is not a no-brainer, quite the opposite... Only if it is repeatedly used in ever deeper unevaluated expressions, such as repeatedly incrementing an IORef counter, without ever forcing the value. In the case of a lazy function ignoring its argument, no space is leaked unless that argument is retained elsewhere, and the function was the sole means of forcing the value. Unreferenced unevaluated thunks get GC'd. Space leaks require ever deeper chains of unevaluated thunks. If laziness always leaked Haskell would not work terribly well. I have code that runs for ~9 hours in constant memory allocating and freeing around 13TB of memory over its lifetime. Various functions it calls do some lazy evaluation or other, and while in some cases forcing the values that are sure to get used might reduce GC activity, there's no space leak. -- Viktor. From svenpanne at gmail.com Fri Jan 4 18:31:02 2019 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 4 Jan 2019 19:31:02 +0100 Subject: [Haskell-cafe] Ord methods too strict? In-Reply-To: <73FEBEC3-3C45-4214-88F2-138CFD3A1DBE@dukhovni.org> References: <63095057-2B1A-46B7-B17E-25BEB559A5D6@kent.ac.uk> <20190102113723.f7ggsrm55ezhr26x@weber> <90E11DAC-EFB9-4A72-B60A-2DFF27D742C4@kent.ac.uk> <47cce08d-9ab1-9f8d-f581-1a0dcf3cd459@gmail.com> <73FEBEC3-3C45-4214-88F2-138CFD3A1DBE@dukhovni.org> Message-ID: Am Fr., 4. Jan. 2019 um 18:24 Uhr schrieb Viktor Dukhovni < ietf-dane at dukhovni.org>: > [...] In the case of a lazy function ignoring its argument, no space is > leaked > unless that argument is retained elsewhere, and the function was the sole > means of forcing the value. This is the scenario I had in mind, but obviously I didn't explain that terribly well... :-} Personally, I think this is not so uncommon, at least in the initial stages of writing a library or program. > [...] Space leaks require ever deeper chains of unevaluated thunks. [...] > Perhaps we have different definitions of "space leak" (is there an "official" one?), but keeping a single thunk alive for a long time, which in turn keeps some huge data structure alive is a kind of leak, too, no deep chains involved. Maybe there is a better term describing this situation. -------------- next part -------------- An HTML attachment was scrubbed... URL: From damien.mattei at gmail.com Sat Jan 5 08:50:19 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Sat, 5 Jan 2019 09:50:19 +0100 Subject: [Haskell-cafe] Maybe type filtered to remove Nothing In-Reply-To: References: <32cc4d05-c9ff-da92-e395-f453db0b7ee6@earth.li> Message-ID: yes both works, code looks like this now: -- remove the records having N°BD NULL let fltWDS = Prelude.filter (\(Only a) -> case a of Nothing -> False Just a -> True) bd_rows_WDS -- let fltWDS = [a | Only (Just a) <- bd_rows_WDS] -- let fltWDS = catMaybes (Prelude.map fromOnly bd_rows_WDS) putStr "bd_rows_WDS filtered fltWDS =" putStrLn $ show fltWDS let lg_fltWDS = Prelude.length fltWDS putStrLn ("lg_fltWDS = " ++ (show lg_fltWDS)) let resBDtxt = if lg_fltWDS == 0 then Nothing else if lg_fltWDS == 1 then --Just (Prelude.head fltWDS) fromOnly (Prelude.head fltWDS) else --trace "WARNING: multiple BD in WDS result" (Just (Prelude.head fltWDS)) trace "WARNING: multiple BD in WDS result" fromOnly (Prelude.head fltWDS) putStr "resBDtxt =" putStrLn (maybe "Empty List" show resBDtxt) i will keep a Maybe type because in fact there is a possibility of having no result or one (extract sometimes from many) from the databases, so there is a possibility for Nothing i must keep and handle for the next instructions... thanks On Thu, Jan 3, 2019 at 3:54 PM Neil Mayhew < neil_mayhew at users.sourceforge.net> wrote: > On 2019-01-03 12:43 AM, Ganesh Sittampalam wrote: > > If you did have [Maybe Text] you could use the library function > > catMaybes :: [Maybe a] -> [a] > > to both do the filtering and change the types. > > ... > > But in your case you actually have [Only (Maybe Text)] rather than [Maybe > Text] so catMaybes won't work. One option is to use a list comprehension > instead: > > let fltWDS = [Only a | Only (Just a) <- bd_rows_WDS] > > > It probably would be helpful to remove the Only wrapper at this stage, so > this might be even better: > > let fltWDS = [a | Only (Just a) <- bd_rows_WDS] > > The way to do it with catMaybes would be to map with fromOnly first: > > let fltWDS = catMaybes (map fromOnly bd_rows_WDS) > > As Ganesh shows, there's no need for a type annotation after you've done > the query, because the compiler can infer the type [Text] from the types of > the functions that are used. The annotations are necessary with query only > because it's polymorphic and can work with a wide variety of types. > _______________________________________________ > 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 doaitse at swierstra.net Sun Jan 6 13:34:18 2019 From: doaitse at swierstra.net (Doaitse Swierstra) Date: Sun, 6 Jan 2019 14:34:18 +0100 Subject: [Haskell-cafe] Consider operator fixity when deriving Show or Read In-Reply-To: References: Message-ID: <4A6436A3-DF95-45EA-A910-0D67F7B1C1A7@swierstra.net> The current GHC implementation constructs Read instances out of other Read instances. In order to make this work some restictions are necessary. Given that a top-down paring strategy is used we cannot easily construct parsers for left-recursive data types. To cope with this problem, and to make sure that at least Read instances can read data written by Show instances, data is written out by Show instances with a sufficjently large number of parentheses. Unfortunately this may make reading data back extremely show. A solution for this problem is described in out Haskell 2008 Workshop paper: @inproceedings{1411296, Address = {New York, NY, USA}, Author = {Viera, Marcos and Swierstra, S. Doaitse and Lempsink, Eelco}, Booktitle = {Haskell Symposium}, Date-Added = {2009-06-06 22:24:07 +0200}, Date-Modified = {2009-06-06 22:24:07 +0200}, Doi = {http://doi.acm.org/10.1145/1411286.1411296}, Isbn = {978-1-60558-064-7}, Location = {Victoria, BC, Canada}, Pages = {63--74}, Publisher = {ACM}, Read = {Yes}, Title = {Haskell, do you read me?: constructing and composing efficient top-down parsers at runtime}, Year = {2008}, }} which I am attaching. Unfortunately the solution to solve all problems is rather involved. The code you can find in the package ChristmasTree: "ChristmasTree (Changing Haskell's Read Implementation Such That by Manipulating ASTs it Reads Expressions Efficiently) is an alternative approach of read that composes grammars instead of parsers. It reads data in linear time, while the function read has an exponential behavior in some cases of data types with infix operators.” Hope this helps answering your question, Doaitse -------------- next part -------------- A non-text attachment was scrubbed... Name: p63-viera.pdf Type: application/pdf Size: 259058 bytes Desc: not available URL: -------------- next part -------------- > Op 6 jan. 2019, om 11:34 heeft Oleg Grenrus het volgende geschreven: > > Report says explicitly "ignoring associativity". Yet, I have written manual Show/Read to make Show of list-like data prettier: I don't know any problem with that. Would be good to know, why report is written as it is. > > - Oleg > > The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. Parentheses are only added where needed, ignoring associativity. No line breaks are added. The result of showis readable by read if all component types are readable. (This is true for all instances defined in the Prelude but may not be true for user-defined instances.) > > Sent from my iPhone > > On 6 Jan 2019, at 3.53, Dannyu NDos wrote: > >> Sorry for the mix-up. I mean associativity, not fixity! >> >> 2019년 1월 6일 (일) 오전 9:06, Dannyu NDos 님이 작성: >> For the following code as an example: >> >> {-# LANGUAGE TypeOperators #-} >> >> infixr 5 :. >> >> data List a = Null | a :. List a deriving (Eq, Ord, Show, Read) >> >> >> The Show instance and the Read instance are inaware of the fixity of (:.): >> >> *Main> 2 :. 3 :. Null >> 2 :. (3 :. Null) >> *Main> read "2 :. 3 :. Null" :: List Int >> *** Exception: Prelude.read: no parse >> *Main> read "2 :. (3 :. Null)" :: List Int >> 2 :. (3 :. Null) >> >> The derived instances should be: >> >> instance Show a => Show (List a) where >> showsPrec p Null = showParen (11 <= p) (showString "Null") >> showsPrec p (x :. xs) = showParen (5 <= p) (go p (x :. xs)) where >> go _ Null = showString "Null" >> go p (x :. xs) = showsPrec p x . showString " :. " . go p xs >> >> instance Read a => Read (List a) where >> readPrec = parens $ do >> Ident "Null" <- lexP >> return Null >> +++ (do >> x <- readPrec >> Symbol ":." <- lexP >> xs <- readPrec >> return (x :. xs) >> ) >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From fis at etc-network.de Sun Jan 6 13:49:33 2019 From: fis at etc-network.de (Matthias Fischmann) Date: Sun, 6 Jan 2019 14:49:33 +0100 Subject: [Haskell-cafe] Call for Participation: BOB 2019 (March 22, Berlin) Message-ID: <20190106134933.kmzxep5aoprdzb7c@localhost.localdomain> ================================================================================ BOB 2019 Conference “What happens if we simply use what’s best?” March 22, 2019, Berlin http://bobkonf.de/2019/ Program: http://bobkonf.de/2019/en/program.html Registration: http://bobkonf.de/2019/en/registration.html ================================================================================ BOB is the conference for developers, architects and decision-makers to explore technologies beyond the mainstream in software development, and to find the best tools available to software developers today. Our goal is for all participants of BOB to return home with new insights that enable them to improve their own software development experiences. The program features 14 talks and 8 tutorials on current topics: http://bobkonf.de/2019/en/program.html The subject range of talks includes functional programming, formal methods, event sourcing, music, advanced SQL, logic, and feeling The tutorials feature introductions to Racket, Clojure, Functional Programming, TypeScript, type-level programming, SQL indexing, probabilistic programming, and hardware. Gabriele Keller will give the keynote talk. Registration is open online: http://bobkonf.de/2019/en/registration.html NOTE: The early-bird rates expire on February 19, 2019! BOB cooperates with the RacketFest conference on the following day: https://racketfest.com/ From godzbanebane at gmail.com Mon Jan 7 08:08:22 2019 From: godzbanebane at gmail.com (Georgi Lyubenov) Date: Mon, 7 Jan 2019 10:08:22 +0200 Subject: [Haskell-cafe] Hide internal modules but expose them for testing Message-ID: Greetings, I want to have internal modules which I do not expose at all. I also want to be able to test them. This however also hides these modules from my tests. The best way I have found to work around this is to include my entire source directory in the test suite (source-dirs). This however means that I can't reuse builds that didn't include the tests. Is there some obvious and "best" solution that I am missing here? For reference I use Stack. Thanks in advance! ======= Georgi -------------- next part -------------- An HTML attachment was scrubbed... URL: From Graham.Hutton at nottingham.ac.uk Mon Jan 7 09:04:26 2019 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Mon, 7 Jan 2019 09:04:26 +0000 Subject: [Haskell-cafe] 10 PhD studentships in Nottingham Message-ID: <5F7CD351-0BAD-44FD-9E15-939612A63952@exmail.nottingham.ac.uk> Dear all, *** FINAL CALL -- APPLICATION DEADLINE 18 JANUARY 2019 *** The School of Computer Science at the University of Nottingham is seeking applications for 10 fully-funded PhD studentships: https://tinyurl.com/10-phds-2019 Applicants in the area of the Functional Programming Laboratory (https://tinyurl.com/fp-notts) are strongly encouraged! If you are interested in applying, please contact a potential supervisor as soon as possible (the application deadline is 18th January): Thorsten Altenkirch - constructive logic, proof assistants, homotopy type theory, category theory, lambda calculus. Venanzio Capretta - type theory, mathematical logic, corecursive structures, proof assistants, category theory, epistemic logic. Graham Hutton - functional programming, program calculation and transformation, correctness and efficiency, category theory. Henrik Nilsson - functional reactive programming, modelling and simulation, domain-specific languages, probabilistic languages. Best wishes, Graham +-----------------------------------------------------------+ 10 Fully-Funded PhD Studentships School of Computer Science University of Nottingham, UK https://tinyurl.com/10-phds-2019 Applications are invited for up to ten fully-funded PhD studentships in the School of Computer Science at the University of Nottingham, starting on 1 October 2019. The topics for the studentships are open, but should relate to one of the School’s research groups: Agents Lab; Automated Scheduling and Planning; Computer Vision Lab; Data Driven Algorithms, Systems and Design; Functional Programming Lab; Intelligent Modelling and Analysis; Uncertainty in Data and Decision Making; Mixed Reality Lab. The studentships are for a minimum of three years and include a stipend of £14,777 per year and tuition fees. They are open to students of any nationality. Applicants are normally expected to have a first-class MSc or BSc in Computer Science or a related discipline, and must obtain the support of a supervisor in the School prior to submitting their application. Initial contact with supervisors should be made at least two weeks prior to the closing date for applications. Informal enquiries may be addressed to SS-PGR-JC at nottingham.ac.uk. To apply, please submit the following items by email to: Christine.Fletcher at nottingham.ac.uk: (1) a brief covering letter that describes your reasons for wishing to pursue a PhD, your proposed research area and topic, and the name of the potential supervisor whose support you have already secured; (2) a copy of your CV, including your actual or expected degree classes, and results of all University examinations; (3) an extended example of your technical writing, such as a project report or dissertation; (4) contact details for two academic referees. Closing date for applications: Friday 18 January 2019 +-----------------------------------------------------------+ 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 lysxia at gmail.com Mon Jan 7 11:10:19 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Mon, 7 Jan 2019 12:10:19 +0100 Subject: [Haskell-cafe] Hide internal modules but expose them for testing In-Reply-To: References: Message-ID: My preferred solution is to put all the implementation in Mylib.Internal.Foo modules that export everything, with the convention that it's not subject to versioning policies (so testing is really the only legitimate use), and reexport the public stuff in Mylib.Foo. Li-yao On 09:08, Mon, Jan 7, 2019 Georgi Lyubenov Greetings, > > I want to have internal modules which I do not expose at all. I also want > to be able to test them. > > This however also hides these modules from my tests. > > The best way I have found to work around this is to include my entire > source directory in the test suite (source-dirs). This however means that I > can't reuse builds that didn't include the tests. > > Is there some obvious and "best" solution that I am missing here? For > reference I use Stack. > > Thanks in advance! > > ======= > Georgi > _______________________________________________ > 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 alexander.vershilov at gmail.com Mon Jan 7 11:17:04 2019 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Mon, 7 Jan 2019 14:17:04 +0300 Subject: [Haskell-cafe] Hide internal modules but expose them for testing In-Reply-To: References: Message-ID: Hello Georgi, while I prefer Internal convention and expose everything, and would advice that as a way forward, your use case is supported by Cabal. There is a way to define an internal/sublibrary that is visible in the package but not exposed outside. You can find relevant documentation with examples in Cabal docs: https://cabal.readthedocs.io/en/latest/developing-packages.html#sublibs On Mon, 7 Jan 2019 at 14:10, Li-yao Xia wrote: > > My preferred solution is to put all the implementation in Mylib.Internal.Foo modules that export everything, with the convention that it's not subject to versioning policies (so testing is really the only legitimate use), and reexport the public stuff in Mylib.Foo. > > Li-yao > > > On 09:08, Mon, Jan 7, 2019 Georgi Lyubenov > >> Greetings, >> >> I want to have internal modules which I do not expose at all. I also want to be able to test them. >> >> This however also hides these modules from my tests. >> >> The best way I have found to work around this is to include my entire source directory in the test suite (source-dirs). This however means that I can't reuse builds that didn't include the tests. >> >> Is there some obvious and "best" solution that I am missing here? For reference I use Stack. >> >> Thanks in advance! >> >> ======= >> Georgi >> _______________________________________________ >> 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. -- Alexander From vanessa.mchale at iohk.io Mon Jan 7 14:25:40 2019 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Mon, 7 Jan 2019 08:25:40 -0600 Subject: [Haskell-cafe] Hide internal modules but expose them for testing In-Reply-To: References: Message-ID: <6b00ea45-2910-b317-148e-6862d01e3668@iohk.io> As of recently you can have private libraries in a package. See e.g. my htoml-megaparsec package for an example: http://hackage.haskell.org/package/htoml-megaparsec where I use it to do exactly what you wanted. On 1/7/19 2:08 AM, Georgi Lyubenov wrote: > Greetings, > > I want to have internal modules which I do not expose at all. I also > want to be able to test them. > > This however also hides these modules from my tests. > > The best way I have found to work around this is to include my entire > source directory in the test suite (source-dirs). This however means > that I can't reuse builds that didn't include the tests. > > Is there some obvious and "best" solution that I am missing here? For > reference I use Stack. > > Thanks in advance! > > ======= > Georgi > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 488 bytes Desc: OpenPGP digital signature URL: From mattei at oca.eu Mon Jan 7 16:13:13 2019 From: mattei at oca.eu (Damien Mattei) Date: Mon, 7 Jan 2019 17:13:13 +0100 Subject: [Haskell-cafe] concatenate two Maybe String... Message-ID: <5C337A99.5040109@oca.eu> hello, i have a variable resBDwords of type ( i expect) Maybe [String], for info it is integer and fractional part of a number example looks like this : resBDwords =Just ["-04","3982"] i want to concatanate "-04" and "3982" in the example, i begin to understand fmap to use the functor hidden in the Maybe ,it worked previously: let resBDstr = fmap Tx.unpack resBDtxt putStr "resBDstr =" putStrLn (show resBDtxt) let resBDwords = fmap words resBDstr putStr "resBDwords =" putStrLn (show resBDwords) which gives: resBDtxt ="-04 3982" resBDstr =Just "-04 3982" just after in my code i have this to concatanate the two strings f and s that are the first and second element of the array: putStr "resBDwords =" putStrLn (show resBDwords) let lgBDwords = length resBDwords let resBDstrFloat = if lgBDwords == 0 then trace "WARNING: BD contains no words" Nothing else if lgBDwords == 1 then trace "WARNING: BD contains only one word" fmap head resBDwords else let f = fmap head resBDwords s = fmap (head . tail) resBDwords in f ++ "." ++ S but i do not know how to concatanate the Maybe String in an elegant way, using somethin like fmap variable which have handled Nothing (from Maybe) automatically i need the counter part for multipe variable i do not want to do it using the hard way with case... of Just x -> nothing ......... i got this error : *Main> :load UpdateSidonie [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) UpdateSidonie.hs:339:43: error: • Couldn't match expected type ‘[Char]’ with actual type ‘Maybe String’ • In the first argument of ‘(++)’, namely ‘f’ In the expression: f ++ "." ++ s In the expression: let f = fmap head resBDwords s = fmap (head . tail) resBDwords in f ++ "." ++ s | 339 | in f ++ "." ++ s | ^ UpdateSidonie.hs:339:43: error: • Couldn't match expected type ‘Maybe String’ with actual type ‘[Char]’ • In the expression: f ++ "." ++ s In the expression: let f = fmap head resBDwords s = fmap (head . tail) resBDwords in f ++ "." ++ s In the expression: if lgBDwords == 1 then trace "WARNING: BD contains only one word" fmap head resBDwords else let f = fmap head resBDwords s = fmap (head . tail) resBDwords in f ++ "." ++ s | 339 | in f ++ "." ++ s | ^^^^^^^^^^^^^ UpdateSidonie.hs:339:55: error: • Couldn't match expected type ‘[Char]’ with actual type ‘Maybe String’ • In the second argument of ‘(++)’, namely ‘s’ In the second argument of ‘(++)’, namely ‘"." ++ s’ In the expression: f ++ "." ++ s | 339 | in f ++ "." ++ s | ^ Failed, no modules loaded. for now this page has been of valuable help: https://pbrisbin.com/posts/maybe_is_just_awesome/ i'm sure it's an obvious question but.... :-) From joshchia at gmail.com Mon Jan 7 22:41:09 2019 From: joshchia at gmail.com (=?UTF-8?B?4piCSm9zaCBDaGlhICjorJ3ku7vkuK0p?=) Date: Tue, 8 Jan 2019 06:41:09 +0800 Subject: [Haskell-cafe] concatenate two Maybe String... In-Reply-To: <5C337A99.5040109@oca.eu> References: <5C337A99.5040109@oca.eu> Message-ID: Firstly, because "resBDwords :: Maybe String", not "resBDwords :: String", "lgBDwords = length resBDwords" probably is not what you want -- it does not give you the number of words in the String that may be in there. Second, for the problem you asked about, you could just use a function that takes a String and do it "the hard way" like you said, using case outside before calling the function. Another way is to use an applicative functor to allow you to have a "Maybe String -> Maybe String -> Maybe String". This is used once for each "++" that you want to do. I don't know exactly what you need to accomplish but I would just write a function "f :: String -> Maybe String" implementing the logic you listed in the second code snippet but operating on String instead of "Maybe String" and do "join . fmap f $ resBDwords". On Tue, Jan 8, 2019 at 12:13 AM Damien Mattei wrote: > hello, > > i have a variable resBDwords of type ( i expect) Maybe [String], for > info it is integer and fractional part of a number > > example looks like this : > resBDwords =Just ["-04","3982"] > > i want to concatanate "-04" and "3982" in the example, i begin to > understand fmap to use the functor hidden in the Maybe ,it worked > previously: > > let resBDstr = fmap Tx.unpack resBDtxt > putStr "resBDstr =" > putStrLn (show resBDtxt) > > let resBDwords = fmap words resBDstr > putStr "resBDwords =" > putStrLn (show resBDwords) > > which gives: > > resBDtxt ="-04 3982" > resBDstr =Just "-04 3982" > > > just after in my code i have this to concatanate the two strings f and s > that are the first and second element of the array: > > > putStr "resBDwords =" > putStrLn (show resBDwords) > > let lgBDwords = length resBDwords > > let resBDstrFloat = if lgBDwords == 0 > then trace "WARNING: BD contains no words" > Nothing > else > if lgBDwords == 1 > then trace "WARNING: BD contains only > one word" fmap head resBDwords > else let f = fmap head resBDwords > s = fmap (head . tail) > resBDwords > in f ++ "." ++ S > > but i do not know how to concatanate the Maybe String in an elegant way, > using somethin like fmap variable which have handled Nothing (from > Maybe) automatically i need the counter part for multipe variable > > i do not want to do it using the hard way with case... of Just x -> > nothing ......... > > i got this error : > *Main> :load UpdateSidonie > [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) > > UpdateSidonie.hs:339:43: error: > • Couldn't match expected type ‘[Char]’ > with actual type ‘Maybe String’ > • In the first argument of ‘(++)’, namely ‘f’ > In the expression: f ++ "." ++ s > In the expression: > let > f = fmap head resBDwords > s = fmap (head . tail) resBDwords > in f ++ "." ++ s > | > 339 | in f ++ "." ++ s > | ^ > > UpdateSidonie.hs:339:43: error: > • Couldn't match expected type ‘Maybe String’ > with actual type ‘[Char]’ > • In the expression: f ++ "." ++ s > In the expression: > let > f = fmap head resBDwords > s = fmap (head . tail) resBDwords > in f ++ "." ++ s > In the expression: > if lgBDwords == 1 then > trace "WARNING: BD contains only one word" fmap head resBDwords > else > let > f = fmap head resBDwords > s = fmap (head . tail) resBDwords > in f ++ "." ++ s > | > 339 | in f ++ "." ++ s > | ^^^^^^^^^^^^^ > > UpdateSidonie.hs:339:55: error: > • Couldn't match expected type ‘[Char]’ > with actual type ‘Maybe String’ > • In the second argument of ‘(++)’, namely ‘s’ > In the second argument of ‘(++)’, namely ‘"." ++ s’ > In the expression: f ++ "." ++ s > | > 339 | in f ++ "." ++ s > | ^ > Failed, no modules loaded. > > for now this page has been of valuable help: > > https://pbrisbin.com/posts/maybe_is_just_awesome/ > > i'm sure it's an obvious question but.... :-) > > _______________________________________________ > 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 jake.waksbaum at gmail.com Mon Jan 7 22:57:10 2019 From: jake.waksbaum at gmail.com (Jake) Date: Mon, 7 Jan 2019 17:57:10 -0500 Subject: [Haskell-cafe] concatenate two Maybe String... In-Reply-To: References: <5C337A99.5040109@oca.eu> Message-ID: On Mon, Jan 7, 2019 at 5:55 PM Jake wrote: > Like Josh mentioned, Applicative Functors > > are what you want. There are two idiomatic ways to do it: > > - You can just use liftA2, which has type (a -> b -> c) -> f a -> f b > -> f c. That means it lifts a binary function to some applicative functor > like maybe, so liftA2 (++) :: Maybe String -> Maybe String -> Maybe String > - In general, for any arity f that you want to lift to an applicative > functor. So you have a function g that takes a bunch of arguments of types > a, b, c, ... and gives you back an r and you want to get a function that > takes an f a, f b, f c, ... and gives you back an f r, you can write f <$> > a <*> b <*> c ... This works because <$> let's you apply g to type f a and > gives you an f (b -> c ..) -> f r, and <*> basically let's you take the > function back out of the f and apply it to the b to get a f (c ..) -> f r > and so on. *tl;dr* you can write (++) <$> s1 <*> s2. In fact, liftA2 > must satisfy the equation liftA2 > > f x y = f <$> x <*> > > y so these are the same thing. > > בתאריך יום ב׳, 7 בינו׳ 2019, 17:41, מאת ☂Josh Chia (謝任中) < > joshchia at gmail.com>: > >> Firstly, because "resBDwords :: Maybe String", not "resBDwords :: >> String", "lgBDwords = length resBDwords" probably is not what you want -- >> it does not give you the number of words in the String that may be in there. >> >> Second, for the problem you asked about, you could just use a function >> that takes a String and do it "the hard way" like you said, using case >> outside before calling the function. Another way is to use an applicative >> functor to allow you to have a "Maybe String -> Maybe String -> Maybe >> String". This is used once for each "++" that you want to do. >> >> I don't know exactly what you need to accomplish but I would just write a >> function "f :: String -> Maybe String" implementing the logic you listed in >> the second code snippet but operating on String instead of "Maybe String" >> and do "join . fmap f $ resBDwords". >> >> On Tue, Jan 8, 2019 at 12:13 AM Damien Mattei wrote: >> >>> hello, >>> >>> i have a variable resBDwords of type ( i expect) Maybe [String], for >>> info it is integer and fractional part of a number >>> >>> example looks like this : >>> resBDwords =Just ["-04","3982"] >>> >>> i want to concatanate "-04" and "3982" in the example, i begin to >>> understand fmap to use the functor hidden in the Maybe ,it worked >>> previously: >>> >>> let resBDstr = fmap Tx.unpack resBDtxt >>> putStr "resBDstr =" >>> putStrLn (show resBDtxt) >>> >>> let resBDwords = fmap words resBDstr >>> putStr "resBDwords =" >>> putStrLn (show resBDwords) >>> >>> which gives: >>> >>> resBDtxt ="-04 3982" >>> resBDstr =Just "-04 3982" >>> >>> >>> just after in my code i have this to concatanate the two strings f and s >>> that are the first and second element of the array: >>> >>> >>> putStr "resBDwords =" >>> putStrLn (show resBDwords) >>> >>> let lgBDwords = length resBDwords >>> >>> let resBDstrFloat = if lgBDwords == 0 >>> then trace "WARNING: BD contains no words" >>> Nothing >>> else >>> if lgBDwords == 1 >>> then trace "WARNING: BD contains only >>> one word" fmap head resBDwords >>> else let f = fmap head resBDwords >>> s = fmap (head . tail) >>> resBDwords >>> in f ++ "." ++ S >>> >>> but i do not know how to concatanate the Maybe String in an elegant way, >>> using somethin like fmap variable which have handled Nothing (from >>> Maybe) automatically i need the counter part for multipe variable >>> >>> i do not want to do it using the hard way with case... of Just x -> >>> nothing ......... >>> >>> i got this error : >>> *Main> :load UpdateSidonie >>> [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) >>> >>> UpdateSidonie.hs:339:43: error: >>> • Couldn't match expected type ‘[Char]’ >>> with actual type ‘Maybe String’ >>> • In the first argument of ‘(++)’, namely ‘f’ >>> In the expression: f ++ "." ++ s >>> In the expression: >>> let >>> f = fmap head resBDwords >>> s = fmap (head . tail) resBDwords >>> in f ++ "." ++ s >>> | >>> 339 | in f ++ "." ++ s >>> | ^ >>> >>> UpdateSidonie.hs:339:43: error: >>> • Couldn't match expected type ‘Maybe String’ >>> with actual type ‘[Char]’ >>> • In the expression: f ++ "." ++ s >>> In the expression: >>> let >>> f = fmap head resBDwords >>> s = fmap (head . tail) resBDwords >>> in f ++ "." ++ s >>> In the expression: >>> if lgBDwords == 1 then >>> trace "WARNING: BD contains only one word" fmap head >>> resBDwords >>> else >>> let >>> f = fmap head resBDwords >>> s = fmap (head . tail) resBDwords >>> in f ++ "." ++ s >>> | >>> 339 | in f ++ "." ++ s >>> | ^^^^^^^^^^^^^ >>> >>> UpdateSidonie.hs:339:55: error: >>> • Couldn't match expected type ‘[Char]’ >>> with actual type ‘Maybe String’ >>> • In the second argument of ‘(++)’, namely ‘s’ >>> In the second argument of ‘(++)’, namely ‘"." ++ s’ >>> In the expression: f ++ "." ++ s >>> | >>> 339 | in f ++ "." ++ s >>> | ^ >>> Failed, no modules loaded. >>> >>> for now this page has been of valuable help: >>> >>> https://pbrisbin.com/posts/maybe_is_just_awesome/ >>> >>> i'm sure it's an obvious question but.... :-) >>> >>> _______________________________________________ >>> 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 steven at steshaw.org Tue Jan 8 00:43:05 2019 From: steven at steshaw.org (Steven Shaw) Date: Tue, 8 Jan 2019 10:43:05 +1000 Subject: [Haskell-cafe] concatenate two Maybe String... In-Reply-To: References: <5C337A99.5040109@oca.eu> Message-ID: A quick and dirty answer might be: fmap (Data.Text.intercalate ".") resBDwords I'd probably write it: Data.Text.intercalate "." <$> resBDwords but you'd probably want to check your input has exactly two elements. You could use pattern matching: f (Just [a, b]) = Just $ a <> "." <> b f _ = Nothing Then (f resBDwords) gives you what you want I think and avoids head and tail. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Tue Jan 8 07:47:20 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Tue, 8 Jan 2019 07:47:20 +0000 Subject: [Haskell-cafe] concatenate two Maybe String... In-Reply-To: <5C337A99.5040109@oca.eu> References: <5C337A99.5040109@oca.eu> Message-ID: <20190108074720.qlqb7jrtzn65zupl@weber> On Mon, Jan 07, 2019 at 05:13:13PM +0100, Damien Mattei wrote: > just after in my code i have this to concatanate the two strings f and s > that are the first and second element of the array: ... > i do not want to do it using the hard way with case... of Just x -> > nothing ......... Just do it the hard way and get some code that works. You can always "improve" it later if you like. "Hard" code that works is orders of magnitude more valuable that "easy" code that doesn't. From damien.mattei at gmail.com Tue Jan 8 10:40:33 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Tue, 8 Jan 2019 11:40:33 +0100 Subject: [Haskell-cafe] concatenate two Maybe String... In-Reply-To: References: <5C337A99.5040109@oca.eu> Message-ID: i had this solution for now: let resBDstrFloat = if lgBDwords == Just 0 then trace "WARNING: BD contains no words" Nothing else if lgBDwords == Just 1 then trace "WARNING: BD contains only one word" fmap head resBDwords else let f = fmap head resBDwords s = fmap (head . tail) resBDwords mp = Just "." :: Maybe String (+++) = liftM2 (++) in f +++ mp +++ s still searching to express it with <*> ..., also there is the problem of if i define "." simply as it is not a Maybe String it fails, perheaps some viadic function that accept multi-type variable but this is complex to do. On Mon, Jan 7, 2019 at 11:58 PM Jake wrote: > > > On Mon, Jan 7, 2019 at 5:55 PM Jake wrote: > >> Like Josh mentioned, Applicative Functors >> >> are what you want. There are two idiomatic ways to do it: >> >> - You can just use liftA2, which has type (a -> b -> c) -> f a -> f b >> -> f c. That means it lifts a binary function to some applicative functor >> like maybe, so liftA2 (++) :: Maybe String -> Maybe String -> Maybe String >> - In general, for any arity f that you want to lift to an applicative >> functor. So you have a function g that takes a bunch of arguments of types >> a, b, c, ... and gives you back an r and you want to get a function that >> takes an f a, f b, f c, ... and gives you back an f r, you can write f <$> >> a <*> b <*> c ... This works because <$> let's you apply g to type f a and >> gives you an f (b -> c ..) -> f r, and <*> basically let's you take the >> function back out of the f and apply it to the b to get a f (c ..) -> f r >> and so on. *tl;dr* you can write (++) <$> s1 <*> s2. In fact, liftA2 >> must satisfy the equation liftA2 >> >> f x y = f <$> x <*> >> >> y so these are the same thing. >> >> בתאריך יום ב׳, 7 בינו׳ 2019, 17:41, מאת ☂Josh Chia (謝任中) < >> joshchia at gmail.com>: >> >>> Firstly, because "resBDwords :: Maybe String", not "resBDwords :: >>> String", "lgBDwords = length resBDwords" probably is not what you want -- >>> it does not give you the number of words in the String that may be in there. >>> >>> Second, for the problem you asked about, you could just use a function >>> that takes a String and do it "the hard way" like you said, using case >>> outside before calling the function. Another way is to use an applicative >>> functor to allow you to have a "Maybe String -> Maybe String -> Maybe >>> String". This is used once for each "++" that you want to do. >>> >>> I don't know exactly what you need to accomplish but I would just write >>> a function "f :: String -> Maybe String" implementing the logic you listed >>> in the second code snippet but operating on String instead of "Maybe >>> String" and do "join . fmap f $ resBDwords". >>> >>> On Tue, Jan 8, 2019 at 12:13 AM Damien Mattei wrote: >>> >>>> hello, >>>> >>>> i have a variable resBDwords of type ( i expect) Maybe [String], for >>>> info it is integer and fractional part of a number >>>> >>>> example looks like this : >>>> resBDwords =Just ["-04","3982"] >>>> >>>> i want to concatanate "-04" and "3982" in the example, i begin to >>>> understand fmap to use the functor hidden in the Maybe ,it worked >>>> previously: >>>> >>>> let resBDstr = fmap Tx.unpack resBDtxt >>>> putStr "resBDstr =" >>>> putStrLn (show resBDtxt) >>>> >>>> let resBDwords = fmap words resBDstr >>>> putStr "resBDwords =" >>>> putStrLn (show resBDwords) >>>> >>>> which gives: >>>> >>>> resBDtxt ="-04 3982" >>>> resBDstr =Just "-04 3982" >>>> >>>> >>>> just after in my code i have this to concatanate the two strings f and s >>>> that are the first and second element of the array: >>>> >>>> >>>> putStr "resBDwords =" >>>> putStrLn (show resBDwords) >>>> >>>> let lgBDwords = length resBDwords >>>> >>>> let resBDstrFloat = if lgBDwords == 0 >>>> then trace "WARNING: BD contains no words" >>>> Nothing >>>> else >>>> if lgBDwords == 1 >>>> then trace "WARNING: BD contains only >>>> one word" fmap head resBDwords >>>> else let f = fmap head resBDwords >>>> s = fmap (head . tail) >>>> resBDwords >>>> in f ++ "." ++ S >>>> >>>> but i do not know how to concatanate the Maybe String in an elegant way, >>>> using somethin like fmap variable which have handled Nothing (from >>>> Maybe) automatically i need the counter part for multipe variable >>>> >>>> i do not want to do it using the hard way with case... of Just x -> >>>> nothing ......... >>>> >>>> i got this error : >>>> *Main> :load UpdateSidonie >>>> [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) >>>> >>>> UpdateSidonie.hs:339:43: error: >>>> • Couldn't match expected type ‘[Char]’ >>>> with actual type ‘Maybe String’ >>>> • In the first argument of ‘(++)’, namely ‘f’ >>>> In the expression: f ++ "." ++ s >>>> In the expression: >>>> let >>>> f = fmap head resBDwords >>>> s = fmap (head . tail) resBDwords >>>> in f ++ "." ++ s >>>> | >>>> 339 | in f ++ "." ++ s >>>> | ^ >>>> >>>> UpdateSidonie.hs:339:43: error: >>>> • Couldn't match expected type ‘Maybe String’ >>>> with actual type ‘[Char]’ >>>> • In the expression: f ++ "." ++ s >>>> In the expression: >>>> let >>>> f = fmap head resBDwords >>>> s = fmap (head . tail) resBDwords >>>> in f ++ "." ++ s >>>> In the expression: >>>> if lgBDwords == 1 then >>>> trace "WARNING: BD contains only one word" fmap head >>>> resBDwords >>>> else >>>> let >>>> f = fmap head resBDwords >>>> s = fmap (head . tail) resBDwords >>>> in f ++ "." ++ s >>>> | >>>> 339 | in f ++ "." ++ s >>>> | ^^^^^^^^^^^^^ >>>> >>>> UpdateSidonie.hs:339:55: error: >>>> • Couldn't match expected type ‘[Char]’ >>>> with actual type ‘Maybe String’ >>>> • In the second argument of ‘(++)’, namely ‘s’ >>>> In the second argument of ‘(++)’, namely ‘"." ++ s’ >>>> In the expression: f ++ "." ++ s >>>> | >>>> 339 | in f ++ "." ++ s >>>> | ^ >>>> Failed, no modules loaded. >>>> >>>> for now this page has been of valuable help: >>>> >>>> https://pbrisbin.com/posts/maybe_is_just_awesome/ >>>> >>>> i'm sure it's an obvious question but.... :-) >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From quentin.liu.0415 at gmail.com Tue Jan 8 13:20:37 2019 From: quentin.liu.0415 at gmail.com (Qingbo Liu) Date: Tue, 8 Jan 2019 21:20:37 +0800 Subject: [Haskell-cafe] conduit: consume part of input and push all other input downstream Message-ID: <4102989c-f005-4301-a816-c40ea01411c0@Spark> Dear Cafe, I am using conduit to parse a file in a streaming fashion. In the middle of the conduit pipeline, I have a conduit that parses a value, returns the value, and then passes all other input downstream. Is there any way to express this? I looked up functions provided by the conduit and it seems that there is no such a function that provides such semantics. My conduit function looks as follows: -- | Run the given `Get` only once and push unconsumed bytes from upstream to -- downstream conduitParseOnce :: (MonadThrow m, MonadResource m) =>                         Get a -> ConduitT BS.ByteString BS.ByteString m a conduitParseOnce g = go0     where       go0 = do x <- await                case x of                  Nothing -> undefined -- throwM SomeException                  Just bs -> go (runGetChunk g Nothing bs)       go (Fail msg bs) = throwM (DecodeError bs msg "conduitParseOnce")       go (Partial f)   = await >>= maybe (go $ f mempty) (go . f)       go (Done v bs)   = leftover bs >> return v The downstream of this conduit will take all remaining inputs and parses them. The issue with this implementation is that the downstream will only be able to get the first chunk of data. Best Regards, Qingbo Liu -------------- next part -------------- An HTML attachment was scrubbed... URL: From doaitse at swierstra.net Tue Jan 8 13:42:00 2019 From: doaitse at swierstra.net (Doaitse Swierstra) Date: Tue, 8 Jan 2019 14:42:00 +0100 Subject: [Haskell-cafe] concatenate two Maybe String... In-Reply-To: References: <5C337A99.5040109@oca.eu> Message-ID: Something like: resBDstrFloat = case resDBWords of Nothing -> trace "WARNING: BD contains no words” Nothing Just [] -> trace "WARNING: BD contains no words” Nothing Just [v] -> trace "WARNING: BD contains only one word” (Just v) Just [v1,v2]) -> Just (v1 ++ “.” ++ v2) - -> trace “unexpected garbage” Nothing seems optimal and easiest to understand to me, Doaitse > Op 8 jan. 2019, om 11:40 heeft Damien Mattei het volgende geschreven: > > i had this solution for now: > > let resBDstrFloat = if lgBDwords == Just 0 > then trace "WARNING: BD contains no words" Nothing > else > if lgBDwords == Just 1 > then trace "WARNING: BD contains only one word" fmap head resBDwords > else let f = fmap head resBDwords > s = fmap (head . tail) resBDwords > mp = Just "." :: Maybe String > (+++) = liftM2 (++) > in f +++ mp +++ s > > still searching to express it with <*> ..., also there is the problem of if i define "." simply as it is not a Maybe String it fails, perheaps some viadic function that accept multi-type variable but this is complex to do. > > On Mon, Jan 7, 2019 at 11:58 PM Jake wrote: > > > On Mon, Jan 7, 2019 at 5:55 PM Jake wrote: > Like Josh mentioned, Applicative Functors are what you want. There are two idiomatic ways to do it: > • You can just use liftA2, which has type (a -> b -> c) -> f a -> f b -> f c. That means it lifts a binary function to some applicative functor like maybe, so liftA2 (++) :: Maybe String -> Maybe String -> Maybe String > • In general, for any arity f that you want to lift to an applicative functor. So you have a function g that takes a bunch of arguments of types a, b, c, ... and gives you back an r and you want to get a function that takes an f a, f b, f c, ... and gives you back an f r, you can write f <$> a <*> b <*> c ... This works because <$> let's you apply g to type f a and gives you an f (b -> c ..) -> f r, and <*> basically let's you take the function back out of the f and apply it to the b to get a f (c ..) -> f r and so on. tl;dr you can write (++) <$> s1 <*> s2. In fact, liftA2 must satisfy the equation liftA2 f x y = f <$> x <*> y so these are the same thing. > בתאריך יום ב׳, 7 בינו׳ 2019, 17:41, מאת ☂Josh Chia (謝任中) : > Firstly, because "resBDwords :: Maybe String", not "resBDwords :: String", "lgBDwords = length resBDwords" probably is not what you want -- it does not give you the number of words in the String that may be in there. > > Second, for the problem you asked about, you could just use a function that takes a String and do it "the hard way" like you said, using case outside before calling the function. Another way is to use an applicative functor to allow you to have a "Maybe String -> Maybe String -> Maybe String". This is used once for each "++" that you want to do. > > I don't know exactly what you need to accomplish but I would just write a function "f :: String -> Maybe String" implementing the logic you listed in the second code snippet but operating on String instead of "Maybe String" and do "join . fmap f $ resBDwords". > > On Tue, Jan 8, 2019 at 12:13 AM Damien Mattei wrote: > hello, > > i have a variable resBDwords of type ( i expect) Maybe [String], for > info it is integer and fractional part of a number > > example looks like this : > resBDwords =Just ["-04","3982"] > > i want to concatanate "-04" and "3982" in the example, i begin to > understand fmap to use the functor hidden in the Maybe ,it worked > previously: > > let resBDstr = fmap Tx.unpack resBDtxt > putStr "resBDstr =" > putStrLn (show resBDtxt) > > let resBDwords = fmap words resBDstr > putStr "resBDwords =" > putStrLn (show resBDwords) > > which gives: > > resBDtxt ="-04 3982" > resBDstr =Just "-04 3982" > > > just after in my code i have this to concatanate the two strings f and s > that are the first and second element of the array: > > > putStr "resBDwords =" > putStrLn (show resBDwords) > > let lgBDwords = length resBDwords > > let resBDstrFloat = if lgBDwords == 0 > then trace "WARNING: BD contains no words" > Nothing > else > if lgBDwords == 1 > then trace "WARNING: BD contains only > one word" fmap head resBDwords > else let f = fmap head resBDwords > s = fmap (head . tail) resBDwords > in f ++ "." ++ S > > but i do not know how to concatanate the Maybe String in an elegant way, > using somethin like fmap variable which have handled Nothing (from > Maybe) automatically i need the counter part for multipe variable > > i do not want to do it using the hard way with case... of Just x -> > nothing ......... > > i got this error : > *Main> :load UpdateSidonie > [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) > > UpdateSidonie.hs:339:43: error: > • Couldn't match expected type ‘[Char]’ > with actual type ‘Maybe String’ > • In the first argument of ‘(++)’, namely ‘f’ > In the expression: f ++ "." ++ s > In the expression: > let > f = fmap head resBDwords > s = fmap (head . tail) resBDwords > in f ++ "." ++ s > | > 339 | in f ++ "." ++ s > | ^ > > UpdateSidonie.hs:339:43: error: > • Couldn't match expected type ‘Maybe String’ > with actual type ‘[Char]’ > • In the expression: f ++ "." ++ s > In the expression: > let > f = fmap head resBDwords > s = fmap (head . tail) resBDwords > in f ++ "." ++ s > In the expression: > if lgBDwords == 1 then > trace "WARNING: BD contains only one word" fmap head resBDwords > else > let > f = fmap head resBDwords > s = fmap (head . tail) resBDwords > in f ++ "." ++ s > | > 339 | in f ++ "." ++ s > | ^^^^^^^^^^^^^ > > UpdateSidonie.hs:339:55: error: > • Couldn't match expected type ‘[Char]’ > with actual type ‘Maybe String’ > • In the second argument of ‘(++)’, namely ‘s’ > In the second argument of ‘(++)’, namely ‘"." ++ s’ > In the expression: f ++ "." ++ s > | > 339 | in f ++ "." ++ s > | ^ > Failed, no modules loaded. > > for now this page has been of valuable help: > > https://pbrisbin.com/posts/maybe_is_just_awesome/ > > i'm sure it's an obvious question but.... :-) > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > 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 mattei at oca.eu Tue Jan 8 14:05:22 2019 From: mattei at oca.eu (Damien Mattei) Date: Tue, 8 Jan 2019 15:05:22 +0100 Subject: [Haskell-cafe] concatenate two Maybe String... In-Reply-To: <20190108074720.qlqb7jrtzn65zupl@weber> References: <5C337A99.5040109@oca.eu> <20190108074720.qlqb7jrtzn65zupl@weber> Message-ID: <5C34AE22.1030101@oca.eu> from the previous solution and posts i can deduce this solution to concatanate N Maybe String, the function could be written: (+++) = \x y -> (++) <$> x <*> y this is basically equivalent to the previous one: (+++) = liftM2 (++) on f +++ mp +++ s i get results like: resBDstrFloat =Just "-04.3982" i will stay with those solutions. Le 08/01/2019 08:47, Tom Ellis a écrit : > On Mon, Jan 07, 2019 at 05:13:13PM +0100, Damien Mattei wrote: >> just after in my code i have this to concatanate the two strings f and s >> that are the first and second element of the array: > ... >> i do not want to do it using the hard way with case... of Just x -> >> nothing ......... > > Just do it the hard way and get some code that works. You can always > "improve" it later if you like. "Hard" code that works is orders of > magnitude more valuable that "easy" code that doesn't. > _______________________________________________ > 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. > -- Damien.Mattei at unice.fr, Damien.Mattei at oca.eu, UNS / OCA / CNRS From john at degoes.net Tue Jan 8 15:06:34 2019 From: john at degoes.net (John A. De Goes) Date: Tue, 8 Jan 2019 08:06:34 -0700 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals Message-ID: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> Dear Haskell Enthusiasts: The LambdaConf 2019 Call for Proposals is open, and we warmly welcome Haskell proposals on topics of interest to aspiring and practicing functional programmers. Historically, Haskell content accounts for more than 50% of content across all 5-8 tracks of the event. Last year’s speakers included Michael Snoyberg, Dana Scott, Jeremy Siek, and many others from both industry and academia. To submit a proposal for LambdaConf 2019, please visit the following website: https://www.papercall.io/lambdaconf-2019 Travel assistance is available, including lodging. ## INTRODUCTION LambdaConf is the largest interdisciplinary functional programming conference in the Mountain West, and one of the largest and most respected functional programming conferences in the world. The conference takes place June 5rd - 7th, in Boulder, Colorado, at the University of Colorado Boulder, and is surrounded by commercial training opportunities. If you are an educator, a researcher, a speaker, a speaker coach, or someone aspiring to one of the preceding, then we warmly welcome you to submit a proposal for LambdaConf 2019. No prior experience is necessary for most proposals, and we welcome beginner-level content. The Call for Proposals closes at the end of January 2019. We recommend submitting as early as you can to ensure sufficient time for editing. LambdaConf attracts everyone from the FP-curious to researchers advancing state-of-the-art; hobbyists, professionals, academics and students. Material at all levels, including beginner content and very advanced content, will find an audience at LambdaConf. Historically, LambdaConf has enjoyed a large selection of sessions on statically-typed functional programming, and a smaller selection of sessions on dynamically-typed functional programming. Some sessions are not tied to specific programming languages, but rather cover topics in abstract algebra, category theory, type theory, programming language theory, functional architecture, and so on, either generically or in a way that applies across many programming languages. ## TOPICS LambdaConf looks for sessions in the following areas: - LANGUAGES. Proposals that overview or dive into specific features of functional, math, or logic programming languages (both new and existing), with the goal of exposing developers to new ideas or helping them master features of languages they already know. LIBRARIES. Proposals that discuss libraries that leverage functional or logic programming to help programmers solve real-world problems. - CONCEPTS. Proposals that discuss functional programming idioms, patterns, or abstractions; or concepts from mathematics, logic, and computer science, all directed at helping developers write software that’s easier to test, easier to reason about, and easier to change safely. - APPLICATIONS. Proposals that discuss how functional programming can help with specific aspects of modern software development, including scalability, distributed systems, concurrency, data processing, security, performance, correctness, user-interfaces, machine learning, and big data. - USE CASES. Proposals that discuss how functional programming enabled a project or team to thrive, or deliver more business value than possible with other approaches. - CHERRY PICKING. Proposals that show how techniques and approaches from functional programming can be adapted and incorporated into mainstream development languages and practices, to the benefit of developers using them. - CAUTIONARY TALES. Proposals that call attention to difficulties of functional programming (both as a cautionary tale but also to raise awareness), especially such proposals that suggest alternatives or a path forward. - EFFICACY. Proposals that present data, measurements, or analysis that suggests different techniques, paradigms, languages, libraries, concepts, or approaches have different efficacies for given specified metrics, which provide actionable takeaways to practicing functional and logic programmers. - OFF-TOPIC. Proposals that have appeal to a mainstream developer audience (the number of off-topic proposals we accept is small, but we do accept some, especially for keynotes). ## SESSION TYPES LambdaConf accepts proposals for the following types of sessions: - LEAP WORKSHOPS (6h). Leap Workshops are approximately 6 hours in length. They are in-depth, hands-on workshops designed to teach mainstream functional programming topics in enough detail, attendees can immediately apply what they learn in their jobs. We require that speakers follow our recommended format for Leap Workshops, although we allow exceptions for experienced teachers. - HOP WORKSHOPS (2h). Hop Workshops are 2 hours in length. Like Leap Workshops, these workshops are in-depth and hands-on, but they cover reduced content and may be specialized to topics that may not have mainstream appeal. We require that speakers follow our recommended format for Hop Workshops, although we allow exceptions for experienced teachers. - DE NOVO SESSIONS (50m). De Novo Sessions are 50 minutes in length. These sessions are designed to present original work from industry and academia. While the requirements for proposals are more rigorous, there is less competition for De Novo slots. - EDUCATIONAL SESSIONS (50m). Educational Sessions are 50 minutes in length. These sessions are designed to clearly and concisely teach one useful concept, skill, aspect, library, or language to attendees. - KEYNOTES (40m). Keynotes are 40 minutes in length, and are presented before all attendees (there are no other sessions concurrent with keynotes). Keynotes are designed to offer thought-provoking, opinionated, and insightful commentary on topics of interest to the community. If you are accepted for a specific type of proposal (e.g. Educational), we cannot guarantee that you will get a slot of this type. Based on scheduling requirements, feedback from the committee, or feedback from your speaker coach, we may require you to change the format of your session. Regards, -- John A. De Goes john at degoes.net Follow me on Twitter @jdegoes From Graham.Hutton at nottingham.ac.uk Wed Jan 9 11:06:28 2019 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Wed, 9 Jan 2019 11:06:28 +0000 Subject: [Haskell-cafe] Call for papers, MPC 2019, Portugal Message-ID: <9AA3F6E8-6E57-4E0B-940E-94F158CC9F1D@exmail.nottingham.ac.uk> Dear all, The next Mathematics of Program Construction (MPC) conference will be held in Portugal in October 2019, co-located with the Symposium on Formal Methods (FM). Paper submission is 3rd May 2019. Please share, and submit your best papers! Best wishes, Graham Hutton Program Chair, MPC 2019 ====================================================================== *** CALL FOR PAPERS -- MPC 2019 *** 13th International Conference on Mathematics of Program Construction 7-9 October 2019, Porto, Portugal Co-located with Formal Methods 2019 https://tinyurl.com/MPC-Porto ====================================================================== TIMELINE: Abstract submission 26th April 2019 Paper submission 3rd May 2019 Author notification 14th June 2019 Camera ready copy 12th July 2019 Conference 7-9 October 2019 BACKGROUND: The International Conference on Mathematics of Program Construction (MPC) aims to promote the development of mathematical principles and techniques that are demonstrably practical and effective in the process of constructing computer programs. MPC 2019 will be held in Porto, Portugal from 7-9 October 2019, and is co-located with the International Symposium on Formal Methods, FM 2019. Previous conferences were held in Königswinter, Germany (2015); Madrid, Spain (2012); Québec City, Canada (2010); Marseille, France (2008); Kuressaare, Estonia (2006); Stirling, UK (2004); Dagstuhl, Germany (2002); Ponte de Lima, Portugal (2000); Marstrand, Sweden (1998); Kloster Irsee, Germany (1995); Oxford, UK (1992); Twente, The Netherlands (1989). SCOPE: MPC seeks original papers on mathematical methods and tools put to use in program construction. Topics of interest range from algorithmics to support for program construction in programming languages and systems. Typical areas include type systems, program analysis and transformation, programming language semantics, security, and program logics. The notion of a 'program' is interpreted broadly, ranging from algorithms to hardware. Theoretical contributions are welcome, provided that their relevance to program construction is clear. Reports on applications are welcome, provided that their mathematical basis is evident. We also encourage the submission of 'programming pearls' that present elegant and instructive examples of the mathematics of program construction. SUBMISSION: Submission is in two stages. Abstracts (plain text, maximum 250 words) must be submitted by 26th April 2019. Full papers (pdf, formatted using the llncs.sty style file for LaTex) must be submitted by 3rd May 2019. There is no prescribed page limit, but authors should strive for brevity. Both abstracts and papers will be submitted using EasyChair. Papers must present previously unpublished work, and not be submitted concurrently to any other publication venue. Submissions will be evaluated by the program committee according to their relevance, correctness, significance, originality, and clarity. Each submission should explain its contributions in both general and technical terms, clearly identifying what has been accomplished, explaining why it is significant, and comparing it with previous work. Accepted papers must be presented in person at the conference by one of the authors. The proceedings of MPC 2019 will be published in the Lecture Notes in Computer Science (LNCS) series, as with all previous instances of the conference. Authors of accepted papers will be expected to transfer copyright to Springer for this purpose. After the conference, authors of the best papers from MPC 2019 and MPC 2015 will be invited to submit revised versions to a special issue of Science of Computer Programming (SCP). For any queries about submission please contact the program chair, Graham Hutton . KEYNOTE SPEAKERS: Assia Mahboubi INRIA, France Annabelle McIver Macquarie University, Australia PROGRAM COMMITTEE: Patrick Bahr IT University of Copenhagen, Denmark Richard Bird University of Oxford, UK Corina Cîrstea University of Southampton, UK Brijesh Dongol University of Surrey, UK João F. Ferreira University of Lisbon, Portugal Jennifer Hackett University of Nottingham, UK William Harrison University of Missouri, USA Ralf Hinze University of Kaiserslautern, Germany Zhenjiang Hu National Institute of Informatics, Japan Graham Hutton (chair) University of Nottingham, UK Cezar Ionescu University of Oxford, UK Mauro Jaskelioff National University of Rosario, Argentina Ranjit Jhala University of California, USA Gabriele Keller Utrecht University, The Netherlands Ekaterina Komendantskaya Heriot-Watt University, UK Chris Martens North Carolina State University, USA Bernhard Möller University of Augsburg, Germany Shin-Cheng Mu Academia Sinica, Taiwan Mary Sheeran Chalmers University of Technology, Sweden Alexandra Silva University College London, UK Georg Struth University of Sheffield, UK CONFERENE VENUE: The conference will be held at the Alfândega Porto Congress Centre, a 150 year old former custom's house located in the historic centre of Porto on the bank of the river Douro. The venue was renovated by a Pritzer prize winning architect and has received many awards. LOCAL ORGANISERS: José Nuno Oliveira University of Minho, Portugal For any queries about local issues please contact the local organiser, José Nuno Oliveira . ====================================================================== 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 icfp.publicity at googlemail.com Thu Jan 10 01:50:43 2019 From: icfp.publicity at googlemail.com (Sam Tobin-Hochstadt) Date: Wed, 09 Jan 2019 20:50:43 -0500 Subject: [Haskell-cafe] Second Call for Papers: PACMPL issue ICFP 2019 Message-ID: <5c36a4f327627_64534650dc193f3@hermes.mail> PACMPL Volume 3, Issue ICFP 2019 Call for Papers accepted papers to be invited for presentation at The 24th ACM SIGPLAN International Conference on Functional Programming Berlin, Germany http://icfp19.sigplan.org/ ### Important dates Submissions due: 1 March 2019 (Friday) Anywhere on Earth https://icfp19.hotcrp.com Author response: 16 April (Tuesday) - 18 Apri (Friday) 14:00 UTC Notification: 3 May (Friday) Final copy due: 22 June (Saturday) Conference: 18 August (Sunday) - 23 August (Friday) ### About PACMPL Proceedings of the ACM on Programming Languages (PACMPL ) is a Gold Open Access journal publishing research on all aspects of programming languages, from design to implementation and from mathematical formalisms to empirical studies. Each issue of the journal is devoted to a particular subject area within programming languages and will be announced through publicized Calls for Papers, like this one. ### Scope [PACMPL](https://pacmpl.acm.org/) issue ICFP 2019 seeks original papers on the art and science of functional programming. Submissions are invited on all topics from principles to practice, from foundations to features, and from abstraction to application. The scope includes all languages that encourage functional programming, including both purely applicative and imperative languages, as well as languages with objects, concurrency, or parallelism. Topics of interest include (but are not limited to): * *Language Design*: concurrency, parallelism, and distribution; modules; components and composition; metaprogramming; type systems; interoperability; domain-specific languages; and relations to imperative, object-oriented, or logic programming. * *Implementation*: abstract machines; virtual machines; interpretation; compilation; compile-time and run-time optimization; garbage collection and memory management; multi-threading; exploiting parallel hardware; interfaces to foreign functions, services, components, or low-level machine resources. * *Software-Development Techniques*: algorithms and data structures; design patterns; specification; verification; validation; proof assistants; debugging; testing; tracing; profiling. * *Foundations*: formal semantics; lambda calculus; rewriting; type theory; monads; continuations; control; state; effects; program verification; dependent types. * *Analysis and Transformation*: control-flow; data-flow; abstract interpretation; partial evaluation; program calculation. * *Applications*: symbolic computing; formal-methods tools; artificial intelligence; systems programming; distributed-systems and web programming; hardware design; databases; XML processing; scientific and numerical computing; graphical user interfaces; multimedia and 3D graphics programming; scripting; system administration; security. * *Education*: teaching introductory programming; parallel programming; mathematical proof; algebra. Submissions will be evaluated according to their relevance, correctness, significance, originality, and clarity. Each submission should explain its contributions in both general and technical terms, clearly identifying what has been accomplished, explaining why it is significant, and comparing it with previous work. The technical content should be accessible to a broad audience. PACMPL issue ICFP 2019 also welcomes submissions in two separate categories — Functional Pearls and Experience Reports — that must be marked as such at the time of submission and that need not report original research results. Detailed guidelines on both categories are given at the end of this call. Please contact the principal editor if you have questions or are concerned about the appropriateness of a topic. ### Preparation of submissions **Deadline**: The deadline for submissions is **Friday, March 1, 2019**, Anywhere on Earth (). This deadline will be strictly enforced. **Formatting**: Submissions must be in PDF format, printable in black and white on US Letter sized paper, and interpretable by common PDF tools. All submissions must adhere to the "ACM Small" template that is available (in both LaTeX and Word formats) from . For authors using LaTeX, a lighter-weight package, including only the essential files, is available from . There is a limit of **25 pages for a full paper or Functional Pearl** and **12 pages for an Experience Report**; in either case, the bibliography will not be counted against these limits. Submissions that exceed the page limits or, for other reasons, do not meet the requirements for formatting, will be summarily rejected. Supplementary material can and should be **separately** submitted (see below). See also PACMPL's Information and Guidelines for Authors at . **Submission**: Submissions will be accepted at Improved versions of a paper may be submitted at any point before the submission deadline using the same web interface. **Author Response Period**: Authors will have a 72-hour period, starting at 14:00 UTC on **Tuesday, April 16, 2019**, to read reviews and respond to them. **Supplementary Material**: Authors have the option to attach supplementary material to a submission, on the understanding that reviewers may choose not to look at it. This supplementary material should **not** be submitted as part of the main document; instead, it should be uploaded as a **separate** PDF document or tarball. Supplementary material should be uploaded **at submission time**, not by providing a URL in the paper that points to an external repository. Authors are free to upload both anonymized and non-anonymized supplementary material. Anonymized supplementary material will be visible to reviewers immediately; non-anonymized supplementary material will be revealed to reviewers only after they have submitted their review of the paper and learned the identity of the author(s). **Authorship Policies**: All submissions are expected to comply with the ACM Policies for Authorship that are detailed at . **Republication Policies**: Each submission must adhere to SIGPLAN's republication policy, as explained on the web at . **Resubmitted Papers**: Authors who submit a revised version of a paper that has previously been rejected by another conference have the option to attach an annotated copy of the reviews of their previous submission(s), explaining how they have addressed these previous reviews in the present submission. If a reviewer identifies him/herself as a reviewer of this previous submission and wishes to see how his/her comments have been addressed, the principal editor will communicate to this reviewer the annotated copy of his/her previous review. Otherwise, no reviewer will read the annotated copies of the previous reviews. ### Review Process This section outlines the two-stage process with lightweight double-blind reviewing that will be used to select papers for PACMPL issue ICFP 2019. We anticipate that there will be a need to clarify and expand on this process, and we will maintain a list of frequently asked questions and answers on the conference website to address common concerns. **PACMPL issue ICFP 2019 will employ a two-stage review process.** The first stage in the review process will assess submitted papers using the criteria stated above and will allow for feedback and input on initial reviews through the author response period mentioned previously. At the review meeting, a set of papers will be conditionally accepted and all other papers will be rejected. Authors will be notified of these decisions on **May 3, 2019**. Authors of conditionally accepted papers will be provided with committee reviews (just as in previous conferences) along with a set of mandatory revisions. After four weeks (May 31, 2019), the authors will provide a second submission. The second and final reviewing phase assesses whether the mandatory revisions have been adequately addressed by the authors and thereby determines the final accept/reject status of the paper. The intent and expectation is that the mandatory revisions can be addressed within four weeks and hence that conditionally accepted papers will in general be accepted in the second phase. The second submission should clearly identify how the mandatory revisions were addressed. To that end, the second submission must be accompanied by a cover letter mapping each mandatory revision request to specific parts of the paper. The cover letter will facilitate a quick second review, allowing for confirmation of final acceptance within two weeks. Conversely, the absence of a cover letter will be grounds for the paper’s rejection. **PACMPL issue ICFP 2019 will employ a lightweight double-blind reviewing process.** To facilitate this, submitted papers must adhere to two rules: 1. **author names and institutions must be omitted**, and 2. **references to authors' own related work should be in the third person** (e.g., not "We build on our previous work ..." but rather "We build on the work of ..."). The purpose of this process is to help the reviewers come to an initial judgement about the paper without bias, not to make it impossible for them to discover the authors if they were to try. Nothing should be done in the name of anonymity that weakens the submission or makes the job of reviewing the paper more difficult (e.g., important background references should not be omitted or anonymized). In addition, authors should feel free to disseminate their ideas or draft versions of their paper as they normally would. For instance, authors may post drafts of their papers on the web or give talks on their research ideas. ### Information for Authors of Accepted Papers * As a condition of acceptance, final versions of all papers must adhere to the new ACM Small format. The page limit for the final versions of papers will be increased by two pages to help authors respond to reviewer comments and mandatory revisions: **27 pages plus bibliography for a regular paper or Functional Pearl, 14 pages plus bibliography for an Experience Report**. * Authors of accepted submissions will be required to agree to one of the three ACM licensing options: open access on payment of a fee (**recommended**, and SIGPLAN can cover the cost as described next); copyright transfer to ACM; or retaining copyright but granting ACM exclusive publication rights. Further information about ACM author rights is available from . * PACMPL is a Gold Open Access journal. It will be archived in ACM’s Digital Library, but no membership or fee is required for access. Gold Open Access has been made possible by generous funding through ACM SIGPLAN, which will cover all open access costs in the event authors cannot. Authors who can cover the costs may do so by paying an Article Processing Charge (APC). PACMPL, SIGPLAN, and ACM Headquarters are committed to exploring routes to making Gold Open Access publication both affordable and sustainable. * ACM offers authors a range of copyright options, one of which is Creative Commons CC-BY publication; this is the option recommended by the PACMPL editorial board. A reasoned argument in favour of this option can be found in the article [Why CC-BY?](https://oaspa.org/why-cc-by/) published by OASPA, the Open Access Scholarly Publishers Association. * We intend that the papers will be freely available for download from the ACM Digital Library in perpetuity via the OpenTOC mechanism. * ACM Author-Izer is a unique service that enables ACM authors to generate and post links on either their home page or institutional repository for visitors to download the definitive version of their articles from the ACM Digital Library at no charge. Downloads through Author-Izer links are captured in official ACM statistics, improving the accuracy of usage and impact measurements. Consistently linking to the definitive version of an ACM article should reduce user confusion over article versioning. After an article has been published and assigned to the appropriate ACM Author Profile pages, authors should visit to learn how to create links for free downloads from the ACM DL. * At least one author of each accepted submissions will be expected to attend and present their paper at the conference. The schedule for presentations will be determined and shared with authors after the full program has been selected. Presentations will be videotaped and released online if the presenter consents. * The official publication date is the date the papers are made available in the ACM Digital Library. This date may be up to *two weeks prior* to the first day of the conference. The official publication date affects the deadline for any patent filings related to published work. ### Artifact Evaluation Authors of papers that are conditionally accepted in the first phase of the review process will be encouraged (but not required) to submit supporting materials for Artifact Evaluation. These items will then be reviewed by an Artifact Evaluation Committee, separate from the paper Review Committee, whose task is to assess how the artifacts support the work described in the associated paper. Papers that go through the Artifact Evaluation process successfully will receive a seal of approval printed on the papers themselves. Authors of accepted papers will be encouraged to make the supporting materials publicly available upon publication of the papers, for example, by including them as "source materials" in the ACM Digital Library. An additional seal will mark papers whose artifacts are made available, as outlined in the ACM guidelines for artifact badging. Participation in Artifact Evaluation is voluntary and will not influence the final decision regarding paper acceptance. ### Special categories of papers In addition to research papers, PACMPL issue ICFP solicits two kinds of papers that do not require original research contributions: Functional Pearls, which are full papers, and Experience Reports, which are limited to half the length of a full paper. Authors submitting such papers should consider the following guidelines. #### Functional Pearls A Functional Pearl is an elegant essay about something related to functional programming. Examples include, but are not limited to: * a new and thought-provoking way of looking at an old idea * an instructive example of program calculation or proof * a nifty presentation of an old or new data structure * an interesting application of functional programming techniques * a novel use or exposition of functional programming in the classroom While pearls often demonstrate an idea through the development of a short program, there is no requirement or expectation that they do so. Thus, they encompass the notions of theoretical and educational pearls. Functional Pearls are valued as highly and judged as rigorously as ordinary papers, but using somewhat different criteria. In particular, a pearl is not required to report original research, but, it should be concise, instructive, and entertaining. A pearl is likely to be rejected if its readers get bored, if the material gets too complicated, if too much specialized knowledge is needed, or if the writing is inelegant. The key to writing a good pearl is polishing. A submission that is intended to be treated as a pearl must be marked as such on the submission web page, and should contain the words "Functional Pearl" somewhere in its title or subtitle. These steps will alert reviewers to use the appropriate evaluation criteria. Pearls will be combined with ordinary papers, however, for the purpose of computing the conference's acceptance rate. #### Experience Reports The purpose of an Experience Report is to help create a body of published, refereed, citable evidence that functional programming really works — or to describe what obstacles prevent it from working. Possible topics for an Experience Report include, but are not limited to: * insights gained from real-world projects using functional programming * comparison of functional programming with conventional programming in the context of an industrial project or a university curriculum * project-management, business, or legal issues encountered when using functional programming in a real-world project * curricular issues encountered when using functional programming in education * real-world constraints that created special challenges for an implementation of a functional language or for functional programming in general An Experience Report is distinguished from a normal PACMPL issue ICFP paper by its title, by its length, and by the criteria used to evaluate it. * Both in the papers and in any citations, the title of each accepted Experience Report must end with the words "(Experience Report)" in parentheses. The acceptance rate for Experience Reports will be computed and reported separately from the rate for ordinary papers. * Experience Report submissions can be at most 12 pages long, excluding bibliography. * Each accepted Experience Report will be presented at the conference, but depending on the number of Experience Reports and regular papers accepted, authors of Experience reports may be asked to give shorter talks. * Because the purpose of Experience Reports is to enable our community to accumulate a body of evidence about the efficacy of functional programming, an acceptable Experience Report need not add to the body of knowledge of the functional-programming community by presenting novel results or conclusions. It is sufficient if the Report states a clear thesis and provides supporting evidence. The thesis must be relevant to ICFP, but it need not be novel. The review committee will accept or reject Experience Reports based on whether they judge the evidence to be convincing. Anecdotal evidence will be acceptable provided it is well argued and the author explains what efforts were made to gather as much evidence as possible. Typically, more convincing evidence is obtained from papers which show how functional programming was used than from papers which only say that functional programming was used. The most convincing evidence often includes comparisons of situations before and after the introduction or discontinuation of functional programming. Evidence drawn from a single person's experience may be sufficient, but more weight will be given to evidence drawn from the experience of groups of people. An Experience Report should be short and to the point: it should make a claim about how well functional programming worked on a particular project and why, and produce evidence to substantiate this claim. If functional programming worked in this case in the same ways it has worked for others, the paper need only summarize the results — the main part of the paper should discuss how well it worked and in what context. Most readers will not want to know all the details of the project and its implementation, but the paper should characterize the project and its context well enough so that readers can judge to what degree this experience is relevant to their own projects. The paper should take care to highlight any unusual aspects of the project. Specifics about the project are more valuable than generalities about functional programming; for example, it is more valuable to say that the team delivered its software a month ahead of schedule than it is to say that functional programming made the team more productive. If the paper not only describes experience but also presents new technical results, or if the experience refutes cherished beliefs of the functional-programming community, it may be better to submit it as a full paper, which will be judged by the usual criteria of novelty, originality, and relevance. The principal editor will be happy to advise on any concerns about which category to submit to. ### ICFP Organizers General Chair: Derek Dreyer (MPI-SWS, Germany) Artifact Evaluation Co-Chairs: Simon Marlow (Facebook, UK) Industrial Relations Chair: Alan Jeffrey (Mozilla Research, USA) Programming Contest Organiser: Ilya Sergey (Yale-NUS College, Singapore) Publicity and Web Chair: Sam Tobin-Hochstadt (Indiana University, USA) Student Research Competition Chair: William J. Bowman (University of British Columbia, Canada) Workshops Co-Chair: Christophe Scholliers (Universiteit Gent, Belgium) Jennifer Hackett (University of Nottingham, UK) Conference Manager: Annabel Satin (P.C.K.) ### PACMPL Volume 3, Issue ICFP 2019 Principal Editor: François Pottier (Inria, France) Review Committee: Lennart Beringer (Princeton University, United States) Joachim Breitner (DFINITY Foundation, Germany) Laura M. Castro (University of A Coruña, Spain) Ezgi Çiçek (Facebook London, United Kingdom) Pierre-Evariste Dagand (LIP6/CNRS, France) Christos Dimoulas (Northwestern University, United States) Jacques-Henri Jourdan (CNRS, LRI, Université Paris-Sud, France) Andrew Kennedy (Facebook London, United Kingdom) Daan Leijen (Microsoft Research, United States) Kazutaka Matsuda (Tohoku University, Japan) Bruno C. d. S. Oliveira (University of Hong Kong, China) Klaus Ostermann (University of Tübingen, Germany) Jennifer Paykin (Galois, United States) Frank Pfenning (Carnegie Mellon University, USA) Mike Rainey (Indiana University, USA) Chung-chieh Shan (Indiana University, USA) Sam Staton (University of Oxford, UK) Pierre-Yves Strub (Ecole Polytechnique, France) German Vidal (Universitat Politecnica de Valencia, Spain) External Review Committee: Michael D. Adams (University of Utah, USA) Robert Atkey (University of Strathclyde, IK) Sheng Chen (University of Louisiana at Lafayette, USA) James Cheney (University of Edinburgh, UK) Adam Chlipala (Massachusetts Institute of Technology, USA) Evelyne Contejean (LRI, Université Paris-Sud, France) Germán Andrés Delbianco (IRIF, Université Paris Diderot, France) Dominique Devriese (Vrije Universiteit Brussel, Belgium) Richard A. Eisenberg (Bryn Mawr College, USA) Conal Elliott (Target, USA) Sebastian Erdweg (Delft University of Technology, Netherlands) Michael Greenberg (Pomona College, USA) Adrien Guatto (IRIF, Université Paris Diderot, France) Jennifer Hackett (University of Nottingham, UK) Troels Henriksen (University of Copenhagen, Denmark) Chung-Kil Hur (Seoul National University, Republic of Korea) Roberto Ierusalimschy (PUC-Rio, Brazil) Ranjit Jhala (University of California, San Diego, USA) Ralf Jung (MPI-SWS, Germany) Ohad Kammar (University of Oxford, UK) Oleg Kiselyov (Tohoku University, Japan) Hsiang-Shang ‘Josh’ Ko (National Institute of Informatics, Japan) Ondřej Lhoták (University of Waterloo, Canada) Dan Licata (Wesleyan University, USA) Geoffrey Mainland (Drexel University, USA) Simon Marlow (Facebook, UK) Akimasa Morihata (University of Tokyo, Japan) Shin-Cheng Mu (Academia Sinica, Taiwan) Guillaume Munch-Maccagnoni (Inria, France) Kim Nguyễn (University of Paris-Sud, France) Ulf Norell (Gothenburg University, Sweden) Atsushi Ohori (Tohoku University, Japan) Rex Page (University of Oklahoma, USA) Zoe Paraskevopoulou (Princeton University, USA) Nadia Polikarpova (University of California, San Diego, USA) Jonathan Protzenko (Microsoft Research, USA) Tiark Rompf (Purdue University, USA) Andreas Rossberg (Dfinity, Germany) KC Sivaramakrishnan (University of Cambridge, UI) Nicholas Smallbone (Chalmers University of Technology, Sweden) Matthieu Sozeau (Inria, France) Sandro Stucki (Chalmers | University of Gothenburg, Sweden) Don Syme (Microsoft, UK) Zachary Tatlock (University of Washington, USA) Sam Tobin-Hochstadt (Indiana University, USA) Takeshi Tsukada (University of Tokyo, Japan) Tarmo Uustalu (Reykjavik University, Iceland) Benoit Valiron (LRI, CentraleSupelec, Univ. Paris Saclay, France) Daniel Winograd-Cort (University of Pennsylvania, USA) Nicolas Wu (University of Bristol, UK) From mattei at oca.eu Thu Jan 10 11:34:04 2019 From: mattei at oca.eu (Damien Mattei) Date: Thu, 10 Jan 2019 12:34:04 +0100 Subject: [Haskell-cafe] overloading functions Message-ID: <5C372DAC.2040809@oca.eu> Hi, i have this definition: {-# LANGUAGE FlexibleInstances #-} class ConcatenateMaybeString a where cms :: Maybe String -> a -> Maybe String instance ConcatenateMaybeString (Maybe String) where cms mf ms = mf >>= (\f -> ms >>= (\s -> return (f ++ s))) instance ConcatenateMaybeString String where cms mf s = mf >>= (\f -> return (f ++ s)) when i use it on : f `cms` ("." ::String) `cms` s it works but not on this: f `cms` "." `cms` s "." is too ambigious to compile: *Main> :load UpdateSidonie [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) UpdateSidonie.hs:373:43: error: • Ambiguous type variable ‘a0’ arising from a use of ‘cms’ prevents the constraint ‘(ConcatenateMaybeString a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance ConcatenateMaybeString (Maybe String) -- Defined at UpdateSidonie.hs:169:11 instance ConcatenateMaybeString String -- Defined at UpdateSidonie.hs:177:11 • In the first argument of ‘cms’, namely ‘f `cms` "."’ In the expression: f `cms` "." `cms` s In the expression: let f = fmap head resBDwords s = fmap (head . tail) resBDwords mp = Just "." :: Maybe String .... in f `cms` "." `cms` s | 373 | in f `cms` "." `cms` s) :: Maybe String | ^^^^^^^^^^^ UpdateSidonie.hs:373:51: error: • Ambiguous type variable ‘a0’ arising from the literal ‘"."’ prevents the constraint ‘(Data.String.IsString a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance Data.String.IsString Query -- Defined in ‘Database.MySQL.Simple.Types’ instance Data.String.IsString Tx.Text -- Defined in ‘Data.Text’ instance (a ~ Char) => Data.String.IsString [a] -- Defined in ‘Data.String’ ...plus six instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the second argument of ‘cms’, namely ‘"."’ In the first argument of ‘cms’, namely ‘f `cms` "."’ In the expression: f `cms` "." `cms` s | 373 | in f `cms` "." `cms` s) :: Maybe String | ^^^ Failed, no modules loaded. Prelude> any idea? Damien From william.fearon at mail.com Thu Jan 10 11:39:44 2019 From: william.fearon at mail.com (William Fearon) Date: Thu, 10 Jan 2019 12:39:44 +0100 Subject: [Haskell-cafe] Second Call for Papers: PACMPL issue ICFP 2019 In-Reply-To: <5c36a4f327627_64534650dc193f3@hermes.mail> References: <5c36a4f327627_64534650dc193f3@hermes.mail> Message-ID: An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Thu Jan 10 12:00:51 2019 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Thu, 10 Jan 2019 20:00:51 +0800 Subject: [Haskell-cafe] overloading functions In-Reply-To: <5C372DAC.2040809@oca.eu> References: <5C372DAC.2040809@oca.eu> Message-ID: On Thu, 10 Jan 2019 at 19:34, Damien Mattei wrote: > Hi, > > i have this definition: > > {-# LANGUAGE FlexibleInstances #-} > > class ConcatenateMaybeString a where > cms :: Maybe String -> a -> Maybe String > > > instance ConcatenateMaybeString (Maybe String) where > cms mf ms = > mf >>= (\f -> > ms >>= (\s -> > return (f ++ s))) > > > > instance ConcatenateMaybeString String where > cms mf s = > mf >>= (\f -> return (f ++ s)) > > when i use it on : > f `cms` ("." ::String) `cms` s > it works > > but not on this: > f `cms` "." `cms` s > > "." is too ambigious to compile: > > *Main> :load UpdateSidonie > [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) > > UpdateSidonie.hs:373:43: error: > • Ambiguous type variable ‘a0’ arising from a use of ‘cms’ > prevents the constraint ‘(ConcatenateMaybeString > a0)’ from being solved. > Probable fix: use a type annotation to specify what ‘a0’ should be. > These potential instances exist: > instance ConcatenateMaybeString (Maybe String) > -- Defined at UpdateSidonie.hs:169:11 > instance ConcatenateMaybeString String > -- Defined at UpdateSidonie.hs:177:11 > • In the first argument of ‘cms’, namely ‘f `cms` "."’ > In the expression: f `cms` "." `cms` s > In the expression: > let > f = fmap head resBDwords > s = fmap (head . tail) resBDwords > mp = Just "." :: Maybe String > .... > in f `cms` "." `cms` s > | > 373 | in f `cms` "." `cms` s) :: > Maybe String > | ^^^^^^^^^^^ > > UpdateSidonie.hs:373:51: error: > • Ambiguous type variable ‘a0’ arising from the literal ‘"."’ > prevents the constraint ‘(Data.String.IsString > a0)’ from being solved. > Probable fix: use a type annotation to specify what ‘a0’ should be. > These potential instances exist: > instance Data.String.IsString Query > -- Defined in ‘Database.MySQL.Simple.Types’ > instance Data.String.IsString Tx.Text -- Defined in ‘Data.Text’ > instance (a ~ Char) => Data.String.IsString [a] > -- Defined in ‘Data.String’ > ...plus six instances involving out-of-scope types > (use -fprint-potential-instances to see them all) > • In the second argument of ‘cms’, namely ‘"."’ > In the first argument of ‘cms’, namely ‘f `cms` "."’ > In the expression: f `cms` "." `cms` s > | > 373 | in f `cms` "." `cms` s) :: > Maybe String > | ^^^ > Failed, no modules loaded. > Prelude> > > > any idea? > Do you have the OverloadedStrings or OverloadedLists LANGUAGE pragmas enabled? > > Damien > > _______________________________________________ > 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. -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From mattei at oca.eu Thu Jan 10 14:15:59 2019 From: mattei at oca.eu (Damien Mattei) Date: Thu, 10 Jan 2019 15:15:59 +0100 Subject: [Haskell-cafe] overloading functions In-Reply-To: References: <5C372DAC.2040809@oca.eu> Message-ID: <5C37539F.8040405@oca.eu> yes for use with the DB (Database.MySQL.Simple.QueryResults) it is necessary. It should be confusing about String for the compiler... Le 10/01/2019 13:00, Ivan Lazar Miljenovic a écrit : > > On Thu, 10 Jan 2019 at 19:34, Damien Mattei > wrote: > > Hi, > > i have this definition: > > {-# LANGUAGE FlexibleInstances #-} > > class ConcatenateMaybeString a where > cms :: Maybe String -> a -> Maybe String > > > instance ConcatenateMaybeString (Maybe String) where > cms mf ms = > mf >>= (\f -> > ms >>= (\s -> > return (f ++ s))) > > > > instance ConcatenateMaybeString String where > cms mf s = > mf >>= (\f -> return (f ++ s)) > > when i use it on : > f `cms` ("." ::String) `cms` s > it works > > but not on this: > f `cms` "." `cms` s > > "." is too ambigious to compile: > > *Main> :load UpdateSidonie > [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) > > UpdateSidonie.hs:373:43: error: > • Ambiguous type variable ‘a0’ arising from a use of ‘cms’ > prevents the constraint ‘(ConcatenateMaybeString > a0)’ from being solved. > Probable fix: use a type annotation to specify what ‘a0’ > should be. > These potential instances exist: > instance ConcatenateMaybeString (Maybe String) > -- Defined at UpdateSidonie.hs:169:11 > instance ConcatenateMaybeString String > -- Defined at UpdateSidonie.hs:177:11 > • In the first argument of ‘cms’, namely ‘f `cms` "."’ > In the expression: f `cms` "." `cms` s > In the expression: > let > f = fmap head resBDwords > s = fmap (head . tail) resBDwords > mp = Just "." :: Maybe String > .... > in f `cms` "." `cms` s > | > 373 | in f `cms` "." `cms` s) :: > Maybe String > | ^^^^^^^^^^^ > > UpdateSidonie.hs:373:51: error: > • Ambiguous type variable ‘a0’ arising from the literal ‘"."’ > prevents the constraint ‘(Data.String.IsString > a0)’ from being solved. > Probable fix: use a type annotation to specify what ‘a0’ > should be. > These potential instances exist: > instance Data.String.IsString Query > -- Defined in ‘Database.MySQL.Simple.Types’ > instance Data.String.IsString Tx.Text -- Defined in ‘Data.Text’ > instance (a ~ Char) => Data.String.IsString [a] > -- Defined in ‘Data.String’ > ...plus six instances involving out-of-scope types > (use -fprint-potential-instances to see them all) > • In the second argument of ‘cms’, namely ‘"."’ > In the first argument of ‘cms’, namely ‘f `cms` "."’ > In the expression: f `cms` "." `cms` s > | > 373 | in f `cms` "." `cms` s) :: > Maybe String > | ^^^ > Failed, no modules loaded. > Prelude> > > > any idea? > > > Do you have the OverloadedStrings or OverloadedLists LANGUAGE pragmas > enabled? > > > > Damien > > _______________________________________________ > 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. > > > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Thu Jan 10 14:27:06 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 10 Jan 2019 14:27:06 +0000 Subject: [Haskell-cafe] overloading functions In-Reply-To: <5C372DAC.2040809@oca.eu> References: <5C372DAC.2040809@oca.eu> Message-ID: <20190110142706.2bp33wbqb4nnkvlv@weber> On Thu, Jan 10, 2019 at 12:34:04PM +0100, Damien Mattei wrote: > i have this definition: > > {-# LANGUAGE FlexibleInstances #-} > > class ConcatenateMaybeString a where > cms :: Maybe String -> a -> Maybe String > > > instance ConcatenateMaybeString (Maybe String) where > cms mf ms = > mf >>= (\f -> > ms >>= (\s -> > return (f ++ s))) > > > > instance ConcatenateMaybeString String where > cms mf s = > mf >>= (\f -> return (f ++ s)) Trying to simulate overloading like this is ultimately going to lead to more frustration than benefit. I strongly suggest you just define two different functions. From mattei at oca.eu Thu Jan 10 15:23:49 2019 From: mattei at oca.eu (Damien Mattei) Date: Thu, 10 Jan 2019 16:23:49 +0100 Subject: [Haskell-cafe] overloading functions In-Reply-To: <20190110142706.2bp33wbqb4nnkvlv@weber> References: <5C372DAC.2040809@oca.eu> <20190110142706.2bp33wbqb4nnkvlv@weber> Message-ID: <5C376385.2040706@oca.eu> Le 10/01/2019 15:27, Tom Ellis a écrit : > On Thu, Jan 10, 2019 at 12:34:04PM +0100, Damien Mattei wrote: >> i have this definition: >> >> {-# LANGUAGE FlexibleInstances #-} >> >> class ConcatenateMaybeString a where >> cms :: Maybe String -> a -> Maybe String >> >> >> instance ConcatenateMaybeString (Maybe String) where >> cms mf ms = >> mf >>= (\f -> >> ms >>= (\s -> >> return (f ++ s))) >> >> >> >> instance ConcatenateMaybeString String where >> cms mf s = >> mf >>= (\f -> return (f ++ s)) > > Trying to simulate overloading like this is ultimately going to lead to more > frustration than benefit. I strongly suggest you just define two different > functions. Hello Tom, those functions could be seen as a "style exercise" , for me,coming from untyped languages such as Scheme or LisP it's Haskell which is a frustration :-) it's not 2 function but more that are necessary because arguments and their corresponding types could be in any order, if i define different functions i will have 3 functions with different names: cms1::String -> Maybe String -> Maybe String cms2::Maybe String -> String -> Maybe String cms3::Maybe String -> Maybe String -> Maybe String i prefer to have a single overloaded operator like this : class ConcatenateMaybeString a b where (+%+) :: a -> b -> Maybe String instance ConcatenateMaybeString (Maybe String) (Maybe String) where (+%+) mf ms = mf >>= (\f -> ms >>= (\s -> return (f ++ s))) instance ConcatenateMaybeString (Maybe String) String where (+%+) mf s = mf >>= (\f -> return (f ++ s)) instance ConcatenateMaybeString String (Maybe String) where (+%+) f ms = ms >>= (\s -> return (f ++ s)) usable like this: f +%+ ("." :: String) +%+ s if i did not need OverloadedStrings i could even simply wrote: f +%+ "." +%+ s From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Thu Jan 10 17:51:51 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 10 Jan 2019 17:51:51 +0000 Subject: [Haskell-cafe] overloading functions In-Reply-To: <5C376385.2040706@oca.eu> References: <5C372DAC.2040809@oca.eu> <20190110142706.2bp33wbqb4nnkvlv@weber> <5C376385.2040706@oca.eu> Message-ID: <20190110175151.ruw3o6lbyxj67v6y@weber> On Thu, Jan 10, 2019 at 04:23:49PM +0100, Damien Mattei wrote: > Le 10/01/2019 15:27, Tom Ellis a écrit : > > On Thu, Jan 10, 2019 at 12:34:04PM +0100, Damien Mattei wrote: > >> i have this definition: > >> > >> {-# LANGUAGE FlexibleInstances #-} > >> > >> class ConcatenateMaybeString a where > >> cms :: Maybe String -> a -> Maybe String > >> > >> > >> instance ConcatenateMaybeString (Maybe String) where > >> cms mf ms = > >> mf >>= (\f -> > >> ms >>= (\s -> > >> return (f ++ s))) > >> > >> > >> > >> instance ConcatenateMaybeString String where > >> cms mf s = > >> mf >>= (\f -> return (f ++ s)) > > > > Trying to simulate overloading like this is ultimately going to lead to more > > frustration than benefit. I strongly suggest you just define two different > > functions. > > those functions could be seen as a "style exercise" , for me,coming from > untyped languages such as Scheme or LisP it's Haskell which is a > frustration :-) I think you're going to get significantly more frustrated with Haskell if you try to learn it like this by yourself rather than by working through some widely approved teaching resource. Of course, how you spend your time is up to you, but if you're frustrated with Haskell then trying to make it up as you go along is only going to worsen the feeling! From william.fearon at mail.com Thu Jan 10 18:24:42 2019 From: william.fearon at mail.com (William Fearon) Date: Thu, 10 Jan 2019 19:24:42 +0100 Subject: [Haskell-cafe] Second Call for Papers: PACMPL issue ICFP 2019 References: <5c36a4f327627_64534650dc193f3@hermes.mail> Message-ID: An HTML attachment was scrubbed... URL: From damien.mattei at gmail.com Thu Jan 10 19:38:23 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Thu, 10 Jan 2019 20:38:23 +0100 Subject: [Haskell-cafe] overloading functions In-Reply-To: <20190110175151.ruw3o6lbyxj67v6y@weber> References: <5C372DAC.2040809@oca.eu> <20190110142706.2bp33wbqb4nnkvlv@weber> <5C376385.2040706@oca.eu> <20190110175151.ruw3o6lbyxj67v6y@weber> Message-ID: i'm not so pessimist,i'm beginning to have fun with haskell...really! about teaching ressource i will be happy to know where i can find them... i only post in haskell cafe when i have not find the answer online (tutorials,stackoverflow,real haskell book etc,etc... in the hunded pages i search i even get a look at Categories for the working Mathematician ) it is only when i have exhausted all the online ressource that i post to the cafe... On Thu, Jan 10, 2019 at 6:52 PM Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > On Thu, Jan 10, 2019 at 04:23:49PM +0100, Damien Mattei wrote: > > Le 10/01/2019 15:27, Tom Ellis a écrit : > > > On Thu, Jan 10, 2019 at 12:34:04PM +0100, Damien Mattei wrote: > > >> i have this definition: > > >> > > >> {-# LANGUAGE FlexibleInstances #-} > > >> > > >> class ConcatenateMaybeString a where > > >> cms :: Maybe String -> a -> Maybe String > > >> > > >> > > >> instance ConcatenateMaybeString (Maybe String) where > > >> cms mf ms = > > >> mf >>= (\f -> > > >> ms >>= (\s -> > > >> return (f ++ s))) > > >> > > >> > > >> > > >> instance ConcatenateMaybeString String where > > >> cms mf s = > > >> mf >>= (\f -> return (f ++ s)) > > > > > > Trying to simulate overloading like this is ultimately going to lead > to more > > > frustration than benefit. I strongly suggest you just define two > different > > > functions. > > > > those functions could be seen as a "style exercise" , for me,coming from > > untyped languages such as Scheme or LisP it's Haskell which is a > > frustration :-) > > I think you're going to get significantly more frustrated with Haskell if > you try to learn it like this by yourself rather than by working through > some widely approved teaching resource. Of course, how you spend your time > is up to you, but if you're frustrated with Haskell then trying to make it > up as you go along is only going to worsen the feeling! > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Jan 10 19:49:55 2019 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 10 Jan 2019 14:49:55 -0500 Subject: [Haskell-cafe] overloading functions In-Reply-To: References: <5C372DAC.2040809@oca.eu> <20190110142706.2bp33wbqb4nnkvlv@weber> <5C376385.2040706@oca.eu> <20190110175151.ruw3o6lbyxj67v6y@weber> Message-ID: Category theory books are almost certainly not what you want to be looking at. Yes, some things in Haskell are inspired by it; but they're entirely usable wthout, and they're all rather simplified compared to the theory. Typeclasses, you might want to start with the Typeclassopedia https://wiki.haskell.org/Typeclassopedia. And understand that it is not general function overloading, and you can get yourself into trouble by trying to treat them as such: types flow "backwards" in Haskell, compared to languages where overloading is common. If all you know about a type is its name, you can't do anything with it. In most OO languages with overloading, you can do anything you want with it and it'll throw an exception if it doesn't support it; in Haskell, the compiler won't let you get away with it at all, it never reaches the point of a runtime exception. Similarly, if you know (Num a), this doesn't mean you can use division; you need to also know (Integral a) to get div, or (Fractional a) to get (/). One thing that follows from how this interacts with typeclasses is return type polymorphism. Consider that maxBound takes no parameters, and decides what to do based on the type it's used at. On Thu, Jan 10, 2019 at 2:38 PM Damien Mattei wrote: > i'm not so pessimist,i'm beginning to have fun with haskell...really! > about teaching ressource i will be happy to know where i can find them... > i only post in haskell cafe when i have not find the answer online > (tutorials,stackoverflow,real haskell book > etc,etc... in the hunded pages i > search i even get a look at Categories for the working Mathematician > ) > it is only when i have exhausted all the online ressource that i post to > the cafe... > > On Thu, Jan 10, 2019 at 6:52 PM Tom Ellis < > tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > >> On Thu, Jan 10, 2019 at 04:23:49PM +0100, Damien Mattei wrote: >> > Le 10/01/2019 15:27, Tom Ellis a écrit : >> > > On Thu, Jan 10, 2019 at 12:34:04PM +0100, Damien Mattei wrote: >> > >> i have this definition: >> > >> >> > >> {-# LANGUAGE FlexibleInstances #-} >> > >> >> > >> class ConcatenateMaybeString a where >> > >> cms :: Maybe String -> a -> Maybe String >> > >> >> > >> >> > >> instance ConcatenateMaybeString (Maybe String) where >> > >> cms mf ms = >> > >> mf >>= (\f -> >> > >> ms >>= (\s -> >> > >> return (f ++ s))) >> > >> >> > >> >> > >> >> > >> instance ConcatenateMaybeString String where >> > >> cms mf s = >> > >> mf >>= (\f -> return (f ++ s)) >> > > >> > > Trying to simulate overloading like this is ultimately going to lead >> to more >> > > frustration than benefit. I strongly suggest you just define two >> different >> > > functions. >> > >> > those functions could be seen as a "style exercise" , for me,coming from >> > untyped languages such as Scheme or LisP it's Haskell which is a >> > frustration :-) >> >> I think you're going to get significantly more frustrated with Haskell if >> you try to learn it like this by yourself rather than by working through >> some widely approved teaching resource. Of course, how you spend your >> time >> is up to you, but if you're frustrated with Haskell then trying to make it >> up as you go along is only going to worsen the feeling! >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From mpevnev at gmail.com Thu Jan 10 23:38:40 2019 From: mpevnev at gmail.com (Michail Pevnev) Date: Fri, 11 Jan 2019 02:38:40 +0300 Subject: [Haskell-cafe] About 'Overloaded functions are not your friend' line in GHC manual Message-ID: <20190110233840.iccbgum5vetdyirn@MishkaPC> Hello everyone. I've been browsing through GHC manual some time ago, mostly to see what extensions there are, and stumbled upon the following paragraph in the 'Advice on: sooner, faster, smaller, thriftier' section, 'faster' subsection: Overloaded functions are not your friend: Haskell’s overloading (using type classes) is elegant, neat, etc., etc., but it is death to performance if left to linger in an inner loop. I don't quite understand the reason behind this. I was under impression that function overloading - existential shenanigans aside - is resolved mostly at compile time. Mostly, because obviously, say, 'show' for an Either still has to examine its argument at runtime and pick appropriate 'show' for one of the inner types. But the same happens for any examination of an Either, really. Does overloading make it worse, and if so, how and why? Or am I completely off track here, and the actual reason is something entirely different? -- Michail. From william.fearon at mail.com Fri Jan 11 11:56:26 2019 From: william.fearon at mail.com (William Fearon) Date: Fri, 11 Jan 2019 12:56:26 +0100 Subject: [Haskell-cafe] Second Call for Papers: PACMPL issue ICFP 2019 Message-ID: An HTML attachment was scrubbed... URL: From william.fearon at mail.com Fri Jan 11 12:07:03 2019 From: william.fearon at mail.com (William Fearon) Date: Fri, 11 Jan 2019 13:07:03 +0100 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals In-Reply-To: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> Message-ID: An HTML attachment was scrubbed... URL: From cdsmith at gmail.com Fri Jan 11 15:51:37 2019 From: cdsmith at gmail.com (Chris Smith) Date: Fri, 11 Jan 2019 10:51:37 -0500 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals In-Reply-To: References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> Message-ID: This might be a good time to reflect on the kind of community we'd like to build and maintain here. I understand there's a lot of history behind LambdaConf and questionable decisions about past speakers, but we can still express opinions in a respectful way. On Fri, Jan 11, 2019 at 7:07 AM William Fearon wrote: > > Johnny Dollar I'm way above your nosegay event. Yay, Yag, Yag. > > > > Dr Fearon > *Sent:* Tuesday, January 08, 2019 at 3:06 PM > *From:* "John A. De Goes" > *To:* Haskell-cafe at haskell.org > *Subject:* [Haskell-cafe] LambdaConf 2019 Call for Proposals > > Dear Haskell Enthusiasts: > > The LambdaConf 2019 Call for Proposals is open, and we warmly welcome > Haskell proposals on topics of interest to aspiring and practicing > functional programmers. Historically, Haskell content accounts for more > than 50% of content across all 5-8 tracks of the event. > > Last year’s speakers included Michael Snoyberg, Dana Scott, Jeremy Siek, > and many others from both industry and academia. > > To submit a proposal for LambdaConf 2019, please visit the following > website: > > https://www.papercall.io/lambdaconf-2019 > > Travel assistance is available, including lodging. > > ## INTRODUCTION > > LambdaConf is the largest interdisciplinary functional programming > conference in the Mountain West, and one of the largest and most respected > functional programming conferences in the world. > > The conference takes place June 5rd - 7th, in Boulder, Colorado, at the > University of Colorado Boulder, and is surrounded by commercial training > opportunities. If you are an educator, a researcher, a speaker, a speaker > coach, or someone aspiring to one of the preceding, then we warmly welcome > you to submit a proposal for LambdaConf 2019. No prior experience is > necessary for most proposals, and we welcome beginner-level content. > > The Call for Proposals closes at the end of January 2019. We recommend > submitting as early as you can to ensure sufficient time for editing. > LambdaConf attracts everyone from the FP-curious to researchers advancing > state-of-the-art; hobbyists, professionals, academics and students. > Material at all levels, including beginner content and very advanced > content, will find an audience at LambdaConf. > > Historically, LambdaConf has enjoyed a large selection of sessions on > statically-typed functional programming, and a smaller selection of > sessions on dynamically-typed functional programming. Some sessions are not > tied to specific programming languages, but rather cover topics in abstract > algebra, category theory, type theory, programming language theory, > functional architecture, and so on, either generically or in a way that > applies across many programming languages. > > ## TOPICS > > LambdaConf looks for sessions in the following areas: > > - LANGUAGES. Proposals that overview or dive into specific features of > functional, math, or logic programming languages (both new and existing), > with the goal of exposing developers to new ideas or helping them master > features of languages they already know. LIBRARIES. Proposals that discuss > libraries that leverage functional or logic programming to help programmers > solve real-world problems. > - CONCEPTS. Proposals that discuss functional programming idioms, > patterns, or abstractions; or concepts from mathematics, logic, and > computer science, all directed at helping developers write software that’s > easier to test, easier to reason about, and easier to change safely. > - APPLICATIONS. Proposals that discuss how functional programming can help > with specific aspects of modern software development, including > scalability, distributed systems, concurrency, data processing, security, > performance, correctness, user-interfaces, machine learning, and big data. > - USE CASES. Proposals that discuss how functional programming enabled a > project or team to thrive, or deliver more business value than possible > with other approaches. > - CHERRY PICKING. Proposals that show how techniques and approaches from > functional programming can be adapted and incorporated into mainstream > development languages and practices, to the benefit of developers using > them. > - CAUTIONARY TALES. Proposals that call attention to difficulties of > functional programming (both as a cautionary tale but also to raise > awareness), especially such proposals that suggest alternatives or a path > forward. > - EFFICACY. Proposals that present data, measurements, or analysis that > suggests different techniques, paradigms, languages, libraries, concepts, > or approaches have different efficacies for given specified metrics, which > provide actionable takeaways to practicing functional and logic programmers. > - OFF-TOPIC. Proposals that have appeal to a mainstream developer audience > (the number of off-topic proposals we accept is small, but we do accept > some, especially for keynotes). > > ## SESSION TYPES > > LambdaConf accepts proposals for the following types of sessions: > > - LEAP WORKSHOPS (6h). Leap Workshops are approximately 6 hours in length. > They are in-depth, hands-on workshops designed to teach mainstream > functional programming topics in enough detail, attendees can immediately > apply what they learn in their jobs. We require that speakers follow our > recommended format for Leap Workshops, although we allow exceptions for > experienced teachers. > - HOP WORKSHOPS (2h). Hop Workshops are 2 hours in length. Like Leap > Workshops, these workshops are in-depth and hands-on, but they cover > reduced content and may be specialized to topics that may not have > mainstream appeal. We require that speakers follow our recommended format > for Hop Workshops, although we allow exceptions for experienced teachers. > - DE NOVO SESSIONS (50m). De Novo Sessions are 50 minutes in length. These > sessions are designed to present original work from industry and academia. > While the requirements for proposals are more rigorous, there is less > competition for De Novo slots. > - EDUCATIONAL SESSIONS (50m). Educational Sessions are 50 minutes in > length. These sessions are designed to clearly and concisely teach one > useful concept, skill, aspect, library, or language to attendees. > - KEYNOTES (40m). Keynotes are 40 minutes in length, and are presented > before all attendees (there are no other sessions concurrent with > keynotes). Keynotes are designed to offer thought-provoking, opinionated, > and insightful commentary on topics of interest to the community. > > If you are accepted for a specific type of proposal (e.g. Educational), we > cannot guarantee that you will get a slot of this type. Based on scheduling > requirements, feedback from the committee, or feedback from your speaker > coach, we may require you to change the format of your session. > > Regards, > -- > John A. De Goes > john at degoes.net > Follow me on Twitter @jdegoes > > > > > > > _______________________________________________ > 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 john at degoes.net Fri Jan 11 16:10:20 2019 From: john at degoes.net (John A. De Goes) Date: Fri, 11 Jan 2019 09:10:20 -0700 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals In-Reply-To: References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> Message-ID: Indeed. While we can all respectfully disagree about whether or not conferences should ban speakers based on their political views, I think we can all agree that homophobic trolling has no place in Haskell Cafe, nor any other professional community. I’m reminded of this: https://mail.haskell.org/pipermail/haskell/2016-September/024995.html Let’s keep things supportive, friendly, and respectful. Regards, -- John A. De Goes john at degoes.net Follow me on Twitter @jdegoes > On Jan 11, 2019, at 8:51 AM, Chris Smith wrote: > > This might be a good time to reflect on the kind of community we'd like to build and maintain here. I understand there's a lot of history behind LambdaConf and questionable decisions about past speakers, but we can still express opinions in a respectful way. > > On Fri, Jan 11, 2019 at 7:07 AM William Fearon > wrote: > > Johnny Dollar I'm way above your nosegay event. Yay, Yag, Yag. > > > > Dr Fearon > Sent: Tuesday, January 08, 2019 at 3:06 PM > From: "John A. De Goes" > > To: Haskell-cafe at haskell.org > Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals > > Dear Haskell Enthusiasts: > > The LambdaConf 2019 Call for Proposals is open, and we warmly welcome Haskell proposals on topics of interest to aspiring and practicing functional programmers. Historically, Haskell content accounts for more than 50% of content across all 5-8 tracks of the event. > > Last year’s speakers included Michael Snoyberg, Dana Scott, Jeremy Siek, and many others from both industry and academia. > > To submit a proposal for LambdaConf 2019, please visit the following website: > > https://www.papercall.io/lambdaconf-2019 > > Travel assistance is available, including lodging. > > ## INTRODUCTION > > LambdaConf is the largest interdisciplinary functional programming conference in the Mountain West, and one of the largest and most respected functional programming conferences in the world. > > The conference takes place June 5rd - 7th, in Boulder, Colorado, at the University of Colorado Boulder, and is surrounded by commercial training opportunities. If you are an educator, a researcher, a speaker, a speaker coach, or someone aspiring to one of the preceding, then we warmly welcome you to submit a proposal for LambdaConf 2019. No prior experience is necessary for most proposals, and we welcome beginner-level content. > > The Call for Proposals closes at the end of January 2019. We recommend submitting as early as you can to ensure sufficient time for editing. LambdaConf attracts everyone from the FP-curious to researchers advancing state-of-the-art; hobbyists, professionals, academics and students. Material at all levels, including beginner content and very advanced content, will find an audience at LambdaConf. > > Historically, LambdaConf has enjoyed a large selection of sessions on statically-typed functional programming, and a smaller selection of sessions on dynamically-typed functional programming. Some sessions are not tied to specific programming languages, but rather cover topics in abstract algebra, category theory, type theory, programming language theory, functional architecture, and so on, either generically or in a way that applies across many programming languages. > > ## TOPICS > > LambdaConf looks for sessions in the following areas: > > - LANGUAGES. Proposals that overview or dive into specific features of functional, math, or logic programming languages (both new and existing), with the goal of exposing developers to new ideas or helping them master features of languages they already know. LIBRARIES. Proposals that discuss libraries that leverage functional or logic programming to help programmers solve real-world problems. > - CONCEPTS. Proposals that discuss functional programming idioms, patterns, or abstractions; or concepts from mathematics, logic, and computer science, all directed at helping developers write software that’s easier to test, easier to reason about, and easier to change safely. > - APPLICATIONS. Proposals that discuss how functional programming can help with specific aspects of modern software development, including scalability, distributed systems, concurrency, data processing, security, performance, correctness, user-interfaces, machine learning, and big data. > - USE CASES. Proposals that discuss how functional programming enabled a project or team to thrive, or deliver more business value than possible with other approaches. > - CHERRY PICKING. Proposals that show how techniques and approaches from functional programming can be adapted and incorporated into mainstream development languages and practices, to the benefit of developers using them. > - CAUTIONARY TALES. Proposals that call attention to difficulties of functional programming (both as a cautionary tale but also to raise awareness), especially such proposals that suggest alternatives or a path forward. > - EFFICACY. Proposals that present data, measurements, or analysis that suggests different techniques, paradigms, languages, libraries, concepts, or approaches have different efficacies for given specified metrics, which provide actionable takeaways to practicing functional and logic programmers. > - OFF-TOPIC. Proposals that have appeal to a mainstream developer audience (the number of off-topic proposals we accept is small, but we do accept some, especially for keynotes). > > ## SESSION TYPES > > LambdaConf accepts proposals for the following types of sessions: > > - LEAP WORKSHOPS (6h). Leap Workshops are approximately 6 hours in length. They are in-depth, hands-on workshops designed to teach mainstream functional programming topics in enough detail, attendees can immediately apply what they learn in their jobs. We require that speakers follow our recommended format for Leap Workshops, although we allow exceptions for experienced teachers. > - HOP WORKSHOPS (2h). Hop Workshops are 2 hours in length. Like Leap Workshops, these workshops are in-depth and hands-on, but they cover reduced content and may be specialized to topics that may not have mainstream appeal. We require that speakers follow our recommended format for Hop Workshops, although we allow exceptions for experienced teachers. > - DE NOVO SESSIONS (50m). De Novo Sessions are 50 minutes in length. These sessions are designed to present original work from industry and academia. While the requirements for proposals are more rigorous, there is less competition for De Novo slots. > - EDUCATIONAL SESSIONS (50m). Educational Sessions are 50 minutes in length. These sessions are designed to clearly and concisely teach one useful concept, skill, aspect, library, or language to attendees. > - KEYNOTES (40m). Keynotes are 40 minutes in length, and are presented before all attendees (there are no other sessions concurrent with keynotes). Keynotes are designed to offer thought-provoking, opinionated, and insightful commentary on topics of interest to the community. > > If you are accepted for a specific type of proposal (e.g. Educational), we cannot guarantee that you will get a slot of this type. Based on scheduling requirements, feedback from the committee, or feedback from your speaker coach, we may require you to change the format of your session. > > Regards, > -- > John A. De Goes > john at degoes.net > Follow me on Twitter @jdegoes > > > > > > > _______________________________________________ > 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 jeremiah at legit.biz Fri Jan 11 16:21:18 2019 From: jeremiah at legit.biz (Jeremiah Peschka) Date: Fri, 11 Jan 2019 08:21:18 -0800 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals In-Reply-To: References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> Message-ID: Two things. 1. This William Fearon account has some history of trolling various conferences, mailing lists, and academics and should probably be removed (see https://www.quora.com/Who-is-Dr-William-Fearon-and-why-does-he-keep-emailing-me-grandiose-claims-about-his-position-in-academia) 2. At the risk of going off topic, nosegay is not a homophobic word and refers to a bunch of sweet smelling flowers. Admittedly, the sentence makes zero sense in this context, but there you have it. Jeremiah Peschka On Jan 11, 2019, 08:11 -0800, John A. De Goes , wrote: > > Indeed. While we can all respectfully disagree about whether or not conferences should ban speakers based on their political views, I think we can all agree that homophobic trolling has no place in Haskell Cafe, nor any other professional community. > > I’m reminded of this: > >    https://mail.haskell.org/pipermail/haskell/2016-September/024995.html > > Let’s keep things supportive, friendly, and respectful. > > Regards, > -- > John A. De Goes > john at degoes.net > Follow me on Twitter @jdegoes > > > > > > > > On Jan 11, 2019, at 8:51 AM, Chris Smith wrote: > > > > This might be a good time to reflect on the kind of community we'd like to build and maintain here.  I understand there's a lot of history behind LambdaConf and questionable decisions about past speakers, but we can still express opinions in a respectful way. > > > > > On Fri, Jan 11, 2019 at 7:07 AM William Fearon wrote: > > > > > > > > Johnny Dollar I'm way above your nosegay event. Yay, Yag, Yag. > > > > > > > > > > > > > > > > Dr Fearon > > > > Sent: Tuesday, January 08, 2019 at 3:06 PM > > > > From: "John A. De Goes" > > > > To: Haskell-cafe at haskell.org > > > > Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals > > > > > > > > Dear Haskell Enthusiasts: > > > > > > > > The LambdaConf 2019 Call for Proposals is open, and we warmly welcome Haskell proposals on topics of interest to aspiring and practicing functional programmers. Historically, Haskell content accounts for more than 50% of content across all 5-8 tracks of the event. > > > > > > > > Last year’s speakers included Michael Snoyberg, Dana Scott, Jeremy Siek, and many others from both industry and academia. > > > > > > > > To submit a proposal for LambdaConf 2019, please visit the following website: > > > > > > > > https://www.papercall.io/lambdaconf-2019 > > > > > > > > Travel assistance is available, including lodging. > > > > > > > > ## INTRODUCTION > > > > > > > > LambdaConf is the largest interdisciplinary functional programming conference in the Mountain West, and one of the largest and most respected functional programming conferences in the world. > > > > > > > > The conference takes place June 5rd - 7th, in Boulder, Colorado, at the University of Colorado Boulder, and is surrounded by commercial training opportunities. If you are an educator, a researcher, a speaker, a speaker coach, or someone aspiring to one of the preceding, then we warmly welcome you to submit a proposal for LambdaConf 2019. No prior experience is necessary for most proposals, and we welcome beginner-level content. > > > > > > > > The Call for Proposals closes at the end of January 2019. We recommend submitting as early as you can to ensure sufficient time for editing. LambdaConf attracts everyone from the FP-curious to researchers advancing state-of-the-art; hobbyists, professionals, academics and students. Material at all levels, including beginner content and very advanced content, will find an audience at LambdaConf. > > > > > > > > Historically, LambdaConf has enjoyed a large selection of sessions on statically-typed functional programming, and a smaller selection of sessions on dynamically-typed functional programming. Some sessions are not tied to specific programming languages, but rather cover topics in abstract algebra, category theory, type theory, programming language theory, functional architecture, and so on, either generically or in a way that applies across many programming languages. > > > > > > > > ## TOPICS > > > > > > > > LambdaConf looks for sessions in the following areas: > > > > > > > > - LANGUAGES. Proposals that overview or dive into specific features of functional, math, or logic programming languages (both new and existing), with the goal of exposing developers to new ideas or helping them master features of languages they already know. LIBRARIES. Proposals that discuss libraries that leverage functional or logic programming to help programmers solve real-world problems. > > > > - CONCEPTS. Proposals that discuss functional programming idioms, patterns, or abstractions; or concepts from mathematics, logic, and computer science, all directed at helping developers write software that’s easier to test, easier to reason about, and easier to change safely. > > > > - APPLICATIONS. Proposals that discuss how functional programming can help with specific aspects of modern software development, including scalability, distributed systems, concurrency, data processing, security, performance, correctness, user-interfaces, machine learning, and big data. > > > > - USE CASES. Proposals that discuss how functional programming enabled a project or team to thrive, or deliver more business value than possible with other approaches. > > > > - CHERRY PICKING. Proposals that show how techniques and approaches from functional programming can be adapted and incorporated into mainstream development languages and practices, to the benefit of developers using them. > > > > - CAUTIONARY TALES. Proposals that call attention to difficulties of functional programming (both as a cautionary tale but also to raise awareness), especially such proposals that suggest alternatives or a path forward. > > > > - EFFICACY. Proposals that present data, measurements, or analysis that suggests different techniques, paradigms, languages, libraries, concepts, or approaches have different efficacies for given specified metrics, which provide actionable takeaways to practicing functional and logic programmers. > > > > - OFF-TOPIC. Proposals that have appeal to a mainstream developer audience (the number of off-topic proposals we accept is small, but we do accept some, especially for keynotes). > > > > > > > > ## SESSION TYPES > > > > > > > > LambdaConf accepts proposals for the following types of sessions: > > > > > > > > - LEAP WORKSHOPS (6h). Leap Workshops are approximately 6 hours in length. They are in-depth, hands-on workshops designed to teach mainstream functional programming topics in enough detail, attendees can immediately apply what they learn in their jobs. We require that speakers follow our recommended format for Leap Workshops, although we allow exceptions for experienced teachers. > > > > - HOP WORKSHOPS (2h). Hop Workshops are 2 hours in length. Like Leap Workshops, these workshops are in-depth and hands-on, but they cover reduced content and may be specialized to topics that may not have mainstream appeal. We require that speakers follow our recommended format for Hop Workshops, although we allow exceptions for experienced teachers. > > > > - DE NOVO SESSIONS (50m). De Novo Sessions are 50 minutes in length. These sessions are designed to present original work from industry and academia. While the requirements for proposals are more rigorous, there is less competition for De Novo slots. > > > > - EDUCATIONAL SESSIONS (50m). Educational Sessions are 50 minutes in length. These sessions are designed to clearly and concisely teach one useful concept, skill, aspect, library, or language to attendees. > > > > - KEYNOTES (40m). Keynotes are 40 minutes in length, and are presented before all attendees (there are no other sessions concurrent with keynotes). Keynotes are designed to offer thought-provoking, opinionated, and insightful commentary on topics of interest to the community. > > > > > > > > If you are accepted for a specific type of proposal (e.g. Educational), we cannot guarantee that you will get a slot of this type. Based on scheduling requirements, feedback from the committee, or feedback from your speaker coach, we may require you to change the format of your session. > > > > > > > > Regards, > > > > -- > > > > John A. De Goes > > > > john at degoes.net > > > > Follow me on Twitter @jdegoes > > > > > > > > > > > > > > > > > > > > > > > > > > > > _______________________________________________ > > > > Haskell-Cafe mailing list > > > > To (un)subscribe, modify options or view archives go to: > > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > Only members subscribed via the mailman list are allowed to post. > > > > _______________________________________________ > > > > Haskell-Cafe mailing list > > > > To (un)subscribe, modify options or view archives go to: > > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Fri Jan 11 16:36:44 2019 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 11 Jan 2019 11:36:44 -0500 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals In-Reply-To: References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> Message-ID: Actually it's belittling: merely a nosegay, not a full bouquet. (Or to switch idioms, appetizer instead of a meal.) But yes, this Fearon person has been rather actively trolling the channel of late; I have him filtered as a result. On Fri, Jan 11, 2019 at 11:21 AM Jeremiah Peschka wrote: > Two things. > > 1. This William Fearon account has some history of trolling various > conferences, mailing lists, and academics and should probably be removed > (see > https://www.quora.com/Who-is-Dr-William-Fearon-and-why-does-he-keep-emailing-me-grandiose-claims-about-his-position-in-academia > ) > > 2. At the risk of going off topic, nosegay is not a homophobic word and > refers to a bunch of sweet smelling flowers. Admittedly, the sentence makes > zero sense in this context, but there you have it. > > Jeremiah Peschka > On Jan 11, 2019, 08:11 -0800, John A. De Goes , wrote: > > > Indeed. While we can all respectfully disagree about whether or not > conferences should ban speakers based on their political views, I think we > can all agree that homophobic trolling has no place in Haskell Cafe, nor > any other professional community. > > I’m reminded of this: > > https://mail.haskell.org/pipermail/haskell/2016-September/024995.html > > Let’s keep things supportive, friendly, and respectful. > > Regards, > -- > John A. De Goes > john at degoes.net > Follow me on Twitter @jdegoes > > > > > > > On Jan 11, 2019, at 8:51 AM, Chris Smith wrote: > > This might be a good time to reflect on the kind of community we'd like to > build and maintain here. I understand there's a lot of history behind > LambdaConf and questionable decisions about past speakers, but we can still > express opinions in a respectful way. > > On Fri, Jan 11, 2019 at 7:07 AM William Fearon > wrote: > >> >> Johnny Dollar I'm way above your nosegay event. Yay, Yag, Yag. >> >> >> >> Dr Fearon >> *Sent:* Tuesday, January 08, 2019 at 3:06 PM >> *From:* "John A. De Goes" >> *To:* Haskell-cafe at haskell.org >> *Subject:* [Haskell-cafe] LambdaConf 2019 Call for Proposals >> >> Dear Haskell Enthusiasts: >> >> The LambdaConf 2019 Call for Proposals is open, and we warmly welcome >> Haskell proposals on topics of interest to aspiring and practicing >> functional programmers. Historically, Haskell content accounts for more >> than 50% of content across all 5-8 tracks of the event. >> >> Last year’s speakers included Michael Snoyberg, Dana Scott, Jeremy Siek, >> and many others from both industry and academia. >> >> To submit a proposal for LambdaConf 2019, please visit the following >> website: >> >> https://www.papercall.io/lambdaconf-2019 >> >> Travel assistance is available, including lodging. >> >> ## INTRODUCTION >> >> LambdaConf is the largest interdisciplinary functional programming >> conference in the Mountain West, and one of the largest and most respected >> functional programming conferences in the world. >> >> The conference takes place June 5rd - 7th, in Boulder, Colorado, at the >> University of Colorado Boulder, and is surrounded by commercial training >> opportunities. If you are an educator, a researcher, a speaker, a speaker >> coach, or someone aspiring to one of the preceding, then we warmly welcome >> you to submit a proposal for LambdaConf 2019. No prior experience is >> necessary for most proposals, and we welcome beginner-level content. >> >> The Call for Proposals closes at the end of January 2019. We recommend >> submitting as early as you can to ensure sufficient time for editing. >> LambdaConf attracts everyone from the FP-curious to researchers advancing >> state-of-the-art; hobbyists, professionals, academics and students. >> Material at all levels, including beginner content and very advanced >> content, will find an audience at LambdaConf. >> >> Historically, LambdaConf has enjoyed a large selection of sessions on >> statically-typed functional programming, and a smaller selection of >> sessions on dynamically-typed functional programming. Some sessions are not >> tied to specific programming languages, but rather cover topics in abstract >> algebra, category theory, type theory, programming language theory, >> functional architecture, and so on, either generically or in a way that >> applies across many programming languages. >> >> ## TOPICS >> >> LambdaConf looks for sessions in the following areas: >> >> - LANGUAGES. Proposals that overview or dive into specific features of >> functional, math, or logic programming languages (both new and existing), >> with the goal of exposing developers to new ideas or helping them master >> features of languages they already know. LIBRARIES. Proposals that discuss >> libraries that leverage functional or logic programming to help programmers >> solve real-world problems. >> - CONCEPTS. Proposals that discuss functional programming idioms, >> patterns, or abstractions; or concepts from mathematics, logic, and >> computer science, all directed at helping developers write software that’s >> easier to test, easier to reason about, and easier to change safely. >> - APPLICATIONS. Proposals that discuss how functional programming can >> help with specific aspects of modern software development, including >> scalability, distributed systems, concurrency, data processing, security, >> performance, correctness, user-interfaces, machine learning, and big data. >> - USE CASES. Proposals that discuss how functional programming enabled a >> project or team to thrive, or deliver more business value than possible >> with other approaches. >> - CHERRY PICKING. Proposals that show how techniques and approaches from >> functional programming can be adapted and incorporated into mainstream >> development languages and practices, to the benefit of developers using >> them. >> - CAUTIONARY TALES. Proposals that call attention to difficulties of >> functional programming (both as a cautionary tale but also to raise >> awareness), especially such proposals that suggest alternatives or a path >> forward. >> - EFFICACY. Proposals that present data, measurements, or analysis that >> suggests different techniques, paradigms, languages, libraries, concepts, >> or approaches have different efficacies for given specified metrics, which >> provide actionable takeaways to practicing functional and logic programmers. >> - OFF-TOPIC. Proposals that have appeal to a mainstream developer >> audience (the number of off-topic proposals we accept is small, but we do >> accept some, especially for keynotes). >> >> ## SESSION TYPES >> >> LambdaConf accepts proposals for the following types of sessions: >> >> - LEAP WORKSHOPS (6h). Leap Workshops are approximately 6 hours in >> length. They are in-depth, hands-on workshops designed to teach mainstream >> functional programming topics in enough detail, attendees can immediately >> apply what they learn in their jobs. We require that speakers follow our >> recommended format for Leap Workshops, although we allow exceptions for >> experienced teachers. >> - HOP WORKSHOPS (2h). Hop Workshops are 2 hours in length. Like Leap >> Workshops, these workshops are in-depth and hands-on, but they cover >> reduced content and may be specialized to topics that may not have >> mainstream appeal. We require that speakers follow our recommended format >> for Hop Workshops, although we allow exceptions for experienced teachers. >> - DE NOVO SESSIONS (50m). De Novo Sessions are 50 minutes in length. >> These sessions are designed to present original work from industry and >> academia. While the requirements for proposals are more rigorous, there is >> less competition for De Novo slots. >> - EDUCATIONAL SESSIONS (50m). Educational Sessions are 50 minutes in >> length. These sessions are designed to clearly and concisely teach one >> useful concept, skill, aspect, library, or language to attendees. >> - KEYNOTES (40m). Keynotes are 40 minutes in length, and are presented >> before all attendees (there are no other sessions concurrent with >> keynotes). Keynotes are designed to offer thought-provoking, opinionated, >> and insightful commentary on topics of interest to the community. >> >> If you are accepted for a specific type of proposal (e.g. Educational), >> we cannot guarantee that you will get a slot of this type. Based on >> scheduling requirements, feedback from the committee, or feedback from your >> speaker coach, we may require you to change the format of your session. >> >> Regards, >> -- >> John A. De Goes >> john at degoes.net >> Follow me on Twitter @jdegoes >> >> >> >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > 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 tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Fri Jan 11 16:37:29 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 11 Jan 2019 16:37:29 +0000 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals In-Reply-To: References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> Message-ID: <20190111163729.zsx5mrgztasopli7@weber> On Fri, Jan 11, 2019 at 08:21:18AM -0800, Jeremiah Peschka wrote: > 1. This William Fearon account has some history of trolling various > conferences, mailing lists, and academics and should probably be removed > (see https://www.quora.com/Who-is-Dr-William-Fearon-and-why-does-he-keep-emailing-me-grandiose-claims-about-his-position-in-academia) Does anyone know who is an administrator for this list? I can't find relevant info in any of the obvious places https://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe https://www.haskell.org/mailing-lists From john at degoes.net Fri Jan 11 16:38:35 2019 From: john at degoes.net (John A. De Goes) Date: Fri, 11 Jan 2019 09:38:35 -0700 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals In-Reply-To: References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> Message-ID: <9793D79C-74EC-4870-871C-85D23EE5B97D@degoes.net> On 2: not “nosegay”—maybe I’m being overly sensitive but the only other time I’ve heard “yag”, it was most definitely a derogatory term for “gay”. Regards, — John A. De Goes john at degoes.net Follow me on Twitter @jdegoes Sent from my iPhone > On Jan 11, 2019, at 9:21 AM, Jeremiah Peschka wrote: > > Two things. > > 1. This William Fearon account has some history of trolling various conferences, mailing lists, and academics and should probably be removed (see https://www.quora.com/Who-is-Dr-William-Fearon-and-why-does-he-keep-emailing-me-grandiose-claims-about-his-position-in-academia) > > 2. At the risk of going off topic, nosegay is not a homophobic word and refers to a bunch of sweet smelling flowers. Admittedly, the sentence makes zero sense in this context, but there you have it. > > Jeremiah Peschka >> On Jan 11, 2019, 08:11 -0800, John A. De Goes , wrote: >> >> Indeed. While we can all respectfully disagree about whether or not conferences should ban speakers based on their political views, I think we can all agree that homophobic trolling has no place in Haskell Cafe, nor any other professional community. >> >> I’m reminded of this: >> >> https://mail.haskell.org/pipermail/haskell/2016-September/024995.html >> >> Let’s keep things supportive, friendly, and respectful. >> >> Regards, >> -- >> John A. De Goes >> john at degoes.net >> Follow me on Twitter @jdegoes >> >> >> >> >> >> >>> On Jan 11, 2019, at 8:51 AM, Chris Smith wrote: >>> >>> This might be a good time to reflect on the kind of community we'd like to build and maintain here. I understand there's a lot of history behind LambdaConf and questionable decisions about past speakers, but we can still express opinions in a respectful way. >>> >>>> On Fri, Jan 11, 2019 at 7:07 AM William Fearon wrote: >>>> >>>> Johnny Dollar I'm way above your nosegay event. Yay, Yag, Yag. >>>> >>>> >>>> >>>> Dr Fearon >>>> Sent: Tuesday, January 08, 2019 at 3:06 PM >>>> From: "John A. De Goes" >>>> To: Haskell-cafe at haskell.org >>>> Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals >>>> >>>> Dear Haskell Enthusiasts: >>>> >>>> The LambdaConf 2019 Call for Proposals is open, and we warmly welcome Haskell proposals on topics of interest to aspiring and practicing functional programmers. Historically, Haskell content accounts for more than 50% of content across all 5-8 tracks of the event. >>>> >>>> Last year’s speakers included Michael Snoyberg, Dana Scott, Jeremy Siek, and many others from both industry and academia. >>>> >>>> To submit a proposal for LambdaConf 2019, please visit the following website: >>>> >>>> https://www.papercall.io/lambdaconf-2019 >>>> >>>> Travel assistance is available, including lodging. >>>> >>>> ## INTRODUCTION >>>> >>>> LambdaConf is the largest interdisciplinary functional programming conference in the Mountain West, and one of the largest and most respected functional programming conferences in the world. >>>> >>>> The conference takes place June 5rd - 7th, in Boulder, Colorado, at the University of Colorado Boulder, and is surrounded by commercial training opportunities. If you are an educator, a researcher, a speaker, a speaker coach, or someone aspiring to one of the preceding, then we warmly welcome you to submit a proposal for LambdaConf 2019. No prior experience is necessary for most proposals, and we welcome beginner-level content. >>>> >>>> The Call for Proposals closes at the end of January 2019. We recommend submitting as early as you can to ensure sufficient time for editing. LambdaConf attracts everyone from the FP-curious to researchers advancing state-of-the-art; hobbyists, professionals, academics and students. Material at all levels, including beginner content and very advanced content, will find an audience at LambdaConf. >>>> >>>> Historically, LambdaConf has enjoyed a large selection of sessions on statically-typed functional programming, and a smaller selection of sessions on dynamically-typed functional programming. Some sessions are not tied to specific programming languages, but rather cover topics in abstract algebra, category theory, type theory, programming language theory, functional architecture, and so on, either generically or in a way that applies across many programming languages. >>>> >>>> ## TOPICS >>>> >>>> LambdaConf looks for sessions in the following areas: >>>> >>>> - LANGUAGES. Proposals that overview or dive into specific features of functional, math, or logic programming languages (both new and existing), with the goal of exposing developers to new ideas or helping them master features of languages they already know. LIBRARIES. Proposals that discuss libraries that leverage functional or logic programming to help programmers solve real-world problems. >>>> - CONCEPTS. Proposals that discuss functional programming idioms, patterns, or abstractions; or concepts from mathematics, logic, and computer science, all directed at helping developers write software that’s easier to test, easier to reason about, and easier to change safely. >>>> - APPLICATIONS. Proposals that discuss how functional programming can help with specific aspects of modern software development, including scalability, distributed systems, concurrency, data processing, security, performance, correctness, user-interfaces, machine learning, and big data. >>>> - USE CASES. Proposals that discuss how functional programming enabled a project or team to thrive, or deliver more business value than possible with other approaches. >>>> - CHERRY PICKING. Proposals that show how techniques and approaches from functional programming can be adapted and incorporated into mainstream development languages and practices, to the benefit of developers using them. >>>> - CAUTIONARY TALES. Proposals that call attention to difficulties of functional programming (both as a cautionary tale but also to raise awareness), especially such proposals that suggest alternatives or a path forward. >>>> - EFFICACY. Proposals that present data, measurements, or analysis that suggests different techniques, paradigms, languages, libraries, concepts, or approaches have different efficacies for given specified metrics, which provide actionable takeaways to practicing functional and logic programmers. >>>> - OFF-TOPIC. Proposals that have appeal to a mainstream developer audience (the number of off-topic proposals we accept is small, but we do accept some, especially for keynotes). >>>> >>>> ## SESSION TYPES >>>> >>>> LambdaConf accepts proposals for the following types of sessions: >>>> >>>> - LEAP WORKSHOPS (6h). Leap Workshops are approximately 6 hours in length. They are in-depth, hands-on workshops designed to teach mainstream functional programming topics in enough detail, attendees can immediately apply what they learn in their jobs. We require that speakers follow our recommended format for Leap Workshops, although we allow exceptions for experienced teachers. >>>> - HOP WORKSHOPS (2h). Hop Workshops are 2 hours in length. Like Leap Workshops, these workshops are in-depth and hands-on, but they cover reduced content and may be specialized to topics that may not have mainstream appeal. We require that speakers follow our recommended format for Hop Workshops, although we allow exceptions for experienced teachers. >>>> - DE NOVO SESSIONS (50m). De Novo Sessions are 50 minutes in length. These sessions are designed to present original work from industry and academia. While the requirements for proposals are more rigorous, there is less competition for De Novo slots. >>>> - EDUCATIONAL SESSIONS (50m). Educational Sessions are 50 minutes in length. These sessions are designed to clearly and concisely teach one useful concept, skill, aspect, library, or language to attendees. >>>> - KEYNOTES (40m). Keynotes are 40 minutes in length, and are presented before all attendees (there are no other sessions concurrent with keynotes). Keynotes are designed to offer thought-provoking, opinionated, and insightful commentary on topics of interest to the community. >>>> >>>> If you are accepted for a specific type of proposal (e.g. Educational), we cannot guarantee that you will get a slot of this type. Based on scheduling requirements, feedback from the committee, or feedback from your speaker coach, we may require you to change the format of your session. >>>> >>>> Regards, >>>> -- >>>> John A. De Goes >>>> john at degoes.net >>>> Follow me on Twitter @jdegoes >>>> >>>> >>>> >>>> >>>> >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Fri Jan 11 16:53:44 2019 From: fa-ml at ariis.it (Francesco Ariis) Date: Fri, 11 Jan 2019 17:53:44 +0100 Subject: [Haskell-cafe] LambdaConf 2019 Call for Proposals In-Reply-To: <20190111163729.zsx5mrgztasopli7@weber> References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> <20190111163729.zsx5mrgztasopli7@weber> Message-ID: <20190111165344.zzl3qublnxbrd3eg@x60s.casa> On Fri, Jan 11, 2019 at 04:37:29PM +0000, Tom Ellis wrote: > Does anyone know who is an administrator for this list? I can't find > relevant info in any of the obvious places > > https://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > https://www.haskell.org/mailing-lists Both of these should do: - haskell.infrastructure at gmail.com or - #haskell-infrastructure IRC channel on freenode.org And please state that on top of writing stupid messages, our troll sends html-only emails :P -F From johannes.waldmann at htwk-leipzig.de Fri Jan 11 18:03:39 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Fri, 11 Jan 2019 19:03:39 +0100 Subject: [Haskell-cafe] About 'Overloaded functions are not your friend' line in GHC manual Message-ID: <5673aabd-6d64-e54d-ac0b-af802cd8393d@htwk-leipzig.de> At run-time, only the branch (Left/Right) is "picked" at run-time. For each branch, the "show" instance is determined at compile-time. The problem is that such instances are represented by dictionaries, and this adds extra cost (extra arguments) to function calls - but only in those cases where these dictionaries are not inlined (that is, removed) statically. But I am thinking that GHC has become very good at inlining. - J.W. From allbery.b at gmail.com Fri Jan 11 18:13:54 2019 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 11 Jan 2019 13:13:54 -0500 Subject: [Haskell-cafe] About 'Overloaded functions are not your friend' line in GHC manual In-Reply-To: <5673aabd-6d64-e54d-ac0b-af802cd8393d@htwk-leipzig.de> References: <5673aabd-6d64-e54d-ac0b-af802cd8393d@htwk-leipzig.de> Message-ID: Only up to a point. Recursive uses — such as show, which delegates to other Show instances for record fields, etc. — are problematic. On Fri, Jan 11, 2019 at 1:04 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > > At run-time, only the branch (Left/Right) is "picked" at run-time. > For each branch, the "show" instance is determined at compile-time. > > The problem is that such instances are represented by dictionaries, > and this adds extra cost (extra arguments) to function calls - > but only in those cases where these dictionaries > are not inlined (that is, removed) statically. > > But I am thinking that GHC has become very good at inlining. > > - J.W. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Fri Jan 11 18:58:37 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Fri, 11 Jan 2019 19:58:37 +0100 Subject: [Haskell-cafe] About 'Overloaded functions are not your friend' line in GHC manual In-Reply-To: References: <5673aabd-6d64-e54d-ac0b-af802cd8393d@htwk-leipzig.de> Message-ID: <11713130-0e94-5ff5-29ca-d4970509809f@htwk-leipzig.de> On 11.01.19 19:13, Brandon Allbery wrote: > Only up to a point. Recursive uses — such as show, which delegates to > other Show instances for record fields, etc. — are problematic. Please explain. Do you mean that size (S (S Z)) and size_N (S (S Z)) are not equivalent for these declarations? class Size t where size :: t -> Int data N = Z | S N instance Size N where size Z = 0 ; size (S n) = succ (size n) size_N Z = 0 ; size_N (S n) = succ (size n) I was trying to read core for this but I'm not sure what's the best way to call ghc. Which of the -ddump-* options is best suited (-ddump-simpl ?) and what do I look for in the output? Thanks - J.W. From william.fearon at mail.com Fri Jan 11 19:21:35 2019 From: william.fearon at mail.com (William Fearon) Date: Fri, 11 Jan 2019 20:21:35 +0100 Subject: [Haskell-cafe] John A. De Goes" LambdaConf 2019 Call for Proposals In-Reply-To: <9793D79C-74EC-4870-871C-85D23EE5B97D@degoes.net> References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> <9793D79C-74EC-4870-871C-85D23EE5B97D@degoes.net> Message-ID: An HTML attachment was scrubbed... URL: From spam at scientician.net Fri Jan 11 19:35:37 2019 From: spam at scientician.net (Bardur Arantsson) Date: Fri, 11 Jan 2019 20:35:37 +0100 Subject: [Haskell-cafe] John A. De Goes" LambdaConf 2019 Call for Proposals In-Reply-To: References: <13FF6E2E-ED2A-471A-AB77-7193B63449AA@degoes.net> <9793D79C-74EC-4870-871C-85D23EE5B97D@degoes.net> Message-ID: On 11/01/2019 20.21, William Fearon wrote: [--snip--] Ok, list admins, can we please ban this Fearon person? From dave at zednenem.com Fri Jan 11 20:34:18 2019 From: dave at zednenem.com (David Menendez) Date: Fri, 11 Jan 2019 15:34:18 -0500 Subject: [Haskell-cafe] About 'Overloaded functions are not your friend' line in GHC manual In-Reply-To: References: <5673aabd-6d64-e54d-ac0b-af802cd8393d@htwk-leipzig.de> Message-ID: Are you talking about instances such as Show a => Show (Maybe a)? If the fields of a record are fixed types, it seems like GHC would be able to inline the dictionaries. On Fri, Jan 11, 2019 at 1:14 PM Brandon Allbery wrote: > > Only up to a point. Recursive uses — such as show, which delegates to other Show instances for record fields, etc. — are problematic. > > On Fri, Jan 11, 2019 at 1:04 PM Johannes Waldmann wrote: >> >> >> At run-time, only the branch (Left/Right) is "picked" at run-time. >> For each branch, the "show" instance is determined at compile-time. >> >> The problem is that such instances are represented by dictionaries, >> and this adds extra cost (extra arguments) to function calls - >> but only in those cases where these dictionaries >> are not inlined (that is, removed) statically. >> >> But I am thinking that GHC has become very good at inlining. >> >> - J.W. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > > > -- > brandon s allbery kf8nh > allbery.b at gmail.com > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Dave Menendez From ryan.reich at gmail.com Sat Jan 12 05:25:19 2019 From: ryan.reich at gmail.com (Ryan Reich) Date: Fri, 11 Jan 2019 21:25:19 -0800 Subject: [Haskell-cafe] Honest constant-space mergesort Message-ID: I am, for entertainment, trying to figure out how to implement a constant-space bottom-up mergesort in Haskell. This is quite easy to at least describe imperatively: break the list into ordered blocks, merge adjacent ones, and repeat with double the length until there's only one block and you're done. For a linked list like [a] in Haskell, this should be constant-space. Unfortunately, it is not. You can definitely express the above algorithm nicely if you organize those blocks into an [[a]], but then you are creating O(n) new lists. Even if you go to extremes to keep the blocks concatenated, though, you still have the issue that every time you merge two lists, you are creating a new list and that involves the allocator. (Note that the implementation of Data.List.sort does this.) The C equivalent would proceed by just overwriting the linking pointers in each node, without allocating new nodes to do so, but of course, that's not going to work in Haskell. I considered using something like STRef to represent the links (so, departing from the plain [a] type) but even then, if you overwrite the contents of one of those, the garbage collector still needs to know. This is better than allocating more space, but it is not necessary because the algorithm never actually makes any of the nodes unreachable. Also, I understand that using a lot of STRefs is bad for efficiency. Is there any way to do this in (GHC) Haskell and get the algorithm down to the bare minimum? If there is, is it any different than just "writing C in Haskell"? That is, can one coerce GHC into emitting the mutable-link operations and not doing collections, from high-level code? Although I've definitely seen examples of algorithms that compile down to such unboxed depths, this one has been really resistant to improvement. Thanks, Ryan Reich -------------- next part -------------- An HTML attachment was scrubbed... URL: From magicloud.magiclouds at gmail.com Sat Jan 12 06:16:54 2019 From: magicloud.magiclouds at gmail.com (Magicloud Magiclouds) Date: Sat, 12 Jan 2019 14:16:54 +0800 Subject: [Haskell-cafe] About pointer taken by C lib in FFI. Message-ID: Hi, Say I have some data, and `poke` into a Ptr. Then I pass the Ptr to some function in C lib. The C lib stores the Ptr somewhere to use later. My question is, how does GHC handle the finalizing of the Ptr? Does it track the "used by foreign lib"? -- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com. From lysxia at gmail.com Sat Jan 12 07:33:27 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Sat, 12 Jan 2019 08:33:27 +0100 Subject: [Haskell-cafe] Honest constant-space mergesort In-Reply-To: References: Message-ID: <90c9118e-7bc4-2212-4038-050594909f1f@gmail.com> On 1/12/19 6:25 AM, Ryan Reich wrote: > I considered using something like > STRef to represent the links (so, departing from the plain [a] type) but > even then, if you overwrite the contents of one of those, the garbage > collector still needs to know.  This is better than allocating more > space, but it is not necessary because the algorithm never actually > makes any of the nodes unreachable. I thought this did not apply to a copying GC, does it? What is actually in an STRef? If it's small enough then unpacking the tail reference like this may be a good idea: data List s a = Nil | Cons a {-# UNPACK #-} !(STRef s (List s a)) Li-yao From frank at fstaals.net Sat Jan 12 21:59:33 2019 From: frank at fstaals.net (Frank Staals) Date: Sat, 12 Jan 2019 22:59:33 +0100 Subject: [Haskell-cafe] Honest constant-space mergesort In-Reply-To: (Ryan Reich's message of "Fri, 11 Jan 2019 21:25:19 -0800") References: Message-ID: Ryan Reich writes: > I am, for entertainment, trying to figure out how to implement a > constant-space bottom-up mergesort in Haskell. This is quite easy to at > least describe imperatively: break the list into ordered blocks, merge > adjacent ones, and repeat with double the length until there's only one > block and you're done. For a linked list like [a] in Haskell, this should > be constant-space. Unfortunately, it is not. > > You can definitely express the above algorithm nicely if you organize those > blocks into an [[a]], but then you are creating O(n) new lists. Even if > you go to extremes to keep the blocks concatenated, though, you still have > the issue that every time you merge two lists, you are creating a new list > and that involves the allocator. (Note that the implementation of > Data.List.sort does this.) > > The C equivalent would proceed by just overwriting the linking pointers in > each node, without allocating new nodes to do so, but of course, that's not > going to work in Haskell. I considered using something like STRef to > represent the links (so, departing from the plain [a] type) but even then, > if you overwrite the contents of one of those, the garbage collector still > needs to know. This is better than allocating more space, but it is not > necessary because the algorithm never actually makes any of the nodes > unreachable. Also, I understand that using a lot of STRefs is bad for > efficiency. > > Is there any way to do this in (GHC) Haskell and get the algorithm down to > the bare minimum? If there is, is it any different than just "writing C in > Haskell"? That is, can one coerce GHC into emitting the mutable-link > operations and not doing collections, from high-level code? Although I've > definitely seen examples of algorithms that compile down to such unboxed > depths, this one has been really resistant to improvement. > > Thanks, > Ryan Reich > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. If you want your sort function to have type: Ord a => [a] -> [a] then I would think that you'd need to at least n new space anyway (where n is the length of the list), since you cannot actually overwrite the input list anyway. -- - Frank From ryan.reich at gmail.com Sun Jan 13 04:38:09 2019 From: ryan.reich at gmail.com (Ryan Reich) Date: Sat, 12 Jan 2019 20:38:09 -0800 Subject: [Haskell-cafe] Honest constant-space mergesort In-Reply-To: References: Message-ID: With list fusion, neither input nor output actually is necessarily allocated. Though I take your point, I'm not griping about setup code that maintains a pure facade, but about the allocations that purity demands in the middle. On Sat, Jan 12, 2019, 13:59 Frank Staals Ryan Reich writes: > > > I am, for entertainment, trying to figure out how to implement a > > constant-space bottom-up mergesort in Haskell. This is quite easy to at > > least describe imperatively: break the list into ordered blocks, merge > > adjacent ones, and repeat with double the length until there's only one > > block and you're done. For a linked list like [a] in Haskell, this > should > > be constant-space. Unfortunately, it is not. > > > > You can definitely express the above algorithm nicely if you organize > those > > blocks into an [[a]], but then you are creating O(n) new lists. Even if > > you go to extremes to keep the blocks concatenated, though, you still > have > > the issue that every time you merge two lists, you are creating a new > list > > and that involves the allocator. (Note that the implementation of > > Data.List.sort does this.) > > > > The C equivalent would proceed by just overwriting the linking pointers > in > > each node, without allocating new nodes to do so, but of course, that's > not > > going to work in Haskell. I considered using something like STRef to > > represent the links (so, departing from the plain [a] type) but even > then, > > if you overwrite the contents of one of those, the garbage collector > still > > needs to know. This is better than allocating more space, but it is not > > necessary because the algorithm never actually makes any of the nodes > > unreachable. Also, I understand that using a lot of STRefs is bad for > > efficiency. > > > > Is there any way to do this in (GHC) Haskell and get the algorithm down > to > > the bare minimum? If there is, is it any different than just "writing C > in > > Haskell"? That is, can one coerce GHC into emitting the mutable-link > > operations and not doing collections, from high-level code? Although > I've > > definitely seen examples of algorithms that compile down to such unboxed > > depths, this one has been really resistant to improvement. > > > > Thanks, > > Ryan Reich > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > If you want your sort function to have type: Ord a => [a] -> [a] then I > would think that you'd need to at least n new space anyway (where n is > the length of the list), since you cannot actually overwrite the input > list anyway. > > -- > > - Frank > -------------- next part -------------- An HTML attachment was scrubbed... URL: From javran.c at gmail.com Sun Jan 13 07:59:36 2019 From: javran.c at gmail.com (Javran Cheng) Date: Sat, 12 Jan 2019 23:59:36 -0800 Subject: [Haskell-cafe] Void is not Monoid? Message-ID: Hi Cafe, I'm wondering why Data.Void does not have a Monoid instance, or, what would be the problem if we do "mempty = absurd mempty"? Long story: I was using a monad with some transformers, then I realize I can collapse State and Reader into RWST with Void being Writer output. (well, I could have just used Unit but I wanna give Void a try...) I know beforehand that Void is Semigroup but is a bit surprise it doesn't have Monoid instance. Javran Cheng -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Sun Jan 13 08:23:46 2019 From: will.yager at gmail.com (William Yager) Date: Sun, 13 Jan 2019 16:23:46 +0800 Subject: [Haskell-cafe] Void is not Monoid? In-Reply-To: References: Message-ID: On Sun, Jan 13, 2019 at 4:00 PM Javran Cheng wrote: > Hi Cafe, > > I'm wondering why Data.Void does not have a Monoid instance, or, what > would be the problem if we do "mempty = absurd mempty"? > This diverges, does it not? A monoid has an identity element, and void does not. > Long story: I was using a monad with some transformers, then I realize I > can collapse State and Reader into RWST with Void being Writer output. > (well, I could have just used Unit but I wanna give Void a try...) I know > beforehand that Void is Semigroup but is a bit surprise it doesn't have > Monoid instance. > How would you write return with void as the writer? You can accomplish what you want with the free monoid over Void - i.e. [Void], which is isomorphic to unit. So unit seems like the right choice. --Will -------------- next part -------------- An HTML attachment was scrubbed... URL: From javran.c at gmail.com Sun Jan 13 08:43:02 2019 From: javran.c at gmail.com (Javran Cheng) Date: Sun, 13 Jan 2019 00:43:02 -0800 Subject: [Haskell-cafe] Fwd: Void is not Monoid? In-Reply-To: References: Message-ID: (forgot to reply all, sorry) Hi Will, Thanks for the reply! > A monoid has an identity element, and void does not. now I feel dull never thought about that. > How would you write return with void as the writer? > You can accomplish what you want with the free monoid over Void - i.e. [Void], which is isomorphic to unit. So unit seems like the right choice. Unit does work fine, but I figure using Void is an interesting idea, as I can make sure that no one can use the "W" part of my RWST. Javran On Sun, Jan 13, 2019 at 12:23 AM William Yager wrote: > On Sun, Jan 13, 2019 at 4:00 PM Javran Cheng wrote: > >> Hi Cafe, >> >> I'm wondering why Data.Void does not have a Monoid instance, or, what >> would be the problem if we do "mempty = absurd mempty"? >> > > This diverges, does it not? > > A monoid has an identity element, and void does not. > > >> Long story: I was using a monad with some transformers, then I realize I >> can collapse State and Reader into RWST with Void being Writer output. >> (well, I could have just used Unit but I wanna give Void a try...) I know >> beforehand that Void is Semigroup but is a bit surprise it doesn't have >> Monoid instance. >> > > How would you write return with void as the writer? > > You can accomplish what you want with the free monoid over Void - i.e. > [Void], which is isomorphic to unit. So unit seems like the right choice. > > --Will > -- Javran (Fang) Cheng -- Javran (Fang) Cheng -------------- next part -------------- An HTML attachment was scrubbed... URL: From isaace71295 at gmail.com Sun Jan 13 09:15:31 2019 From: isaace71295 at gmail.com (Isaac Elliott) Date: Sun, 13 Jan 2019 19:15:31 +1000 Subject: [Haskell-cafe] Fwd: Void is not Monoid? In-Reply-To: References: Message-ID: If you had an `RWST r Void s m a`, then you would be able to produce an `m (a, s, Void)`, which is `absurd`. On Sun, 13 Jan. 2019, 6:43 pm Javran Cheng, wrote: > (forgot to reply all, sorry) > > Hi Will, > > Thanks for the reply! > > > A monoid has an identity element, and void does not. > > now I feel dull never thought about that. > > > How would you write return with void as the writer? > > You can accomplish what you want with the free monoid over Void - i.e. > [Void], which is isomorphic to unit. So unit seems like the right choice. > > Unit does work fine, but I figure using Void is an interesting idea, as I > can make sure that no one can use the "W" part of my RWST. > > Javran > > > On Sun, Jan 13, 2019 at 12:23 AM William Yager > wrote: > >> On Sun, Jan 13, 2019 at 4:00 PM Javran Cheng wrote: >> >>> Hi Cafe, >>> >>> I'm wondering why Data.Void does not have a Monoid instance, or, what >>> would be the problem if we do "mempty = absurd mempty"? >>> >> >> This diverges, does it not? >> >> A monoid has an identity element, and void does not. >> >> >>> Long story: I was using a monad with some transformers, then I realize I >>> can collapse State and Reader into RWST with Void being Writer output. >>> (well, I could have just used Unit but I wanna give Void a try...) I >>> know beforehand that Void is Semigroup but is a bit surprise it doesn't >>> have Monoid instance. >>> >> >> How would you write return with void as the writer? >> >> You can accomplish what you want with the free monoid over Void - i.e. >> [Void], which is isomorphic to unit. So unit seems like the right choice. >> >> --Will >> > > > -- > Javran (Fang) Cheng > > > -- > Javran (Fang) Cheng > _______________________________________________ > 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 javran.c at gmail.com Sun Jan 13 09:52:40 2019 From: javran.c at gmail.com (Javran Cheng) Date: Sun, 13 Jan 2019 01:52:40 -0800 Subject: [Haskell-cafe] Fwd: Void is not Monoid? In-Reply-To: References: Message-ID: That's a valid point. come to think of it, is there any use case where Void appears on a positive position? On Sun, Jan 13, 2019 at 1:15 AM Isaac Elliott wrote: > If you had an `RWST r Void s m a`, then you would be able to produce an `m > (a, s, Void)`, which is `absurd`. > > On Sun, 13 Jan. 2019, 6:43 pm Javran Cheng, wrote: > >> (forgot to reply all, sorry) >> >> Hi Will, >> >> Thanks for the reply! >> >> > A monoid has an identity element, and void does not. >> >> now I feel dull never thought about that. >> >> > How would you write return with void as the writer? >> > You can accomplish what you want with the free monoid over Void - i.e. >> [Void], which is isomorphic to unit. So unit seems like the right choice. >> >> Unit does work fine, but I figure using Void is an interesting idea, as I >> can make sure that no one can use the "W" part of my RWST. >> >> Javran >> >> >> On Sun, Jan 13, 2019 at 12:23 AM William Yager >> wrote: >> >>> On Sun, Jan 13, 2019 at 4:00 PM Javran Cheng wrote: >>> >>>> Hi Cafe, >>>> >>>> I'm wondering why Data.Void does not have a Monoid instance, or, what >>>> would be the problem if we do "mempty = absurd mempty"? >>>> >>> >>> This diverges, does it not? >>> >>> A monoid has an identity element, and void does not. >>> >>> >>>> Long story: I was using a monad with some transformers, then I realize >>>> I can collapse State and Reader into RWST with Void being Writer output. >>>> (well, I could have just used Unit but I wanna give Void a try...) I >>>> know beforehand that Void is Semigroup but is a bit surprise it doesn't >>>> have Monoid instance. >>>> >>> >>> How would you write return with void as the writer? >>> >>> You can accomplish what you want with the free monoid over Void - i.e. >>> [Void], which is isomorphic to unit. So unit seems like the right choice. >>> >>> --Will >>> >> >> >> -- >> Javran (Fang) Cheng >> >> >> -- >> Javran (Fang) Cheng >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > -- Javran (Fang) Cheng -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Sun Jan 13 09:57:02 2019 From: michael at snoyman.com (Michael Snoyman) Date: Sun, 13 Jan 2019 11:57:02 +0200 Subject: [Haskell-cafe] Fwd: Void is not Monoid? In-Reply-To: References: Message-ID: Functions like `forever` can put Void in positive position as a proof that the value is never produced. On Sun, Jan 13, 2019 at 11:53 AM Javran Cheng wrote: > That's a valid point. come to think of it, is there any use case where > Void appears on a positive position? > > On Sun, Jan 13, 2019 at 1:15 AM Isaac Elliott > wrote: > >> If you had an `RWST r Void s m a`, then you would be able to produce an >> `m (a, s, Void)`, which is `absurd`. >> >> On Sun, 13 Jan. 2019, 6:43 pm Javran Cheng, wrote: >> >>> (forgot to reply all, sorry) >>> >>> Hi Will, >>> >>> Thanks for the reply! >>> >>> > A monoid has an identity element, and void does not. >>> >>> now I feel dull never thought about that. >>> >>> > How would you write return with void as the writer? >>> > You can accomplish what you want with the free monoid over Void - i.e. >>> [Void], which is isomorphic to unit. So unit seems like the right choice. >>> >>> Unit does work fine, but I figure using Void is an interesting idea, as >>> I can make sure that no one can use the "W" part of my RWST. >>> >>> Javran >>> >>> >>> On Sun, Jan 13, 2019 at 12:23 AM William Yager >>> wrote: >>> >>>> On Sun, Jan 13, 2019 at 4:00 PM Javran Cheng >>>> wrote: >>>> >>>>> Hi Cafe, >>>>> >>>>> I'm wondering why Data.Void does not have a Monoid instance, or, what >>>>> would be the problem if we do "mempty = absurd mempty"? >>>>> >>>> >>>> This diverges, does it not? >>>> >>>> A monoid has an identity element, and void does not. >>>> >>>> >>>>> Long story: I was using a monad with some transformers, then I realize >>>>> I can collapse State and Reader into RWST with Void being Writer output. >>>>> (well, I could have just used Unit but I wanna give Void a try...) I >>>>> know beforehand that Void is Semigroup but is a bit surprise it doesn't >>>>> have Monoid instance. >>>>> >>>> >>>> How would you write return with void as the writer? >>>> >>>> You can accomplish what you want with the free monoid over Void - i.e. >>>> [Void], which is isomorphic to unit. So unit seems like the right choice. >>>> >>>> --Will >>>> >>> >>> >>> -- >>> Javran (Fang) Cheng >>> >>> >>> -- >>> Javran (Fang) Cheng >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> > > -- > Javran (Fang) Cheng > _______________________________________________ > 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 nick.rudnick at gmail.com Sun Jan 13 12:43:40 2019 From: nick.rudnick at gmail.com (Nick Rudnick) Date: Sun, 13 Jan 2019 13:43:40 +0100 Subject: [Haskell-cafe] =?utf-8?q?Binary_Data_Access_via_PIC=E2=80=A6=3F?= =?utf-8?q?=3F?= Message-ID: On NL FP day, it struck me again when I saw an almost 1 MB *.hs file with apparent sole purpose of getting a quantity of raw data incorporated to the binary – applying some funny text encoding constructs. I remembered that, to my best knowledge, with major downside that it's compile time, this appears to be the best solution to me… Another approach I did notice several times was, say, the use of super fast parsing, to read in binary data at run time. Did I miss something? Or, more specifically – I am speaking about that kind of binary data which is (1) huge! – the 1 MB mentioned above rather being at the lower limit, (2) completely independent from the version of the Haskell compiler, (3) guaranteed (externally!) to match the structural requirements of the application referred to, (4) well managed in some way, concerning ABI issues, too (e.g. versioning, metadata headers etc.), and the question is in how far – as I believe other languages do, too – we can exploit PIC (position independent code), to read in really large quantities of binary data at run time or immediately before run time, without the need for parsing at all. E.g., a textual data representation Haskell file will generate an an object file already, for which linking only should have a limited amount of assumptions regarding its inner structure. Imagining I have a huge but simple DB table, and a kind of converter which by some simplification of a Haskell compiler generates an object file that equally matches these (limited, as I believe) assumptions, and at the end can build a 'fake' the linker accepts instead of one dummy file skeleton – couldn't that be a way leading into the direction of directly getting in vast amounts of binary data in one part? In case there are stronger integrity needs, extra metadata like should be usable for verification of the origin from a valid code generator. Of course, while not completely necessary, true run time loading would be even greater… while direct interfacing to foreign (albeit simple) memory spaces deems much more intricate to me. I regularly stumbled about such cases – so I do believe this to useful. I would be happy to learn more about this – any thoughts…?? Cheers, and all the best, Nick -------------- next part -------------- An HTML attachment was scrubbed... URL: From ian at zenhack.net Sun Jan 13 20:02:59 2019 From: ian at zenhack.net (Ian Denhardt) Date: Sun, 13 Jan 2019 15:02:59 -0500 Subject: [Haskell-cafe] Binary Data Access via PIC…?? In-Reply-To: References: Message-ID: <154740977976.4896.12709727056528738128@localhost.localdomain> Shameless plug for one of my own libraries, which seems at least relevant to the problem space: https://hackage.haskell.org/package/capnp Though as a disclaimer I haven't done any benchmarking myself; my personal interest is more in RPC than in super-fast serialization. There will be a release with RPC support sometime later this month. That said, I have heard from one user who's using it to communicate with a part of their application written in C++, who switched over to from protobufs for perf, and because they needed to handle very large (> 2GiB) data. -Ian Quoting Nick Rudnick (2019-01-13 07:43:40) > On NL FP day, it struck me again when I saw an almost 1 MB *.hs file > with apparent sole purpose of getting a quantity of raw data > incorporated to the binary � applying some funny text encoding > constructs. I remembered that, to my best knowledge, with major > downside that it's compile time, this appears to be the best solution > to me� > Another approach I did notice several times was, say, the use of super > fast parsing, to read in binary data at run time. > Did I miss something? > Or, more specifically � I am speaking about that kind of binary data > which is > (1) huge! � the 1 MB mentioned above rather being at the lower limit, > (2) completely independent from the version of the Haskell compiler, > (3) guaranteed (externally!) to match the structural requirements of > the application referred to, > (4) well managed in some way, concerning ABI issues, too (e.g. > versioning, metadata headers etc.), > and the question is in how far � as I believe other languages do, too � > we can exploit PIC (position independent code), to read in really large > quantities of binary data at run time or immediately before run time, > without the need for parsing at all. > E.g., a textual data representation Haskell file will generate an an > object file already, for which linking only should have a limited > amount of assumptions regarding its inner structure. Imagining I have a > huge but simple DB table, and a kind of converter which by some > simplification of a Haskell compiler generates an object file that > equally matches these (limited, as I believe) assumptions, and at the > end can build a 'fake' the linker accepts instead of one dummy file > skeleton � couldn't that be a way leading into the direction of > directly getting in vast amounts of binary data in one part? > In case there are stronger integrity needs, extra metadata like should > be usable for verification of the origin from a valid code generator. > Of course, while not completely necessary, true run time loading would > be even greater� while direct interfacing to foreign (albeit simple) > memory spaces deems much more intricate to me. > I regularly stumbled about such cases � so I do believe this to useful. > I would be happy to learn more about this � any thoughts�?? > Cheers, and all the best, Nick From sylvain at haskus.fr Sun Jan 13 22:58:33 2019 From: sylvain at haskus.fr (Sylvain Henry) Date: Sun, 13 Jan 2019 23:58:33 +0100 Subject: [Haskell-cafe] About pointer taken by C lib in FFI. In-Reply-To: References: Message-ID: <54248a5e-fc07-8f33-f25b-bd208e1a9c43@haskus.fr> Hi, Ptr has no finalizer: you have to explicitly free the attached memory if necessary. You can use ForeignPtr to associate finalizers to a pointer: finalizers are functions that are called when the ForeignPtr object is to be collected by the GC. GHC can't track if the pointer is still stored/used by the C lib though. Hope that helps, Sylvain On 12/01/2019 07:16, Magicloud Magiclouds wrote: > Hi, > > Say I have some data, and `poke` into a Ptr. Then I pass the Ptr to > some function in C lib. The C lib stores the Ptr somewhere to use > later. > > My question is, how does GHC handle the finalizing of the Ptr? Does it > track the "used by foreign lib"? > From mail at nh2.me Mon Jan 14 14:42:51 2019 From: mail at nh2.me (=?UTF-8?Q?Niklas_Hamb=c3=bcchen?=) Date: Mon, 14 Jan 2019 15:42:51 +0100 Subject: [Haskell-cafe] About pointer taken by C lib in FFI. In-Reply-To: References: Message-ID: <74bfbf87-ff64-1105-c931-0a26a5515d7e@nh2.me> Hi, nice question. > Does it track the "used by foreign lib"? No, `Ptr` is a simple primitive numeric value, like `void *` in C itself. GHC does not track what you do with it at all. The lifetime and ownership of the pointer depends on how you created it. For example, the `withCString` function of type withCString :: String -> (Ptr CChar -> IO a) -> IO a https://hackage.haskell.org/package/base-4.12.0.0/docs/Foreign-C-String.html#v:withCString used e.g. like withCString "hello" $ \ptr -> do -- do something with with ptr here keeps the pointer alive exactly within the (do ...) block. Afterwards, the memory the `ptr` points to will be freed. Similar for `allocaBytes :: Int -> (Ptr a -> IO b) -> IO b`. You might do allocaBytes 1000 $ \(ptr :: Ptr void) -> do poke (castPtr ptr) ('c' :: Char) poke (castPtr ptr) (1234 :: Word64) -- call FFI function doing something with `ptr` and after allocaBytes itself returns, the memory is gone. Other functions, such as malloc :: Storable a => IO (Ptr a) mallocBytes :: Int -> IO (Ptr a) only allocate the memory and never free it, and you need to free it later yourself (you can also use C's `free()` on the C side for that). This may be what you want if you want the C code to take ownership of it. In that case, you must take care that this is async-exception safe, e.g. that you don't leak the allocated memory when an async exception comes in (e.g. from the `timeout` function or the user pressing Ctrl+C and you handling it and continuing). In general, one deals with async exceptions by using code blocks that temporarily disable them, like the `bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c` function does; see its docs as https://hackage.haskell.org/package/base-4.12.0.0/docs/Control-Exception-Base.html#v:bracket. Two examples of how non-bracketet `malloc` can go wrong: Example A (no ownership change involved): ptr <- mallocBytes 1000 -- async exception comes in here someOtherCodeDoingSomethingWith ptr free ptr Example B: ptr <- mallocBytes 1000 -- async exception comes in here ffiCodeThatChangesOwnershipToCLibrary ptr This would be bad, your allocced-bytes are unreachable and will memory leak forever. `bracket` can trivially solve the problem in example A, because the lifetime of `ptr` is lexically scoped. But for the handover in example B, the lifetime is not lexically scoped. You generally have 2 approaches to do a safe hand-over to C for non-lexically-scoped cases: 1. malloc the memory on the C side in the first place, and pass the pointer to Haskell so it can poke values in. In this case, the C side had the ownership the entire time, so it allocated and freed the memory. 2. Store the information whether Haskell still has the memory ownership somewhere, and always modify the pointer and this information together in some atomic fashion (for example using `bracket` so that it cannot be interrupted in the middle). The pointer and a mutable Bool reference would be such an information pair. Equivalent would be a double-pointer, where the outer pointer points to NULL to indicate that the memory is already owned by C. Below is a sketch of how to do it with the double-pointer approach: bracket acquireResource releaseResource (\ptrPtr -> do ptr <- peek ptrPtr poke ptr ('c' :: Char) poke ptr ('c' :: Word64) mask_ $ do -- we don't want to get interrupted in this block ffiCodeThatChangesOwnershipToCLibrary ptr poke ptrPtr nullPtr -- do some more work here return yourresult ) where acquireResource :: IO (Ptr (Ptr void)) acquireResource = do ptrPtr :: Ptr (Ptr void) <- malloc ptr :: Ptr void <- malloc poke ptrPtr ptr return ptrPtr releaseResource :: Ptr (Ptr void) -> IO yourresult releaseResource ptrPtr = do -- If ptrPtr points to NULL, then the ownership change happend. -- In that case we don't have to free `ptr` (and we cannot, as it is NULL). -- Otherwise, we still own the memory, and free it. ptr <- peek ptrPtr when (ptr == nullPtr) $ free ptr free ptrPtr (It is recommended to get familiar with `bracket` and `mask_` before understanding this.) The above works in a single-threaded case; if concurrency comes into play and you wrote code so that parts of this might be executed by different threads, you'll naturally have to put locks (e.g. `MVar`s) around the `poke ptrPtr ...` and the place where the `== nullPtr` check is done. I hope this helps! Niklas PS: I work for a Haskell consultancy. If answers like this would help move your project forward, consider us :) From magicloud.magiclouds at gmail.com Mon Jan 14 18:28:23 2019 From: magicloud.magiclouds at gmail.com (Magicloud Magiclouds) Date: Tue, 15 Jan 2019 02:28:23 +0800 Subject: [Haskell-cafe] About pointer taken by C lib in FFI. In-Reply-To: <54248a5e-fc07-8f33-f25b-bd208e1a9c43@haskus.fr> References: <54248a5e-fc07-8f33-f25b-bd208e1a9c43@haskus.fr> Message-ID: Thanks. I was meant to ask ForeignPtr as well. On Mon, Jan 14, 2019 at 6:59 AM Sylvain Henry wrote: > > Hi, > > Ptr has no finalizer: you have to explicitly free the attached memory if > necessary. > > You can use ForeignPtr to associate finalizers to a pointer: finalizers > are functions that are called when the ForeignPtr object is to be > collected by the GC. GHC can't track if the pointer is still stored/used > by the C lib though. > > Hope that helps, > Sylvain > > > On 12/01/2019 07:16, Magicloud Magiclouds wrote: > > Hi, > > > > Say I have some data, and `poke` into a Ptr. Then I pass the Ptr to > > some function in C lib. The C lib stores the Ptr somewhere to use > > later. > > > > My question is, how does GHC handle the finalizing of the Ptr? Does it > > track the "used by foreign lib"? > > > _______________________________________________ > 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. -- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com. From magicloud.magiclouds at gmail.com Mon Jan 14 18:30:20 2019 From: magicloud.magiclouds at gmail.com (Magicloud Magiclouds) Date: Tue, 15 Jan 2019 02:30:20 +0800 Subject: [Haskell-cafe] About pointer taken by C lib in FFI. In-Reply-To: <74bfbf87-ff64-1105-c931-0a26a5515d7e@nh2.me> References: <74bfbf87-ff64-1105-c931-0a26a5515d7e@nh2.me> Message-ID: Thanks. On Mon, Jan 14, 2019 at 10:42 PM Niklas Hambüchen wrote: > > Hi, nice question. > > > Does it track the "used by foreign lib"? > > No, `Ptr` is a simple primitive numeric value, like `void *` in C itself. > GHC does not track what you do with it at all. > > The lifetime and ownership of the pointer depends on how you created it. > > For example, the `withCString` function of type > withCString :: String -> (Ptr CChar -> IO a) -> IO a > https://hackage.haskell.org/package/base-4.12.0.0/docs/Foreign-C-String.html#v:withCString > used e.g. like > withCString "hello" $ \ptr -> do > -- do something with with ptr here > keeps the pointer alive exactly within the (do ...) block. > Afterwards, the memory the `ptr` points to will be freed. > > Similar for `allocaBytes :: Int -> (Ptr a -> IO b) -> IO b`. > You might do > > allocaBytes 1000 $ \(ptr :: Ptr void) -> do > poke (castPtr ptr) ('c' :: Char) > poke (castPtr ptr) (1234 :: Word64) > -- call FFI function doing something with `ptr` > > and after allocaBytes itself returns, the memory is gone. > > Other functions, such as > malloc :: Storable a => IO (Ptr a) > mallocBytes :: Int -> IO (Ptr a) > only allocate the memory and never free it, and you need to free it later yourself (you can also use C's `free()` on the C side for that). > > This may be what you want if you want the C code to take ownership of it. > > In that case, you must take care that this is async-exception safe, e.g. that you don't leak the allocated memory when an async exception comes in (e.g. from the `timeout` function or the user pressing Ctrl+C and you handling it and continuing). > In general, one deals with async exceptions by using code blocks that temporarily disable them, like the `bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c` function does; > see its docs as https://hackage.haskell.org/package/base-4.12.0.0/docs/Control-Exception-Base.html#v:bracket. > Two examples of how non-bracketet `malloc` can go wrong: > > Example A (no ownership change involved): > > ptr <- mallocBytes 1000 > -- async exception comes in here > someOtherCodeDoingSomethingWith ptr > free ptr > > Example B: > > ptr <- mallocBytes 1000 > -- async exception comes in here > ffiCodeThatChangesOwnershipToCLibrary ptr > > This would be bad, your allocced-bytes are unreachable and will memory leak forever. > `bracket` can trivially solve the problem in example A, because the lifetime of `ptr` is lexically scoped. > > But for the handover in example B, the lifetime is not lexically scoped. > > You generally have 2 approaches to do a safe hand-over to C for non-lexically-scoped cases: > > 1. malloc the memory on the C side in the first place, and pass the pointer to Haskell so it can poke values in. In this case, the C side had the ownership the entire time, so it allocated and freed the memory. > > 2. Store the information whether Haskell still has the memory ownership somewhere, and always modify the pointer and this information together in some atomic fashion (for example using `bracket` so that it cannot be interrupted in the middle). > The pointer and a mutable Bool reference would be such an information pair. > Equivalent would be a double-pointer, where the outer pointer points to NULL to indicate that the memory is already owned by C. > > Below is a sketch of how to do it with the double-pointer approach: > > bracket > acquireResource > releaseResource > (\ptrPtr -> do > ptr <- peek ptrPtr > poke ptr ('c' :: Char) > poke ptr ('c' :: Word64) > mask_ $ do -- we don't want to get interrupted in this block > ffiCodeThatChangesOwnershipToCLibrary ptr > poke ptrPtr nullPtr > -- do some more work here > return yourresult > ) > > where > acquireResource :: IO (Ptr (Ptr void)) > acquireResource = do > ptrPtr :: Ptr (Ptr void) <- malloc > ptr :: Ptr void <- malloc > poke ptrPtr ptr > return ptrPtr > > releaseResource :: Ptr (Ptr void) -> IO yourresult > releaseResource ptrPtr = do > -- If ptrPtr points to NULL, then the ownership change happend. > -- In that case we don't have to free `ptr` (and we cannot, as it is NULL). > -- Otherwise, we still own the memory, and free it. > ptr <- peek ptrPtr > when (ptr == nullPtr) $ free ptr > free ptrPtr > > (It is recommended to get familiar with `bracket` and `mask_` before understanding this.) > > The above works in a single-threaded case; if concurrency comes into play and you wrote code so that parts of this might be executed by different threads, you'll naturally have to put locks (e.g. `MVar`s) around the `poke ptrPtr ...` and the place where the `== nullPtr` check is done. > > I hope this helps! > > Niklas > > > PS: > I work for a Haskell consultancy. If answers like this would help move your project forward, consider us :) -- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com. From george at wils.online Tue Jan 15 06:54:28 2019 From: george at wils.online (George Wilson) Date: Tue, 15 Jan 2019 16:54:28 +1000 Subject: [Haskell-cafe] ANN: New Haskell.org Committee Member Message-ID: Following the nomination period and discussion, the Haskell.org committee has selected the following member for a new three-year term, expiring 2021: * Emily Pillmore As per the rules of the committee, this discussion was held among the current members of the committee, and the outgoing member of the committee who was not seeking reappointment. Thank you to all the many candidates who submitted a self-nomination. We received a number of strong nominations. We would encourage all those who nominated themselves to consider self-nominating again in the future. The outgoing member is Gershom Bazerman. He served not one but two terms for the Haskell.org committee, and he was chair during his last term. During this long period, Gershom has undeniably made the community a better place with his leadership and efforts. Thank you for your service! Since Gershom was our chair, the committee, including the new member, will hold a discussion and elect a new chair from amongst ourselves. Regards, George Wilson From frantisek at farka.eu Tue Jan 15 09:46:59 2019 From: frantisek at farka.eu (=?utf-8?Q?Franti=C5=A1ek?= Farka) Date: Tue, 15 Jan 2019 09:46:59 +0000 Subject: [Haskell-cafe] PPDP 2019 CFP - Principles and Practice of Declarative Programming Message-ID: <20190115094645.GA1323@farka.eu> [Apologies for cross-posting; please circulate] ====================================================================== CALL FOR PAPERS -- PPDP 2019 21st International Symposium on Principles and Practice of Declarative Programming 7–9 October 2019, Porto, Portugal Collocated with FM'19 http://ppdp2019.macs.hw.ac.uk ====================================================================== Important Dates --------------- Title and abstract registration 26 April 2019 (AoE) Paper submission 3 May 2019 (AoE) Rebuttal period (48 hours) 3 June 2019 (AoE) Author notification 14 June 2019 Final paper version 15 July 2019 Conference 7–9 October 2019 About PPDP ---------- The PPDP 2019 symposium brings together researchers from the declarative programming communities, including those working in the functional, logic, answer-set, and constraint handling programming paradigms. The goal is to stimulate research in the use of logical formalisms and methods for analyzing, performing, specifying, and reasoning about computations, including mechanisms for concurrency, security, static analysis, and verification. Scope ----- Submissions are invited on all topics related to declarative programming, from principles to practice, from foundations to applications. Topics of interest include, but are not limited to - Language Design: domain-specific languages; interoperability; concurrency, parallelism, and distribution; modules; probabilistic languages; reactive languages; database languages; knowledge representation languages; languages with objects; language extensions for tabulation; metaprogramming. - Implementations: abstract machines; interpreters; compilation; compile-time and run-time optimization; memory management. - Foundations: types; logical frameworks; monads and effects; semantics. - Analysis and Transformation: partial evaluation; abstract interpretation; control flow; data flow; information flow; termination analysis; resource analysis; type inference and type checking; verification; validation; debugging; testing. - Tools and Applications: programming and proof environments; verification tools; case studies in proof assistants or interactive theorem provers; certification; novel applications of declarative programming inside and outside of CS; declarative programming pearls; practical experience reports and industrial application; education. The PC chair (Ekaterina Komendanstkaya ) will be happy to advise on the appropriateness of a topic. Submission Categories --------------------- Submissions can be made in three categories: regular Research Papers, System Descriptions, and Experience Reports. Submissions of Research Papers must present original research which is unpublished and not submitted elsewhere. They must not exceed 12 pages ACM style 2-column (including figures, but excluding bibliography). Work that already appeared in unpublished or informally published workshop proceedings may be submitted (please contact the PC chair in case of questions). Research papers will be judged on originality, significance, correctness, clarity, and readability. Submission of System Descriptions must describe a working system whose description has not been published or submitted elsewhere. They must not exceed 10 pages and should contain a link to a working system. System Descriptions must be marked as such at the time of submission and will be judged on originality, significance, usefulness, clarity, and readability. Submissions of Experience Reports are meant to help create a body of published, refereed, citable evidence where declarative programming such as functional, logic, answer-set, constraint programming, etc., is used in practice. They must not exceed 5 pages **including references**. Experience Reports must be marked as such at the time of submission and need not report original research results. They will be judged on significance, usefulness, clarity, and readability. Supplementary material may be provided in a clearly marked appendix beyond the above-mentioned page limits. Reviewers are not required to study any material beyond the respective page limit. Format of a Submission ---------------------- For each paper category, you must use the most recent version of the "Current ACM Master Template" which is available at . The most recent version at the time of writing is 1.48. You must use the LaTeX sigconf proceedings template as the conference organizers are unable to process final submissions in other formats. In case of problems with the templates, contact ACM's TeX support team at Aptara . Authors should note ACM's statement on author's rights (http://authors.acm.org/) which apply to final papers. Submitted papers should meet the requirements of ACM's plagiarism policy (http://www.acm.org/publications/policies/plagiarism_policy). Requirements for Publication ---------------------------- At least one author of each accepted submission will be expected to attend and present the work at the conference. The pc chair may retract a paper that is not presented. The pc chair may also retract a paper if complaints about the paper's correctness are raised which cannot be resolved by the final paper deadline. Program Committee Chair ----------------------- Ekaterina Komendantskaya Heriot-Watt University, UK Program Committee ----------------- Henning Basold CNRS, ENS de Lyon, France Jasmin Christian Blanchette Vrije Universiteit Amsterdam, The Netherlands Maria Paola Bonacina University of Verona, Italy Dmitry Boulytchev Saint–Petersburg University, Russia William Byrd University of Alabama at Birmingham, USA Ornela Dardha University of Glasgow, UK Marco Gaboardi University at Buffalo, SUNY, USA Arie Gurfinkel University of Waterloo, Canada Zhenjiang Hu National Institute of Informatics, Japan Moa Johansson Chalmers University of Technology, Sweden Neelakantan Krishnaswami University of Cambridge, UK Ralf Lämmel University of Koblenz · Landau, Germany Anthony Widjaja Lin University of Oxford, UK Aart Middeldorp University of Innsbruck, Austria Gopalan Nadathur University of Minnesota, USA Keisuke Nakano Tohoku University, Japan Dominic Orchard University of Kent, UK Alberto Pardo University of the Republic, Uruguay Aleksy Schubert University of Warsaw, Poland Peter J. Stuckey The University of Melbourne, Australia Tarmo Uustalu Reykjavik University, Iceland Local Chair ----------- José Nuno Oliveira INESC TEC & University of Minho, Portugal For any queries about local issues please contact the local organiser, José Nuno Oliveira . Publicity Chair --------------- František Farka University of St Andrews & Heriot-Watt University, UK From dennis.raddle at gmail.com Wed Jan 16 07:26:40 2019 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Tue, 15 Jan 2019 23:26:40 -0800 Subject: [Haskell-cafe] building with stack, need some older versions for one library Message-ID: I'm assembling a large stack project from various places. I just did "stack new", using the default resolver, copied in most of my code, and got it compiled. Except I'm stuck on one thing. I need to use the 'midi-0.2.2' library (reads/writes MIDI files). Its depends on older versions of the same of the core packages. What should I do now? Do I modify the LTS resolver to something older and then type "stack build" again? How can I find an appropriate resolver without hit-and-miss? Mike -------------- next part -------------- An HTML attachment was scrubbed... URL: From lysxia at gmail.com Wed Jan 16 07:30:55 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Wed, 16 Jan 2019 08:30:55 +0100 Subject: [Haskell-cafe] building with stack, need some older versions for one library In-Reply-To: References: Message-ID: Stackage has the list of snapshots a package (all its versions) appears in. https://www.stackage.org/package/midi/snapshots 0.2.2 doesn't appear, but shouldn't 0.2.2.2 and 0.2.2.1 be compatible with it? Li-yao On 1/16/19 8:26 AM, Dennis Raddle wrote: > I'm assembling a large stack project from various places. > > I just did "stack new", using the default resolver, copied in most of my > code, and got it compiled. > > Except I'm stuck on one thing. I need to use the 'midi-0.2.2' library > (reads/writes MIDI files). Its depends on older versions of the same of > the core packages. > > What should I do now? Do I modify the LTS resolver to something older > and then type "stack build" again? How can I find an appropriate > resolver without hit-and-miss? > > Mike > > > _______________________________________________ > 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 magicloud.magiclouds at gmail.com Wed Jan 16 08:52:42 2019 From: magicloud.magiclouds at gmail.com (Magicloud Magiclouds) Date: Wed, 16 Jan 2019 16:52:42 +0800 Subject: [Haskell-cafe] How to set ghc options while building Setup.hs in cabal package? Message-ID: Hi, I have some code in Setup.hs in a cabalized project. I'd like them to be warning-free. But I could not find a way to set -Wall. I tried ghc-options in ~/.cabal/config. But seems like it did not kick in. ``` /bin/ghc --make -fbuilding-cabal-package -odir /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup -hidir /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup -i -i/home/shida/src/Personal/cairo-core/. -optP-include -optP/home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup_macros.h -hide-all-packages -no-user-package-db -package-db /home/shida/.cabal/store/ghc-8.6.3/package.db -package-db /home/shida/src/Personal/cairo-core/dist-newstyle/packagedb/ghc-8.6.3 -package-id Cabal-2.4.0.1 -package-id base-4.12.0.0 -package-id directory-1.3.3.0 -package-id filepath-1.4.2.1 -package-id haskell-src-exts-1.21.0-f3e84a9ee8883b0dcaaaaba712d74996854b441aa843a4dedc055c685debcfdb /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup.hs -o /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup -threaded ``` -- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com. From dennis.raddle at gmail.com Wed Jan 16 09:20:03 2019 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Wed, 16 Jan 2019 01:20:03 -0800 Subject: [Haskell-cafe] intero flymake not working Message-ID: I recently updated a stack project to a later version of GHC, and Intero isn't quite behaving the same as before. I can't see any evidence that flycheck or flymake is working. Any idea what to look for? Mike -------------- next part -------------- An HTML attachment was scrubbed... URL: From dhelta.diaz at gmail.com Wed Jan 16 09:55:36 2019 From: dhelta.diaz at gmail.com (=?UTF-8?Q?Daniel_D=C3=ADaz_Casanueva?=) Date: Wed, 16 Jan 2019 10:55:36 +0100 Subject: [Haskell-cafe] How to set ghc options while building Setup.hs in cabal package? In-Reply-To: References: Message-ID: Hi. I haven't tried myself, but perhaps the OPTIONS_GHC pragma will do what you want. Just add {-# OPTIONS_GHC -Wall #-} to the beginning of your Setup.hs file. More info: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/using.html#source-file-options I hope that helps. Best, Daniel Am Mi., 16. Jan. 2019, 09:54 hat Magicloud Magiclouds < magicloud.magiclouds at gmail.com> geschrieben: > Hi, > > I have some code in Setup.hs in a cabalized project. I'd like them to > be warning-free. But I could not find a way to set -Wall. > > I tried ghc-options in ~/.cabal/config. But seems like it did not kick in. > > ``` > /bin/ghc --make -fbuilding-cabal-package -odir > > /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup > -hidir > /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup > -i -i/home/shida/src/Personal/cairo-core/. -optP-include > > -optP/home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup_macros.h > -hide-all-packages -no-user-package-db -package-db > /home/shida/.cabal/store/ghc-8.6.3/package.db -package-db > /home/shida/src/Personal/cairo-core/dist-newstyle/packagedb/ghc-8.6.3 > -package-id Cabal-2.4.0.1 -package-id base-4.12.0.0 -package-id > directory-1.3.3.0 -package-id filepath-1.4.2.1 -package-id > > haskell-src-exts-1.21.0-f3e84a9ee8883b0dcaaaaba712d74996854b441aa843a4dedc055c685debcfdb > > /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup.hs > -o > /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup > -threaded > ``` > -- > 竹密岂妨流水过 > 山高哪阻野云飞 > > And for G+, please use magiclouds#gmail.com. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From magicloud.magiclouds at gmail.com Wed Jan 16 10:32:58 2019 From: magicloud.magiclouds at gmail.com (Magicloud Magiclouds) Date: Wed, 16 Jan 2019 18:32:58 +0800 Subject: [Haskell-cafe] How to set ghc options while building Setup.hs in cabal package? In-Reply-To: References: Message-ID: Ah, thanks. On Wed, Jan 16, 2019 at 5:55 PM Daniel Díaz Casanueva wrote: > > Hi. > > I haven't tried myself, but perhaps the OPTIONS_GHC pragma will do what you want. Just add > > {-# OPTIONS_GHC -Wall #-} > > to the beginning of your Setup.hs file. > > More info: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/using.html#source-file-options > > I hope that helps. > > Best, > Daniel > > Am Mi., 16. Jan. 2019, 09:54 hat Magicloud Magiclouds geschrieben: >> >> Hi, >> >> I have some code in Setup.hs in a cabalized project. I'd like them to >> be warning-free. But I could not find a way to set -Wall. >> >> I tried ghc-options in ~/.cabal/config. But seems like it did not kick in. >> >> ``` >> /bin/ghc --make -fbuilding-cabal-package -odir >> /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup >> -hidir /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup >> -i -i/home/shida/src/Personal/cairo-core/. -optP-include >> -optP/home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup_macros.h >> -hide-all-packages -no-user-package-db -package-db >> /home/shida/.cabal/store/ghc-8.6.3/package.db -package-db >> /home/shida/src/Personal/cairo-core/dist-newstyle/packagedb/ghc-8.6.3 >> -package-id Cabal-2.4.0.1 -package-id base-4.12.0.0 -package-id >> directory-1.3.3.0 -package-id filepath-1.4.2.1 -package-id >> haskell-src-exts-1.21.0-f3e84a9ee8883b0dcaaaaba712d74996854b441aa843a4dedc055c685debcfdb >> /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup.hs >> -o /home/shida/src/Personal/cairo-core/dist-newstyle/build/x86_64-linux/ghc-8.6.3/cairo-core-1.16.0/setup/setup >> -threaded >> ``` >> -- >> 竹密岂妨流水过 >> 山高哪阻野云飞 >> >> And for G+, please use magiclouds#gmail.com. >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. -- 竹密岂妨流水过 山高哪阻野云飞 And for G+, please use magiclouds#gmail.com. From johannes.waldmann at htwk-leipzig.de Wed Jan 16 12:24:57 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Wed, 16 Jan 2019 13:24:57 +0100 Subject: [Haskell-cafe] looking for yesod-newsfeed example Message-ID: <18422a9f-5fc4-0475-78c8-744753e9ac2e@htwk-leipzig.de> Dear Cafe, I want to add news feeds to a yesod application. Is there some example code that shows real-life usage of https://hackage.haskell.org/package/yesod-newsfeed ? Thanks - J.W. From michael at snoyman.com Wed Jan 16 12:35:29 2019 From: michael at snoyman.com (Michael Snoyman) Date: Wed, 16 Jan 2019 14:35:29 +0200 Subject: [Haskell-cafe] looking for yesod-newsfeed example In-Reply-To: <18422a9f-5fc4-0475-78c8-744753e9ac2e@htwk-leipzig.de> References: <18422a9f-5fc4-0475-78c8-744753e9ac2e@htwk-leipzig.de> Message-ID: Two immediately come to my mind: https://github.com/snoyberg/snoyman.com/blob/28a1094437fa5ec2704e094850a570d51c3cfa18/src/SnoymanCom.hs#L444 https://github.com/yesodweb/yesodweb.com/blob/5c6414a5ac54fd966bb608ee5780aaa3d5241c5b/src/Handler/Blog.hs#L73 HTH, Michael On Wed, Jan 16, 2019 at 2:25 PM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > Dear Cafe, I want to add news feeds to a yesod application. > Is there some example code that shows real-life usage of > https://hackage.haskell.org/package/yesod-newsfeed ? > Thanks - J.W. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tdammers at gmail.com Wed Jan 16 16:12:24 2019 From: tdammers at gmail.com (Tobias Dammers) Date: Wed, 16 Jan 2019 17:12:24 +0100 Subject: [Haskell-cafe] HDBC database: error on accent table name In-Reply-To: <5BFFC089.1070505@oca.eu> References: <5BFFC089.1070505@oca.eu> Message-ID: <20190116161221.ipjmfbtfn2sbut3l@nibbler> On Thu, Nov 29, 2018 at 11:33:45AM +0100, Damien Mattei wrote: > Hi, > > i have this error: > *** Exception: SqlError {seState = "", seNativeError = 1064, seErrorMsg > = "You have an error in your SQL syntax; check the manual that > corresponds to your MariaDB server version for the right syntax to use > near 'es where Nom = 'A 20'' at line 1"} > > when doing this : > > rows_coordonnees <- quickQuery' conn "select * from sidonie.Coordonnées > where Nom = 'A 20'" [] > > it seems tha the tabel name: Coordonnées that contain an accent is > causing serious problem to the parser at some point, if i use a table > name without accent it works fine. > > i'm at the point to rename the table which have great impact on all the > project build with many other languages (Scheme) that deal correctly the > table name with accent. > > any idea? to make accent works with haskell. So you're using MariaDB, which is essentially MySQL, and that means that queries are sent as bytestrings without encoding information; the correct encoding for each client is stored per connection, and defaults to whatever is the server default IIRC. Therefor, as a general best practice, it is common to set the connection charset explicitly at the beginning, and make sure the queries you send are encoded accordingly. HDBC will not however do this for you. HDBC-MySQL uses withCStringLen to marshal Haskell's String type to the raw C string that MySQL expects, and that uses the current locale (on the client, that is) for the conversion - on most modern *nix installs, this is going to amount to utf-8. A typical MySQL (or MariaDB) server's default encoding, however, is NOT utf-8, but some flavor of latin-1. So my wild guess as to why it fails is this - the server is set to default to latin-1, while your Haskell code uses the local system's locale, and thus encodes queries as UTF-8. This resource explains MySQL connection charsets and collations in more depth: https://dev.mysql.com/doc/refman/5.7/en/charset-connection.html In a nutshell, right after connecting, and assuming your client system uses some UTF-8 locale, you run the query "SET NAMES utf8;" once, and that should do the trick. From ozataman at gmail.com Wed Jan 16 16:28:14 2019 From: ozataman at gmail.com (Ozgun Ataman) Date: Wed, 16 Jan 2019 11:28:14 -0500 Subject: [Haskell-cafe] [Job] Soostone is hiring Haskell developers (NYC or remote) Message-ID: Dear Haskell Cafe, Soostone (http://www.soostone.com) is looking to hire for engineering positions in our Haskell development and operations team. At Soostone, you will be crafting and deploying products with various AI and optimization elements dealing with large quantities of data at their core to transform the way our clients tackle opportunities in consumer intelligence, marketing and pricing. We aim to develop high quality, reliable software while moving fast, being pragmatic and constantly improving our capabilities. Haskell usually makes this a little easier and we're big fans. We are located in New York City, but these are remote-friendly positions with little to no travel requirements. We will prefer candidates in North America, but will also consider qualified applications from elsewhere as long as the legal realities can be aligned. We are flexible in the work arrangement; depending on your jurisdiction and circumstances, these will either be direct hire or full-time contractor positions. Day-to-day, you will be interacting with technologies/components/libraries such as: - A relatively large Haskell codebase (500+ modules) spanning multiple applications and several reusable in-house libraries/packages - 200+ libraries from the Haskell ecosystem - Databases: PostgreSQL, Redis, DynamoDB - Analytics: Google BigQuery, tailor-made SQL EDSL/automation - A large suite of AWS and Google cloud solutions - APIs responding to millions of requests per day - Datasets spanning billions of rows …and typical activities will include: - Collaborative architecting and software design around new features - End-to-end implementation of entire components, from first line of code to the test suite - Interfacing with other languages, API services, foreign interfaces/functions as needed - Opportunities to work on all aspects of our platform, including both backend and frontend - Design/implementation of DSLs/EDSLs that supercharge tedious elements in the ecosystem - Abstract functionality into libraries and other reusable tools that ease the pain for other developers - Be on the lookout for opportunities to contribute back to the community through OSS work - Occasional trips to the land of Python, Typescript/JavaScript and Purescript for mission-specific needs Candidates of all skill/experience levels are invited to apply and will receive consideration, although these positions are likely not ideal for Haskell beginners or entry level developers without any experience. If you're interested, we encourage you to submit an application even if we've previously had conversations. If you have OSS contributions or a listing/linking of previous projects, please let us know as that's tremendously helpful to us in getting to know you. Please see the link below for more detail on the position and to submit an application. You can also reach out to us at jobs at soostone.com for any questions or ask here and we'll do our best to answer. Job Link: https://soostone-inc.workable.com/jobs/678589 The Soostone Team -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.lelechenko at gmail.com Wed Jan 16 20:26:00 2019 From: andrew.lelechenko at gmail.com (Andrew Lelechenko) Date: Wed, 16 Jan 2019 20:26:00 +0000 Subject: [Haskell-cafe] Taking over maintainership of bitvec Message-ID: I would like to take over `bitvec` package (https://hackage.haskell.org/package/bitvec). Unfortunately, the source code has not been updated for years and the test suite does not build nowadays. There are also known issues. I have prepared patches and tried to reach its maintainer James Cook (cced) by email, but have not heard back. There was a takeover of another James' package in October 2018 (https://mail.haskell.org/pipermail/libraries/2018-October/029062.html). In that case James appeared to be out of reach. -- Best regards, Andrew From damien.mattei at gmail.com Wed Jan 16 21:07:41 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Wed, 16 Jan 2019 22:07:41 +0100 Subject: [Haskell-cafe] HDBC database: error on accent table name In-Reply-To: <20190116161221.ipjmfbtfn2sbut3l@nibbler> References: <5BFFC089.1070505@oca.eu> <20190116161221.ipjmfbtfn2sbut3l@nibbler> Message-ID: thank for your answer, since the time of question (late november 2018) as i had no solution else remove the accent from database which would have for consequence to change a lot in existing code (in Java,Scheme,Kawa and Haskell) i had used Database.MySQL.Simple which worked 'out of the box' for accents. i have checked the locale on both client and server and it is the same: LANG=en_US.UTF-8 client: [mattei at asteroide Haskell]$ echo $LANG en_US.UTF-8 server: [root at moita ~]# echo $LANG en_US.UTF-8 if i unset LANG it's worse all accent character display as ? or disappears: *Main> main 2139 select `NumBD` from 'sidonie.Coordonn?es' where Nom = 'A 20' *** Exception: SqlError {seState = "", seNativeError = 1064, seErrorMsg = "You have an error in your SQL syntax; check the manual that corresponds to your MariaDB server version for the right syntax to use near ''sidonie.Coordonnes' where Nom = 'A 20'' at line 1"} but the database seems to use latin1 as show below: MariaDB [sidonie]> SHOW FULL COLUMNS FROM Coordonnées; +----------------+-------------+-------------------+------+-----+---------+-------+---------------------------------+---------+ | Field | Type | Collation | Null | Key | Default | Extra | Privileges | Comment | +----------------+-------------+-------------------+------+-----+---------+-------+---------------------------------+---------+ | N° Fiche | int(11) | NULL | NO | PRI | 0 | | select,insert,update,references | | | Alpha 2000 | double | NULL | YES | | NULL | | select,insert,update,references | | | Delta 2000 | double | NULL | YES | | NULL | | select,insert,update,references | | | N° ADS | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | NomSidonie | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | mag1 | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | mag2 | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | N° BD | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | Spectre | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | N°Type | float | NULL | YES | | NULL | | select,insert,update,references | | | N° HIP | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | Orb | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | Modif | datetime | NULL | YES | | NULL | | select,insert,update,references | | | Date de saisie | datetime | NULL | YES | | NULL | | select,insert,update,references | | | Nom opérateur | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | | Nom | varchar(50) | latin1_swedish_ci | YES | | NULL | | select,insert,update,references | | +----------------+-------------+-------------------+------+-----+---------+-------+---------------------------------+---------+ 16 rows in set (0.00 sec) i still do not know woth HDBC where to put the options at the connection to set encoding in my code i had this: do conn <- connectMySQL defaultMySQLConnectInfo { mysqlHost = "moita", mysqlUser = "mattei", mysqlPassword = "" } i can not fin in doc an option for encoding http://hackage.haskell.org/package/HDBC-mysql-0.7.1.0/docs/Database-HDBC-MySQL.html#t:MySQLConnectInfo the solution to do :SET NAMES utf8; i try this: config <- quickQuery' conn "SET NAMES utf8" [] but i get an error : *Main> main *** Exception: SqlError {seState = "", seNativeError = 2053, seErrorMsg = "Attempt to read a row while there is no result set associated with the statement"} because SET return an empty result list, do not know how to make it work.... Damien On Wed, Jan 16, 2019 at 5:13 PM Tobias Dammers wrote: > On Thu, Nov 29, 2018 at 11:33:45AM +0100, Damien Mattei wrote: > > Hi, > > > > i have this error: > > *** Exception: SqlError {seState = "", seNativeError = 1064, seErrorMsg > > = "You have an error in your SQL syntax; check the manual that > > corresponds to your MariaDB server version for the right syntax to use > > near 'es where Nom = 'A 20'' at line 1"} > > > > when doing this : > > > > rows_coordonnees <- quickQuery' conn "select * from sidonie.Coordonnées > > where Nom = 'A 20'" [] > > > > it seems tha the tabel name: Coordonnées that contain an accent is > > causing serious problem to the parser at some point, if i use a table > > name without accent it works fine. > > > > i'm at the point to rename the table which have great impact on all the > > project build with many other languages (Scheme) that deal correctly the > > table name with accent. > > > > any idea? to make accent works with haskell. > > So you're using MariaDB, which is essentially MySQL, and that means that > queries are sent as bytestrings without encoding information; the > correct encoding for each client is stored per connection, and defaults > to whatever is the server default IIRC. Therefor, as a general best > practice, it is common to set the connection charset explicitly at the > beginning, and make sure the queries you send are encoded accordingly. > HDBC will not however do this for you. > > HDBC-MySQL uses withCStringLen to marshal Haskell's String type to the > raw C string that MySQL expects, and that uses the current locale (on > the client, that is) for the conversion - on most modern *nix installs, > this is going to amount to utf-8. A typical MySQL (or MariaDB) server's > default encoding, however, is NOT utf-8, but some flavor of latin-1. > > So my wild guess as to why it fails is this - the server is set to > default to latin-1, while your Haskell code uses the local system's > locale, and thus encodes queries as UTF-8. > > This resource explains MySQL connection charsets and collations in more > depth: https://dev.mysql.com/doc/refman/5.7/en/charset-connection.html > > In a nutshell, right after connecting, and assuming your client system > uses some UTF-8 locale, you run the query "SET NAMES utf8;" once, and > that should do the trick. > _______________________________________________ > 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 rudy at matela.com.br Thu Jan 17 02:10:29 2019 From: rudy at matela.com.br (Rudy Matela) Date: Wed, 16 Jan 2019 23:10:29 -0300 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing Message-ID: <20190117021029.dra5xfb3wp75g77f@zero.localdomain> Hello Haskell Café, A new version of LeanCheck is out (v0.9.0). LeanCheck is a property testing library (like QuickCheck) that tests values enumeratively. _Example._ Here's a simple example of LeanCheck in action showing that sorting is idempotent and list union is not commutative: > import Test.LeanCheck > import Data.List (sort, union) > check $ \xs -> sort (sort xs) == sort (xs::[Int]) +++ OK, passed 200 tests. > check $ \xs ys -> xs `union` ys == ys `union` (xs::[Int]) *** Failed! Falsifiable (after 4 tests): [] [0,0] LeanCheck works on all types that are instances of the Listable typeclass and is able to derive instances automatically using either Template Haskell or GHC.Generics. See [LeanCheck's Haddock documentation] for more details. _Whats new?_ Version 0.9.0 marks the addition of Listable typeclass instances for most standard Haskell types defined in the Haskell 2010 Language Report. This means you'll be able to test more functions without needing to define Listable instances yourself. [LeanCheck's changelog] provides more details. A separate package [leancheck-instances] provides instances for other types in the Haskell Platform. _Installing._ You can find LeanCheck on [Hackage] or [GitHub]. It is also tracked on [Stackage]. As usual, you can install it with: $ cabal install leancheck -- Rudy [Hackage]: https://hackage.haskell.org/package/leancheck [GitHub]: https://github.com/rudymatela/leancheck [Stackage]: https://www.stackage.org/package/leancheck [LeanCheck's changelog]: https://hackage.haskell.org/package/leancheck/changelog [LeanCheck's Haddock documentation]: https://hackage.haskell.org/package/leancheck/docs/Test-LeanCheck.html -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Thu Jan 17 06:08:30 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Thu, 17 Jan 2019 01:08:30 -0500 Subject: [Haskell-cafe] Taking over maintainership of bitvec In-Reply-To: References: Message-ID: <644E9E86-896A-46D1-B7E2-78EFA75F5018@dukhovni.org> > On Jan 16, 2019, at 3:26 PM, Andrew Lelechenko wrote: > > I would like to take over `bitvec` package > (https://hackage.haskell.org/package/bitvec). > > Unfortunately, the source code has not been updated for years and the > test suite does not build nowadays. There are also known issues. I > have prepared patches and tried to reach its maintainer James Cook > (cced) by email, but have not heard back. If you do (good luck!), I hope you might find a bit of time for less terse documentation, adding some expository text about the module in general above the brief per-function descriptions, and ideally a few code snippets illustrating usage. Many a library, and I think this one among them, has documentation that is much too anaemic. -- Viktor. From aeroboy94 at gmail.com Thu Jan 17 09:57:17 2019 From: aeroboy94 at gmail.com (Arian van Putten) Date: Thu, 17 Jan 2019 10:57:17 +0100 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing In-Reply-To: <20190117021029.dra5xfb3wp75g77f@zero.localdomain> References: <20190117021029.dra5xfb3wp75g77f@zero.localdomain> Message-ID: Awesome. I always wondered what the pros/cons are compared to random testing like Quick check. When should I reach to enumerative testing? On Thu, Jan 17, 2019, 03:11 Rudy Matela Hello Haskell Café, > > A new version of LeanCheck is out (v0.9.0). LeanCheck is a property > testing library (like QuickCheck) that tests values enumeratively. > > *Example.* Here’s a simple example of LeanCheck in action showing that > sorting is idempotent and list union is not commutative: > > > import Test.LeanCheck > > import Data.List (sort, union) > > > check $ \xs -> sort (sort xs) == sort (xs::[Int]) > +++ OK, passed 200 tests. > > > check $ \xs ys -> xs `union` ys == ys `union` (xs::[Int]) > *** Failed! Falsifiable (after 4 tests): > [] [0,0] > > LeanCheck works on all types that are instances of the Listable typeclass > and is able to derive instances automatically using either Template Haskell > or GHC.Generics. See LeanCheck’s Haddock documentation > > for more details. > > *Whats new?* Version 0.9.0 marks the addition of Listable typeclass > instances for most standard Haskell types defined in the Haskell 2010 > Language Report. This means you’ll be able to test more functions without > needing to define Listable instances yourself. LeanCheck’s changelog > provides more > details. > > A separate package [leancheck-instances] provides instances for other > types in the Haskell Platform. > > *Installing.* You can find LeanCheck on Hackage > or GitHub > . It is also tracked on Stackage > . As usual, you can install > it with: > > $ cabal install leancheck > > – Rudy > _______________________________________________ > 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 Jan 17 13:33:14 2019 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Thu, 17 Jan 2019 14:33:14 +0100 (CET) Subject: [Haskell-cafe] determine a type by universal property Message-ID: <1717582736.1615177.1547731994157@webmail.strato.de> Dear cafe, We know how to derive free theorems from a type [1]. But there exist also examples where the existence of a certain function determines the type. I suppose this is a special case of a free theorem? For example, every functor that is right adjoint to another functor in Hask is representable in the sense of [2], that is, isomorphic to (r->) for some type r. [see * below] I have two type signatures where I conjecture the only functors satisfying these are the Identity functor and functors of the form (,)s. Can anyone give hints as how to tackle a proof? Signature 1: What functors t admit a function forall f. Functor f => t (f a) -> f (t a) Signature 2: What functors t admit a function t (t a -> b) -> a -> b Signature 1 is like Data.Traversable.sequence, only the Applicative constraint is weakened to Functor. It is somewhat dual to Distributive [3]. Signature 2 can, with some currying, for t = (,)s be transformed into Data.Function.flip. I am unable to comprehend the free theorem for signature 2. For signature 1, the Rank-2 type seems to cause trouble with free-theorems? Thanks, Olaf [1] https://hackage.haskell.org/package/free-theorems [2] https://hackage.haskell.org/package/adjunctions [3] https://hackage.haskell.org/package/distributive [*] The argument goes like this: (1) bottoms aside, every type x is isomorphic to () -> x. (2) f and g are adjoint if and only if (f a -> b) is isomorphic to (a -> g b). (3) g b is isomorphic to () -> g b by (1) with x = g b (4) () -> g b is isomorphic to f () -> b by (2) with a = (). (5) By (3) and (4), g b is isomorphic to f () -> b. We have found g = (r->) with r = f (). From mail at joachim-breitner.de Thu Jan 17 14:46:01 2019 From: mail at joachim-breitner.de (Joachim Breitner) Date: Thu, 17 Jan 2019 15:46:01 +0100 Subject: [Haskell-cafe] determine a type by universal property In-Reply-To: <1717582736.1615177.1547731994157@webmail.strato.de> References: <1717582736.1615177.1547731994157@webmail.strato.de> Message-ID: Hi, Am Donnerstag, den 17.01.2019, 14:33 +0100 schrieb Olaf Klinke: > I have two type signatures where I conjecture the only functors satisfying these > are the Identity functor and functors of the form (,)s. Can anyone give hints as > how to tackle a proof? > > Signature 1: What functors t admit a function > forall f. Functor f => t (f a) -> f (t a) What about the functor data Void1 a It seems I can write g :: forall f. Functor f => t (f a) -> f (t a) g x = case x of {} but Void1 is not the identity. (I guess it is `(,) Void`, if you want…) So if you allow the latter, let’s try a proof. Assume we have t, and g :: forall f. Functor f => t (f a) -> f (t a) We want to prove that there is an isomorphism from t to ((,) s) for some type s. Define s = t () (because what else could it be.) Now we need functions f1 :: forall a. t a -> (t (), a) f2 :: forall a. (t (), a) -> t a that are isomorphisms. Here is one implementation: f1 :: forall a. t a -> (t (), a) f1 = swap . g . fmap (λx → (x,())) {- note: x1 :: t a x2 :: t ((,) a ()) x2 = fmap (λx → (x,())) x1 x3 :: (,) a (t ()) x3 = g x2 x4 :: (t (), a) x4 = swap x3 -} f2 :: forall a. (t (), a) -> t a f2 (s, x) = x <$ s Now, are these isomorphisms? At this point I am not sure how to proceed… probably invoking the free theorem of g? But even that will not work nicely. Consider type T = (,) Integer g :: forall f. Functor => T (f a) -> f (T a) g (c, fx) = (,) (c + 1) <$> fx here we count the number of invocations of g. Surely with this g, f2 . f1 cannot be the identity. Cheers, Joachim -- 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 oleg.grenrus at iki.fi Thu Jan 17 15:00:54 2019 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Thu, 17 Jan 2019 17:00:54 +0200 Subject: [Haskell-cafe] determine a type by universal property In-Reply-To: References: <1717582736.1615177.1547731994157@webmail.strato.de> Message-ID: I'd say that     forall f. t (f a) -> f (t a) with f = Identity     should be identity. And there's probably some composition/associativity law, about t (f (g a)) -> f (g (t a)) --- I also sent direct answer, which would benefit from this additional laws too: Lensy/Traveral business this is. I immediately see     forall f a b. Functor f => (a -> f b) -> t a -> f (t b) which is Lens' (t a) a, which is an iso    exists e. (t a) ~ (e, a) Maybe that helps to find some pointers. You can remove Functor f using yoneda lemma, so you get Rank1Type     forall a b. t a -> (a, b -> t b) For which you can apply free theorem's machinery? - Oleg On 17.1.2019 16.46, Joachim Breitner wrote: > Hi, > > Am Donnerstag, den 17.01.2019, 14:33 +0100 schrieb Olaf Klinke: >> I have two type signatures where I conjecture the only functors satisfying these >> are the Identity functor and functors of the form (,)s. Can anyone give hints as >> how to tackle a proof? >> >> Signature 1: What functors t admit a function >> forall f. Functor f => t (f a) -> f (t a) > What about the functor > > data Void1 a > > It seems I can write > > g :: forall f. Functor f => t (f a) -> f (t a) > g x = case x of {} > > but Void1 is not the identity. (I guess it is `(,) Void`, if you want…) > > So if you allow the latter, let’s try a proof. Assume we have t, and > > g :: forall f. Functor f => t (f a) -> f (t a) > > We want to prove that there is an isomorphism from t to ((,) s) for > some type s. Define > > s = t () > > (because what else could it be.) Now we need functions > > f1 :: forall a. t a -> (t (), a) > f2 :: forall a. (t (), a) -> t a > > that are isomorphisms. Here is one implementation: > > f1 :: forall a. t a -> (t (), a) > f1 = swap . g . fmap (λx → (x,())) > > {- note: > x1 :: t a > x2 :: t ((,) a ()) > x2 = fmap (λx → (x,())) x1 > x3 :: (,) a (t ()) > x3 = g x2 > x4 :: (t (), a) > x4 = swap x3 > -} > > f2 :: forall a. (t (), a) -> t a > f2 (s, x) = x <$ s > > Now, are these isomorphisms? At this point I am not sure how to > proceed… probably invoking the free theorem of g? But even that will > not work nicely. Consider > > type T = (,) Integer > g :: forall f. Functor => T (f a) -> f (T a) > g (c, fx) = (,) (c + 1) <$> fx > > here we count the number of invocations of g. Surely with this g, > f2 . f1 cannot be the identity. > > > Cheers, > Joachim > > _______________________________________________ > 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 -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 833 bytes Desc: OpenPGP digital signature URL: From johannes.waldmann at htwk-leipzig.de Thu Jan 17 17:28:32 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 17 Jan 2019 18:28:32 +0100 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing Message-ID: Yes, leancheck is awesome. > When should I reach to enumerative testing? I think enumerative testing is best suited to algebraic data types. https://mail.haskell.org/pipermail/haskell-cafe/2018-September/129951.html In the past I had one standard example where random enumeration seems better than enumerative: (non)associativity of floating point ops (I like to use this in teaching) That's immediate in Quickcheck quickCheck $ \ x y z -> (x::Double) + (y+z) == (x+y)+z *** Failed! Falsifiable (after 3 tests and 3 shrinks): -0.3 -1.4266097805446862 -1.2543117889178947 You don't get to see a counterexample in Smallcheck Prelude Test.SmallCheck> smallCheck 5 $ \ x y z -> (x::Double) + (y+z) == (x+y)+z Completed 50653 tests without failure. To my surprise, we now have Prelude Test.LeanCheck> check $ \ x y z -> (x::Double) + (y+z) == (x+y)+z *** Failed! Falsifiable (after 87 tests): 0.0 Infinity (-Infinity) and I get the above (with "real" numbers) via Prelude Test.LeanCheck> checkFor 1000 $ \ x y z -> isInfinite x || isInfinite y || isInfinite z || (x::Double) + (y+z) == (x+y)+z *** Failed! Falsifiable (after 306 tests): 1.0 1.0 0.3333333333333333 Turns out the enumeration in Leancheck uses Rationals, while Smallcheck uses encodeFloat, which happens to produce only "nice" numbers (very few bits set) in the beginning. Prelude Test.LeanCheck> list 3 series :: [Double] [0.0,1.0,-1.0,2.0,0.5,-2.0,4.0,0.25,-0.5,-4.0,-0.25] Prelude Test.LeanCheck> take 12 $ list :: [Double] [0.0,1.0,-1.0,Infinity,0.5,2.0,-Infinity,-0.5,-2.0,0.3333333333333333,3.0,-0.3333333333333333] - J.W. PS: this post wouldn't be complete without me complaining that I cannot (easily) put the type annotation where it belongs - in the declaration of the name: Prelude Test.LeanCheck> check $ \ (x::Double) y z -> x + (y+z) == (x+y)+z :22:12: error: Illegal type signature: ‘Double’ Type signatures are only allowed in patterns with ScopedTypeVariables Wat? TypeVariables? There aren't any! From johannes.waldmann at htwk-leipzig.de Thu Jan 17 17:34:00 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Thu, 17 Jan 2019 18:34:00 +0100 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing In-Reply-To: References: Message-ID: <9cf62b91-b75f-66c4-5046-00b7d1ef8da9@htwk-leipzig.de> Sorry - I copy-pasted the prompt wrongly. This is actually using Smallcheck: > Prelude Test.LeanCheck> list 3 series :: [Double] > [0.0,1.0,-1.0,2.0,0.5,-2.0,4.0,0.25,-0.5,-4.0,-0.25] and this is Leancheck: > Prelude Test.LeanCheck> take 12 $ list :: [Double] > [0.0,1.0,-1.0,Infinity,0.5,2.0,-Infinity,-0.5,-2.0,0.3333333333333333,3.0,-0.3333333333333333] From rudy at matela.com.br Fri Jan 18 00:24:02 2019 From: rudy at matela.com.br (Rudy Matela) Date: Thu, 17 Jan 2019 21:24:02 -0300 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing In-Reply-To: References: <20190117021029.dra5xfb3wp75g77f@zero.localdomain> Message-ID: <20190118002402.pztxhsz4wdigvfx7@zero.localdomain> Hi Arian, When in doubt and with a bit of time to spare, you can always use both :-) But here is some quick list of pros and cons: * LeanCheck/enumerative guarantees the smallest/simplest counterexample if one is found. This without the need of shrinking. * LeanCheck/enumerative allows for existential properties. * LeanCheck/enumerative guarantees that tests aren't repeated most of the time. * QuickCheck/random always hits different test cases, so in the long run you may get more test coverage. With LeanCheck you only get more coverage when you configure more tests. * LeanCheck/enumerative is more memory intensive when compared to QuickCheck/random. With LeanCheck you may run out of memory when you're running tens of millions of tests. You can find more details here: https://github.com/rudymatela/leancheck/blob/master/doc/faq.md#what-are-the-differences-between-quickcheck-and-leancheck On Thu, Jan 17, 2019 at 10:57:17AM +0100, Arian van Putten wrote: > Awesome. I always wondered what the pros/cons are compared to random > testing like Quick check. When should I reach to enumerative testing? -------------- next part -------------- An HTML attachment was scrubbed... URL: From rudy at matela.com.br Fri Jan 18 01:00:35 2019 From: rudy at matela.com.br (Rudy Matela) Date: Thu, 17 Jan 2019 22:00:35 -0300 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing In-Reply-To: References: Message-ID: <20190118010035.sweof4hymhnmkw43@zero.localdomain> On Thu, Jan 17, 2019 at 06:28:32PM +0100, Johannes Waldmann wrote: > Prelude Test.LeanCheck> checkFor 1000 $ \ x y z -> isInfinite x || > isInfinite y || isInfinite z || (x::Double) + (y+z) == (x+y)+z > *** Failed! Falsifiable (after 306 tests): > 1.0 1.0 0.3333333333333333 > > Turns out the enumeration in Leancheck uses Rationals, > while Smallcheck uses encodeFloat, which happens to > produce only "nice" numbers (very few bits set) in the beginning. I improved the LeanCheck floating enumeration starting with v0.8.0 to catch exactly this kind of error. :-) > PS: this post wouldn't be complete without me complaining > that I cannot (easily) put the type annotation > where it belongs - in the declaration of the name: > > Prelude Test.LeanCheck> check $ \ (x::Double) y z -> x + (y+z) == (x+y)+z > > :22:12: error: > Illegal type signature: ‘Double’ > Type signatures are only allowed in patterns with ScopedTypeVariables > > Wat? TypeVariables? There aren't any! You can get the above to parse by passing `-XScopedTypeVariables` to GHC: $ ghci -XScopedTypeVariables > import Test.LeanCheck > check $ \(x::Double) y z -> x + (y+z) == (x+y) + z *** Failed! Falsifiable (after 87 tests): 0.0 Infinity (-Infinity) -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Fri Jan 18 01:36:31 2019 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 17 Jan 2019 20:36:31 -0500 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing In-Reply-To: <20190118010035.sweof4hymhnmkw43@zero.localdomain> References: <20190118010035.sweof4hymhnmkw43@zero.localdomain> Message-ID: I think they're complaining about the name of the extension. Years ago, it was a separate extension, but it got folded into ScopedTypeVariables. On Thu, Jan 17, 2019 at 8:01 PM Rudy Matela wrote: > On Thu, Jan 17, 2019 at 06:28:32PM +0100, Johannes Waldmann wrote: > > Prelude Test.LeanCheck> checkFor 1000 $ \ x y z -> isInfinite x || > isInfinite y || isInfinite z || (x::Double) + (y+z) == (x+y)+z *** Failed! > Falsifiable (after 306 tests): 1.0 1.0 0.3333333333333333 > > Turns out the enumeration in Leancheck uses Rationals, while Smallcheck > uses encodeFloat, which happens to produce only “nice” numbers (very few > bits set) in the beginning. > > I improved the LeanCheck floating enumeration starting with v0.8.0 to > catch exactly this kind of error. :-) > > PS: this post wouldn’t be complete without me complaining that I cannot > (easily) put the type annotation where it belongs - in the declaration of > the name: > > Prelude Test.LeanCheck> check $ \ (x::Double) y z -> x + (y+z) == (x+y)+z > > :22:12: error: Illegal type signature: ‘Double’ Type signatures are only > allowed in patterns with ScopedTypeVariables > > Wat? TypeVariables? There aren’t any! > > You can get the above to parse by passing -XScopedTypeVariables to GHC: > > $ ghci -XScopedTypeVariables > > import Test.LeanCheck > > check $ \(x::Double) y z -> x + (y+z) == (x+y) + z > *** Failed! Falsifiable (after 87 tests): > 0.0 Infinity (-Infinity) > > _______________________________________________ > 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 Fri Jan 18 06:29:50 2019 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Fri, 18 Jan 2019 07:29:50 +0100 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing In-Reply-To: References: <20190118010035.sweof4hymhnmkw43@zero.localdomain> Message-ID: <73a6cdd1-1682-c38a-9d00-5a74a6bd3c16@htwk-leipzig.de> On 1/18/19 2:36 AM, Brandon Allbery wrote: > I think they're complaining about the name of the extension. Yes. And hat I need to use an extension at all - to be allowed to annotate the declaration of an identifier with its type. Of course it's easy to work around, but I think it does not look good, especially when teaching. - J. From mail at joachim-breitner.de Fri Jan 18 15:22:19 2019 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 18 Jan 2019 16:22:19 +0100 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing In-Reply-To: References: Message-ID: Hi, Am Donnerstag, den 17.01.2019, 18:28 +0100 schrieb Johannes Waldmann: > :22:12: error: > Illegal type signature: ‘Double’ > Type signatures are only allowed in patterns with ScopedTypeVariables > > Wat? TypeVariables? There aren't any! I feel your pain: https://github.com/ghc-proposals/ghc-proposals/pull/119 Let’s hope we get Haskell2x somewhen, including (at least) PatternSignatures, or even all of ScopedTypeVariables. Interestingly, my proposal cites a rant from you from 10 years ago: https://mail.haskell.org/pipermail/haskell-cafe/2009-April/059519.html :-) Cheers, Joachim -- 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 polux2001 at gmail.com Sat Jan 19 09:57:48 2019 From: polux2001 at gmail.com (Paul Brauner) Date: Sat, 19 Jan 2019 10:57:48 +0100 Subject: [Haskell-cafe] ANN: LeanCheck v0.9.0 -- enumerative property testing In-Reply-To: References: Message-ID: Leancheck looks great! Could you also please compare it to feat? That's what I've been using for enumerating algebraic datatypes by size (vs depth) so far. On Fri, Jan 18, 2019, 16:22 Joachim Breitner Hi, > > > Am Donnerstag, den 17.01.2019, 18:28 +0100 schrieb Johannes Waldmann: > > :22:12: error: > > Illegal type signature: ‘Double’ > > Type signatures are only allowed in patterns with > ScopedTypeVariables > > > > Wat? TypeVariables? There aren't any! > > I feel your pain: > https://github.com/ghc-proposals/ghc-proposals/pull/119 > > Let’s hope we get Haskell2x somewhen, including (at least) > PatternSignatures, or even all of ScopedTypeVariables. > > Interestingly, my proposal cites a rant from you from 10 years ago: > https://mail.haskell.org/pipermail/haskell-cafe/2009-April/059519.html > :-) > > Cheers, > Joachim > > -- > Joachim Breitner > mail at joachim-breitner.de > http://www.joachim-breitner.de/ > > _______________________________________________ > 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 evan at evanrutledgeborden.dreamhosters.com Sat Jan 19 15:34:44 2019 From: evan at evanrutledgeborden.dreamhosters.com (evan@evan-borden.com) Date: Sat, 19 Jan 2019 09:34:44 -0600 Subject: [Haskell-cafe] ANN: network 3.0.0.0 Message-ID: Announcing the release of network 3.0.0.0 http://hackage.haskell.org/package/network-3.0.0.0 Version 3.0.0.0 of network is less platform dependent, easier to build, easier to use correctly (yay no more String api), more extensible, and all around safer. Kazu Yamamoto and Tamar Christina deserve a special shout out, they put an exceptional amount of thought and work into this version and it really shows. Thanks to network's contributors for kicking the tires and continuing to keep quality high. Version 3.0.0.0 * Breaking change: the Network and Network.BSD are removed. Network.BSD is provided a new package: network-bsd. * Breaking change: the signatures are changed: ``` old fdSocket :: Socket -> CInt new fdSocket :: Socket -> IO CInt old mkSocket :: CInt -> Family -> SocketType -> ProtocolNumber -> SocketStatus -> IO Socket new mkSocket :: CInt Socket ``` * Breaking change: the deprecated APIs are removed: send, sendTo, recv, recvFrom, recvLen, htonl, ntohl, inet_addr, int_ntoa, bindSocket, sClose, SocketStatus, isConnected, isBound, isListening, isReadable, isWritable, sIsConnected, sIsBound, sIsListening, sIsReadable, sIsWritable, aNY_PORT, iNADDR_ANY, iN6ADDR_ANY, sOMAXCONN, sOL_SOCKET, sCM_RIGHTS, packSocketType, getPeerCred. * Breaking chage: SockAddrCan is removed from SockAddr. * Socket addresses are extendable with Network.Socket.Address. * "socket" is now asynchronous-exception-safe. [#336](https://github.com/haskell/network/pull/336) * "recvFrom" returns (0, addr) instead of throwing an error on EOF. [#360](https://github.com/haskell/network/pull/360) * All APIs are available on any platforms. * Build system is simplified. * Bug fixes. -- Evan Borden -------------- next part -------------- An HTML attachment was scrubbed... URL: From b at chreekat.net Sat Jan 19 15:41:01 2019 From: b at chreekat.net (Bryan Richter) Date: Sat, 19 Jan 2019 17:41:01 +0200 Subject: [Haskell-cafe] ANN: network 3.0.0.0 In-Reply-To: References: Message-ID: Excellent! FYI Hackage isn't showing Haddocks for network yet, although I've noticed this for a few packages again recently. On Sat, 19 Jan 2019, 17.35 evan at evan-borden.com < evan at evanrutledgeborden.dreamhosters.com wrote: > Announcing the release of network 3.0.0.0 > http://hackage.haskell.org/package/network-3.0.0.0 > > Version 3.0.0.0 of network is less platform dependent, easier to build, > easier to use correctly (yay no more String api), more extensible, and all > around safer. Kazu Yamamoto and Tamar Christina deserve a special shout > out, they put an exceptional amount of thought and work into this version > and it really shows. Thanks to network's contributors for kicking the tires > and continuing to keep quality high. > > Version 3.0.0.0 > > * Breaking change: the Network and Network.BSD are removed. > Network.BSD is provided a new package: network-bsd. > * Breaking change: the signatures are changed: > ``` > old fdSocket :: Socket -> CInt > new fdSocket :: Socket -> IO CInt > > old mkSocket :: CInt -> Family -> SocketType -> ProtocolNumber -> > SocketStatus -> IO Socket > new mkSocket :: CInt Socket > ``` > * Breaking change: the deprecated APIs are removed: send, sendTo, recv, > recvFrom, recvLen, htonl, ntohl, inet_addr, int_ntoa, bindSocket, sClose, > SocketStatus, isConnected, isBound, isListening, isReadable, isWritable, > sIsConnected, sIsBound, sIsListening, sIsReadable, sIsWritable, aNY_PORT, > iNADDR_ANY, iN6ADDR_ANY, sOMAXCONN, sOL_SOCKET, sCM_RIGHTS, packSocketType, > getPeerCred. > * Breaking chage: SockAddrCan is removed from SockAddr. > * Socket addresses are extendable with Network.Socket.Address. > * "socket" is now asynchronous-exception-safe. > [#336](https://github.com/haskell/network/pull/336) > * "recvFrom" returns (0, addr) instead of throwing an error on EOF. > [#360](https://github.com/haskell/network/pull/360) > * All APIs are available on any platforms. > * Build system is simplified. > * Bug fixes. > > -- > Evan Borden > _______________________________________________ > 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 nh2.me Sat Jan 19 15:56:46 2019 From: mail at nh2.me (=?UTF-8?Q?Niklas_Hamb=c3=bcchen?=) Date: Sat, 19 Jan 2019 16:56:46 +0100 Subject: [Haskell-cafe] ANN: network 3.0.0.0 In-Reply-To: References: Message-ID: <4d0029d6-d8c4-8da2-8081-1b165312c17a@nh2.me> Hey Evan, it's great that work is being done on network, that is very appreciated. I do find one thing problematic though: Why do breaking type changes like `fdSocket` and `mkSocket` not go through a deprecation cycle? It's a best-practice to not break types of fundamental packages unless absolutely necessary. In this case it seems like these functions could have been deprecated, kept forever, and new functions with the improved types could have been added. This would avoid breakage for network's many users. Given that rest of the changelog in which deprecations are mentioned, it seems `network` contributers generall understand that and agree on that. Why was the deprecation approach not chosen for these functions? What in general is network's decision process for deprecation vs breaking change? Was any analysis performed that showed that only the fewest of network's 926 Hackage dependencies use these functions? Or should we expect major ecosystem breakages? Also interesting is that in https://github.com/haskell/network/commit/d69c3072071859a28a442ff713e90f8499882d21 `fdSocket` was deprecated, but that deprecation was about a slightly different change and never made it into any Hackage release so users never saw an advance hint that `fdSocket` would soon be changed. Personally, it bugs me out that we can't get deprecations right in Haskell, when other ecosystems have understood and successfully executed the "deprecate and make better functions" approach for a very long time. But I'd be happy to hear why I'm wrong and this approach couldn't be used here. Niklas From evan at evanrutledgeborden.dreamhosters.com Sat Jan 19 16:35:33 2019 From: evan at evanrutledgeborden.dreamhosters.com (Evan Borden) Date: Sat, 19 Jan 2019 10:35:33 -0600 Subject: [Haskell-cafe] ANN: network 3.0.0.0 In-Reply-To: <4d0029d6-d8c4-8da2-8081-1b165312c17a@nh2.me> References: <4d0029d6-d8c4-8da2-8081-1b165312c17a@nh2.me> Message-ID: Niklas, I appreciate and empathize with your concerns. Care was taken to utilize a deprecation cycle for as much of the API as possible, as we knew that these changes would cause churn in the ecosystem. As you noted, some breaking changes were not communicated early through these means. Instead we decided to mark an epoch change in network to signal that there would be significant breakage. This follows conventions established by Ed Kmett, which are documented here https://pvp.haskell.org/faq/. I'm not sure a specific convention exists for a situation where the type of a function will change in a future version. I'd love to hear ideas. Thank you very much for the feedback. Constructive criticism is necessary to improve our handling of these issues and is always welcome with open arms. On Sat, Jan 19, 2019 at 9:56 AM Niklas Hambüchen wrote: > Hey Evan, > > it's great that work is being done on network, that is very appreciated. > I do find one thing problematic though: > > Why do breaking type changes like `fdSocket` and `mkSocket` not go through > a deprecation cycle? > > It's a best-practice to not break types of fundamental packages unless > absolutely necessary. > In this case it seems like these functions could have been deprecated, > kept forever, and new functions with the improved types could have been > added. > This would avoid breakage for network's many users. > > Given that rest of the changelog in which deprecations are mentioned, it > seems `network` contributers generall understand that and agree on that. > Why was the deprecation approach not chosen for these functions? > > What in general is network's decision process for deprecation vs breaking > change? Was any analysis performed that showed that only the fewest of > network's 926 Hackage dependencies use these functions? Or should we expect > major ecosystem breakages? > > Also interesting is that in > https://github.com/haskell/network/commit/d69c3072071859a28a442ff713e90f8499882d21 > `fdSocket` was deprecated, but that deprecation was about a slightly > different change and never made it into any Hackage release so users never > saw an advance hint that `fdSocket` would soon be changed. > > Personally, it bugs me out that we can't get deprecations right in > Haskell, when other ecosystems have understood and successfully executed > the "deprecate and make better functions" approach for a very long time. > But I'd be happy to hear why I'm wrong and this approach couldn't be used > here. > > Niklas > -- -- Evan Borden -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at nh2.me Sat Jan 19 17:38:09 2019 From: mail at nh2.me (=?UTF-8?Q?Niklas_Hamb=c3=bcchen?=) Date: Sat, 19 Jan 2019 18:38:09 +0100 Subject: [Haskell-cafe] ANN: network 3.0.0.0 In-Reply-To: References: <4d0029d6-d8c4-8da2-8081-1b165312c17a@nh2.me> Message-ID: <3dd735ed-f1fe-c16d-c43e-19371d2e3e9b@nh2.me> Thanks for the quick reply! > I'd love to hear ideas. I recommend the following way: * Never change the type of an existing function unless absolutely necessary. * Do not change the the behaviour/semantics of a function unless it's an obvious fix/improvement. (In other words, if somebody may in some reasonable way rely on the old behaviour, don't change it). * Improve functions by introducing new functions with names, marking the old functions as deprecated. * GHC will show deprecation warnings to users. ** In the deprecation message, point out the intended replacement. ** If a deprecated function is planned to be removed in the next release, say it in the message. * Consider removing deprecated functions after some years. But only if e.g. maintainability demands it. ** In some cases, consider moving the functions to an `.Old` module or similar. Key point: * Use deprecations and new functions liberally to make progress. Almost never break existing functions. I like to call this approach "the Java way of deprecation", and it helps an ecosystem to move forward swiftly while keeping people happy a whole lot. This is because it allows incremental transitions instead of hard cutoff points that often don't align with people's schedules or test plans. How this relates to the PVP: This thought process happens *before* PVP considerations enter the stage. After you've made your changes (hopefully as few breaking ones as possible), you can use the PVP to determine what the new version should be. The reverse logic should not be applied: If some change made demands a major version bump (e.g. removal of an old deprecated function that nobody uses), that does not "allow" other functions to be removed more liberally. The rationale is that our goal is not to do as much as a given version jump allows, but to minimise breaking changes for users even when we know that some breaking changes must be made. (Also, while the PVP as mentioned doesn't tell you what to do with your package contents and applies afterwards, the diagram in https://pvp.haskell.org/pvp-decision-tree.svg mentions "Consider renaming the function instead" next to "Did the behaviour of any exported functions change", so I think what I recommend is in the spirit of those that came up with the process). Concrete example: This is how I imagine applying the above to network 3.0.0.0 would have worked: * Deprecate `send`, `sendTo`, `recv`, etc. (As correctly done in network-2.7) * Do NOT remove them. Leave at least 2 years time before touching them. * In this case, move them to Network.Socket.String, instead of removing them. For 2 reasons: ** These functions have been this ways since forever and lots of code will use them. Putting them into a legacy module will allow projects to trivially get into a compiling state again with one `import` change, vs having to fix every use site. This eases migration. ** While certainly not a good idea, the String based functions aren't so fatally flawed that they have no justification for further existence, so keeping them in a legacy module would do no harm. * Introduce `socketToFd :: Socket -> IO CInt` * Deprecate `fdSocket`, saying why it's bad and that `socketToFd` is the replacement * Keep `fdSocket` forever (Just to be clear, I think the `String` based network API is bug; a reasonable and modern programming ecosystem shouldn't have that, and this should be addressed. So I'm not recommending this approach because I think these functions are great, but because I think this is how to transition away from design bugs in general.) Then, looking at the above changes, if we follow PVP, we'd look at the PVP decision tree, and determine what the new version should be that way. If (after a long time period) we'd do the "move to Network.Socket.String", it would tell us that a major bump is necessary. Of course one can also introduce a major version bump when PVP says that a minor bump would be sufficient if one wants to "mark an epoch change" -- that is at the liberty of the maintainer. Discussion: I found this approach to work very well and am convinced of it. But I'm happy to hear other people's opinion about it to see if it's really as agreeable as I think. If yes, I'd be happy to write down these deprecation guidelines in some repo so that projects can refer to them and say "we follow that general approach" (similar to the PVP FAQ link). What do you think? Niklas From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Sat Jan 19 18:18:01 2019 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 19 Jan 2019 18:18:01 +0000 Subject: [Haskell-cafe] ANN: network 3.0.0.0 In-Reply-To: <3dd735ed-f1fe-c16d-c43e-19371d2e3e9b@nh2.me> References: <4d0029d6-d8c4-8da2-8081-1b165312c17a@nh2.me> <3dd735ed-f1fe-c16d-c43e-19371d2e3e9b@nh2.me> Message-ID: <20190119181801.2lqxyiidozrogx6a@weber> On Sat, Jan 19, 2019 at 06:38:09PM +0100, Niklas Hambüchen wrote: > I recommend the following way: [...] > I'd be happy to write down these deprecation guidelines in some repo so > that projects can refer to them I think that's a great idea. Opaleye roughly follows your specification. I try to announce deprecations in major version N, implement the deprecation in N+1 and remove the deprecated entity no earlier than N+2. NB that network could still be changed to follow your plan if a new version were released and 3.0.0.0 deprecated (hah!). Tom From ietf-dane at dukhovni.org Sat Jan 19 21:20:24 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sat, 19 Jan 2019 16:20:24 -0500 Subject: [Haskell-cafe] Fragile GHC rank-2 type inference? Message-ID: <20190119212023.GV79754@straasha.imrryr.org> [ I am seeing somewhat subtle, and to me surprising, type-inference obstacles. I am presently using GHC 8.6.3. I don't know whether what I'm seeing is a feature or a bug. ] Given a function 'mkEnv' (a command-line option parser built using optparse-applicative) that returns a rank-2 type (via ApplicativeDo): {-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} type Locker = forall a. IO a -> IO a data Env = Env { envLocker :: Locker, ... } mkEnv :: Locker -> Env mkEnv envLocker = do ... pure Env{..} in my complete program, the call to 'mkEnv' fails to compile, when called via: mkLockEnv :: IO Env mkLockEnv = do lock <- newMVar () let locker :: Locker locker = withMVar lock . const ... (mkEnv locker) -- Error message: * Couldn't match type ‘a’ with ‘a0’ ‘a’ is a rigid type variable bound by a type expected by the context: Locker at ... 132 Expected type: IO a -> IO a Actual type: IO a0 -> IO a0 * In the second argument of ‘mkEnv’, namely ‘locker’ * Relevant bindings include locker :: IO a0 -> IO a0 (bound at ...) | 132 | ... (mkEnv locker) | ^^^^^^ But after inlining the "locker" binding, the code compiles: mkLockEnv :: IO Env mkLockEnv = do lock <- newMVar () ... (mkEnv (withMVar lock . const)) Given "let-bound polymorphism": https://kseo.github.io/posts/2016-12-27-higher-rank-polymorphism.html I would not have expected the change to make a difference... In trying to simplify the code (attached) to understand the source of the problem, surprisingly, the simplified program compiles in either form. It is not apparent what facet of the larger program has a bearing on the construction of the rank-2 environment. The background is that some of my Haskell applications employ a shared lock to serialize writes to stdout from concurrent forkIO "threads". The lock is the usual: type Lock = MVar () withLock :: Lock -> IO a -> IO a withLock lock = withMVar lock . const I am however tempted to abstract away the concrete lock type, leaving just a polymorphic closure, which results in 'Env' having a rank-2 type: {-# LANGUAGE RankNTypes #-} data Env = Env { envLocker :: Locker, ... } type Locker = forall a. IO a -> IO a type EnvReader a = ReaderT Env IO a runLocked :: forall a. EnvReader a -> EnvReader a runLocked action = ask >>= \env at Env{..} -> liftIO $ envLocker $ runReaderT action env and this works in the attached sample program which builds and runs: $ echo "The answer to life the universe and everything is:" | ./locker --answer 42 The answer to life the universe and everything is: 42 but a larger program where a "runLocked" call is located deeper in the call chain, fails to compile except as described at the top of the message. -- Viktor. -------------- next part -------------- A non-text attachment was scrubbed... Name: Locker.hs Type: text/x-haskell Size: 1617 bytes Desc: not available URL: From olf at aatal-apotheke.de Sat Jan 19 22:37:53 2019 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Sat, 19 Jan 2019 23:37:53 +0100 Subject: [Haskell-cafe] determine a type by universal property In-Reply-To: References: Message-ID: <207AB9AB-2FF5-4259-9A70-20170366B893@aatal-apotheke.de> Am 18.01.2019 um 13:00 schrieb haskell-cafe-request at haskell.org: > > Am Donnerstag, den 17.01.2019, 14:33 +0100 schrieb Olaf Klinke: >> I have two type signatures where I conjecture the only functors satisfying these >> are the Identity functor and functors of the form (,)s. Can anyone give hints as >> how to tackle a proof? >> >> Signature 1: What functors t admit a function >> forall f. Functor f => t (f a) -> f (t a) > > What about the functor > > data Void1 a > > It seems I can write > > g :: forall f. Functor f => t (f a) -> f (t a) > g x = case x of {} > > but Void1 is not the identity. (I guess it is `(,) Void`, if you want…) > > So if you allow the latter, let’s try a proof. Assume we have t, and > > g :: forall f. Functor f => t (f a) -> f (t a) > > We want to prove that there is an isomorphism from t to ((,) s) for > some type s. Define > > s = t () > > (because what else could it be.) Now we need functions > > f1 :: forall a. t a -> (t (), a) > f2 :: forall a. (t (), a) -> t a > > that are isomorphisms. Here is one implementation: > > f1 :: forall a. t a -> (t (), a) > f1 = swap . g . fmap (λx → (x,())) > > {- note: > x1 :: t a > x2 :: t ((,) a ()) > x2 = fmap (λx → (x,())) x1 > x3 :: (,) a (t ()) > x3 = g x2 > x4 :: (t (), a) > x4 = swap x3 > -} > > f2 :: forall a. (t (), a) -> t a > f2 (s, x) = x <$ s > > Now, are these isomorphisms? At this point I am not sure how to > proceed… probably invoking the free theorem of g? But even that will > not work nicely. Consider > > type T = (,) Integer > g :: forall f. Functor => T (f a) -> f (T a) > g (c, fx) = (,) (c + 1) <$> fx > > here we count the number of invocations of g. Surely with this g, > f2 . f1 cannot be the identity. > > > Cheers, > Joachim Hi Joachim, thanks a lot for the clue. I had not thought about the function \x -> (x,()). Your last example of g shows that if a g exists, it is not necessarily unique. Possibly I am missing a law for the function g that entails uniqueness. The identity law in Data.Traversable comes to mind and would rule out your last example. > Am 17.01.2019 um 15:42 schrieb Oleg Grenrus : > > I immediately see > > forall f a b. Functor f => (a -> f b) -> t a -> f (t b) indeed my type forall a f. Functor f => t (f a) -> f (t a) is interdefinable with your type above. > > which is Lens' (t a) a, agreed. > which is an iso > > exists e. (t a) ~ (e, a) I fail to follow this step. How does the Lens above imply this isomorphism? Is this a lens-specific thing or were you thinking along the same lines as Joachim? Let me give a bit of context. I was looking at generic functions that give rise to monad transformer instances of the form MonadFoo m => MonadFoo (BarT m) e.g. MonadExcept m => MonadExcept (StateT s m) One can factor StateT s into two adjoint functors, G = (s->) and F = (,)s. For defining the instance above generically it was necessary for the functor F to aadmit functions with the signatures in my original post. Then I conjectured that I actually had not generalized anything if the signatures forced my F to be of the form (,)s. Olaf From ietf-dane at dukhovni.org Sun Jan 20 00:09:04 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sat, 19 Jan 2019 19:09:04 -0500 Subject: [Haskell-cafe] Fragile GHC rank-2 type inference? In-Reply-To: <20190119212023.GV79754@straasha.imrryr.org> References: <20190119212023.GV79754@straasha.imrryr.org> Message-ID: <20190120000904.GW79754@straasha.imrryr.org> On Sat, Jan 19, 2019 at 04:20:23PM -0500, Viktor Dukhovni wrote: > in my complete program, the call to 'mkEnv' fails to compile, when > called via: > > mkLockEnv :: IO Env > mkLockEnv = do > lock <- newMVar () > let locker :: Locker > locker = withMVar lock . const > ... (mkEnv locker) > > But after inlining the "locker" binding, the code compiles: > > mkLockEnv :: IO Env > mkLockEnv = do > lock <- newMVar () > ... (mkEnv (withMVar lock . const)) > > Given "let-bound polymorphism": > > https://kseo.github.io/posts/2016-12-27-higher-rank-polymorphism.html > > I would not have expected the change to make a difference... Well, it turns out that some of the difference between the simplified and complete program is that my "Reader Env IO" monad gets some additional constraints via: http://hackage.haskell.org/package/http-conduit-2.3.4/docs/Network-HTTP-Client-Conduit.html#v:withResponse withResponse :: ( MonadUnliftIO m, MonadIO n, MonadReader env m , HasHttpManager env) => Request -> (Response (ConduitM i ByteString n ()) -> m a) -> m a Removing the call to 'withResponse' allows a simplified program compile without inlining the let-bind. Inspired by that, I cobbled together the below, which fails to compile unless one either uncomments the explicit type declaration for the let-bind, or else inlines the value: {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} module Main (main) where import Control.Monad.IO.Unlift (MonadUnliftIO, withRunInIO) import Control.Concurrent.MVar (newMVar, withMVar) import Control.Monad.IO.Class (liftIO) import Control.Monad.Reader (MonadReader, ReaderT, runReaderT, asks) data Env = Env { envLocker :: !Locker, envString :: String } type Locker = forall a. IO a -> IO a runLocked :: (env ~ Env, MonadReader env m, MonadUnliftIO m) => forall a. m a -> m a runLocked action = asks envLocker >>= \locker -> withRunInIO $ \run -> locker $ run action -- XXX: To compile, uncomment let-bind type, or else inline! mkEnv :: IO Env mkEnv = newMVar () >>= \lock -> let -- locker :: Locker locker = withMVar lock . const in go locker "Hello World!" where go :: Locker -> String -> IO Env go envLocker envString = Env{..} main :: IO () main = mkEnv >>= runReaderT (runLocked $ asks envString >>= liftIO . putStrLn) And yet, adding a type declaration for the let-bind still is not enough for the full program, only inlining "withMVar lock . const" makes GHC happy. Don't yet know why... • Couldn't match type ‘a’ with ‘a0’ ‘a’ is a rigid type variable bound by a type expected by the context: forall a. IO a -> IO a at Jname.hs:135:32-56 Expected type: IO a -> IO a Actual type: IO a0 -> IO a0 • In the second argument of ‘optsParser’, namely ‘locker’ In the second argument of ‘(<*>)’, namely ‘optsParser manager locker’ In the first argument of ‘O.info’, namely ‘(O.helper <*> optsParser manager locker)’ • Relevant bindings include locker :: IO a0 -> IO a0 (bound at Jname.hs:132:9) | 135 | $ O.info (O.helper <*> optsParser manager locker) | ^^^^^^ -- Viktor. From viercc at gmail.com Sun Jan 20 02:09:19 2019 From: viercc at gmail.com (=?UTF-8?B?5a6u6YeMIOa0uOWPuA==?=) Date: Sun, 20 Jan 2019 11:09:19 +0900 Subject: [Haskell-cafe] Fragile GHC rank-2 type inference? In-Reply-To: <20190120000904.GW79754@straasha.imrryr.org> References: <20190119212023.GV79754@straasha.imrryr.org> <20190120000904.GW79754@straasha.imrryr.org> Message-ID: The error in the simplified program can be explained. > ... which fails to compile unless one either > uncomments the explicit type declaration for the let-bind, or else > inlines the value: > > {-# LANGUAGE RankNTypes #-} > {-# LANGUAGE TypeFamilies #-} > module Main (main) where > import Control.Monad.IO.Unlift (MonadUnliftIO, withRunInIO) > import Control.Concurrent.MVar (newMVar, withMVar) > import Control.Monad.IO.Class (liftIO) > import Control.Monad.Reader (MonadReader, ReaderT, runReaderT, asks) > > data Env = Env { envLocker :: !Locker, envString :: String } > type Locker = forall a. IO a -> IO a > > runLocked :: (env ~ Env, MonadReader env m, MonadUnliftIO m) > => forall a. m a -> m a > runLocked action = asks envLocker >>= \locker -> > withRunInIO $ \run -> locker $ run action > > -- XXX: To compile, uncomment let-bind type, or else inline! > mkEnv :: IO Env > mkEnv = newMVar () >>= \lock -> > let -- locker :: Locker > locker = withMVar lock . const > in go locker "Hello World!" > where > go :: Locker -> String -> IO Env > go envLocker envString = Env{..} > > main :: IO () > main = mkEnv >>= runReaderT (runLocked $ asks envString >>= liftIO . putStrLn) You enabled TypeFamilies extension, which subsumes MonoLocalBinds. MonoLocalBinds disables automatic let-generalization. Unless you attach type annotation, the type of locker is not (forall a. IO a -> IO a). This is a pure guess, but I think your error in the actual code is caused by ApplicativeDo. The following code fails to compile but disabling ApplicativeDo solves the problem. {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ApplicativeDo #-} module Main where import Control.Concurrent.MVar type Locker = forall a. IO a -> IO a main :: IO () main = do lock1 <- newMVar () let locker1 :: Locker locker1 = withMVar lock1 . const lock2 <- newMVar () let locker2 :: Locker locker2 = withMVar lock2 . const f locker1 locker2 f :: Locker -> Locker -> IO () f _ _ = putStrLn "dummy" I think this is ApplicativeDo-side bug, not type checking bug. -- /* Koji Miyazato */ From ietf-dane at dukhovni.org Sun Jan 20 02:39:10 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sat, 19 Jan 2019 21:39:10 -0500 Subject: [Haskell-cafe] Fragile GHC rank-2 type inference? In-Reply-To: References: <20190119212023.GV79754@straasha.imrryr.org> <20190120000904.GW79754@straasha.imrryr.org> Message-ID: <2F1DB4ED-B9BC-4B05-977F-7E3DACE365C9@dukhovni.org> > On Jan 19, 2019, at 9:09 PM, 宮里 洸司 wrote: > > You enabled TypeFamilies extension, which subsumes MonoLocalBinds. > MonoLocalBinds disables automatic let-generalization. Unless you > attach type annotation, the type of locker is not (forall a. IO a -> IO a). Thanks, that makes sense. And indeed I only did that while trying to understand how the use of "withResponse" plays into the story, but just adding the type annotation is not enough, so the real problem is elsewhere... > This is a pure guess, but I think your error in the actual code is > caused by ApplicativeDo. The following code fails to compile but > disabling ApplicativeDo solves the problem. Nice example, thanks! Indeed that seems to be much closer to the heart of the problem. > {-# LANGUAGE RankNTypes #-} > {-# LANGUAGE ApplicativeDo #-} > module Main where > > import Control.Concurrent.MVar > > type Locker = forall a. IO a -> IO a > > main :: IO () > main = > do lock1 <- newMVar () > let locker1 :: Locker > locker1 = withMVar lock1 . const > lock2 <- newMVar () > let locker2 :: Locker > locker2 = withMVar lock2 . const > f locker1 locker2 > > f :: Locker -> Locker -> IO () > f _ _ = putStrLn "dummy" > > I think this is ApplicativeDo-side bug, not type checking bug. Yes, removing ApplicativeDo and rewriting the option parser as: Env locker <$> f1 <*> f2 <*> ... <*> fN solves the problem, but results in IMHO harder to maintain code, because of the required positional correspondence between the Env constructor fields and the placement of the field parsers. It is certainly surprising that ApplicativeDo affects the type inference of "locker" in: type Locker = forall a. IO a -> IO a data Env = Env { locker :: Locker, f1 :: T1, ... , fN :: TN } f locker = do f1 <- parser1 f2 <- parser2 ... fN <- parserN pure Env{..} in a way that breaks: lock <- newMVar () let locker :: Locker locker = withMVar lock . const f locker but does not break: lock <- newMVar () f (mkLocker lock) where mkLocker :: MVar () -> Locker mkLocker lock = withMVar lock . const Would it be appropriate to file a bug report? Your example seems suitably succinct. -- Viktor. From viercc at gmail.com Sun Jan 20 07:09:29 2019 From: viercc at gmail.com (=?UTF-8?B?5a6u6YeMIOa0uOWPuA==?=) Date: Sun, 20 Jan 2019 16:09:29 +0900 Subject: [Haskell-cafe] Fragile GHC rank-2 type inference? In-Reply-To: <2F1DB4ED-B9BC-4B05-977F-7E3DACE365C9@dukhovni.org> References: <20190119212023.GV79754@straasha.imrryr.org> <20190120000904.GW79754@straasha.imrryr.org> <2F1DB4ED-B9BC-4B05-977F-7E3DACE365C9@dukhovni.org> Message-ID: > Would it be appropriate to file a bug report? Found that there's a related bug report: https://ghc.haskell.org/trac/ghc/ticket/11982 From ietf-dane at dukhovni.org Sun Jan 20 07:24:39 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sun, 20 Jan 2019 02:24:39 -0500 Subject: [Haskell-cafe] Fragile GHC rank-2 type inference? In-Reply-To: References: <20190119212023.GV79754@straasha.imrryr.org> <20190120000904.GW79754@straasha.imrryr.org> <2F1DB4ED-B9BC-4B05-977F-7E3DACE365C9@dukhovni.org> Message-ID: > On Jan 20, 2019, at 2:09 AM, 宮里 洸司 wrote: > >> Would it be appropriate to file a bug report? > > Found that there's a related bug report: > https://ghc.haskell.org/trac/ghc/ticket/11982 Yes, that looks close. I think that your example could be added to the bug report, making a more compelling case for fixing it. I've tidied it up a bit more below my signature. Would you like to add this to that ticket, or should I? -- Viktor. {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ApplicativeDo #-} module Main where import Control.Concurrent.MVar type Locker = forall a. IO a -> IO a main :: IO () main = do line <- getLine lock <- newMVar () let locker :: Locker locker = withMVar lock . const f line locker f :: String -> Locker -> IO () f line locker = locker $ putStrLn line From ietf-dane at dukhovni.org Sun Jan 20 09:04:25 2019 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sun, 20 Jan 2019 04:04:25 -0500 Subject: [Haskell-cafe] Fragile GHC rank-2 type inference? In-Reply-To: References: <20190119212023.GV79754@straasha.imrryr.org> <20190120000904.GW79754@straasha.imrryr.org> <2F1DB4ED-B9BC-4B05-977F-7E3DACE365C9@dukhovni.org> Message-ID: <568BB8BC-0CC1-476D-99D4-4195E50C83BB@dukhovni.org> > On Jan 20, 2019, at 2:24 AM, Viktor Dukhovni wrote: > > I've tidied it up a bit more below my signature. Would you like > to add this to that ticket, or should I? I went ahead and updated the ticket. I hope you don't mind... -- Viktor. From viercc at gmail.com Sun Jan 20 11:44:55 2019 From: viercc at gmail.com (=?UTF-8?B?5a6u6YeMIOa0uOWPuA==?=) Date: Sun, 20 Jan 2019 20:44:55 +0900 Subject: [Haskell-cafe] Fragile GHC rank-2 type inference? In-Reply-To: <568BB8BC-0CC1-476D-99D4-4195E50C83BB@dukhovni.org> References: <20190119212023.GV79754@straasha.imrryr.org> <20190120000904.GW79754@straasha.imrryr.org> <2F1DB4ED-B9BC-4B05-977F-7E3DACE365C9@dukhovni.org> <568BB8BC-0CC1-476D-99D4-4195E50C83BB@dukhovni.org> Message-ID: No problem! I rather thank you for taking your time to report the example. -- /* Koji Miyazato */ From gale at sefer.org Sun Jan 20 16:53:39 2019 From: gale at sefer.org (Yitzchak Gale) Date: Sun, 20 Jan 2019 18:53:39 +0200 Subject: [Haskell-cafe] building with stack, need some older versions for one library In-Reply-To: References: Message-ID: If it's just one library, another technique is to add the specific version of that library to `extra-deps` in `stack.yaml` rather than changing the entire resolver. On Wed, Jan 16, 2019 at 9:31 AM Li-yao Xia wrote: > > Stackage has the list of snapshots a package (all its versions) appears in. > > https://www.stackage.org/package/midi/snapshots > > 0.2.2 doesn't appear, but shouldn't 0.2.2.2 and 0.2.2.1 be compatible > with it? > > Li-yao > > On 1/16/19 8:26 AM, Dennis Raddle wrote: > > I'm assembling a large stack project from various places. > > > > I just did "stack new", using the default resolver, copied in most of my > > code, and got it compiled. > > > > Except I'm stuck on one thing. I need to use the 'midi-0.2.2' library > > (reads/writes MIDI files). Its depends on older versions of the same of > > the core packages. > > > > What should I do now? Do I modify the LTS resolver to something older > > and then type "stack build" again? How can I find an appropriate > > resolver without hit-and-miss? > > > > Mike > > > > > > _______________________________________________ > > 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 alexander.kjeldaas at gmail.com Sun Jan 20 20:22:47 2019 From: alexander.kjeldaas at gmail.com (Alexander Kjeldaas) Date: Sun, 20 Jan 2019 21:22:47 +0100 Subject: [Haskell-cafe] ANN: network 3.0.0.0 In-Reply-To: <3dd735ed-f1fe-c16d-c43e-19371d2e3e9b@nh2.me> References: <4d0029d6-d8c4-8da2-8081-1b165312c17a@nh2.me> <3dd735ed-f1fe-c16d-c43e-19371d2e3e9b@nh2.me> Message-ID: While those are good suggestions, the biggest problem is not whether a given deprecation strategy is correct or not. The biggest problem with the PVP in this case is that it does *not say anything about how to release a "pre" release* so any deprecation strategy could be tested by the community. This makes the concept of *learning* painful, because mistakes are way too expensive. Can this be fixed first, then later we can figure out how to do deprecations? Or am I wrong? Alexander On Sat, Jan 19, 2019 at 6:38 PM Niklas Hambüchen wrote: > Thanks for the quick reply! > > > I'd love to hear ideas. > > I recommend the following way: > > * Never change the type of an existing function unless absolutely > necessary. > * Do not change the the behaviour/semantics of a function unless it's an > obvious fix/improvement. > (In other words, if somebody may in some reasonable way rely on the old > behaviour, don't change it). > * Improve functions by introducing new functions with names, marking the > old functions as deprecated. > * GHC will show deprecation warnings to users. > ** In the deprecation message, point out the intended replacement. > ** If a deprecated function is planned to be removed in the next release, > say it in the message. > * Consider removing deprecated functions after some years. But only if > e.g. maintainability demands it. > ** In some cases, consider moving the functions to an `.Old` module or > similar. > > Key point: > * Use deprecations and new functions liberally to make progress. Almost > never break existing functions. > > I like to call this approach "the Java way of deprecation", and it helps > an ecosystem to move forward swiftly while keeping people happy a whole > lot. This is because it allows incremental transitions instead of hard > cutoff points that often don't align with people's schedules or test plans. > > How this relates to the PVP: > This thought process happens *before* PVP considerations enter the stage. > After you've made your changes (hopefully as few breaking ones as > possible), you can use the PVP to determine what the new version should be. > The reverse logic should not be applied: If some change made demands a > major version bump (e.g. removal of an old deprecated function that nobody > uses), that does not "allow" other functions to be removed more liberally. > The rationale is that our goal is not to do as much as a given version jump > allows, but to minimise breaking changes for users even when we know that > some breaking changes must be made. > > (Also, while the PVP as mentioned doesn't tell you what to do with your > package contents and applies afterwards, the diagram in > https://pvp.haskell.org/pvp-decision-tree.svg mentions "Consider renaming > the function instead" next to "Did the behaviour of any exported functions > change", so I think what I recommend is in the spirit of those that came up > with the process). > > Concrete example: > > This is how I imagine applying the above to network 3.0.0.0 would have > worked: > > * Deprecate `send`, `sendTo`, `recv`, etc. (As correctly done in > network-2.7) > * Do NOT remove them. Leave at least 2 years time before touching them. > * In this case, move them to Network.Socket.String, instead of removing > them. For 2 reasons: > ** These functions have been this ways since forever and lots of code will > use them. Putting them into a legacy module will allow projects to > trivially get into a compiling state again with one `import` change, vs > having to fix every use site. This eases migration. > ** While certainly not a good idea, the String based functions aren't so > fatally flawed that they have no justification for further existence, so > keeping them in a legacy module would do no harm. > * Introduce `socketToFd :: Socket -> IO CInt` > * Deprecate `fdSocket`, saying why it's bad and that `socketToFd` is the > replacement > * Keep `fdSocket` forever > > (Just to be clear, I think the `String` based network API is bug; a > reasonable and modern programming ecosystem shouldn't have that, and this > should be addressed. So I'm not recommending this approach because I think > these functions are great, but because I think this is how to transition > away from design bugs in general.) > > Then, looking at the above changes, if we follow PVP, we'd look at the PVP > decision tree, and determine what the new version should be that way. If > (after a long time period) we'd do the "move to Network.Socket.String", it > would tell us that a major bump is necessary. > Of course one can also introduce a major version bump when PVP says that a > minor bump would be sufficient if one wants to "mark an epoch change" -- > that is at the liberty of the maintainer. > > Discussion: > > I found this approach to work very well and am convinced of it. > But I'm happy to hear other people's opinion about it to see if it's > really as agreeable as I think. > If yes, I'd be happy to write down these deprecation guidelines in some > repo so that projects can refer to them and say "we follow that general > approach" (similar to the PVP FAQ link). > > What do you think? > > Niklas > _______________________________________________ > 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 kazu at iij.ad.jp Mon Jan 21 08:23:57 2019 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Mon, 21 Jan 2019 17:23:57 +0900 (JST) Subject: [Haskell-cafe] ANN: network 3.0.0.0 In-Reply-To: <3dd735ed-f1fe-c16d-c43e-19371d2e3e9b@nh2.me> References: <4d0029d6-d8c4-8da2-8081-1b165312c17a@nh2.me> <3dd735ed-f1fe-c16d-c43e-19371d2e3e9b@nh2.me> Message-ID: <20190121.172357.202432394621802411.kazu@iij.ad.jp> Hello, > * Never change the type of an existing function unless absolutely necessary. The change of mkSocket and fdSocket is inevitable because the old definition of Socket is: data Socket = MkSocket CInt Family SocketType ProtocolNumber (MVar SocketStatus) while new one is: data Socket = Socket !(IORef CInt) CInt {- for Show -} Why this drastic change? Well, believing or not, old Socket cannot be GCed because of MVar! mkWeakMVar does not solve this issue. So, we decided to get rid of MVar. But without SocketStatus (ie Socket CInt), "close" becomes unsafe if "close" is called multiple time. To fix this, IORef was introduced. Now a closed Socket contains (-1). If you type "fdScoket" or "GC" to the github repo search, you can find a lot of discussions about this. --Kazu From damien.mattei at gmail.com Mon Jan 21 19:48:31 2019 From: damien.mattei at gmail.com (Damien Mattei) Date: Mon, 21 Jan 2019 20:48:31 +0100 Subject: [Haskell-cafe] avoid to print empty string Message-ID: i have this in a Monad IO: forM_ fltrdNamesBDs $ \(name,bdSidonie,bdWDS) -> if (bdWDS /= bdSidonie) then putStrLn $ name ++ " " ++ (show (bdSidonie :: Maybe Float)) ++ " " ++ show (bdWDS :: Maybe Float) ++ " " ++ show (bdWDS == bdSidonie) else putStr "" is there a way to remove the silly putStr "" that output an empty string, i tried with when.... but as when return Nothing in case of False it fails to compile -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Mon Jan 21 19:50:28 2019 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 21 Jan 2019 14:50:28 -0500 Subject: [Haskell-cafe] avoid to print empty string In-Reply-To: References: Message-ID: You want: return () (Look at the type of putStrLn.) On Mon, Jan 21, 2019 at 2:49 PM Damien Mattei wrote: > i have this in a Monad IO: > > forM_ fltrdNamesBDs $ \(name,bdSidonie,bdWDS) -> > if (bdWDS /= bdSidonie) > then > putStrLn $ name ++ " " ++ (show (bdSidonie :: Maybe Float)) > ++ " " ++ show (bdWDS :: Maybe Float) ++ " " ++ show (bdWDS == bdSidonie) > else > putStr "" > > is there a way to remove the silly putStr "" that output an empty string, > i tried with when.... but as when return Nothing in case of False it fails > to compile > > _______________________________________________ > 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 monkleyon at gmail.com Mon Jan 21 21:47:05 2019 From: monkleyon at gmail.com (MarLinn) Date: Mon, 21 Jan 2019 22:47:05 +0100 Subject: [Haskell-cafe] avoid to print empty string In-Reply-To: References: Message-ID: > i have this in a Monad IO: > > forM_ fltrdNamesBDs $ \(name,bdSidonie,bdWDS) -> > if (bdWDS /= bdSidonie) > then > putStrLn $ name ++ " " ++ (show (bdSidonie :: Maybe Float)) > ++ " " ++ show (bdWDS :: Maybe Float) ++ " " ++ show (bdWDS == bdSidonie) > else > putStr "" > > is there a way to remove the silly putStr "" that output an empty string, i > tried with when.... but as when return Nothing in case of False it fails to > compile I don't see the problem with when? This (in the expanded version) doesn't work? forM_ fltrdNamesBDs $ \(name,bdSidonie,bdWDS) -> when (bdWDS /= bdSidonie) $ showStuff name bdSidonie bdWDS As an extra remark, whenever I want to output a whole bunch of stuff in a row like this, I like to refactor into a concat, just to make the code more readable. If I can factor out the types, all the better: where showStuff :: String -> Maybe Float -> Maybe Float -> IO () showStuff name bdSidonie bdWDS = putStrLn $ concat [name," ",show bdSidonie," ",show bdWDS," False"] Or even showStuff :: String -> Maybe Float -> Maybe Float -> IO () showStuff name bdSidonie bdWDS = putStrLn $ Data.List.intercalate " " [name,show bdSidonie,show bdWDS,show False] Cheers. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ashesh.ambasta at getcentralapp.com Wed Jan 23 09:45:02 2019 From: ashesh.ambasta at getcentralapp.com (Ashesh Ambasta) Date: Wed, 23 Jan 2019 10:45:02 +0100 Subject: [Haskell-cafe] [Job] Senior back-end engineer at CentralApp In-Reply-To: <5ead518e-f5a3-dc44-b6ca-91eebc0f3aeb@centralapp.com> References: <5ead518e-f5a3-dc44-b6ca-91eebc0f3aeb@centralapp.com> Message-ID: <3b2e0b5f-9b48-3357-160a-010916646750@centralapp.com> Hi everyone, This is my first post to Haskell-Cafe, so pardon me for any errors. I'm writing on behalf of my company, CentralApp, to pitch our job opening. We're a small company and I'm the sole back-end engineer so far, and we're investing heavily only in Haskell as our back-end language of choice. A large part of our codebase is in Scala, since that was the choice I made 4-5 years ago. Since then, I got introduced to Haskell and I'm only considering it as the programming language of choice for our back-end infrastructure. We have plenty of engineering challenges in the pipeline since we're undergoing good growth. We serve millions of API requests per week and we're scaling the product out further. We also don't have much in the way of technological debt going forward. Some of the recent /interesting/ Haskell projects we've introduced to our infrastructure are: _Lazy SSL engine based on LetsEncrypt _ This is a Haskell program that issues SSL certificates using LetsEncrypt by doing /on-the-fly/ and /lazy/ certificate issuance. This allows us to vastly simplify HTTPS for 100's of domains we serve. _API Gateway for request pipe-lining_ We're a service oriented architecture. This usually entails that most of our API requests need to be serviced by a combination of back-end services, instead of just one. A trivial way to solve it would be: say a request needs to be passed to service A and then to B, then the responses from each of these services need to be accumulated into one client response. A can first receive the client request, do something, and then make another request to B to do something else. A can then accumulate the response from B along with its own response, and reply to the client. As one might imagine, it becomes increasingly cumbersome and hard to debug this kind of setup. Not only do you introduce dependencies between services A and B, coupling them tighter than you'd like, but it gets really messy when you're going to deal with authentication, authorisation and rapid changes in either A or B. In the worst case, you end up with request cycles (e.g. B makes a request to A), which are requests that never terminate and can bring down large parts of your infrastructure. The other big elephant in the room is also service discovery in a distributed environment. What makes sure that service A can reach a healthy instance of service B? To address this growing pain, we wrote a Haskell API Gateway service, which we lovingly call Quasar (I'm a fan of astronomical names) which flattens request pipe-lining at the API gateway level. What it does is: 1. recognises the request (based on verb + path) 2. identifies the resources being affected in this request (based on the query params/ JSON body) 3. authenticates the user 4. authorises the user for access to the identified resources 5. performs a request based pipeline flow: which is just a traversal of a request-tree, where each node is an "operation" to be performed on an input and output. The input being the response of the previous operation, and the output being the response of this operation. We leverage Haskell's elegant abstraction over operations like this (STM in particular) to ensure the responses are accumulated and returned to the client. -- These are some of the ways we're using Haskell and how it has benefited us. Going forward, given we have a fairly large codebase in Scala, we'd embark on replacing a service with its Haskell equivalent given the amount of changes required in the Scala counterpart is larger than a threshold. All new services that go into our infrastructure, however, will be written in Haskell. So far, our staple libraries of choice are: * Squeal * Servant ... and the usual suspects (Wai/Warp, Aeson, etc.) -- Other than that, we're based in the heart of Brussels, which is a fantastic city to work in, and we will offer a competitive compensation. Free weekly Belgian beers are on us. If this sounds interesting, please feel free to apply on the link above (https://centralapp.workable.com/j/9AFEDD1C3C). Or if you have any questions, please ask! While we'd prefer colleagues based /in /Belgium, or willing to relocate, we're still open to considering all applications. Thanks! -- Best, Ashesh Ambasta Founder (Engineering) CentralApp SA -------------- next part -------------- An HTML attachment was scrubbed... URL: From palotai.robin at gmail.com Fri Jan 25 21:48:33 2019 From: palotai.robin at gmail.com (Robin Palotai) Date: Fri, 25 Jan 2019 22:48:33 +0100 Subject: [Haskell-cafe] Is there a recursion-scheme function to push info down one level? Message-ID: I came up with this utility function so I can access some info (`n`) from the parent's level: hoistWithUpper :: forall f g s t n . (Functor g) => (forall a. f a -> n) -> n -> (forall a. n -> f a -> g a) -> (n -> s -> t) -> Free f s -> Free g t hoistWithUpper fu n0 hoistFr hoistPure = go n0 where go :: n -> Free f s -> Free g t go n fr = case fr of Pure s -> Pure (hoistPure n s) Free f -> let n2 = fu f in Free (go n2 <$> (hoistFr n f :: g (Free f s))) I wonder if there's already a generalized form of this in recursion-schemes? Admittedly I'm fine with my helper so don't loose nights on this, but a little type golfing never hurts. There's a similar function `inherit` [1] in fixplate, but that operates on Fix (Mu there), not Free. With Free I guess the complication is managing the different way of maintaining annotation at the Free and Pure ctors. Practically I pass in (\n f -> ConstProd (Pair (Const n) f)) -- for hoistFr (\n u -> (n,u)) -- for hoistPure. where newtype ConstProd c f a = ConstProd (Product (Const c) f a) Thanks! Robin [1]: http://hackage.haskell.org/package/fixplate-0.1.7/docs/src/Data-Generics-Fixplate-Attributes.html#inherit -------------- next part -------------- An HTML attachment was scrubbed... URL: From lysxia at gmail.com Fri Jan 25 22:58:47 2019 From: lysxia at gmail.com (Li-yao Xia) Date: Fri, 25 Jan 2019 17:58:47 -0500 Subject: [Haskell-cafe] Is there a recursion-scheme function to push info down one level? In-Reply-To: References: Message-ID: Hi Robin, I don't think there is a combinator that would make this function simpler, but you might find it interesting to see how this can be implemented with cata. Note that the constraint gets switched to Functor f instead of Functor g, and the eta expansion (fr0) to handle the order of arguments of cata. {-# LANGUAGE RankNTypes #-} import Data.Functor.Foldable import Control.Monad.Free import qualified Control.Monad.Trans.Free as Trans hoistWithUpper' :: forall f g s t n . (Functor f) => (forall a. f a -> n) -> n -> (forall a. n -> f a -> g a) -> (n -> s -> t) -> Free f s -> Free g t hoistWithUpper' fu n0 hoistFr hoistPure fr0 = cata (\fr n -> case fr of Trans.Pure a -> Pure (hoistPure n a) Trans.Free f -> let n2 = fu f in Free (hoistFr n (fmap ($ n2) f))) fr0 n0 Another solution, taking advantage of the particular choice of g you have, is to notice that Free (ConstProd n f) (n, s) is isomorphic to FreeT f ((,) n) s, where FreeT is a free monad transformer. The pairing with the annotation n thus gets refactored in a single location in the source. {-# LANGUAGE RankNTypes #-} import Data.Functor.Foldable import Data.Functor.Compose import Control.Monad.Free import qualified Control.Monad.Trans.Free as Trans hoistWithUpper'' :: forall f g s t n . (Functor f) => (forall a. f a -> n) -> n -> Free f s -> Trans.FreeT f ((,) n) s hoistWithUpper'' fu n0 fr = transverse (\fr n -> Compose (n, case fr of Trans.Pure a -> Trans.Pure a Trans.Free f -> Trans.Free (fmap ($ n2) f) where n2 = fu f)) fr n0 -- recursion-schemes >= 5.1 -- https://hackage.haskell.org/package/recursion-schemes-5.1/docs/Data-Functor-Foldable.html#v:transverse transverse :: (Recursive s, Corecursive t, Functor f) => (forall a. Base s (f a) -> f (Base t a)) -> (s -> f t) transverse n = cata (fmap embed . n) There is probably a similar construction with (CoFree _ n) instead of (FreeT _ ((,) n) _) as well. Regards, Li-yao On 1/25/19 4:48 PM, Robin Palotai wrote: > I came up with this utility function so I can access some info (`n`) > from the parent's level: > > hoistWithUpper >     :: forall f g s t n >      . (Functor g) >     => (forall a. f a -> n) >     -> n >     -> (forall a. n -> f a -> g a) >     -> (n -> s -> t) >     -> Free f s >     -> Free g t > hoistWithUpper fu n0 hoistFr hoistPure = go n0 >   where >     go :: n -> Free f s -> Free g t >     go n fr = case fr of >         Pure s -> Pure (hoistPure n s) >         Free f -> let n2 = fu f >                   in Free (go n2 <$> (hoistFr n f :: g (Free f s))) > > I wonder if there's already a generalized form of this in > recursion-schemes? Admittedly I'm fine with my helper so don't loose > nights on this, but a little type golfing never hurts. > > There's a similar function `inherit` [1] in fixplate, but that operates > on Fix (Mu there), not Free. With Free I guess the complication is > managing the different way of maintaining annotation at the Free and > Pure ctors. > > Practically I pass in > >    (\n f -> ConstProd (Pair (Const n) f))  -- for hoistFr >    (\n u -> (n,u))  -- for hoistPure. > > where > >     newtype ConstProd c f a = ConstProd (Product (Const c) f a) > > Thanks! > Robin > > [1]: > http://hackage.haskell.org/package/fixplate-0.1.7/docs/src/Data-Generics-Fixplate-Attributes.html#inherit > > _______________________________________________ > 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 zocca.marco at gmail.com Sat Jan 26 12:43:31 2019 From: zocca.marco at gmail.com (Marco Zocca) Date: Sat, 26 Jan 2019 13:43:31 +0100 Subject: [Haskell-cafe] generics-sop : deep flattening of nested algebraic values ? Message-ID: Hi all, I'm a bit at a loss regarding this: say we have a value from a nested algebraic type (definitions at the bottom) testT2 :: T2 testT2 = T2 B (Left 42) a generic encoding computed with `from` only goes one level deep, leaving the sub-terms as they are : λ> from testT2 SOP (Z (I B :* (I (Left 42) :* Nil))) However, is it possible to recursively encode and collect all the sub-terms, until primitive types or enumerations are encountered? The encoded sub-terms from the example above are as follows: λ> from B SOP (S (Z Nil)) λ> from (Left 32 :: Either Int Char) SOP (Z (I 32 :* Nil)) where {-# language DeriveGeneric #-} import qualified GHC.Generics as G import Generics.SOP data T1 = A | B | C deriving (G.Generic) instance Generic T1 data T2 = T2 { t21 :: T1 , t22 :: Either Int Char } deriving (G.Generic) instance Generic T2 From aeroboy94 at gmail.com Sat Jan 26 13:28:54 2019 From: aeroboy94 at gmail.com (Arian van Putten) Date: Sat, 26 Jan 2019 14:28:54 +0100 Subject: [Haskell-cafe] generics-sop : deep flattening of nested algebraic values ? In-Reply-To: References: Message-ID: http://hackage.haskell.org/package/generics-mrsop comes with both a deep and a shallow encoding of datatypes. The paper is here: https://doi.org/10.1145/3240719.3241786 On Sat, Jan 26, 2019, 13:44 Marco Zocca Hi all, > > I'm a bit at a loss regarding this: say we have a value from a nested > algebraic type (definitions at the bottom) > > testT2 :: T2 > testT2 = T2 B (Left 42) > > a generic encoding computed with `from` only goes one level deep, > leaving the sub-terms as they are : > > λ> from testT2 > SOP (Z (I B :* (I (Left 42) :* Nil))) > > However, is it possible to recursively encode and collect all the > sub-terms, until primitive types or enumerations are encountered? The > encoded sub-terms from the example above are as follows: > > λ> from B > SOP (S (Z Nil)) > λ> from (Left 32 :: Either Int Char) > SOP (Z (I 32 :* Nil)) > > where > > {-# language DeriveGeneric #-} > import qualified GHC.Generics as G > import Generics.SOP > > data T1 = A | B | C deriving (G.Generic) > instance Generic T1 > > data T2 = T2 { t21 :: T1 , t22 :: Either Int Char } deriving (G.Generic) > instance Generic T2 > _______________________________________________ > 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 boich249 at gmail.com Sat Jan 26 23:54:34 2019 From: boich249 at gmail.com (Asher Klein) Date: Sat, 26 Jan 2019 18:54:34 -0500 Subject: [Haskell-cafe] Montreal Haskell Message-ID: Hi everyone! New member here! Anyone know of Haskell jobs in Montreal for new grads? Thanks! -------------- next part -------------- An HTML attachment was scrubbed... URL: From zocca.marco at gmail.com Sun Jan 27 06:45:33 2019 From: zocca.marco at gmail.com (Marco Zocca) Date: Sun, 27 Jan 2019 07:45:33 +0100 Subject: [Haskell-cafe] generics-sop : deep flattening of nested algebraic values ? In-Reply-To: References: Message-ID: Ah, thank you for the reference! However I prefer to stay within generics-sop if possible. I am studying the implementations of `geq` and `gshow` in `basic-sop`, since they look like they're doing what I want. > http://hackage.haskell.org/package/generics-mrsop comes with both a deep and a shallow encoding of datatypes. > > The paper is here: https://doi.org/10.1145/3240719.3241786 > From leah at vuxu.org Sun Jan 27 13:07:05 2019 From: leah at vuxu.org (Leah Neukirchen) Date: Sun, 27 Jan 2019 14:07:05 +0100 Subject: [Haskell-cafe] Munich Haskell Meeting, 2019-01-28 @ 19:30 Message-ID: <87h8duw8p2.fsf@vuxu.org> Dear all, Next week, our monthly Munich Haskell Meeting will take place again on Monday, January 28 at Cafe Puck at 19h30. For details see here: http://muenchen.haskell.bayern/dates.html If you plan to join, please add yourself to this dudle so we can reserve enough seats! It is OK to add yourself to the dudle anonymously or pseudonymously. https://dudle.inf.tu-dresden.de/haskell-munich-jan-2019/ Everybody is welcome! cu, -- Leah Neukirchen http://leah.zone From blamario at ciktel.net Sun Jan 27 13:56:14 2019 From: blamario at ciktel.net (=?UTF-8?Q?Mario_Bla=c5=beevi=c4=87?=) Date: Sun, 27 Jan 2019 08:56:14 -0500 Subject: [Haskell-cafe] Montreal Haskell In-Reply-To: References: Message-ID: <41ec3af0-3a73-c0a2-7b0f-22933c2dd9aa@ciktel.net> On 2019-01-26 6:54 p.m., Asher Klein wrote: > Hi everyone! New member here! Anyone know of Haskell jobs in Montreal > for new grads? Thanks! > You're more likely to get an answer at https://www.meetup.com/lambda-montreal/ From johnz at pleasantnightmare.com Sun Jan 27 17:41:55 2019 From: johnz at pleasantnightmare.com (John Z.) Date: Sun, 27 Jan 2019 12:41:55 -0500 Subject: [Haskell-cafe] Montreal Haskell In-Reply-To: References: Message-ID: <20190127174155.GA27354@johnslap> > Hi everyone! New member here! Anyone know of Haskell jobs in Montreal for > new grads? Thanks! I'm in MTL myself, and I'm working with Haskell for past 6 years; the best I've found among general jobs in functional programming is Scala (and perhaps Kotlin) - but those are all OOP jobs where people adopt languages with fp features purely for 'cleaner syntax'. If you're looking for strict division between runtime and compile time knowledge, type safety - you're out of luck. The best I've found is a practice obsessed with unit testing. Morgan-Stanley do their own internal version of Haskell, and they're strongly oriented towards performance and correctness, and the people that interviewed me seemed quite experienced and smart - I had really awesome interview experience with Morgan-Stanley, even in comparison to Google. I've failed both interviews, tho :-D In any case, there are job postings here sometimes, and often companies are willing to consider remote work, given that haskell jobs and haskell professionals are scarcely distributed all around the world. That lambda meeting mentioned, I was looking into that myself, but afaik - it hasn't happened in a long, long time. Salut! -- "That gum you like is going to come back in style." From boich249 at gmail.com Sun Jan 27 19:20:07 2019 From: boich249 at gmail.com (Asher Klein) Date: Sun, 27 Jan 2019 14:20:07 -0500 Subject: [Haskell-cafe] Montreal Haskell In-Reply-To: <20190127174155.GA27354@johnslap> References: <20190127174155.GA27354@johnslap> Message-ID: Thanks, John, for your response! Personally I'm looking for a culture with some interesting mathematical background, more than any particular language feature. Would you be able to tell me some more about what goes on at Morgan Stanley? Thanks On Sun, Jan 27, 2019, 12:42 PM John Z. > Hi everyone! New member here! Anyone know of Haskell jobs in Montreal for > > new grads? Thanks! > > I'm in MTL myself, and I'm working with Haskell for past 6 years; > the best I've found among general jobs in functional programming is > Scala (and perhaps Kotlin) - but those are all OOP jobs where people > adopt languages with fp features purely for 'cleaner syntax'. If you're > looking for strict division between runtime and compile time knowledge, > type safety - you're out of luck. The best I've found is a practice > obsessed with unit testing. > > Morgan-Stanley do their own internal version of Haskell, and they're > strongly oriented towards performance and correctness, and the people > that interviewed me seemed quite experienced and smart - I had really > awesome interview experience with Morgan-Stanley, even in comparison to > Google. > I've failed both interviews, tho :-D > > In any case, there are job postings here sometimes, and often > companies are willing to consider remote work, given that haskell jobs > and haskell professionals are scarcely distributed all around the world. > > That lambda meeting mentioned, I was looking into that myself, but > afaik - it hasn't happened in a long, long time. > > Salut! > > > -- > "That gum you like is going to come back in style." > _______________________________________________ > 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 johnz at pleasantnightmare.com Sun Jan 27 19:45:49 2019 From: johnz at pleasantnightmare.com (John Z.) Date: Sun, 27 Jan 2019 14:45:49 -0500 Subject: [Haskell-cafe] Montreal Haskell In-Reply-To: References: <20190127174155.GA27354@johnslap> Message-ID: <20190127194549.GB27354@johnslap> > Thanks, John, for your response! Personally I'm looking for a culture with > some interesting mathematical background, more than any particular language > feature. I figured ;-) That's what I'm looking for too, but its really, REALLY hard to find a company that's trying to do something different. > Would you be able to tell me some more about what goes on at Morgan Stanley? They have state of the art trading engine/service. I am not sure how far do they go with formal methods, when it comes to the design, but they are very mindful of roperties of control and data structures they use to model it. At the very least, that's the impression I've got during the interview: they asked me to develop a small statistical algorithm, and then asked to optimize it to hit at least O(log n). They're also constantly looking for C++ and Java programmers, so you could apply there, get employed, and then work to switch to their Haskell team. -- "That gum you like is going to come back in style." From boich249 at gmail.com Sun Jan 27 19:48:21 2019 From: boich249 at gmail.com (Asher Klein) Date: Sun, 27 Jan 2019 14:48:21 -0500 Subject: [Haskell-cafe] Montreal Haskell In-Reply-To: <20190127194549.GB27354@johnslap> References: <20190127174155.GA27354@johnslap> <20190127194549.GB27354@johnslap> Message-ID: What about directly to their Haskell team?? On Sun, Jan 27, 2019, 2:46 PM John Z. > Thanks, John, for your response! Personally I'm looking for a culture > with > > some interesting mathematical background, more than any particular > language > > feature. > > I figured ;-) That's what I'm looking for too, but its really, REALLY > hard to find a company that's trying to do something different. > > > Would you be able to tell me some more about what goes on at Morgan > Stanley? > > They have state of the art trading engine/service. I am not sure how far > do they go with formal methods, when it comes to the design, but they > are very mindful of roperties of control and data structures they use to > model it. At the very least, that's the impression I've got during the > interview: they asked me to develop a small statistical algorithm, and > then asked to optimize it to hit at least O(log n). > > They're also constantly looking for C++ and Java programmers, so you > could apply there, get employed, and then work to switch to their > Haskell team. > > > > -- > "That gum you like is going to come back in style." > _______________________________________________ > 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 doug at cs.dartmouth.edu Mon Jan 28 14:13:43 2019 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Mon, 28 Jan 2019 09:13:43 -0500 Subject: [Haskell-cafe] Montreal Haskell Message-ID: <201901281413.x0SEDho8131955@tahoe.cs.Dartmouth.EDU> > Morgan-Stanley do their own internal version of Haskell, and they're > strongly oriented towards performance and correctness Interestingly eclectic. They also employ Bjarne Stroustup, the eminence grise of C++. Doug McIlroy From carette at mcmaster.ca Wed Jan 30 02:00:58 2019 From: carette at mcmaster.ca (Jacques Carette) Date: Tue, 29 Jan 2019 21:00:58 -0500 Subject: [Haskell-cafe] Seeking: 12 month internship opportunities for Haskell enthusiasts Message-ID: I'm writing on behalf of some (quite good) undergraduate students in CS who have been quite taken by Haskell, whose program includes a 12 month internship at a company.  Start time could be anytime between May and September, and duration would be 12 months.  [Some students who start in May end up doing 16 months]. If anyone here has leads on such opportunities, please contact me.  Location is flexible, as long as the language of work is English. Jacques From ichistmeinname at web.de Wed Jan 30 07:07:05 2019 From: ichistmeinname at web.de (Sandra Dylus) Date: Wed, 30 Jan 2019 08:07:05 +0100 Subject: [Haskell-cafe] Library for common AST transformations based on haskell-src-exts In-Reply-To: References: Message-ID: Hi, in the last couple of years we had a number of projects that used haskell-src-exts [1]. In most of these cases we wanted to do some common AST transformations, e.g., translating function definitions via several rules into one rule using case expressions. So, after needing these transformations a couple of times, I was wondering if there is a library that works on top of haskell-src-exts and implements common transformations like the one mentioned. I took a look at the reverse dependencies of haskell-src-exts, but only found projects implementing these transformations as part of a bigger project. In a nutshell, I am asking if I did miss such a library or if there does not exist such a library yet. If the latter is the case, we will definitely implement such a library as part of the next student project that builds upon haskell-src-exts. Cheers Sandra [1] http://hackage.haskell.org/package/haskell-src-exts -------------- next part -------------- An HTML attachment was scrubbed... URL: From hjgtuyl at chello.nl Thu Jan 31 01:56:36 2019 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Thu, 31 Jan 2019 02:56:36 +0100 Subject: [Haskell-cafe] Patents on Maybe and Tuple Message-ID: L.S., I just read the article "Apple Patents Swift".[0] It says that Apple has two patents regarding Swift: [1][2]; these patents state, amongst others, that there are new types of variables: "Additionally, an embodiment of the new language introduces advanced types not found in Objective-C. These types include Tuples and Optionals. Tuples enable a developer to create and pass groupings of values. Tuples group multiple values into a single compound value." and "In one embodiment, an optional type is provided that handles the absence of a value. Optionals are a way to say either “there is a value, and it equals x” or “there isn't a value at all.”" I hope we don't get arrested for using the Maybe monad or tuples in Haskell. Regards, Henk-Jan van Tuyl [0] https://www.i-programmer.info/news/98-languages/12495-apple-patents-swift.html [1] https://patents.google.com/patent/US9952841B2 [2] https://patents.google.com/patent/US9329844B2 -- Message from Stanford University: Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://foldingathome.stanford.edu/ -- http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From saurabhnanda at gmail.com Thu Jan 31 02:46:21 2019 From: saurabhnanda at gmail.com (Saurabh Nanda) Date: Thu, 31 Jan 2019 08:16:21 +0530 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: Broadly speaking, when reading a patent it is the independent claims that matter most. If your work is not infringing the independent claims, then everything else can be ignored -- especially the description & background sections of the patent, which are primarily used to make sense of the completely abstract terms in which the invention is described by the claims. The independent claims in these two patents are given below along with my understanding of what kind of inventions they're trying to cover (IANAL, but I was an Intellectual Property analyst in a previous job). *Patent US9329844B2* 1. A non-transitory computer-readable medium with instructions stored > therein, the instructions, when executed by a processor, cause the > processor to perform operations comprising: Hurray! You just described a computer! Btw, I never read the "non-transitory" part when in patents earlier. Some interesting background - https://www.smithhopen.com/glossary_term/149/Non-transitory-Media > > - receiving a first request to compile a first set of program > instructions coded in a first high-level language, the first high-level > language a C language based object-oriented programming language; > > Some invention containing a C, or C-like compiler.... > > - receiving a second request to compile a second set of program > instructions related to the first set of program instructions, the second > set of program instructions coded in a second high-level language including > object-oriented elements and procedural elements, wherein second high-level > language is not compatible with the C language; > > ...gets interesting here. A second compiler for a non C-like language. The two compilers are being used to compile two different, but related programs... > > - compiling the first set of program instructions and the second set > of program instructions using a modular compilation system including > multiple front-end compilers, the first set of program instructions > compiled into a first intermediate representation of the first set of > program instructions and the second set of program instructions compiled > into a second intermediate representation of the second set of program > instructions; > > this seems to be describing typical GCC or LLVM architecture, right? (I'm not a compiler engineer!) > > - linking the first and second intermediate representations; and > > ... nothing special here... > > - compiling the first and second intermediate representations using a > back-end compiler that is specific to a target processor. > > Again, standard cross compilation? This independent claim seems too broad to be true. There is nothing novel, apart from the presence of 2 compilers, that seems to be going on between the two programs being compiled or the two compilers. Let's narrow the scope using some dependent claims.... 4. The medium of claim 1, further comprising instructions to perform > additional operations including optimizing the first and second > intermediate representations during a compile-time optimization. 5. The medium of claim 1, further comprising instructions to perform > additional operations including optimizing the first and second > intermediate representations during a link-time optimization. > 7. The medium of claim 1, wherein compiling the second set of program > instructions includes performing compile-time data-type overflow checking > by default. > 8. The medium of claim 1, wherein compiling the second set of program > instructions includes performing compile-time data structure bounds > checking by default. > 9. The medium of claim 1, wherein compiling the second set of program > instructions includes performing one or more compile-time type safety > operations in conjunction with one or more type inference operations. *Aha! Something gets interesting here. There is optimisation happening between two programs written in two unrelated languages, by converting them into an IL and using both the ILs to perform optimisation. Does anyone know where Apple is using such compiler technology? *After reading the description & background section of the patents my guess is that they have patented all the concepts of Swift *in conjunction with* existing C/Obj-C code. Also, the wording seems to be sufficiently broad to cause some concern to Haskell & Rust compilers, but the compilation of two programs in two unrelated languages will probably prevent an infringement. 10. A system comprising: > > - [...] removed clauses similar to first independent claim [...] > > > - wherein the second set of program instructions are not compatible > with the C language and includes a data type provided by the second > high-level language to indicate absence of a value of any type. > > Take a look at the last clause. This is where the concept of `Maybe` is making its way into an independent claim. However, all of this is *in conjunction with* with a system comprising two compilers of unrelated languages. > 15. A computer-implemented method comprising: > > - [...] removed clauses similar to first independent claim [...] > > > - linking the first and second intermediate representations, wherein > linking the first and second intermediate representations includes > optimizing the first and second intermediate representations in response to > a compile-time request to optimize the program instructions; and > > > - compiling the first and second intermediate representations using a > back-end compiler that is specific to the target processor. > > Not sure what's new about this claim over and above the first claim, but I'm tired now... Moving on to the next patent... *Patent US9952841B2* 1. A non-transitory computer-readable medium with instructions stored > therein, the instructions, when executed by a processor, cause the > processor to perform operations comprising: Again -- you're describing a computer, Sherlock! > > - receiving a first request to compile a first set of program > instructions coded in a first high-level language, the first high-level > language a C language based object-oriented programming language; > > > - receiving a second request to compile a second set of program > instructions related to the first set of program instructions, the second > set of program instructions coded in a second high-level language including > object-oriented elements and procedural elements, wherein the second set of > program instructions includes a data type provided by the second high-level > language to indicate absence of a value of any type; > > > - compiling the first set of program instructions and the second set > of program instructions using a modular compilation system including > multiple front-end compilers, the first set of program instructions > compiled into a first intermediate representation of the first set of > program instructions and the second set of program instructions compiled > into a second intermediate representation of the second set of program > instructions; > > > - linking the first and second intermediate representations; and > > > - compiling the first and second intermediate representations using a > back-end compiler that is specific to a target processor. > > Again, talking about a similar 2-compiler system as the first patent. Let's look at some dependent claims.... 17. The method as in claim 16, wherein the second set of program > instructions are related to the first set of program instructions, the > second set of program instructions are coded in a second high-level > language that includes object-oriented and procedural elements, the second > set of program instructions are not compatible with the C language, and the > second set of program instructions includes an interpolated string. > 18. The method as in claim 16, wherein the back-end compiler is a > just-in-time compiler. > 19. The method as in claim 16, wherein compiling the second set of program > instructions includes performing compile-time data-type overflow checking > and compile-time data structure bounds checking by default. > They seem to be patenting numerous advanced compile-time checks in a 2-compiler system. (there are two more independent claims in this patent, but I'm really tired now!) -- Saurabh. On Thu, Jan 31, 2019 at 7:27 AM Henk-Jan van Tuyl wrote: > > L.S., > > I just read the article "Apple Patents Swift".[0] It says that Apple has > two patents regarding Swift: [1][2]; these patents state, amongst others, > that there are new types of variables: > > "Additionally, an embodiment of the new language introduces advanced types > not found in Objective-C. These types include Tuples and Optionals. Tuples > enable a developer to create and pass groupings of values. Tuples group > multiple values into a single compound value." > > and > > "In one embodiment, an optional type is provided that handles the absence > of a value. Optionals are a way to say either “there is a value, and it > equals x” or “there isn't a value at all.”" > > I hope we don't get arrested for using the Maybe monad or tuples in > Haskell. > > Regards, > Henk-Jan van Tuyl > > > [0] > > https://www.i-programmer.info/news/98-languages/12495-apple-patents-swift.html > [1] https://patents.google.com/patent/US9952841B2 > [2] https://patents.google.com/patent/US9329844B2 > > > -- > Message from Stanford University: > > Folding at home > > What if you could share your unused computer power to help find a cure? In > just 5 minutes you can join the world's biggest networked computer and get > us closer sooner. Watch the video. > http://foldingathome.stanford.edu/ > > -- > http://members.chello.nl/hjgtuyl/tourdemonad.html > Haskell programming > -- > _______________________________________________ > 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. -- http://www.saurabhnanda.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From saurabhnanda at gmail.com Thu Jan 31 02:50:52 2019 From: saurabhnanda at gmail.com (Saurabh Nanda) Date: Thu, 31 Jan 2019 08:20:52 +0530 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: > > Also, the wording seems to be sufficiently broad to cause some concern to > Haskell & Rust compilers, but the compilation of two programs in two > unrelated languages will probably prevent an infringement. > Actually, the teams working on languages like Eta, Kotlin, and Scala should be really worried about these series of patents and should get infringement analysis done by an experienced IP lawyer, and/or press for invalidation of these patents. -- Saurabh. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fvillanustre at gmail.com Thu Jan 31 03:16:35 2019 From: fvillanustre at gmail.com (Flavio Villanustre) Date: Wed, 30 Jan 2019 22:16:35 -0500 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: I'm no patent attorney either, but there is a temporal component when it comes to invalidating patents due to prior art, and Haskell is demonstrably "very prior" to these claims, even though it's not mentioned there. Only something that appeared after the patent was filed initially would potentially constitute infringement, as long as the claims made in the patent weren't made public by the inventors themselves prior to the filing, of course. I guess, Haskell is safe and we live to see another day... :) Flavio On Wed, Jan 30, 2019, 21:51 Saurabh Nanda Also, the wording seems to be sufficiently broad to cause some concern to >> Haskell & Rust compilers, but the compilation of two programs in two >> unrelated languages will probably prevent an infringement. >> > > Actually, the teams working on languages like Eta, Kotlin, and Scala > should be really worried about these series of patents and should get > infringement analysis done by an experienced IP lawyer, and/or press for > invalidation of these patents. > > -- Saurabh. > > _______________________________________________ > 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 asm13243546 at gmail.com Thu Jan 31 03:21:27 2019 From: asm13243546 at gmail.com (Alfred Matthews) Date: Wed, 30 Jan 2019 22:21:27 -0500 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: @Saurabh thanks. Well done. Are the patents each not effectively processor-specific? At the very least, the LLVM and subsidiary IRs are of interest. On Wed, Jan 30, 2019, 10:17 PM Flavio Villanustre wrote: > I'm no patent attorney either, but there is a temporal component when it > comes to invalidating patents due to prior art, and Haskell is demonstrably > "very prior" to these claims, even though it's not mentioned there. > > Only something that appeared after the patent was filed initially would > potentially constitute infringement, as long as the claims made in the > patent weren't made public by the inventors themselves prior to the filing, > of course. > > I guess, Haskell is safe and we live to see another day... :) > > Flavio > > On Wed, Jan 30, 2019, 21:51 Saurabh Nanda >> Also, the wording seems to be sufficiently broad to cause some concern to >>> Haskell & Rust compilers, but the compilation of two programs in two >>> unrelated languages will probably prevent an infringement. >>> >> >> Actually, the teams working on languages like Eta, Kotlin, and Scala >> should be really worried about these series of patents and should get >> infringement analysis done by an experienced IP lawyer, and/or press for >> invalidation of these patents. >> >> -- Saurabh. >> >> _______________________________________________ >> 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 asm13243546 at gmail.com Thu Jan 31 03:42:13 2019 From: asm13243546 at gmail.com (Alfred Matthews) Date: Wed, 30 Jan 2019 22:42:13 -0500 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: Also by my reading a patent derived from LLVM does not restrict either LLVM or ( the same thing ) its IR. The patent covers (only) processor-specific instructions and such forks and their subsidiary. At the least, not its ideas. Uninteresting, in our context. I am an untitled intelligent reader. Pay me if you wish. Ymmv. On Wed, Jan 30, 2019, 10:21 PM Alfred Matthews wrote: > @Saurabh thanks. Well done. > > Are the patents each not effectively processor-specific? > > At the very least, the LLVM and subsidiary IRs are of interest. > > > On Wed, Jan 30, 2019, 10:17 PM Flavio Villanustre > wrote: > >> I'm no patent attorney either, but there is a temporal component when it >> comes to invalidating patents due to prior art, and Haskell is demonstrably >> "very prior" to these claims, even though it's not mentioned there. >> >> Only something that appeared after the patent was filed initially would >> potentially constitute infringement, as long as the claims made in the >> patent weren't made public by the inventors themselves prior to the filing, >> of course. >> >> I guess, Haskell is safe and we live to see another day... :) >> >> Flavio >> >> On Wed, Jan 30, 2019, 21:51 Saurabh Nanda > >>> Also, the wording seems to be sufficiently broad to cause some concern >>>> to Haskell & Rust compilers, but the compilation of two programs in two >>>> unrelated languages will probably prevent an infringement. >>>> >>> >>> Actually, the teams working on languages like Eta, Kotlin, and Scala >>> should be really worried about these series of patents and should get >>> infringement analysis done by an experienced IP lawyer, and/or press for >>> invalidation of these patents. >>> >>> -- Saurabh. >>> >>> _______________________________________________ >>> 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 asm13243546 at gmail.com Thu Jan 31 03:43:45 2019 From: asm13243546 at gmail.com (Alfred Matthews) Date: Wed, 30 Jan 2019 22:43:45 -0500 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: http://lists.llvm.org/pipermail/llvm-dev/2017-August/116266.html Sorry, this is a necessary omission by me. On Wed, Jan 30, 2019, 10:42 PM Alfred Matthews wrote: > Also by my reading a patent derived from LLVM does not restrict either > LLVM or ( the same thing ) its IR. The patent covers (only) > processor-specific instructions and such forks and their subsidiary. > > At the least, not its ideas. > > Uninteresting, in our context. > > I am an untitled intelligent reader. Pay me if you wish. > > Ymmv. > > On Wed, Jan 30, 2019, 10:21 PM Alfred Matthews > wrote: > >> @Saurabh thanks. Well done. >> >> Are the patents each not effectively processor-specific? >> >> At the very least, the LLVM and subsidiary IRs are of interest. >> >> >> On Wed, Jan 30, 2019, 10:17 PM Flavio Villanustre >> wrote: >> >>> I'm no patent attorney either, but there is a temporal component when it >>> comes to invalidating patents due to prior art, and Haskell is demonstrably >>> "very prior" to these claims, even though it's not mentioned there. >>> >>> Only something that appeared after the patent was filed initially would >>> potentially constitute infringement, as long as the claims made in the >>> patent weren't made public by the inventors themselves prior to the filing, >>> of course. >>> >>> I guess, Haskell is safe and we live to see another day... :) >>> >>> Flavio >>> >>> On Wed, Jan 30, 2019, 21:51 Saurabh Nanda >> >>>> Also, the wording seems to be sufficiently broad to cause some concern >>>>> to Haskell & Rust compilers, but the compilation of two programs in two >>>>> unrelated languages will probably prevent an infringement. >>>>> >>>> >>>> Actually, the teams working on languages like Eta, Kotlin, and Scala >>>> should be really worried about these series of patents and should get >>>> infringement analysis done by an experienced IP lawyer, and/or press for >>>> invalidation of these patents. >>>> >>>> -- Saurabh. >>>> >>>> _______________________________________________ >>>> 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 saurabhnanda at gmail.com Thu Jan 31 03:53:43 2019 From: saurabhnanda at gmail.com (Saurabh Nanda) Date: Thu, 31 Jan 2019 09:23:43 +0530 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: > > Are the patents each not effectively processor-specific? > Alfred, if you're saying this because of the following clause in the independent claim... > compiling the first and second intermediate representations using a back-end compiler that is specific to a target processor. ...then I'm not so sure, because isn't every backend compiler specific to an architecture/processor? -------------- next part -------------- An HTML attachment was scrubbed... URL: From raoknz at gmail.com Thu Jan 31 13:29:18 2019 From: raoknz at gmail.com (Richard O'Keefe) Date: Fri, 1 Feb 2019 02:29:18 +1300 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: Haskell's "Maybe t" is essentially the same as ML's "'t option". ECMA Eiffel has a distinction between "T" and "T?" types which is related. The idea of a compiler system with multiple front- ends for dissimilar languages goes back to Burroughs (where type checking applied cross-language) and to Univac (where several languages used the same back end) and with multiple source languages sharing a common IR with multiple target-specific back ends goes back at least to the Amsterdam Compiler Kit. Back in 1984 the idea of retaining code in an intermediate form until it was about to be executed with so far from novel that I used it in a design. JIT compiling goes back at least to Brown's "throw- away compiling" for BASIC (compact IR, bulky native code compiled into a smallish buffer at need and periodically thrown away) and commercial Smalltalk systems. (And there is at least one Smalltalk out there with Lisp and Prolog syntax on offer as well.) Then there is the Poplog system, which incrementally compiled ML, Common Lisp (CLtL1 vintage), Pop-11, and Prolog, all quite different looking (and Pop-11 being arguably OO), into a common IR, with native code generation for multiple target processors. There may well be innovative things in Swift, but nothing in this thread would have seemed novel 30 years ago. On Thu, 31 Jan 2019 at 16:54, Saurabh Nanda wrote: > > >> Are the patents each not effectively processor-specific? >> > > Alfred, if you're saying this because of the following clause in the > independent claim... > > > compiling the first and second intermediate representations using a > back-end compiler that is specific to a target processor. > > ...then I'm not so sure, because isn't every backend compiler specific to > an architecture/processor? > _______________________________________________ > 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 alan.zimm at gmail.com Thu Jan 31 18:44:05 2019 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Thu, 31 Jan 2019 20:44:05 +0200 Subject: [Haskell-cafe] Library for common AST transformations based on haskell-src-exts In-Reply-To: References: Message-ID: I think the haskell-tools[1] project may have something in it that can help. It also provides various utility libraries [2],[3]. Alan [1] https://github.com/haskell-tools/haskell-tools [2] http://hackage.haskell.org/package/haskell-tools-ast [3] http://hackage.haskell.org/package/haskell-tools-ast-trf On Wed, 30 Jan 2019 at 09:07, Sandra Dylus wrote: > Hi, > > in the last couple of years we had a number of projects that used > haskell-src-exts [1]. In most of these cases we wanted to do some common > AST transformations, e.g., translating function definitions via several > rules into one rule using case expressions. So, after needing these > transformations a couple of times, I was wondering if there is a library > that works on top of haskell-src-exts and implements common transformations > like the one mentioned. I took a look at the reverse dependencies of > haskell-src-exts, but only found projects implementing these > transformations as part of a bigger project. > > In a nutshell, I am asking if I did miss such a library or if there does > not exist such a library yet. If the latter is the case, we will definitely > implement such a library as part of the next student project that builds > upon haskell-src-exts. > > Cheers > Sandra > > [1] http://hackage.haskell.org/package/haskell-src-exts > _______________________________________________ > 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 jack at jackkelly.name Thu Jan 31 22:28:30 2019 From: jack at jackkelly.name (Jack Kelly) Date: Fri, 1 Feb 2019 09:28:30 +1100 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: It's great that we know this, but does anyone who knows the patent system know that we know this? -- Jack On Fri, Feb 1, 2019 at 12:30 AM Richard O'Keefe wrote: > > Haskell's "Maybe t" is essentially the same as ML's "'t option". > ECMA Eiffel has a distinction between "T" and "T?" types which > is related. The idea of a compiler system with multiple front- > ends for dissimilar languages goes back to Burroughs (where > type checking applied cross-language) and to Univac (where several > languages used the same back end) and with multiple source languages sharing a common IR with multiple target-specific > back ends goes back at least to the Amsterdam Compiler Kit. Back > in 1984 the idea of retaining code in an intermediate form until > it was about to be executed with so far from novel that I used it > in a design. JIT compiling goes back at least to Brown's "throw- > away compiling" for BASIC (compact IR, bulky native code compiled > into a smallish buffer at need and periodically thrown away) and > commercial Smalltalk systems. (And there is at least one Smalltalk > out there with Lisp and Prolog syntax on offer as well.) Then there > is the Poplog system, which incrementally compiled ML, Common Lisp > (CLtL1 vintage), Pop-11, and Prolog, all quite different looking > (and Pop-11 being arguably OO), into a common IR, with native code generation for multiple target processors. > > There may well be innovative things in Swift, but nothing in this > thread would have seemed novel 30 years ago. > > On Thu, 31 Jan 2019 at 16:54, Saurabh Nanda wrote: >> >> >>> >>> Are the patents each not effectively processor-specific? >> >> >> Alfred, if you're saying this because of the following clause in the independent claim... >> >> > compiling the first and second intermediate representations using a back-end compiler that is specific to a target processor. >> >> ...then I'm not so sure, because isn't every backend compiler specific to an architecture/processor? >> _______________________________________________ >> 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 cma at bitemyapp.com Thu Jan 31 22:31:15 2019 From: cma at bitemyapp.com (Christopher Allen) Date: Thu, 31 Jan 2019 15:31:15 -0700 Subject: [Haskell-cafe] Patents on Maybe and Tuple In-Reply-To: References: Message-ID: IANAL, but from what I have seen said about this by IP lawyers: The USPTO doesn’t seem consider it their job to adjudicate things like this. They let most stuff through for the courts to sort out. > On Jan 31, 2019, at 3:28 PM, Jack Kelly wrote: > > It's great that we know this, but does anyone who knows the patent > system know that we know this? > > -- Jack > > On Fri, Feb 1, 2019 at 12:30 AM Richard O'Keefe wrote: >> >> Haskell's "Maybe t" is essentially the same as ML's "'t option". >> ECMA Eiffel has a distinction between "T" and "T?" types which >> is related. The idea of a compiler system with multiple front- >> ends for dissimilar languages goes back to Burroughs (where >> type checking applied cross-language) and to Univac (where several >> languages used the same back end) and with multiple source languages sharing a common IR with multiple target-specific >> back ends goes back at least to the Amsterdam Compiler Kit. Back >> in 1984 the idea of retaining code in an intermediate form until >> it was about to be executed with so far from novel that I used it >> in a design. JIT compiling goes back at least to Brown's "throw- >> away compiling" for BASIC (compact IR, bulky native code compiled >> into a smallish buffer at need and periodically thrown away) and >> commercial Smalltalk systems. (And there is at least one Smalltalk >> out there with Lisp and Prolog syntax on offer as well.) Then there >> is the Poplog system, which incrementally compiled ML, Common Lisp >> (CLtL1 vintage), Pop-11, and Prolog, all quite different looking >> (and Pop-11 being arguably OO), into a common IR, with native code generation for multiple target processors. >> >> There may well be innovative things in Swift, but nothing in this >> thread would have seemed novel 30 years ago. >> >> On Thu, 31 Jan 2019 at 16:54, Saurabh Nanda wrote: >>> >>> >>>> >>>> Are the patents each not effectively processor-specific? >>> >>> >>> Alfred, if you're saying this because of the following clause in the independent claim... >>> >>>> compiling the first and second intermediate representations using a back-end compiler that is specific to a target processor. >>> >>> ...then I'm not so sure, because isn't every backend compiler specific to an architecture/processor? >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post.