From stephen.tetley at gmail.com Fri Jun 1 17:34:10 2018 From: stephen.tetley at gmail.com (Stephen Tetley) Date: Fri, 1 Jun 2018 18:34:10 +0100 Subject: [Haskell-cafe] [ANN] karya, music editor In-Reply-To: References: Message-ID: Hi Evan Congratulations the release,I know from the haskell-art list you've been working on this for a good while. Best wishes Stephen On 28 May 2018 at 04:22, Evan Laforge wrote: > This is an announcement for Karya, which is a music editor written in Haskell. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Jun 1 18:10:20 2018 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 1 Jun 2018 19:10:20 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either Message-ID: <20180601181020.of2q6h2qwq2zzsfl@weber> I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` * `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded` Is there a particular reason for that? It might be tricky to implement toEnum :: Int -> a fromEnum :: a -> Int but in the presence of `Bounded` that should be possible. Tom From lysxia at gmail.com Fri Jun 1 18:23:58 2018 From: lysxia at gmail.com (Li-yao Xia) Date: Fri, 1 Jun 2018 14:23:58 -0400 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <20180601181020.of2q6h2qwq2zzsfl@weber> References: <20180601181020.of2q6h2qwq2zzsfl@weber> Message-ID: One issue is that (Int, Int) is too big to define toEnum/fromEnum. On 06/01/2018 02:10 PM, Tom Ellis wrote: > I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` > > * `(,)` has no instance for `Enum` > * `Either` has no instance for `Enum` or `Bounded` > > Is there a particular reason for that? It might be tricky to implement > > toEnum :: Int -> a > fromEnum :: a -> Int > > but in the presence of `Bounded` that should be possible. > > 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 tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Jun 1 18:32:55 2018 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 1 Jun 2018 19:32:55 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: References: <20180601181020.of2q6h2qwq2zzsfl@weber> Message-ID: <20180601183255.eukdyjlxbq6jq4bs@weber> True. I think I would propose instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) instance (Bounded a, Bounded b) => Enum (Bounded a b) instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b) On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote: > One issue is that (Int, Int) is too big to define toEnum/fromEnum. > > On 06/01/2018 02:10 PM, Tom Ellis wrote: > > I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` > > > > * `(,)` has no instance for `Enum` > > * `Either` has no instance for `Enum` or `Bounded` > > > > Is there a particular reason for that? It might be tricky to implement > > > > toEnum :: Int -> a > > fromEnum :: a -> Int > > > > but in the presence of `Bounded` that should be possible. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Jun 1 18:43:05 2018 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 1 Jun 2018 19:43:05 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <20180601183255.eukdyjlxbq6jq4bs@weber> References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> Message-ID: <20180601184305.pefw7p6ifzzjyoun@weber> I made a typo in the second one. It should be instance (Bounded a, Bounded b) => Bounded (Either a b) On Fri, Jun 01, 2018 at 07:32:55PM +0100, Tom Ellis wrote: > True. I think I would propose > > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) > instance (Bounded a, Bounded b) => Enum (Bounded a b) > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b) > > On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote: > > One issue is that (Int, Int) is too big to define toEnum/fromEnum. > > > > On 06/01/2018 02:10 PM, Tom Ellis wrote: > > > I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` > > > > > > * `(,)` has no instance for `Enum` > > > * `Either` has no instance for `Enum` or `Bounded` > > > > > > Is there a particular reason for that? It might be tricky to implement > > > > > > toEnum :: Int -> a > > > fromEnum :: a -> Int > > > > > > but in the presence of `Bounded` that should be possible. > _______________________________________________ > 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 tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Jun 1 19:20:54 2018 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 1 Jun 2018 20:20:54 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <20180601184305.pefw7p6ifzzjyoun@weber> References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> <20180601184305.pefw7p6ifzzjyoun@weber> Message-ID: <20180601192054.4iwv6rxohwdwnasf@weber> And to be precise, this seems to work {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} data P a b = P a b deriving (Eq, Bounded, Show) data E a b = L a | R b deriving (Eq, Show) instance (Bounded a, Bounded b) => Bounded (E a b) where minBound = L minBound maxBound = R maxBound instance forall a b. (Bounded a, Bounded b, Enum a, Enum b) => Enum (E a b) where fromEnum = \case L a -> fromEnum a R b -> fromEnum (maxBound :: a) + fromEnum b + 1 toEnum n = let m = fromEnum (maxBound :: a) in if n <= m then L (toEnum n) else R (toEnum (n - 1 - m)) instance forall a b. (Bounded a, Bounded b, Enum a, Enum b) => Enum (P a b) where fromEnum = \case P a b -> fromEnum a * (fromEnum (maxBound :: b) + 1) + fromEnum b toEnum n = let (q, r) = quotRem n (fromEnum (maxBound :: b) + 1) in P (toEnum q) (toEnum r) -- Test data Few = F1 | F2 | F3 deriving (Show, Eq, Bounded, Enum) data Several = S1 | S2 | S3 | S4 | S5 | S6 | S7 deriving (Show, Eq, Bounded, Enum) fromEnumP :: P Few Several -> Int fromEnumP = fromEnum fromEnumE :: E Few Several -> Int fromEnumE = fromEnum idP1 :: P Few Several -> P Few Several idP1 = toEnum . fromEnum idP2 :: Int -> Int idP2 = fromEnumP . toEnum idE1 :: E Few Several -> E Few Several idE1 = toEnum . fromEnum idE2 :: Int -> Int idE2 = fromEnumE . toEnum allPs :: [P Few Several] allPs = P <$> [minBound..maxBound] <*> [minBound..maxBound] -- > allPs -- [P F1 S1,P F1 S2,P F1 S3,P F1 S4,P F1 S5,P F1 S6,P F1 S7,P F2 S1,P F2 S2,P F2 S3,P F2 S4,P F2 S5,P F2 S6,P F2 S7,P F3 S1,P F3 S2,P F3 S3,P F3 S4,P F3 S5,P F3 S6,P F3 S7] allEs :: [E Few Several] allEs = map L [minBound..maxBound] ++ map R [minBound..maxBound] -- > allEs -- [L F1,L F2,L F3,R S1,R S2,R S3,R S4,R S5,R S6,R S7] test = and [ map idP2 [0..20] == [0..20] , map idE2 [0..9] == [0..9] , map idP1 allPs == allPs , map idE1 allEs == allEs ] -- > test -- True On Fri, Jun 01, 2018 at 07:43:05PM +0100, Tom Ellis wrote: > I made a typo in the second one. It should be > > instance (Bounded a, Bounded b) => Bounded (Either a b) > > > On Fri, Jun 01, 2018 at 07:32:55PM +0100, Tom Ellis wrote: > > True. I think I would propose > > > > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) > > instance (Bounded a, Bounded b) => Enum (Bounded a b) > > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b) > > > > On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote: > > > One issue is that (Int, Int) is too big to define toEnum/fromEnum. > > > > > > On 06/01/2018 02:10 PM, Tom Ellis wrote: > > > > I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` > > > > > > > > * `(,)` has no instance for `Enum` > > > > * `Either` has no instance for `Enum` or `Bounded` > > > > > > > > Is there a particular reason for that? It might be tricky to implement > > > > > > > > toEnum :: Int -> a > > > > fromEnum :: a -> Int > > > > > > > > but in the presence of `Bounded` that should be possible. > > _______________________________________________ > > 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 monkleyon at gmail.com Fri Jun 1 19:28:07 2018 From: monkleyon at gmail.com (MarLinn) Date: Fri, 1 Jun 2018 21:28:07 +0200 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <20180601183255.eukdyjlxbq6jq4bs@weber> References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> Message-ID: Counterargument: overlapping instances     instance (Bounded b, Enum b) => Enum (Either a b) instance (Bounded b) => Bounded (Either a b) instance (Applicative f, Bounded a) => Bounded (f a)     instance (Bounded a, Enum a) => Enum (Either a b) instance (Bounded a) => Bounded (Either a b) instance (Bounded a, Enum a, Monoid b) => Enum (a, b) instance (Bounded b, Enum b, Monoid a) => Enum (a, b) Also note that what you're talking about is a special type of objects, namely     type BoundedEnum a = (Bounded a, Enum a) -- using ConstraintKinds (I'm sure the mathematicians have a better name for this) So IF someone where to add these somewhere, might I suggest also adding essentials like     enumAll :: (Bounded a, Enum a) => [a]   -- i.e. enumAll :: (BoundedEnum a) => [a] Lastly, because it's its own type of objects, I'm sure there's a library out there doing just that. (Plus maybe other stuff like EnumMap's). On 2018-06-01 20:32, Tom Ellis wrote: > True. I think I would propose > > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) > instance (Bounded a, Bounded b) => Enum (Bounded a b) > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b) > > On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote: >> One issue is that (Int, Int) is too big to define toEnum/fromEnum. >> >> On 06/01/2018 02:10 PM, Tom Ellis wrote: >>> I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` >>> >>> * `(,)` has no instance for `Enum` >>> * `Either` has no instance for `Enum` or `Bounded` >>> >>> Is there a particular reason for that? It might be tricky to implement >>> >>> toEnum :: Int -> a >>> fromEnum :: a -> Int >>> >>> but in the presence of `Bounded` that should be possible. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Jun 1 19:33:18 2018 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 1 Jun 2018 20:33:18 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> Message-ID: <20180601193318.5zd56j56k2q5zhgp@weber> Sorry, could you explain further? I don't understand what the implementation of any of those proposed instances is supposed to be. On Fri, Jun 01, 2018 at 09:28:07PM +0200, MarLinn wrote: > Counterargument: overlapping instances > >     instance (Bounded b, Enum b) => Enum (Either a b) > instance (Bounded b) => Bounded (Either a b) > instance (Applicative f, Bounded a) => Bounded (f a) >     instance (Bounded a, Enum a) => Enum (Either a b) > instance (Bounded a) => Bounded (Either a b) > instance (Bounded a, Enum a, Monoid b) => Enum (a, b) > instance (Bounded b, Enum b, Monoid a) => Enum (a, b) > > Also note that what you're talking about is a special type of objects, > namely > >     type BoundedEnum a = (Bounded a, Enum a) -- using ConstraintKinds > > (I'm sure the mathematicians have a better name for this) > > So IF someone where to add these somewhere, might I suggest also adding > essentials like > >     enumAll :: (Bounded a, Enum a) => [a] >   -- i.e. enumAll :: (BoundedEnum a) => [a] > > Lastly, because it's its own type of objects, I'm sure there's a library out > there doing just that. (Plus maybe other stuff like EnumMap's). > > On 2018-06-01 20:32, Tom Ellis wrote: > > True. I think I would propose > > > > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) > > instance (Bounded a, Bounded b) => Enum (Bounded a b) > > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b) > > > > On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote: > > > One issue is that (Int, Int) is too big to define toEnum/fromEnum. > > > > > > On 06/01/2018 02:10 PM, Tom Ellis wrote: > > > > I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` > > > > > > > > * `(,)` has no instance for `Enum` > > > > * `Either` has no instance for `Enum` or `Bounded` > > > > > > > > Is there a particular reason for that? It might be tricky to implement > > > > > > > > toEnum :: Int -> a > > > > fromEnum :: a -> Int > > > > > > > > but in the presence of `Bounded` that should be possible. > > _______________________________________________ > 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 Jun 1 19:33:30 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 1 Jun 2018 15:33:30 -0400 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> Message-ID: The BoundedEnum thing is already something of a sunk cost, since there's already magic behavior of Enum when a type is also Bounded. (Go look at how Enum deriving is specified.) On Fri, Jun 1, 2018 at 3:28 PM MarLinn wrote: > Counterargument: overlapping instances > > instance (Bounded b, Enum b) => Enum (Either a b) > instance (Bounded b) => Bounded (Either a b) > instance (Applicative f, Bounded a) => Bounded (f a) > instance (Bounded a, Enum a) => Enum (Either a b) > instance (Bounded a) => Bounded (Either a b) > instance (Bounded a, Enum a, Monoid b) => Enum (a, b) > instance (Bounded b, Enum b, Monoid a) => Enum (a, b) > > Also note that what you're talking about is a special type of objects, > namely > > type BoundedEnum a = (Bounded a, Enum a) -- using ConstraintKinds > > (I'm sure the mathematicians have a better name for this) > > So IF someone where to add these somewhere, might I suggest also adding > essentials like > > enumAll :: (Bounded a, Enum a) => [a] > -- i.e. enumAll :: (BoundedEnum a) => [a] > > > Lastly, because it's its own type of objects, I'm sure there's a library > out there doing just that. (Plus maybe other stuff like EnumMap's). > > On 2018-06-01 20:32, Tom Ellis wrote: > > True. I think I would propose > > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) > instance (Bounded a, Bounded b) => Enum (Bounded a b) > instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b) > > On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote: > > One issue is that (Int, Int) is too big to define toEnum/fromEnum. > > On 06/01/2018 02:10 PM, Tom Ellis wrote: > > I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` > > * `(,)` has no instance for `Enum` > * `Either` has no instance for `Enum` or `Bounded` > > Is there a particular reason for that? It might be tricky to implement > > toEnum :: Int -> a > fromEnum :: a -> Int > > but in the presence of `Bounded` that should be possible. > > > _______________________________________________ > 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 sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Fri Jun 1 19:47:47 2018 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Fri, 1 Jun 2018 15:47:47 -0400 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <20180601192054.4iwv6rxohwdwnasf@weber> References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> <20180601184305.pefw7p6ifzzjyoun@weber> <20180601192054.4iwv6rxohwdwnasf@weber> Message-ID: > On Jun 1, 2018, at 3:20 PM, Tom Ellis wrote: > > instance forall a b. (Bounded a, Bounded b, Enum a, Enum b) => Enum (E a b) where > fromEnum = \case > L a -> fromEnum a > R b -> fromEnum (maxBound :: a) + fromEnum b + 1 This appears to assume that (fromEnum b) is never negative. (effectively that (minBound :: b) >= 0). Ignoring overflow issues, this should perhaps be: R b -> fromEnum (maxBound :: a) + (fromEnum b - fromEnum (minBound :: b)) + 1 This will of course overflow when ranges of a and/or b are large enough. -- Viktor. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Jun 1 19:52:35 2018 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 1 Jun 2018 20:52:35 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> <20180601184305.pefw7p6ifzzjyoun@weber> <20180601192054.4iwv6rxohwdwnasf@weber> Message-ID: <20180601195235.tth3eadaukf64few@weber> On Fri, Jun 01, 2018 at 03:47:47PM -0400, Viktor Dukhovni wrote: > > On Jun 1, 2018, at 3:20 PM, Tom Ellis wrote: > > > > instance forall a b. (Bounded a, Bounded b, Enum a, Enum b) => Enum (E a b) where > > fromEnum = \case > > L a -> fromEnum a > > R b -> fromEnum (maxBound :: a) + fromEnum b + 1 > > This appears to assume that (fromEnum b) is never negative. > (effectively that (minBound :: b) >= 0). It assumes that minBound == 0, which we can see is wrong by considering Int. > Ignoring overflow issues, this should perhaps be: > > R b -> fromEnum (maxBound :: a) + (fromEnum b - fromEnum (minBound :: b)) + 1 Yes, thanks, I think that's the kind of thing we want to do. > This will of course overflow when ranges of a and/or b are large enough. Naturally. From monkleyon at gmail.com Fri Jun 1 20:21:45 2018 From: monkleyon at gmail.com (MarLinn) Date: Fri, 1 Jun 2018 22:21:45 +0200 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <20180601193318.5zd56j56k2q5zhgp@weber> References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> <20180601193318.5zd56j56k2q5zhgp@weber> Message-ID: <98211e03-ef6e-4f9e-bdd1-22a974c70771@gmail.com> > Sorry, could you explain further? I don't understand what the > implementation of any of those proposed instances is supposed to be. Sure. {-# LANGUAGE ConstraintKinds #-} type BoundedEnum a = (Bounded a, Enum a)     instance (BoundedEnum b) => Enum (Either a b) where fromEnum (Left _) = 0 fromEnum (Right x) = 1 + fromEnum x toEnum 0 = error "toEnum: zero" -- could also add a Monoid constraint instead toEnum n = Right . toEnum $ n-1 instance (Bounded b) => Bounded (Either a b) where minBound = Right minBound maxBound = Right maxBound Rationale: these two implement the use case of working on something from a finite selection of elements inside a monad stack. In other words it's a special case of  instance (Applicative f, Bounded a) => Bounded (f a) where minBound = pure minBound maxBound = pure maxBound Is it a good idea to implement this? Probably not, but it serves as an illustration. On the other hand, many error types are bounded and enumerable, so why not enhance the error handling instead? instance (BoundedEnum a, Monoid b) => Enum (Either a b) where -- okay, I cheated by adding the Monoid constraint this time fromEnum (Right _) = 0 fromEnum (Left e) = 1 + fromEnum e toEnum 0 = Right mempty toEnum n = Left . toEnum $ n-1 instance (Bounded a) => Bounded (Either a b) where minBound = Left minBound maxBound = Left maxBound Which is better? That depends. Now for product types: instance (Enum a, Monoid b) => Enum (a, b) where toEnum = (,mempty) . toEnum fromEnum = fromEnum . fst instance (Enum b, Monoid a) => Enum (a, b) where toEnum = (mempty,) . toEnum fromEnum = fromEnum . snd And to be thorough     enumAll :: (BoundedEnum a) => [a] enumAll = enumFromTo minBound maxBound Hope it's clearer now what I meant. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sat Jun 2 05:39:28 2018 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 2 Jun 2018 06:39:28 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <98211e03-ef6e-4f9e-bdd1-22a974c70771@gmail.com> References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> <20180601193318.5zd56j56k2q5zhgp@weber> <98211e03-ef6e-4f9e-bdd1-22a974c70771@gmail.com> Message-ID: <20180602053928.7v52qhh7ucznnpu7@weber> On Fri, Jun 01, 2018 at 10:21:45PM +0200, MarLinn wrote: > > > Sorry, could you explain further? I don't understand what the > > implementation of any of those proposed instances is supposed to be. > > Sure. [...] > Hope it's clearer now what I meant. It's clearer what you meant, but I always assumed that fromEnum and toEnum must be mutually inverse. I can't see that law written anywhere in the docs but it seems to be an almost useless class without that assumption. The default implementations of the other methods seems to be completely based on that assumption, for example: http://hackage.haskell.org/package/base-4.11.1.0/docs/src/GHC.Enum.html#Enum From jon.fairbairn at cl.cam.ac.uk Sat Jun 2 09:36:56 2018 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Sat, 02 Jun 2018 10:36:56 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either References: <20180601181020.of2q6h2qwq2zzsfl@weber> Message-ID: Tom Ellis writes: > I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` > > * `(,)` has no instance for `Enum` > * `Either` has no instance for `Enum` or `Bounded` > > Is there a particular reason for that? It might be tricky to implement > > toEnum :: Int -> a > fromEnum :: a -> Int > > but in the presence of `Bounded` that should be possible. You don’t need Bounded to do that. For example, you could start at (0,0) and go out in diamond shaped rings. A more pressing reason is that there are too many possible enumerations, and if we picked one it would probably be the wrong one for most applications. -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sat Jun 2 09:48:45 2018 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 2 Jun 2018 10:48:45 +0100 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: References: <20180601181020.of2q6h2qwq2zzsfl@weber> Message-ID: <20180602094845.3hmbnbyhqazzent7@weber> On Sat, Jun 02, 2018 at 10:36:56AM +0100, Jon Fairbairn wrote: > Tom Ellis writes: > > > I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` > > > > * `(,)` has no instance for `Enum` > > * `Either` has no instance for `Enum` or `Bounded` > > > > Is there a particular reason for that? It might be tricky to implement > > > > toEnum :: Int -> a > > fromEnum :: a -> Int > > > > but in the presence of `Bounded` that should be possible. > > You don’t need Bounded to do that. For example, you could start > at (0,0) and go out in diamond shaped rings. A more pressing > reason is that there are too many possible enumerations, and if > we picked one it would probably be the wrong one for most > applications. This is all true, but I was implicitly assuming that Bounded and Enum ought to agree with Ord. We've already picked Ords for (,) and Either so why not also pick the Enums and Boundeds that agree with them? From andrew.thaddeus at gmail.com Sat Jun 2 14:14:57 2018 From: andrew.thaddeus at gmail.com (Andrew Martin) Date: Sat, 2 Jun 2018 10:14:57 -0400 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <20180602053928.7v52qhh7ucznnpu7@weber> References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> <20180601193318.5zd56j56k2q5zhgp@weber> <98211e03-ef6e-4f9e-bdd1-22a974c70771@gmail.com> <20180602053928.7v52qhh7ucznnpu7@weber> Message-ID: <33D6B0FC-13E4-44B2-A0A1-0C40032EE8CF@gmail.com> The way I understand it is more like: they should be Mutual inverses if the type has fewer inhabitants than Int does, and otherwise, just kind of do the best you can. What about the instance for Integer? Sent from my iPhone > On Jun 2, 2018, at 1:39 AM, Tom Ellis wrote: > >> On Fri, Jun 01, 2018 at 10:21:45PM +0200, MarLinn wrote: >> >>> Sorry, could you explain further? I don't understand what the >>> implementation of any of those proposed instances is supposed to be. >> >> Sure. > [...] >> Hope it's clearer now what I meant. > > It's clearer what you meant, but I always assumed that fromEnum and toEnum > must be mutually inverse. I can't see that law written anywhere in the docs > but it seems to be an almost useless class without that assumption. The > default implementations of the other methods seems to be completely based on > that assumption, for example: > > http://hackage.haskell.org/package/base-4.11.1.0/docs/src/GHC.Enum.html#Enum > _______________________________________________ > 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 ryan.reich at gmail.com Sat Jun 2 16:34:38 2018 From: ryan.reich at gmail.com (Ryan Reich) Date: Sat, 2 Jun 2018 09:34:38 -0700 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <33D6B0FC-13E4-44B2-A0A1-0C40032EE8CF@gmail.com> References: <20180601181020.of2q6h2qwq2zzsfl@weber> <20180601183255.eukdyjlxbq6jq4bs@weber> <20180601193318.5zd56j56k2q5zhgp@weber> <98211e03-ef6e-4f9e-bdd1-22a974c70771@gmail.com> <20180602053928.7v52qhh7ucznnpu7@weber> <33D6B0FC-13E4-44B2-A0A1-0C40032EE8CF@gmail.com> Message-ID: Which raises the question, why is there not an Enumerate class with Integer in place of Int? It would agree better with Integral. On Jun 2, 2018 07:15, "Andrew Martin" wrote: The way I understand it is more like: they should be Mutual inverses if the type has fewer inhabitants than Int does, and otherwise, just kind of do the best you can. What about the instance for Integer? Sent from my iPhone > On Jun 2, 2018, at 1:39 AM, Tom Ellis < tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote: > >> On Fri, Jun 01, 2018 at 10:21:45PM +0200, MarLinn wrote: >> >>> Sorry, could you explain further? I don't understand what the >>> implementation of any of those proposed instances is supposed to be. >> >> Sure. > [...] >> Hope it's clearer now what I meant. > > It's clearer what you meant, but I always assumed that fromEnum and toEnum > must be mutually inverse. I can't see that law written anywhere in the docs > but it seems to be an almost useless class without that assumption. The > default implementations of the other methods seems to be completely based on > that assumption, for example: > > http://hackage.haskell.org/package/base-4.11.1.0/docs/src/GHC.Enum.html#Enum > _______________________________________________ > 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 mail at joachim-breitner.de Sat Jun 2 17:32:43 2018 From: mail at joachim-breitner.de (Joachim Breitner) Date: Sat, 02 Jun 2018 19:32:43 +0200 Subject: [Haskell-cafe] (names for) invariants for Eq and Ord? In-Reply-To: <0aa941ff-89bd-d587-e8aa-bc1e09deaccc@htwk-leipzig.de> References: <0aa941ff-89bd-d587-e8aa-bc1e09deaccc@htwk-leipzig.de> Message-ID: Hi Johannes, Am Montag, den 28.05.2018, 16:47 +0200 schrieb Johannes Waldmann: > Do we (Haskell) need something similar to "consistent with equals"? not authorative, but the formalization of the base library in Coq, as part of the the hs-to-coq project, says Eq and Ord need to be compatible: Class OrdLaws (t : Type) {HEq : Eq_ t} {HOrd : Ord t} {HEqLaw : EqLaws t} := { (* The axioms *) Ord_antisym : forall a b, a <= b = true -> b <= a = true -> a == b = true; Ord_trans_le : forall a b c, a <= b = true -> b <= c = true -> a <= c = true; Ord_total : forall a b, a <= b = true \/ b <= a = true; (* The other operations, in terms of <= or == *) Ord_compare_Lt : forall a b, compare a b = Lt <-> b <= a = false; Ord_compare_Eq : forall a b, compare a b = Eq <-> a == b = true; Ord_compare_Gt : forall a b, compare a b = Gt <-> a <= b = false; Ord_lt_le : forall a b, a < b = negb (b <= a); Ord_ge_le : forall a b, a >= b = (b <= a); Ord_gt_le : forall a b, a > b = negb (a <= b); }. https://github.com/antalsz/hs-to-coq/blob/86f4c36dfe4b096eb7d48205cea3fddeeab23eaa/examples/containers/theories/OrdTactic.v#L14 Because we have a tactic that automates reasoning with lawfull Ord instances and uses Ord_antisym and Ord_compare_Eq internally I cannot easily check if these laws are actually used in the verification of Data.Set. One could argue that “total order” implies “antisymmetric” which implies a relation with (==). 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 lysxia at gmail.com Sun Jun 3 00:18:41 2018 From: lysxia at gmail.com (Li-yao Xia) Date: Sat, 2 Jun 2018 20:18:41 -0400 Subject: [Haskell-cafe] A law for MonadReader Message-ID: <733fae2c-a832-f2cc-55fb-8f90d5de82f4@gmail.com> Hello Café, While trying to document laws for mtl classes (https://github.com/haskell/mtl/issues/5) I have been puzzling over the subtle logical relationships between a few variants. Consider the following four possible laws for MonadReader's ask: (1) (ask >> ask) = ask (2) (ask >>= \r1 -> ask >>= \r2 -> return (r1, r2)) = (ask >>= \r -> return (r, r)) (3) (ask >> return ()) = return () Let reader :: MonadReader r m => (r -> a) -> m a reader f = fmap f ask (4) reader is a monad homomorphism from ((->) r) to m, i.e.: reader (\_ -> a) = return a (reader m >>= \x -> reader (k x)) = reader (m >>= k) Question: which ones imply which ones? Note that (1) and (2) do not imply (3) or (4). Intuitively, (1) and (2) say that ask is idempotent ("asking twice is the same as asking once"), but (3) and (4) imply the stronger property of nullipotence ("ask has no side effects"). --- Any help with the following conjectures is welcome (we're assuming the monad laws hold in the first place): A. (1) and (2) are equivalent. I can prove that (2) implies (1). However the converse eludes me. B. (3) and (4) are equivalent. Again, I can prove that (4) implies (3), but I had no success with the converse. C. ((3) or (4)) implies ((1) and (2)) ((3) implies (1)), and ((4) implies ((1) and (2))) are straightforward, but without the above equivalence, the missing bit is ((3) implies (2)) It seems that parametricity plays an important role in the conjectured implications. I didn't manage to apply free theorems to this problem, but perhaps you will have better luck. Regards, Li-yao From foxbenjaminfox at gmail.com Sun Jun 3 07:32:29 2018 From: foxbenjaminfox at gmail.com (Benjamin Fox) Date: Sun, 3 Jun 2018 09:32:29 +0200 Subject: [Haskell-cafe] A law for MonadReader In-Reply-To: <733fae2c-a832-f2cc-55fb-8f90d5de82f4@gmail.com> References: <733fae2c-a832-f2cc-55fb-8f90d5de82f4@gmail.com> Message-ID: As far as I can tell, (1) on it's own does not imply (2). I even have a counterexample, assuming no further laws on `ask` and no laws on `local`. Requiring `local` makes things more complicated (as `local` always does) and it may well be that a sufficiently strong law for `local` would rule out cases where (1) and (2) differ. (I'm not sure of that, I'll need to think about it a bit more.) Here is the counterexample: instance MonadReader (IORef Int) IO where ask = newIORef 0 local _ = id This obeys law (1): (newIORef 0 >> newIORef 0) == newIORef 0. But not (2): (newIORef 0 >>= \r1 -> newIORef 0 >>= \r2 -> return (r1, r2)) ≠ (newIORef 0 >>= \r -> return (r, r)). The left side of (2) returns a tuple containing two different IORefs (both containing 0), whereas the right side returns a tuple containing two references to the same IORef. On Sun, Jun 3, 2018 at 2:19 AM Li-yao Xia wrote: > Hello Café, > > While trying to document laws for mtl classes > (https://github.com/haskell/mtl/issues/5) I have been puzzling over the > subtle logical relationships between a few variants. > > Consider the following four possible laws for MonadReader's ask: > > (1) (ask >> ask) = ask > > (2) (ask >>= \r1 -> ask >>= \r2 -> return (r1, r2)) = (ask >>= \r -> > return (r, r)) > > (3) (ask >> return ()) = return () > > Let > > reader :: MonadReader r m => (r -> a) -> m a > reader f = fmap f ask > > (4) reader is a monad homomorphism from ((->) r) to m, i.e.: > > reader (\_ -> a) = return a > (reader m >>= \x -> reader (k x)) = reader (m >>= k) > > Question: which ones imply which ones? > > Note that (1) and (2) do not imply (3) or (4). Intuitively, (1) and (2) > say that ask is idempotent ("asking twice is the same as asking once"), > but (3) and (4) imply the stronger property of nullipotence ("ask has no > side effects"). > > --- > > Any help with the following conjectures is welcome (we're assuming the > monad laws hold in the first place): > > A. (1) and (2) are equivalent. > > I can prove that (2) implies (1). However the converse eludes me. > > B. (3) and (4) are equivalent. > > Again, I can prove that (4) implies (3), but I had no success with the > converse. > > C. ((3) or (4)) implies ((1) and (2)) > > ((3) implies (1)), and ((4) implies ((1) and (2))) are straightforward, > but without the above equivalence, the missing bit is ((3) implies (2)) > > It seems that parametricity plays an important role in the conjectured > implications. I didn't manage to apply free theorems to this problem, > but perhaps you will have better luck. > > 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 ietf-dane at dukhovni.org Sun Jun 3 07:46:56 2018 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Sun, 3 Jun 2018 03:46:56 -0400 Subject: [Haskell-cafe] A law for MonadReader In-Reply-To: References: <733fae2c-a832-f2cc-55fb-8f90d5de82f4@gmail.com> Message-ID: <3B95E8EE-2628-4965-A27F-4695F55182A8@dukhovni.org> > On Jun 3, 2018, at 3:32 AM, Benjamin Fox wrote: > > Here is the counterexample: > > instance MonadReader (IORef Int) IO where > ask = newIORef 0 > local _ = id > > This obeys law (1): (newIORef 0 >> newIORef 0) == newIORef 0. Can you explain what you mean? Prelude> :m + Data.IORef Prelude Data.IORef> let z = 0 :: Int Prelude Data.IORef> a <- newIORef z Prelude Data.IORef> b <- newIORef z Prelude Data.IORef> let c = newIORef z Prelude Data.IORef> let d = newIORef z Prelude Data.IORef> a == b False Prelude Data.IORef> c == d :8:1: error: • No instance for (Eq (IO (IORef Int))) arising from a use of ‘==’ • In the expression: c == d In an equation for ‘it’: it = c == d -- Viktor. From foxbenjaminfox at gmail.com Sun Jun 3 11:55:36 2018 From: foxbenjaminfox at gmail.com (Benjamin Fox) Date: Sun, 3 Jun 2018 13:55:36 +0200 Subject: [Haskell-cafe] A law for MonadReader In-Reply-To: <3B95E8EE-2628-4965-A27F-4695F55182A8@dukhovni.org> References: <733fae2c-a832-f2cc-55fb-8f90d5de82f4@gmail.com> <3B95E8EE-2628-4965-A27F-4695F55182A8@dukhovni.org> Message-ID: Here, as in general in the definitions of laws, the relevent question is referential transparency, not Eq instances. (You'll note that generally in the definitions of laws the symbol "=" is used, not "==". Sometimes that's written as "≡", to be even clearer about what it represents, as for instance the Monad Laws page on the Haskell wiki does.) For some laws, like the "fmap id = id" Functor law, this is obviously the only possible interpretation, as both sides of that equation are necessarily functions, and functions don't have an Eq instance. So in this case, what the first law is asking for is that "ask >> ask" is the same as "ask", in that any instance of "ask" in a program can be replaced with "ask >> ask", or vice versa, without that changing the program's semantics. On Sun, Jun 3, 2018 at 9:47 AM Viktor Dukhovni wrote: > > > > On Jun 3, 2018, at 3:32 AM, Benjamin Fox > wrote: > > > > Here is the counterexample: > > > > instance MonadReader (IORef Int) IO where > > ask = newIORef 0 > > local _ = id > > > > This obeys law (1): (newIORef 0 >> newIORef 0) == newIORef 0. > > Can you explain what you mean? > > Prelude> :m + Data.IORef > Prelude Data.IORef> let z = 0 :: Int > Prelude Data.IORef> a <- newIORef z > Prelude Data.IORef> b <- newIORef z > Prelude Data.IORef> let c = newIORef z > Prelude Data.IORef> let d = newIORef z > Prelude Data.IORef> a == b > False > Prelude Data.IORef> c == d > > :8:1: error: > • No instance for (Eq (IO (IORef Int))) arising from a use of ‘==’ > • In the expression: c == d > In an equation for ‘it’: it = c == d > > -- > Viktor. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lysxia at gmail.com Sun Jun 3 13:09:24 2018 From: lysxia at gmail.com (Li-yao Xia) Date: Sun, 3 Jun 2018 09:09:24 -0400 Subject: [Haskell-cafe] A law for MonadReader In-Reply-To: References: <733fae2c-a832-f2cc-55fb-8f90d5de82f4@gmail.com> Message-ID: <7dd27198-b744-a095-cb47-de80ae6d3135@gmail.com> On 06/03/2018 03:32 AM, Benjamin Fox wrote: > As far as I can tell, (1) on it's own does not imply (2). I even have a > counterexample, assuming no further laws on `ask` and no laws on > `local`. Requiring `local` makes things more complicated (as `local` > always does) and it may well be that a sufficiently strong law for > `local` would rule out cases where (1) and (2) differ. (I'm not sure of > that, I'll need to think about it a bit more.) > > Here is the counterexample: > > instance MonadReader (IORef Int) IO where >     ask = newIORef 0 >     local _ = id > > This obeys law (1): (newIORef 0 >> newIORef 0) == newIORef 0. But not > (2): (newIORef 0 >>= \r1 -> newIORef 0 >>= \r2 -> return (r1, r2))≠ > (newIORef 0 >>= \r -> return (r, r)). The left side of (2) returns a > tuple containing two different IORefs (both containing 0), whereas the > right side returns a tuple containing two references to the same IORef. > Thanks Benjamin, that's a good counterexample. It also shows that the other missing implications (((3) => (4)) and ((3) => (2))) do not hold. Indeed, I had incorrectly assumed that even if we discard the result of an action, we can reconstruct it by observing the action's effects, and (1) and (3) were meant to imply that those effects must be trivial, but newIORef contradicts this because the creation of a new reference is only made observable by using it. Li-yao From ivanperezdominguez at gmail.com Sun Jun 3 16:55:51 2018 From: ivanperezdominguez at gmail.com (Ivan Perez) Date: Sun, 3 Jun 2018 12:55:51 -0400 Subject: [Haskell-cafe] A law for MonadReader In-Reply-To: References: <733fae2c-a832-f2cc-55fb-8f90d5de82f4@gmail.com> <3B95E8EE-2628-4965-A27F-4695F55182A8@dukhovni.org> Message-ID: > This obeys law (1): (newIORef 0 >> newIORef 0) == newIORef 0. Doesn't this change the state in the IO monad (which is why (2) does not hold for this instance)? If so, would it still be true? Ivan On 3 June 2018 at 07:55, Benjamin Fox wrote: > Here, as in general in the definitions of laws, the relevent question is > referential transparency, not Eq instances. > > (You'll note that generally in the definitions of laws the symbol "=" is > used, not "==". Sometimes that's written as "≡", to be even clearer about > what it represents, as for instance the Monad Laws page > on the Haskell wiki does.) > > For some laws, like the "fmap id = id" Functor law, this is obviously the > only possible interpretation, as both sides of that equation are > necessarily functions, and functions don't have an Eq instance. > > So in this case, what the first law is asking for is that "ask >> ask" is > the same as "ask", in that any instance of "ask" in a program can be > replaced with "ask >> ask", or vice versa, without that changing the > program's semantics. > > > On Sun, Jun 3, 2018 at 9:47 AM Viktor Dukhovni > wrote: > >> >> >> > On Jun 3, 2018, at 3:32 AM, Benjamin Fox >> wrote: >> > >> > Here is the counterexample: >> > >> > instance MonadReader (IORef Int) IO where >> > ask = newIORef 0 >> > local _ = id >> > >> > This obeys law (1): (newIORef 0 >> newIORef 0) == newIORef 0. >> >> Can you explain what you mean? >> >> Prelude> :m + Data.IORef >> Prelude Data.IORef> let z = 0 :: Int >> Prelude Data.IORef> a <- newIORef z >> Prelude Data.IORef> b <- newIORef z >> Prelude Data.IORef> let c = newIORef z >> Prelude Data.IORef> let d = newIORef z >> Prelude Data.IORef> a == b >> False >> Prelude Data.IORef> c == d >> >> :8:1: error: >> • No instance for (Eq (IO (IORef Int))) arising from a use of ‘==’ >> • In the expression: c == d >> In an equation for ‘it’: it = c == d >> >> -- >> Viktor. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From foxbenjaminfox at gmail.com Sun Jun 3 17:55:03 2018 From: foxbenjaminfox at gmail.com (Benjamin Fox) Date: Sun, 3 Jun 2018 19:55:03 +0200 Subject: [Haskell-cafe] A law for MonadReader In-Reply-To: References: <733fae2c-a832-f2cc-55fb-8f90d5de82f4@gmail.com> <3B95E8EE-2628-4965-A27F-4695F55182A8@dukhovni.org> Message-ID: No, newIORef does not itself change any state. It returns an IO value because each invocation returns a different IORef, but there isn't any way to tell how many or which IORefs were created. So newIORef 0 >> newIORef 0 doesn't differ in any way from newIORef 0, except in that an additional object being created and then immediately garbage collected. This is exactly the same as how the expression Just 0 >> Just 0 is the equivalent to Just 0, except again with an additional object being created and then garbage collected behind the scenes. If you'd agree that Just 0 >> Just 0 ≡ Just 0, then I think you have to also agree that newIORef 0 >> newIORef 0 ≡ newIORef 0. In both cases, each side of the equivalence has the exact same semantics (save perhaps for additional allocations, which we generally ignore when doing this kind of analysis). No program which you could write could differentiate between the two sides (again, save by doing some trickery such as benchmarking the program and seeing which allocates more.) On Sun, Jun 3, 2018 at 6:56 PM Ivan Perez wrote: > > This obeys law (1): (newIORef 0 >> newIORef 0) == newIORef 0. > > Doesn't this change the state in the IO monad (which is why (2) does not > hold for this instance)? If so, would it still be true? > > Ivan > > On 3 June 2018 at 07:55, Benjamin Fox wrote: > >> Here, as in general in the definitions of laws, the relevent question is >> referential transparency, not Eq instances. >> >> (You'll note that generally in the definitions of laws the symbol "=" is >> used, not "==". Sometimes that's written as "≡", to be even clearer about >> what it represents, as for instance the Monad Laws page >> on the Haskell wiki does.) >> >> For some laws, like the "fmap id = id" Functor law, this is obviously the >> only possible interpretation, as both sides of that equation are >> necessarily functions, and functions don't have an Eq instance. >> >> So in this case, what the first law is asking for is that "ask >> ask" is >> the same as "ask", in that any instance of "ask" in a program can be >> replaced with "ask >> ask", or vice versa, without that changing the >> program's semantics. >> >> >> On Sun, Jun 3, 2018 at 9:47 AM Viktor Dukhovni >> wrote: >> >>> >>> >>> > On Jun 3, 2018, at 3:32 AM, Benjamin Fox >>> wrote: >>> > >>> > Here is the counterexample: >>> > >>> > instance MonadReader (IORef Int) IO where >>> > ask = newIORef 0 >>> > local _ = id >>> > >>> > This obeys law (1): (newIORef 0 >> newIORef 0) == newIORef 0. >>> >>> Can you explain what you mean? >>> >>> Prelude> :m + Data.IORef >>> Prelude Data.IORef> let z = 0 :: Int >>> Prelude Data.IORef> a <- newIORef z >>> Prelude Data.IORef> b <- newIORef z >>> Prelude Data.IORef> let c = newIORef z >>> Prelude Data.IORef> let d = newIORef z >>> Prelude Data.IORef> a == b >>> False >>> Prelude Data.IORef> c == d >>> >>> :8:1: error: >>> • No instance for (Eq (IO (IORef Int))) arising from a use of ‘==’ >>> • In the expression: c == d >>> In an equation for ‘it’: it = c == d >>> >>> -- >>> Viktor. >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Sun Jun 3 18:31:46 2018 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Sun, 3 Jun 2018 20:31:46 +0200 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either Message-ID: <41E3054D-2DAE-4CA4-ADF0-B495B824320B@aatal-apotheke.de> >Also note that what you're talking about is a special type of objects, >namely > > type BoundedEnum a = (Bounded a, Enum a) -- using ConstraintKinds > >(I'm sure the mathematicians have a better name for this) Indeed the Prelude states no laws for Bounded. But maybe we all agree on this: forall a. fromEnum minBound <= fromEnum a <= fromEnum maxBound With this law and the rule fromEnum.toEnum=id (for those integers that this type's toEnum accepts) we can say that (Bounded a,Enum a) is the class of all types which have a distinguished finite subset. If one assumes further the law toEnum.fromEnum=id (which is violated e.g. by Double) then (Bounded a,Enum a) are precisely the constructively finite types, that is, the types for which one can exhibit an isomorphism with a finite cardinal. Note that in constructive mathematics, a set may be known to be finite in the sense that the assumption it is infinite is absurd, yet one can not name an isomorphism with a finite cardinal. [*] As Jon Fairbairn pointed out, (Int,Int) can be given an Enum instance. The same is true for every type that is build from types that already have an Enum instance using only sum and product. >This is all true, but I was implicitly assuming that Bounded and Enum ought >to agree with Ord. Consider this: From every type's Enum instance you can derive an Ord instance: compare = compare `Data.Function.on` fromEnum -- Olaf [*] In the text [1] by Andrej Bauer I found this funny theorem: Excluded middle is equivalent to the statement that subsets of finite sets are finite. [1] http://www.ams.org/journals/bull/2017-54-03/S0273-0979-2016-01556-4/S0273-0979-2016-01556-4.pdf From slucas at dsic.upv.es Mon Jun 4 08:02:22 2018 From: slucas at dsic.upv.es (Salvador Lucas) Date: Mon, 4 Jun 2018 10:02:22 +0200 Subject: [Haskell-cafe] WST 2018 - Call for Participation (July 18-19, 2018) Message-ID: <86d04791-fb69-64d0-4e88-0cb50a355ba5@dsic.upv.es> ==========================================================================                        WST 2018 - Call for Participation                    16th International Workshop on Termination                               part of FLoC 2018                     July 18-19, 2018, Oxford, United Kingdom                           http://wst2018.webs.upv.es/ ========================================================================== REGISTRATION (June 6th is the last day for early registration!)    http://www.floc2018.org/register/ INVITED SPEAKERS:     James Worrell - University of Oxford        "Termination Checking and Invariant Synthesis for Affine Programs"     Akihisa Yamada - NII Japan        "Towards a Unified Method for Termination" PROGRAMME (see also the list of accepted papers attached below):    https://easychair.org/smart-program/FLoC2018/WST-program.html TERMINATION AND COMPLEXITY COMPETITION: In 2018, the Termination and Complexity Competition (TERCOMP) will run in parallel with FLoC 2018 as part of the FLoC Olympic Games. The results of the competition will be presented and discussed during a special session at WST 2018. ACCEPTED PAPERS: Eric Hehner. Objective and Subjective Specifications. Guillaume Genestier and Frédéric Blanqui. Termination of Lambda-Pi modulo rewriting using the size-change principle Jera Hensel, Florian Frohn and Jürgen Giesl. Complexity Analysis for Bitvector Programs Alfons Geser, Dieter Hofbauer and Johannes Waldmann. Comparing on Strings: Semantic Kachinuki Order Nachum Dershowitz and Jean-Pierre Jouannaud. GPO: A Path Ordering for Graphs Jose Divasón, Sebastiaan Joosten, René Thiemann and Akihisa Yamada. A Perron-Frobenius Theorem for Jordan Blocks for Complexity Proving Jonas Schöpf and Christian Sternagel. TTT2 with Termination Templates for Teaching Cristina David, Daniel Kroening and Peter Schrammel. Procedure-Modular Termination Analysis Salvador Lucas. Well-founded models in proofs of termination Aalok Thakkar, Balaji Krishnamurthy and Piyush Gupta. Verification of Rewriting-based Query Optimizers Jesús J. Doménech, Samir Genaim and John P. Gallagher. Control-Flow Refinement via Partial Evaluation Alicia Merayo Corcoba and Samir Genaim. Inference of Linear Upper-Bounds on the Expected Cost by Solving Cost Relations Dieter Hofbauer. Embracing Infinity - Termination of String Rewriting by Almost Linear Weight Functions Carsten Fuhs and Cynthia Kop. Improving Static Dependency Pairs for Higher-Order Rewriting From zemyla at gmail.com Mon Jun 4 16:49:17 2018 From: zemyla at gmail.com (Zemyla) Date: Mon, 4 Jun 2018 11:49:17 -0500 Subject: [Haskell-cafe] No Enum for (,), no Enum or Bounded for Either In-Reply-To: <41E3054D-2DAE-4CA4-ADF0-B495B824320B@aatal-apotheke.de> References: <41E3054D-2DAE-4CA4-ADF0-B495B824320B@aatal-apotheke.de> Message-ID: Not from Rational, Float, or Double. On Sun, Jun 3, 2018, 13:32 Olaf Klinke wrote: > >Also note that what you're talking about is a special type of objects, > >namely > > > > type BoundedEnum a = (Bounded a, Enum a) -- using ConstraintKinds > > > >(I'm sure the mathematicians have a better name for this) > > Indeed the Prelude states no laws for Bounded. But maybe we all agree on > this: > > forall a. fromEnum minBound <= fromEnum a <= fromEnum maxBound > > With this law and the rule fromEnum.toEnum=id (for those integers that > this type's toEnum accepts) we can say that (Bounded a,Enum a) is the class > of all types which have a distinguished finite subset. If one assumes > further the law toEnum.fromEnum=id (which is violated e.g. by Double) then > (Bounded a,Enum a) are precisely the constructively finite types, that is, > the types for which one can exhibit an isomorphism with a finite cardinal. > Note that in constructive mathematics, a set may be known to be finite in > the sense that the assumption it is infinite is absurd, yet one can not > name an isomorphism with a finite cardinal. [*] > > As Jon Fairbairn pointed out, (Int,Int) can be given an Enum instance. The > same is true for every type that is build from types that already have an > Enum instance using only sum and product. > > >This is all true, but I was implicitly assuming that Bounded and Enum > ought > >to agree with Ord. > > Consider this: From every type's Enum instance you can derive an Ord > instance: > compare = compare `Data.Function.on` fromEnum > > -- Olaf > > [*] In the text [1] by Andrej Bauer I found this funny theorem: Excluded > middle is equivalent to the statement that subsets of finite sets are > finite. > [1] > http://www.ams.org/journals/bull/2017-54-03/S0273-0979-2016-01556-4/S0273-0979-2016-01556-4.pdf > _______________________________________________ > 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 gershomb at gmail.com Tue Jun 5 03:50:06 2018 From: gershomb at gmail.com (Gershom B) Date: Mon, 4 Jun 2018 23:50:06 -0400 Subject: [Haskell-cafe] Wanted: New Admin for Planet.Haskell.Org Message-ID: Dear all — the planet.haskell.org server is a low-maintenance feed-aggregator that uses the planet venus software to pull together feeds of haskell-related content. I think it is a great resource, and I’ve used it for years. For some time the planet at haskell.org address hadn’t been well-monitored, meaning that requests for adding new rss feeds had languished. I’ve gone through and tried to act on the outstanding requests, and will be doing so for the time being. However, I have a lot on my plate, and would like to pass this responsibility on to a volunteer. It basically means, on the occasional recipt of an email, logging into the server, updating a config file, running a command, and logging back out again. If you’re interested in helping out with this, please contact me. Cheers, Gershom -------------- next part -------------- An HTML attachment was scrubbed... URL: From tiredpixel at posteo.de Tue Jun 5 09:10:04 2018 From: tiredpixel at posteo.de (tiredpixel) Date: Tue, 05 Jun 2018 10:10:04 +0100 Subject: [Haskell-cafe] Wanted: New Admin for Planet.Haskell.Org In-Reply-To: References: Message-ID: <6bcfe312fca21db9c990fe81206b5db422b96c72.camel@posteo.de> On Mon, 2018-06-04 at 23:50 -0400, Gershom B wrote: > Dear all — the planet.haskell.org server is a low-maintenance feed- > aggregator that uses the planet venus software to pull together feeds > of haskell-related content. I think it is a great resource, and I’ve > used it for years. For some time the planet at haskell.org address > hadn’t been well-monitored, meaning that requests for adding new rss > feeds had languished. I’ve gone through and tried to act on the > outstanding requests, and will be doing so for the time being. > However, I have a lot on my plate, and would like to pass this > responsibility on to a volunteer. It basically means, on the > occasional recipt of an email, logging into the server, updating a > config file, running a command, and logging back out again. > > If you’re interested in helping out with this, please contact me. > > Cheers, > Gershom I am interested in volunteering a little time to help with this. I wasn't actually aware of the service, but it looks like a valuable resource. I've been doing programming and systems engineering for years, including open-source (https://github.com/tiredpixel/), and although I haven't open-sourced any Haskell code to-date, it's the principal language being used at my tech company, Pavouk OÜ (https://ww w.pavouk.tech/), so I'm very much invested in it. In addition, should there be a need for hosting, I/we might be able to help with that. Peace, tiredpixel -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 488 bytes Desc: This is a digitally signed message part URL: From twhitehead at gmail.com Tue Jun 5 21:58:38 2018 From: twhitehead at gmail.com (Tyson Whitehead) Date: Tue, 5 Jun 2018 17:58:38 -0400 Subject: [Haskell-cafe] Parsing a matrix table with Data.Frames Message-ID: I have a case where some of my data is stored in CSV matrix form like this example of a table telling whether person i has pet j ,cat,dog,goldfish bill,true,true,false sue,false,true,true fred,false,false,true I can't see any obvious way to read this sort of thing in with the Data.Frames package. Would love to be told differently. Thanks! -Tyson From will.yager at gmail.com Wed Jun 6 00:34:11 2018 From: will.yager at gmail.com (William Yager) Date: Tue, 5 Jun 2018 20:34:11 -0400 Subject: [Haskell-cafe] Parsing a matrix table with Data.Frames In-Reply-To: References: Message-ID: What's the issue you're running into? If it's confusion with the API, hopefully this example is helpful: > readRow (ParserOptions Nothing "," NoQuoting) "bill,true,true,false" :: Rec (Either Text) ["Name" :-> Text, "Cat" :-> Bool, "Dog" :-> Bool, "Goldfish" :-> Bool] {Right Name :-> "bill", Right Cat :-> True, Right Dog :-> True, Right Goldfish :-> False} Requires OverloadedStrings, DataKinds, TypeOperators. If you then want to extract data you can then do something like > rget (Proxy :: Proxy ("Name" :-> Text)) row Right Name :-> "bill" I assume there is some easier API for this (looks like via template haskell?). Seems kind of sad if there's no convenient way to do things without using TH, but I don't see anything obvious. --Will On Tue, Jun 5, 2018 at 5:58 PM, Tyson Whitehead wrote: > I have a case where some of my data is stored in CSV matrix form like this > example of a table telling whether person i has pet j > > ,cat,dog,goldfish > bill,true,true,false > sue,false,true,true > fred,false,false,true > > I can't see any obvious way to read this sort of thing in with the > Data.Frames package. Would love to be told differently. > > Thanks! -Tyson > _______________________________________________ > 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 twhitehead at gmail.com Wed Jun 6 01:03:02 2018 From: twhitehead at gmail.com (Tyson Whitehead) Date: Tue, 5 Jun 2018 21:03:02 -0400 Subject: [Haskell-cafe] Parsing a matrix table with Data.Frames In-Reply-To: References: Message-ID: Thanks Will, I can see I wasn't clear at all. The issue is that the animals are not known ahead of time and can vary from file to file. That is, the normalized form of the data is personal,animal,has bill,cat,true bill,dog,true bill,goldfish,false sue,cat,false sue,dog,true sue,goldfish,true fred,cat,false fred,dog,false fred,goldfish,true but the CSV files I have to read in are expressed in the matrix form ,cat,dog,goldfish bill,true,true,false sue,false,true,true fred,false,false,true Thanks! -Tyson On Tue, 5 Jun 2018 at 20:34, William Yager wrote: > > What's the issue you're running into? If it's confusion with the API, hopefully this example is helpful: > > > readRow (ParserOptions Nothing "," NoQuoting) "bill,true,true,false" :: Rec (Either Text) ["Name" :-> Text, "Cat" :-> Bool, "Dog" :-> Bool, "Goldfish" :-> Bool] > > {Right Name :-> "bill", Right Cat :-> True, Right Dog :-> True, Right Goldfish :-> False} > > > Requires OverloadedStrings, DataKinds, TypeOperators. > > > If you then want to extract data you can then do something like > > > > rget (Proxy :: Proxy ("Name" :-> Text)) row > > Right Name :-> "bill" > > > I assume there is some easier API for this (looks like via template haskell?). Seems kind of sad if there's no convenient way to do things without using TH, but I don't see anything obvious. > > > --Will > > > > On Tue, Jun 5, 2018 at 5:58 PM, Tyson Whitehead wrote: >> >> I have a case where some of my data is stored in CSV matrix form like this example of a table telling whether person i has pet j >> >> ,cat,dog,goldfish >> bill,true,true,false >> sue,false,true,true >> fred,false,false,true >> >> I can't see any obvious way to read this sort of thing in with the Data.Frames package. Would love to be told differently. >> >> Thanks! -Tyson >> _______________________________________________ >> 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 aquagnu at gmail.com Thu Jun 7 11:21:09 2018 From: aquagnu at gmail.com (PY) Date: Thu, 7 Jun 2018 14:21:09 +0300 Subject: [Haskell-cafe] Usage of `pure` Message-ID: <2f91536f-e94b-17d9-e34b-0851eb1bba9e@gmail.com> Hello, Dear Cafe! Consider, I have big application with monad and applicative related code. What problems I can hit if I will replace all `return`s with `pure` (in `do`-blocks, anywhere). So, `return` will be totally eliminated. === Best regards, Paul From fa-ml at ariis.it Thu Jun 7 12:10:04 2018 From: fa-ml at ariis.it (Francesco Ariis) Date: Thu, 7 Jun 2018 14:10:04 +0200 Subject: [Haskell-cafe] Usage of `pure` In-Reply-To: <2f91536f-e94b-17d9-e34b-0851eb1bba9e@gmail.com> References: <2f91536f-e94b-17d9-e34b-0851eb1bba9e@gmail.com> Message-ID: <20180607121004.2kxlawt6hjf7domh@x60s.casa> On Thu, Jun 07, 2018 at 02:21:09PM +0300, PY wrote: > Consider, I have big application with monad and applicative related code. > What problems I can hit if I will replace all `return`s with `pure` (in > `do`-blocks, anywhere). So, `return` will be totally eliminated. Hello Paul, that might be a problem only if you need to support the (very very old) GHC 7.8 (or previous versions) -F From simon.jakobi at googlemail.com Thu Jun 7 12:20:13 2018 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Thu, 7 Jun 2018 14:20:13 +0200 Subject: [Haskell-cafe] Usage of `pure` In-Reply-To: <2f91536f-e94b-17d9-e34b-0851eb1bba9e@gmail.com> References: <2f91536f-e94b-17d9-e34b-0851eb1bba9e@gmail.com> Message-ID: Hi Paul, in case you're using -Wredundant-constraints, you might get some warnings that a function that previously required Monad, now only requires Applicative. Cheers, Simon 2018-06-07 13:21 GMT+02:00 PY : > Hello, Dear Cafe! > > Consider, I have big application with monad and applicative related code. > What problems I can hit if I will replace all `return`s with `pure` (in > `do`-blocks, anywhere). So, `return` will be totally eliminated. > > === > > Best regards, Paul > > _______________________________________________ > 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 litchard.michael at gmail.com Thu Jun 7 16:41:44 2018 From: litchard.michael at gmail.com (Michael Litchard) Date: Thu, 7 Jun 2018 09:41:44 -0700 Subject: [Haskell-cafe] removing a cookie via ghcjs Message-ID: Using ghcjs, I am able to read a cookie using getCookie. There's no corresponding remove/deleteCookie that I can find. Could I get some assistance in how to remove the same cookie I can see using getCookie? -------------- next part -------------- An HTML attachment was scrubbed... URL: From nikivazou at gmail.com Thu Jun 7 16:57:48 2018 From: nikivazou at gmail.com (Niki Vazou) Date: Thu, 7 Jun 2018 12:57:48 -0400 Subject: [Haskell-cafe] TyDe 2018: SUBMISSION DEADLINE EXTENDED TO JUNE 13th. Message-ID: Hey all, the TyDe submission deadline got extended for one week! CALL FOR CONTRIBUTIONS: DEADLINE EXTENDED TO JUNE 13th. TyDe 2018: Type-Driven Development https://icfp18.sigplan.org/track/tyde-2018 23-29 Sep, 2018, St. Louis, Missouri (co-located with ICFP) ============================================== *Call for Contributions* We welcome all contributions, both theoretical and practical, on a range of topics including: dependently typed programming; generic programming; design and implementation of programming languages, exploiting types in novel ways; exploiting typed data, data dependent data, or type providers; static and dynamic analyses of typed programs; tools, IDEs, or testing tools exploiting type information; pearls, being elegant, instructive examples of types used in the derivation, calculation, or construction of programs. *Important Dates* **Extended paper submission deadline: Wednesday, June 13, 2018** Extended abstract deadline: Wednesday, June 13, 2018 Author notification: Friday, June 29, 2018 Deadline for camera ready version: August 5, 2018 Workshop: Thursday, September 27, 2018 *Program Committee* - Guillaume Allais, Radboud University Nijmegen, Netherlands - Zena M. Ariola, University of Oregon, USA - David Darais, University of Vermont, USA - Richard Eisenberg, Bryn Mawr College, USA (co-chair) - Jennifer Hackett, University of Nottingham, UK - Shin-ya Katsumata, National Institute of Informatics, Japan - Daan Leijen, Microsoft Research, USA - Shin-Cheng Mu, Academia Sinica, Taiwan - Dominic Orchard, University of Kent, UK - Peter-Michael Osera, Grinnell College, USA - Zoe Paraskevopoulou, Princeton University, USA - Alberto Pardo, Universidad de la Republica, Uruguay - Matthieu Sozeau, University of Paris Diderot, Paris 7, France - Niki Vazou, University of Maryland, USA (co-chair) *Submission details* Submissions should fall into one of two categories: - Regular research papers (12 pages) - Extended abstracts (2 pages) The bibliography will not be counted against the page limits for either category. Regular research papers are expected to present novel and interesting research results, and will be included in the formal proceedings. Extended abstracts should report work in progress that the authors would like to present at the workshop. Extended abstracts will be distributed to workshop attendees but will not be published in the formal proceedings. We welcome submissions from PC members (with the exception of the two co-chairs), but these submissions will be held to a higher standard. Submission is handled through HotCRP: https://tyde18.hotcrp.com/ All submissions should be in portable document format (PDF) and formatted using the ACM SIGPLAN style guidelines: http://www.sigplan.org/Resources/Author/ Note that the ACM SIGPLAN style guidelines have changed from previous years! In particular, submissions should use the new ‘acmart’ format and the two-column ‘sigplan’ subformat (not to be confused with the one-column ‘acmlarge’ subformat!). Extended abstracts must be submitted with the label ‘Extended abstract’ clearly in the title. Best, Niki Vazou -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeremy at n-heptane.com Thu Jun 7 17:28:01 2018 From: jeremy at n-heptane.com (Jeremy Shaw) Date: Thu, 7 Jun 2018 12:28:01 -0500 Subject: [Haskell-cafe] removing a cookie via ghcjs In-Reply-To: References: Message-ID: Hello, There is no underlying 'deleteCookie' support in browsers. Instead you call 'setCookie' and set the expiration date to be in the past. Then the browser will delete the cookie. https://stackoverflow.com/questions/2144386/how-to-delete-a-cookie Not sure which getCookie function you are using, but there is likely a setCookie function nearby. - jeremy On Thu, Jun 7, 2018 at 11:41 AM, Michael Litchard < litchard.michael at gmail.com> wrote: > Using ghcjs, I am able to read a cookie using getCookie. There's no > corresponding remove/deleteCookie that I can find. Could I get some > assistance in how to remove the same cookie I can see using getCookie? > > > > _______________________________________________ > 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 litchard.michael at gmail.com Thu Jun 7 17:56:10 2018 From: litchard.michael at gmail.com (Michael Litchard) Date: Thu, 7 Jun 2018 10:56:10 -0700 Subject: [Haskell-cafe] removing a cookie via ghcjs In-Reply-To: References: Message-ID: Jeremy, Thank you. I had been experimenting with setCookie, but wasn't setting the expiration date correctly. All good now. On Thu, Jun 7, 2018 at 10:28 AM, Jeremy Shaw wrote: > Hello, > > There is no underlying 'deleteCookie' support in browsers. Instead you > call 'setCookie' and set the expiration date to be in the past. Then the > browser will delete the cookie. > > https://stackoverflow.com/questions/2144386/how-to-delete-a-cookie > > Not sure which getCookie function you are using, but there is likely a > setCookie function nearby. > > - jeremy > > On Thu, Jun 7, 2018 at 11:41 AM, Michael Litchard < > litchard.michael at gmail.com> wrote: > >> Using ghcjs, I am able to read a cookie using getCookie. There's no >> corresponding remove/deleteCookie that I can find. Could I get some >> assistance in how to remove the same cookie I can see using getCookie? >> >> >> >> _______________________________________________ >> 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 Fri Jun 8 06:53:49 2018 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 8 Jun 2018 07:53:49 +0100 Subject: [Haskell-cafe] removing a cookie via ghcjs In-Reply-To: References: Message-ID: <20180608065348.uxyqccrp2prhaeko@weber> Any idea why this functionality isn't just wrapped up in a function called 'deleteCookie'? On Thu, Jun 07, 2018 at 12:28:01PM -0500, Jeremy Shaw wrote: > There is no underlying 'deleteCookie' support in browsers. Instead you call > 'setCookie' and set the expiration date to be in the past. Then the browser > will delete the cookie. > > https://stackoverflow.com/questions/2144386/how-to-delete-a-cookie > > On Thu, Jun 7, 2018 at 11:41 AM, Michael Litchard < > litchard.michael at gmail.com> wrote: > > > Using ghcjs, I am able to read a cookie using getCookie. There's no > > corresponding remove/deleteCookie that I can find. Could I get some > > assistance in how to remove the same cookie I can see using getCookie? From johannes.waldmann at htwk-leipzig.de Sun Jun 10 13:51:37 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Sun, 10 Jun 2018 15:51:37 +0200 Subject: [Haskell-cafe] how to prevent 'stack' from installing 'ghc'? Message-ID: <74bcc33f-9f23-8509-16ac-95eb3fe8cd29@htwk-leipzig.de> Dear Cafe, 'stack' tries to download and install a 'ghc' binary in case 'ghc' in $PATH does not match what is needed for the resolver given in 'stack.yaml' How can I switch this off completely and reliably? I much rather 'stack' just fails when it detects the mismatch. putting 'system-ghc: true' in 'stack.yaml' and '~/.stack/config.yaml' apparently is not enough. 'stack' does warn before downloading, but sometimes I'm not seeing the warning, e.g., because the whole thing is triggered silently from using 'intero'. I do have several ghc executables (built from source) in /opt/ghc/ghc-$version/bin/ghc and I just need to set PATH accordingly. It would be even better if I could tell 'stack' (once and for all) about these locations. I think I understand why 'stack' does what it does (reproducible builds) but I really want to minimize the number of other people's binaries on my machine. I do use the auto-download feature for easier CI builds - so I agree it can be useful. - J.W. From michael at snoyman.com Sun Jun 10 13:54:04 2018 From: michael at snoyman.com (Michael Snoyman) Date: Sun, 10 Jun 2018 06:54:04 -0700 Subject: [Haskell-cafe] how to prevent 'stack' from installing 'ghc'? In-Reply-To: <74bcc33f-9f23-8509-16ac-95eb3fe8cd29@htwk-leipzig.de> References: <74bcc33f-9f23-8509-16ac-95eb3fe8cd29@htwk-leipzig.de> Message-ID: You can use the install-ghc option, either in your stack.yaml, or on the command line. On Sun, Jun 10, 2018, 6:52 AM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > Dear Cafe, > > > 'stack' tries to download and install a 'ghc' binary > in case 'ghc' in $PATH does not match > what is needed for the resolver given in 'stack.yaml' > > How can I switch this off completely and reliably? > I much rather 'stack' just fails when it detects the mismatch. > putting 'system-ghc: true' in 'stack.yaml' > and '~/.stack/config.yaml' apparently is not enough. > > > 'stack' does warn before downloading, > but sometimes I'm not seeing the warning, > e.g., because the whole thing is triggered silently > from using 'intero'. > > > I do have several ghc executables (built from source) > in /opt/ghc/ghc-$version/bin/ghc > and I just need to set PATH accordingly. > > It would be even better if I could tell > 'stack' (once and for all) about these locations. > > > I think I understand why 'stack' does what it does > (reproducible builds) but I really want to minimize > the number of other people's binaries on my machine. > I do use the auto-download feature for easier CI builds - > so I agree it can be useful. > > > - 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 tanuki at gmail.com Mon Jun 11 23:35:39 2018 From: tanuki at gmail.com (Theodore Lief Gannon) Date: Mon, 11 Jun 2018 16:35:39 -0700 Subject: [Haskell-cafe] Disable default-to-DeriveAnyClass warning with DerivingStrategies? Message-ID: Is there a flag to disable this warning? There's no mystery or surprise to the default, but if I want all three of GeneralizedNewtypeDeriving, DeriveAnyClass and DerivingStrategies enabled, I'm currently stuck with a warning for e.g. deriving (Generic, ToJSON). The only way to use strategy keywords is on standalone deriving lines, which seems unnecessarily verbose. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Tue Jun 12 06:27:53 2018 From: gershomb at gmail.com (Gershom B) Date: Tue, 12 Jun 2018 02:27:53 -0400 Subject: [Haskell-cafe] Announce: Haskell Platform 8.4.3 Message-ID: On behalf of the Haskell Platform team, I'm happy to announce the release of Haskell Platform 8.4.3 Now available at https://www.haskell.org/platform/ This includes GHC 8.4.3, cabal-install 2.2.0.0, and stack 1.7.1. A full list of contents is available at https://www.haskell.org/platform/contents.html Outside of the update of the GHC to 8.4.3, the only substantive change in this release is to the new version of the primitive library, which includes a range of fixes and improvements. The list of GHC changes is available at: https://ghc.haskell.org/trac/ghc/blog/ghc-8.4.3-released And the list of changes to Primitive is available at: http://hackage.haskell.org/package/primitive-0.6.4.0/changelog There are (still) currently no 32 bit Windows builds available. We're looking into the issues preventing us from building an installer for that platform. The components all appear to work individually in such a case, and can be installed separately by users who so desire. Happy Haskell Hacking all, Gershom From hilco.wijbenga at gmail.com Wed Jun 13 03:58:39 2018 From: hilco.wijbenga at gmail.com (Hilco Wijbenga) Date: Tue, 12 Jun 2018 20:58:39 -0700 Subject: [Haskell-cafe] How far can you take overloading with type classes? Message-ID: Hi all, Given definitions of Line and Lines is it possible to define a type class (or maybe multiple type classes) that would allow for the following: (++) :: Line -> Line -> Lines (++) :: Line -> Lines -> Lines (++) :: Lines -> Line -> Lines (++) :: Lines -> Lines -> Lines I.e. is there a way to overload (++) such that it supports each of these 4 combinations? (Let's ignore that (++) already exists for the moment.) Cheers, Hilco From lexi.lambda at gmail.com Wed Jun 13 04:37:11 2018 From: lexi.lambda at gmail.com (Alexis King) Date: Tue, 12 Jun 2018 23:37:11 -0500 Subject: [Haskell-cafe] How far can you take overloading with type classes? In-Reply-To: References: Message-ID: <0F1B368C-7D47-4592-ACE2-4A8E9E06B75A@gmail.com> Sure, it can certainly be done: class CombineLines a b where (++) :: a -> b -> Lines instance CombineLines Line Line where { ... } instance CombineLines Line Lines where { ... } instance CombineLines Lines Line where { ... } instance CombineLines Lines Lines where { ... } Of course, whether or not such a class is an especially useful thing is another matter entirely. Other encodings might be more helpful in practice. Perhaps something like this is closer to what you really want: class ToLines a where toLines :: a -> Lines instance ToLines Line where toLines = lineToLines instance ToLines Lines where toLines = id (++) :: (ToLines a, ToLines b) => a -> b -> Lines x ++ y = toLines x `addLines` toLines y Or perhaps none of these are really all that helpful in practice, and the overloading isn’t really worth it. > On Jun 12, 2018, at 22:58, Hilco Wijbenga wrote: > > Hi all, > > Given definitions of Line and Lines is it possible to define a type > class (or maybe multiple type classes) that would allow for the > following: > > (++) :: Line -> Line -> Lines > (++) :: Line -> Lines -> Lines > (++) :: Lines -> Line -> Lines > (++) :: Lines -> Lines -> Lines > > I.e. is there a way to overload (++) such that it supports each of > these 4 combinations? (Let's ignore that (++) already exists for the > moment.) > > Cheers, > Hilco From johannes.waldmann at htwk-leipzig.de Wed Jun 13 08:14:26 2018 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Wed, 13 Jun 2018 10:14:26 +0200 Subject: [Haskell-cafe] Announce: Haskell Platform 8.4.3 Message-ID: <55af43e4-626d-9304-f9e0-e33aa89aa335@htwk-leipzig.de> > Haskell Platform 8.4.3 Nice. Now I'm wondering - is there an estimated release date for stackage LTS for ghc-8.4.3? That's a genuine question. I know stackage has (a lot) more packages (platform: less than 100?, last LTS: 2474?) so it involves more interfaces (to software, to humans) that can break in many more ways. - J.W. From michael at snoyman.com Wed Jun 13 08:24:22 2018 From: michael at snoyman.com (Michael Snoyman) Date: Wed, 13 Jun 2018 11:24:22 +0300 Subject: [Haskell-cafe] Announce: Haskell Platform 8.4.3 In-Reply-To: <55af43e4-626d-9304-f9e0-e33aa89aa335@htwk-leipzig.de> References: <55af43e4-626d-9304-f9e0-e33aa89aa335@htwk-leipzig.de> Message-ID: We typically do LTS major releases every 3-6 months. LTS 11.0 was released on March 12, so we're now officially in the range of "could be any day." I'll bring it up with the curator team. On Wed, Jun 13, 2018 at 11:15 AM Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > > Haskell Platform 8.4.3 > > Nice. > > Now I'm wondering - is there an estimated > release date for stackage LTS for ghc-8.4.3? > > That's a genuine question. > I know stackage has (a lot) more packages > (platform: less than 100?, last LTS: 2474?) > so it involves more interfaces (to software, > to humans) that can break in many more ways. > > - 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 arjanen.loic at gmail.com Wed Jun 13 08:44:58 2018 From: arjanen.loic at gmail.com (=?ISO-8859-1?Q?ARJANEN_Lo=EFc_Jean_David?=) Date: Wed, 13 Jun 2018 15:44:58 +0700 Subject: [Haskell-cafe] LIA bindings? Message-ID: <5b20d98f.1c69fb81.53ced.b7e2@mx.google.com> Dear Café, I saw in the report that the standard libraries’ operations don’t conform to LIA and that such operations should be done in an external library. Does such a library exist ? Regards,ARJANEN Loïc -------------- next part -------------- An HTML attachment was scrubbed... URL: From brucker at spamfence.net Thu Jun 14 08:44:48 2018 From: brucker at spamfence.net (Achim D. Brucker) Date: Thu, 14 Jun 2018 09:44:48 +0100 Subject: [Haskell-cafe] CFP: One Month Until Left For Submitting to The Workshop in OCL and Textual Modeling (OCL 2018) Message-ID: <20180614084448.qwni64qovmkpyorp@kandagawa.home.brucker.ch> (Apologies for duplicates) ********************************************************** ** Only one month left until the submission deadline! *** ********************************************************** CALL FOR PAPERS 18th International Workshop on OCL and Textual Modeling Co-located with MODELS 2018: ACM/IEEE 21th International Conference on Model Driven Engineering Languages and System, October 14, 2018, Copenhagen, Denmark http://oclworkshop.github.io Modeling started out with UML and its precursors as a graphical notation. Such visual representations enable direct intuitive capturing of reality, but they have weaknesses: for example, detailed visual representations bear the risk of becoming overcrowded faster than textual models and some of the visual features lack the level of precision required to create complete and unambiguous specifications. These weaknesses of graphical notations encouraged the development of text-based modeling languages that either integrate with or replace graphical notations for modeling. Typical examples of such languages are OCL, textual MOF, Epsilon, and Alloy. Textual modeling languages have their roots in formal language paradigms like logic, programming and databases. The goal of this workshop is to create a forum where researchers and practitioners interested in building models using OCL or other kinds of textual languages can directly interact, report advances, share results, identify tools for language development, and discuss appropriate standards. In particular, the workshop will encourage discussions for achieving synergy from different modeling language concepts and modeling language use. The close interaction will enable researchers and practitioners to identify common interests and options for potential cooperation. ## Topics of interest Topics of interest include (but are not limited to): - Mappings between textual modeling languages and other languages/formalisms - Mathematical models and/or formal semantics for textual modeling languages - Algorithms, evaluation strategies and optimizations in the context of textual modeling languages for: - validation, verification, and testing, - model transformation and code generation, - meta-modeling and DSLs, and - query and constraint specifications - Alternative graphical/textual notations for textual modeling languages - Evolution, transformation and simplification of textual modeling expressions - Libraries, templates and patterns for textual modeling languages - Tools that support textual modeling languages (e.g., verification of OCL formulae, runtime monitoring of invariants) - Model-driven security using textual modeling languages - Complexity results for textual modeling languages - Quality models and benchmarks for comparing and evaluating textual modeling tools and algorithms - Successful applications of textual modeling languages - Case studies on industrial applications of textual modeling languages - Experience reports: - usage of textual modeling languages and tools in complex domains, - usability of textual modeling languages and tools for end-users - Empirical studies about the benefits and drawbacks of textual modeling languages - Innovative textual modeling tools - Comparison, evaluation and integration of modeling languages - Correlation between modeling languages and modeling tasks We particularly encourage submissions describing applications and case studies of textual modeling as well as test suites and benchmark collections for evaluating textual modeling tools. ## Venue This workshop will be organized as a part of MODELS 2018 Conference in Copenhagen, Denmark. Similar to its predecessors, the workshop addresses both people from academia and industry. The aim is to provide a forum for addressing integration of OCL and other textual modeling languages, as well as tools for textual modeling, and for disseminating good practice and discussing the new requirements for textual modeling. ## Workshop Format The workshop will include short (about 15 min) presentations, parallel sessions of working groups, and sum-up discussions. ## Submissions Two types of papers will be considered: * Short contributions (between 5 and 7 pages) describing new ideas, innovative tools or position papers. * Full papers (between 10 and 14 pages). in LNCS format. Submissions should be uploaded to [EasyChair](https://easychair.org/conferences/?conf=ocl2018). The program committee will review the submissions (minimum 2 reviews per paper, usually 3 reviews) and select papers according to their relevance and interest for discussions that will take place at the workshop. Accepted papers will be published online, as part of the MODELS workshop proceedings, in [CEUR](http://www.ceur-ws.org). ## Important Dates - Submission of papers: July 17, 2018 - Notification: August 17, 2018 - Workshop date: October 14, 2018 -- Dr. Achim D. Brucker | Software Assurance & Security | University of Sheffield https://www.brucker.ch | https://logicalhacking.com/blog @adbrucker | @logicalhacking From a.pelenitsyn at gmail.com Thu Jun 14 09:28:27 2018 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Thu, 14 Jun 2018 11:28:27 +0200 Subject: [Haskell-cafe] How far can you take overloading with type classes? In-Reply-To: <0F1B368C-7D47-4592-ACE2-4A8E9E06B75A@gmail.com> References: <0F1B368C-7D47-4592-ACE2-4A8E9E06B75A@gmail.com> Message-ID: Hello, The first solution by Alexis needs the languages extension for multiparameter type classes to be on. So you have to add, e.g. {-# LANGUAGE MultiParamTypeClasses #-} at the beginning of your source file. The second solution is preferable, of course. -- Thanks, Artem ср, 13 июня 2018 г. в 6:37, Alexis King : > Sure, it can certainly be done: > > class CombineLines a b where > (++) :: a -> b -> Lines > > instance CombineLines Line Line where { ... } > instance CombineLines Line Lines where { ... } > instance CombineLines Lines Line where { ... } > instance CombineLines Lines Lines where { ... } > > Of course, whether or not such a class is an especially useful thing is > another matter entirely. Other encodings might be more helpful in > practice. Perhaps something like this is closer to what you really want: > > class ToLines a where > toLines :: a -> Lines > > instance ToLines Line where > toLines = lineToLines > instance ToLines Lines where > toLines = id > > (++) :: (ToLines a, ToLines b) => a -> b -> Lines > x ++ y = toLines x `addLines` toLines y > > Or perhaps none of these are really all that helpful in practice, and > the overloading isn’t really worth it. > > > > On Jun 12, 2018, at 22:58, Hilco Wijbenga > wrote: > > > > Hi all, > > > > Given definitions of Line and Lines is it possible to define a type > > class (or maybe multiple type classes) that would allow for the > > following: > > > > (++) :: Line -> Line -> Lines > > (++) :: Line -> Lines -> Lines > > (++) :: Lines -> Line -> Lines > > (++) :: Lines -> Lines -> Lines > > > > I.e. is there a way to overload (++) such that it supports each of > > these 4 combinations? (Let's ignore that (++) already exists for the > > moment.) > > > > Cheers, > > Hilco > > _______________________________________________ > 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 petr.mvd at gmail.com Thu Jun 14 20:20:18 2018 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Thu, 14 Jun 2018 22:20:18 +0200 Subject: [Haskell-cafe] the purpose of QuickCheck's size parameter Message-ID: Hi everyone, I'd like to better understand the principles behind the 'size' parameter. Looking at quickCheckWithResult [1], its computation seems to be somewhat non-trivial, or even arbitrary. As far as I understand it, the size is varied throughout tests, increasing from small to larger values. I see two main purposes: - Test on smaller as well as larger values. But with generators having proper distribution of values, this should happen anyway, just as if we had a constant, larger 'size' parameter. - Starting with smaller sizes allows to find smaller count-examples first. But with shrinking, it doesn't matter that much, big counter-examples are shrunk to smaller ones anyway in most cases. So is this parameter actually necessary? Would anything change considerably if it was dropped? Thanks, Petr [1] http://hackage.haskell.org/package/QuickCheck-2.11.3/docs/src/Test-QuickCheck-Test.html#quickCheckWithResult -------------- next part -------------- An HTML attachment was scrubbed... URL: From petr.mvd at gmail.com Thu Jun 14 20:24:07 2018 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Thu, 14 Jun 2018 22:24:07 +0200 Subject: [Haskell-cafe] Hedgehog - Integrated shrinking, shrinks obey invariants by construction. Message-ID: Hi everyone, I found the above interesting sentence in Hedgehog's [1] documentation. What does this mean? Is construction there somewhat tied to shrinking, perhaps something like going in the reverse direction? Thanks, Petr [1] https://github.com/hedgehogqa/haskell-hedgehog#features -------------- next part -------------- An HTML attachment was scrubbed... URL: From lysxia at gmail.com Thu Jun 14 21:11:31 2018 From: lysxia at gmail.com (Li-yao Xia) Date: Thu, 14 Jun 2018 17:11:31 -0400 Subject: [Haskell-cafe] Hedgehog - Integrated shrinking, shrinks obey invariants by construction. In-Reply-To: References: Message-ID: <523c3dad-ae1c-eab3-39ea-077e85663a3f@gmail.com> Generators can be interpreted as the sets of values they generate, and "integrated shrinking" makes shrinking produce values that belong to the same set, by deriving it from the generator. In contrast, in QuickCheck, generators and shrinkers are separate, so if a property we want to test has some precondition, we need to remember to make both the generator and the shrinker satisfy these preconditions. Li-yao On 06/14/2018 04:24 PM, Petr Pudlák wrote: > Hi everyone, > > I found the above interesting sentence in Hedgehog's [1] documentation. > What does this mean? Is construction there somewhat tied to shrinking, > perhaps something like going in the reverse direction? > > Thanks, > Petr > > [1] https://github.com/hedgehogqa/haskell-hedgehog#features > > > _______________________________________________ > 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 david.feuer at gmail.com Thu Jun 14 21:31:16 2018 From: david.feuer at gmail.com (David Feuer) Date: Thu, 14 Jun 2018 17:31:16 -0400 Subject: [Haskell-cafe] the purpose of QuickCheck's size parameter In-Reply-To: References: Message-ID: data Foo a = Leaf a | Node [Foo a] Without the size parameter, it's a bit tricky to control the distribution to avoid generating extremely large trees. I certainly agree, however, that the size parameter is an ugly and ill-specified hack. On Thu, Jun 14, 2018, 4:20 PM Petr Pudlák wrote: > Hi everyone, > > I'd like to better understand the principles behind the 'size' parameter. > Looking at quickCheckWithResult [1], its computation seems to be somewhat > non-trivial, or even arbitrary. As far as I understand it, the size is > varied throughout tests, increasing from small to larger values. I see two > main purposes: > > - Test on smaller as well as larger values. But with generators having > proper distribution of values, this should happen anyway, just as if we had > a constant, larger 'size' parameter. > - Starting with smaller sizes allows to find smaller count-examples first. > But with shrinking, it doesn't matter that much, big counter-examples are > shrunk to smaller ones anyway in most cases. > > So is this parameter actually necessary? Would anything change > considerably if it was dropped? > > Thanks, > Petr > > [1] > http://hackage.haskell.org/package/QuickCheck-2.11.3/docs/src/Test-QuickCheck-Test.html#quickCheckWithResult > _______________________________________________ > 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 Thu Jun 14 22:22:21 2018 From: lysxia at gmail.com (Li-yao Xia) Date: Thu, 14 Jun 2018 18:22:21 -0400 Subject: [Haskell-cafe] the purpose of QuickCheck's size parameter In-Reply-To: References: Message-ID: <719aa78b-26dc-ead1-b46b-6d12f595d00e@gmail.com> The purpose of the size parameter is not well-defined formally, but it is a very convenient knob to easily tune the test suite in various situations, that is definitely worth the negligible cost of having it around unconditionally. Without a size parameter, a fixed distribution means that if we want the generator to cover all possible cases, we have to keep a small probability of generating humongous examples and thus go OOM. We can avoid that by making the size of generated values bounded by the size parameter (or a function thereof), which we can increase easily when more resources become available. Furthermore, if we really want to generate very large examples, the only way with a fixed distribution is to wait longer. Instead, using a size parameter, we can make smaller values less likely to target further regions in the search space more accurately. Some properties can take a while to test on larger examples (either because of the generators or the actual verification process) so we might like to keep the size small during development, and raise it again once we're done. The Arbitrary class assigns a "default" generator for every type. While it is not always a good choice, having a parameter to tweak makes Arbitrary more generally useful. As for your last point, small examples are faster to generate and check, so it seems like a decent strategy to start small by default. Li-yao From publicityifl at gmail.com Fri Jun 15 08:45:11 2018 From: publicityifl at gmail.com (Jurriaan Hage) Date: Fri, 15 Jun 2018 04:45:11 -0400 Subject: [Haskell-cafe] Call for draft papers for presentation at IFL 2018 (Implementation and Application of Functional Languages) Message-ID: Hello, Please, find below the fourth call for papers for IFL 2018. Please forward these to anyone you think may be interested. Apologies for any duplicates you may receive. best regards, Jurriaan Hage Publicity Chair of IFL --- Call for Draft papers for presentations ================================================================================ IFL 2018 30th Symposium on Implementation and Application of Functional Languages University of Massachusetts Lowell, MA, USA September 5th-7th, 2018 http://iflconference.org ================================================================================ ### Scope The goal of the IFL symposia is to bring together researchers actively engaged in the implementation and application of functional and function-based programming languages. IFL 2018 will be a venue for researchers to present and discuss new ideas and concepts, work in progress, and publication-ripe results related to the implementation and application of functional languages and function-based programming. Topics of interest to IFL include, but are not limited to: - language concepts - type systems, type checking, type inferencing - compilation techniques - staged compilation - run-time function specialization - run-time code generation - partial evaluation - (abstract) interpretation - metaprogramming - generic programming - automatic program generation - array processing - concurrent/parallel programming - concurrent/parallel program execution - embedded systems - web applications - (embedded) domain specific languages - security - novel memory management techniques - run-time profiling performance measurements - debugging and tracing - virtual/abstract machine architectures - validation, verification of functional programs - tools and programming techniques - (industrial) applications ### Keynote Speakers * Adam Chlipala, Massachusetts Institute of Technology CSAIL * Arjun Guha, University of Massachusetts Amherst ### Submissions and peer-review Differently from previous editions of IFL, IFL 2018 solicits two kinds of submissions: * Regular papers (12 pages including references) * Draft papers for presentations ('weak' limit between 8 and 15 pages) Regular papers will undergo a rigorous review by the program committee, and will be evaluated according to their correctness, novelty, originality, relevance, significance, and clarity. A set of regular papers will be conditionally accepted for publication. Authors of conditionally accepted papers will be provided with committee reviews along with a set of mandatory revisions. Regular papers not accepted for publication will be considered as draft papers, at the request of the author. Draft papers will be screened to make sure that they are within the scope of IFL, and will be accepted for presentation or rejected accordingly. Prior to the symposium: Authors of conditionally accepted papers and accepted presentations will submit a pre-proceedings version of their work that will appear in the draft proceedings distributed at the symposium. The draft proceedings does not constitute a formal publication. We require that at least one of the authors present the work at IFL 2018. After the symposium: Authors of conditionally accepted papers will submit a revised versions of their paper for the formal post-proceedings. The program committee will assess whether the mandatory revisions have been adequately addressed by the authors and thereby determines the final accept/reject status of the paper. Our interest is to ultimately accept all conditionally accepted papers. If you are an author of a conditionally accepted paper, please make sure that you address all the concerns of the reviewers. Authors of accepted presentations will be given the opportunity to incorporate the feedback from discussions at the symposium and will be invited to submit a revised full article for the formal post-proceedings. The program committee will evaluate these submissions according to their correctness, novelty, originality, relevance, significance, and clarity, and will thereby determine whether the paper is accepted or rejected. ### Publication The formal proceedings will appear in the International Conference Proceedings Series of the ACM Digital Library. At no time may work submitted to IFL be simultaneously submitted to other venues; submissions must adhere to ACM SIGPLAN's republication policy: http://www.sigplan.org/Resources/Policies/Republication ### Important dates Submission of regular papers: May 25, 2018 [PASSED!] Submission of draft papers: July 17, 2018 [UPCOMING!] Regular and draft papers notification: July 20, 2018 Deadline for early registration: August 8, 2018 Submission of pre-proceedings version: August 29, 2018 IFL Symposium: September 5-7, 2018 Submission of papers for post-proceedings: November 7, 2018 Notification of acceptance: December 22, 2018 Camera-ready version: February 10, 2019 ### Submission details All contributions must be written in English. Papers must use the ACM two columns conference format, which can be found at: http://www.acm.org/publications/proceedings-template Authors submit through EasyChair: https://easychair.org/conferences/?conf=ifl2018 ### Peter Landin Prize The Peter Landin Prize is awarded to the best paper presented at the symposium every year. The honored article is selected by the program committee based on the submissions received for the formal review process. The prize carries a cash award equivalent to 150 Euros. ### Organization and Program committee Chairs: Jay McCarthy & Matteo Cimini, University of Massachusetts Lowell, USA Program Committee: * Arthur Chargueraud, Inria, FR * Ben Delaware, Purdue University, USA * Christos Dimoulas, Northwestern University, USA * David Darais, University of Vermont, USA * Dominic Orchard, University of Kent, UK * Ekaterina Komendantskaya, Heriot-Watt University, UK * Garrett Morris, University of Kansas, USA * Heather Miller, EPFL & Northeastern University, CH & USA * Jeremy Yallop, University of Cambridge, UK * Keiko Nakata, SAP Innovation Center Potsdam, DE * Laura Castro, University of A Coruna, ESP * Magnus Myreen, Chalmers University of Technology, SWE * Natalia Chechina, Bournemouth University, UK * Peter Achten, Radboud Universiteit Nijmegen, NL * Peter-Michael Osera, Grinnell College, USA * Richard Eisenberg, Bryn Mawr College, USA * Trevor McDonell, University of New South Wales, AUS * Yukiyoshi Kameyama, University of Tsukuba, JAP ### Venue The 30th IFL is organized by the University of Massachusetts Lowell. The City of Lowell is located at the heart of the Merrimack Valley just 30 miles northwest of Boston. Lowell can be easily reached by train or taxi. See the website for more information on the venue. ### Acknowledgments This call-for-papers is an adaptation and evolution of content from previous instances of IFL. We are grateful to prior organizers for their work, which is reused here. A part of IFL 2018 format and CFP language that describes conditionally accepted papers has been adapted from call-for-papers of OOPSLA conferences. -------------- next part -------------- An HTML attachment was scrubbed... URL: From petr.mvd at gmail.com Fri Jun 15 11:31:44 2018 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Fri, 15 Jun 2018 13:31:44 +0200 Subject: [Haskell-cafe] Hedgehog - Integrated shrinking, shrinks obey invariants by construction. In-Reply-To: <523c3dad-ae1c-eab3-39ea-077e85663a3f@gmail.com> References: <523c3dad-ae1c-eab3-39ea-077e85663a3f@gmail.com> Message-ID: That's interesting! Could you please elaborate how this is implemented? Thanks, Petr Dne čt 14. 6. 2018 23:12 uživatel Li-yao Xia napsal: > Generators can be interpreted as the sets of values they generate, and > "integrated shrinking" makes shrinking produce values that belong to the > same set, by deriving it from the generator. In contrast, in QuickCheck, > generators and shrinkers are separate, so if a property we want to test > has some precondition, we need to remember to make both the generator > and the shrinker satisfy these preconditions. > > Li-yao > > On 06/14/2018 04:24 PM, Petr Pudlák wrote: > > Hi everyone, > > > > I found the above interesting sentence in Hedgehog's [1] documentation. > > What does this mean? Is construction there somewhat tied to shrinking, > > perhaps something like going in the reverse direction? > > > > Thanks, > > Petr > > > > [1] https://github.com/hedgehogqa/haskell-hedgehog#features > > > > > > _______________________________________________ > > 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 Jun 15 12:50:04 2018 From: lysxia at gmail.com (Li-yao Xia) Date: Fri, 15 Jun 2018 08:50:04 -0400 Subject: [Haskell-cafe] Hedgehog - Integrated shrinking, shrinks obey invariants by construction. In-Reply-To: References: <523c3dad-ae1c-eab3-39ea-077e85663a3f@gmail.com> Message-ID: <3d73b431-9e1f-cedd-da79-c2de24c74bbd@gmail.com> On 06/15/2018 07:31 AM, Petr Pudlák wrote: > That's interesting! Could you please elaborate how this is implemented? Sure. Whereas QuickCheck declares "shrink" as a function, in Hedgehog generating and shrinking are performed simultaneously. Instead of generating a single value, we can generate a rose tree of them, where the main output is at the root, and the other nodes carry shrunk versions of it, with the smallest ones at the leaves. It works quite nicely and efficiently in Haskell thanks to laziness, so that the shrinking part only happens as needed. The main drawback might be that there is some duplicated work during shrinking ((>>=) applies its second argument to different arguments), but it is quite minor since shrinking is only needed in exceptional cases, and it usually terminates in few steps. Li-yao From arjanen.loic at gmail.com Fri Jun 15 13:55:35 2018 From: arjanen.loic at gmail.com (=?UTF-8?Q?ARJANEN_Lo=c3=afc_Jean_David?=) Date: Fri, 15 Jun 2018 20:55:35 +0700 Subject: [Haskell-cafe] LIA bindings? In-Reply-To: References: <5b20d98f.1c69fb81.53ced.b7e2@mx.google.com> Message-ID: <741af76d-722e-0c7d-c64a-dfcc35be2740@gmail.com> Hello, It was purely curiosity which made me ask that question given that the report mentions this standard but as you said, if no one maintains it there’s little point in making bindings for it. Regards, ARJANEN Loïc Le 2018-06-13 à 22:48, Richard O'Keefe a écrit : > A couple of years ago I inquired about adding a new module to > the LIA standards to describe binary and decimal fixed point > arithmetic, having run into a standard which deferred the > semantics of its fixed point arithmetic to LIA. That was a > bit odd, because LIA explicitly refused to say anything about > the matter. The result was the implementations not agreeing, > in quite fundamental ways, with each other. I offered a > draft executable specification in Haskell, checked with > QuickCheck. I basically got the answer "nice work, but nobody > in the industry cares about LIA any more, which is why LIA-1 > was revised but LIA-2 and LIA-3 never were and never will be." > > So the question has to be asked: what exactly would be the > benefit in building library code to support a standard that > nobody wants to maintain any more? > > On 13 June 2018 at 20:44, ARJANEN Loïc Jean David > > wrote: > > Dear Café, > > I saw in the report that the standard libraries’ operations don’t > conform to LIA and that such operations should be done in an > external library. Does such a library exist? > > Regards, > ARJANEN Loïc > > _______________________________________________ > 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 johnw at newartisans.com Fri Jun 15 19:55:23 2018 From: johnw at newartisans.com (John Wiegley) Date: Fri, 15 Jun 2018 12:55:23 -0700 Subject: [Haskell-cafe] Hedgehog - Integrated shrinking, shrinks obey invariants by construction. In-Reply-To: <3d73b431-9e1f-cedd-da79-c2de24c74bbd@gmail.com> (Li-yao Xia's message of "Fri, 15 Jun 2018 08:50:04 -0400") References: <523c3dad-ae1c-eab3-39ea-077e85663a3f@gmail.com> <3d73b431-9e1f-cedd-da79-c2de24c74bbd@gmail.com> Message-ID: >>>>> "LX" == Li-yao Xia writes: LX> The main drawback might be that there is some duplicated work during LX> shrinking ((>>=) applies its second argument to different arguments), but LX> it is quite minor since shrinking is only needed in exceptional cases, and LX> it usually terminates in few steps. I've recently switched from QuickCheck to Hedgehog for my property testing, and having found that the implied shrinking is indeed a very nice behavior. Shrinking is one of those principled ideas that rarely happens in execution, so any methodology for automating it is appreciated. -- John Wiegley GPG fingerprint = 4710 CF98 AF9B 327B B80F http://newartisans.com 60E1 46C4 BD1A 7AC1 4BA2 From aaronngray.lists at gmail.com Sat Jun 16 15:07:04 2018 From: aaronngray.lists at gmail.com (Aaron Gray) Date: Sat, 16 Jun 2018 16:07:04 +0100 Subject: [Haskell-cafe] Lattice and calculation of Least Upper Bounds Message-ID: Hi, I am trying to work out how to use the Algebra.Lattice family of Lattice data structures. Firstly how do I construct a lattice ? What I am wanting to do is to be able to construct a lattice to represent a multiple inheritance hierarchy. Then I to be able to find the Least Upper Bound of a set of classes/types. This is in order to find the type of a multiple case expression. I am not sure if the Haskell classes are actually applicable ? but if they are how do I apply them to the following problem please ? -- Aaron Gray Independent Open Source Software Engineer, Computer Language Researcher, Information Theorist, and amateur computer scientist. -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg.grenrus at iki.fi Sat Jun 16 16:11:49 2018 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Sat, 16 Jun 2018 19:11:49 +0300 Subject: [Haskell-cafe] the purpose of QuickCheck's size parameter In-Reply-To: References: Message-ID: Not only avoid extremely large trees, but in general guarantee termination of the generation process Sent from my iPhone > On 15 Jun 2018, at 0.31, David Feuer wrote: > > data Foo a = Leaf a | Node [Foo a] > > Without the size parameter, it's a bit tricky to control the distribution to avoid generating extremely large trees. I certainly agree, however, that the size parameter is an ugly and ill-specified hack. > >> On Thu, Jun 14, 2018, 4:20 PM Petr Pudlák wrote: >> Hi everyone, >> >> I'd like to better understand the principles behind the 'size' parameter. Looking at quickCheckWithResult [1], its computation seems to be somewhat non-trivial, or even arbitrary. As far as I understand it, the size is varied throughout tests, increasing from small to larger values. I see two main purposes: >> >> - Test on smaller as well as larger values. But with generators having proper distribution of values, this should happen anyway, just as if we had a constant, larger 'size' parameter. >> - Starting with smaller sizes allows to find smaller count-examples first. But with shrinking, it doesn't matter that much, big counter-examples are shrunk to smaller ones anyway in most cases. >> >> So is this parameter actually necessary? Would anything change considerably if it was dropped? >> >> Thanks, >> Petr >> >> [1] http://hackage.haskell.org/package/QuickCheck-2.11.3/docs/src/Test-QuickCheck-Test.html#quickCheckWithResult >> _______________________________________________ >> 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 petr.mvd at gmail.com Sat Jun 16 21:18:03 2018 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Sat, 16 Jun 2018 23:18:03 +0200 Subject: [Haskell-cafe] the purpose of QuickCheck's size parameter In-Reply-To: <719aa78b-26dc-ead1-b46b-6d12f595d00e@gmail.com> References: <719aa78b-26dc-ead1-b46b-6d12f595d00e@gmail.com> Message-ID: Thank you for your extended explanation. Let me reply my thoughts inline below. pá 15. 6. 2018 v 0:22 odesílatel Li-yao Xia napsal: > The purpose of the size parameter is not well-defined formally, but it > is a very convenient knob to easily tune the test suite in various > situations, that is definitely worth the negligible cost of having it > around unconditionally. > That's what has been disturbing me. Is it a bound on a data structure size? The amount of memory it occupies (which can be quite different due to laziness)? Or a time bound on the tested algorithm running time? If we take a specific example, a typical recursive data structure is some kind of a tree. When generating a random binary tree, should the size bound it's height? Or its average height? Or the number of its elements? As the size bound it it's not really defined, everyone uses it differently, so in the end all we now that there is *some* bound and that we can make it larger or smaller, but that's really all. > > Without a size parameter, a fixed distribution means that if we want the > generator to cover all possible cases, we have to keep a small > probability of generating humongous examples and thus go OOM. We can > avoid that by making the size of generated values bounded by the size > parameter (or a function thereof), which we can increase easily when > more resources become available. > That's true, but I'd assume that if we use something like the exponential distribution , the probability of an example that'd cause OOM can be really tiny. (Possibly smaller than the change that there is a human-introduced bug causing OOM, for example.) > > Furthermore, if we really want to generate very large examples, the only > way with a fixed distribution is to wait longer. Instead, using a size > parameter, we can make smaller values less likely to target further > regions in the search space more accurately. > That's probably the most convincing argument for me. Without a size bound, as the size of a structure increases, the likelihood of it's appearance must approach zero probability. To test larger structures as well, it makes sense to something like "pick a size between 1 and 1M and then generate a structure of that size", so we have a naturally occurring bound in such tests. But still I have doubts if it wouldn't be better to either: - Express this limit explicitly for generators of such structures of variable size, like in vectorOf, or - Define the meaning of 'size' more rigorously to make the behavior more consistent among different data structures. > > Some properties can take a while to test on larger examples (either > because of the generators or the actual verification process) so we > might like to keep the size small during development, and raise it again > once we're done. > > The Arbitrary class assigns a "default" generator for every type. While > it is not always a good choice, having a parameter to tweak makes > Arbitrary more generally useful. > Here I'd argue that not having a precisely defined meaning of size, tweaking Arbitrary instances by modifying its size parameter before produces very vague results. If one needs at least some level of confidence in the behavior of a test, it's usually necessary to use parametrized functions that document the distribution of the values depending on parameters > > As for your last point, small examples are faster to generate and check, > so it seems like a decent strategy to start small by default. > I'd say that this applies only during fixing a bug, as you mentioned above. As long as the test is failing, starting with smaller example indeed makes is fail faster. But for example for tests in continuous integration, we expect all of them to succeed and we need to test both small and large, so here the advantage of starting with small ones vanishes. Best, Petr > > 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 petr.mvd at gmail.com Sun Jun 17 09:18:00 2018 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Sun, 17 Jun 2018 11:18:00 +0200 Subject: [Haskell-cafe] the purpose of QuickCheck's size parameter In-Reply-To: References: Message-ID: PS: Just to make clear, it's not that I have something against QuickCheck or similar libraries, on the contrary, they're great! I'm just playing the devil's advocate to analyze and understand the concept. ne 17. 6. 2018 v 4:05 odesílatel Oleg Grenrus napsal: > Not only avoid extremely large trees, but in general guarantee termination > of the generation process > > Sent from my iPhone > > On 15 Jun 2018, at 0.31, David Feuer wrote: > > data Foo a = Leaf a | Node [Foo a] > > Without the size parameter, it's a bit tricky to control the distribution > to avoid generating extremely large trees. I certainly agree, however, that > the size parameter is an ugly and ill-specified hack. > > On Thu, Jun 14, 2018, 4:20 PM Petr Pudlák wrote: > >> Hi everyone, >> >> I'd like to better understand the principles behind the 'size' parameter. >> Looking at quickCheckWithResult [1], its computation seems to be somewhat >> non-trivial, or even arbitrary. As far as I understand it, the size is >> varied throughout tests, increasing from small to larger values. I see two >> main purposes: >> >> - Test on smaller as well as larger values. But with generators having >> proper distribution of values, this should happen anyway, just as if we had >> a constant, larger 'size' parameter. >> - Starting with smaller sizes allows to find smaller count-examples >> first. But with shrinking, it doesn't matter that much, big >> counter-examples are shrunk to smaller ones anyway in most cases. >> >> So is this parameter actually necessary? Would anything change >> considerably if it was dropped? >> >> Thanks, >> Petr >> >> [1] >> http://hackage.haskell.org/package/QuickCheck-2.11.3/docs/src/Test-QuickCheck-Test.html#quickCheckWithResult >> _______________________________________________ >> 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 jon.fairbairn at cl.cam.ac.uk Sun Jun 17 09:27:56 2018 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Sun, 17 Jun 2018 10:27:56 +0100 Subject: [Haskell-cafe] ghc_ticker not checking return code? Message-ID: I’ve just been rebuilding something I wrote ages ago, using stack with lts-11.6 (so that I can use a recent Conduit). Part (not a part I was modifying) of the code runs as a CGI script, and I was horrified to find that when run by httpd it soaked up CPU like nobody’s business without producing any output. Running it at the command line worked fine, so I traced the problem via audit: type=AVC msg=audit(1529223103.790:1705516): avc: denied { read } for pid=36764 comm="ghc_ticker" path="[timerfd]" dev=anon_inodefs ino=4597 scontext=system_u:system_r:httpd_sys_script_t:s0 tcontext=system_u:object_r:anon_inodefs_t:s0 tclass=file type=AVC msg=audit(1529223103.790:1705517): avc: denied { read } for pid=36764 comm="ghc_ticker" path="[timerfd]" dev=anon_inodefs ino=4597 scontext=system_u:system_r:httpd_sys_script_t:s0 tcontext=system_u:object_r:anon_inodefs_t:s0 tclass=file The solution is to add an audit rule to allow that, but surely ghc_ticker shouldn’t be trying again so fast when whatever it is trying to do isn’t permitted? I don’t know what component ghc_ticker belongs to, so where should I report the problem? -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From ollie at ocharles.org.uk Sun Jun 17 10:28:32 2018 From: ollie at ocharles.org.uk (Oliver Charles) Date: Sun, 17 Jun 2018 11:28:32 +0100 Subject: [Haskell-cafe] the purpose of QuickCheck's size parameter In-Reply-To: References: Message-ID: Is SmallCheck more principles in this regard, or would people consider that equally hacky? On Sun, 17 Jun 2018, 10:18 am Petr Pudlák, wrote: > PS: Just to make clear, it's not that I have something against QuickCheck > or similar libraries, on the contrary, they're great! I'm just playing the > devil's advocate to analyze and understand the concept. > > ne 17. 6. 2018 v 4:05 odesílatel Oleg Grenrus > napsal: > >> Not only avoid extremely large trees, but in general guarantee >> termination of the generation process >> >> Sent from my iPhone >> >> On 15 Jun 2018, at 0.31, David Feuer wrote: >> >> data Foo a = Leaf a | Node [Foo a] >> >> Without the size parameter, it's a bit tricky to control the distribution >> to avoid generating extremely large trees. I certainly agree, however, that >> the size parameter is an ugly and ill-specified hack. >> >> On Thu, Jun 14, 2018, 4:20 PM Petr Pudlák wrote: >> >>> Hi everyone, >>> >>> I'd like to better understand the principles behind the 'size' >>> parameter. Looking at quickCheckWithResult [1], its computation seems to be >>> somewhat non-trivial, or even arbitrary. As far as I understand it, the >>> size is varied throughout tests, increasing from small to larger values. I >>> see two main purposes: >>> >>> - Test on smaller as well as larger values. But with generators having >>> proper distribution of values, this should happen anyway, just as if we had >>> a constant, larger 'size' parameter. >>> - Starting with smaller sizes allows to find smaller count-examples >>> first. But with shrinking, it doesn't matter that much, big >>> counter-examples are shrunk to smaller ones anyway in most cases. >>> >>> So is this parameter actually necessary? Would anything change >>> considerably if it was dropped? >>> >>> Thanks, >>> Petr >>> >>> [1] >>> http://hackage.haskell.org/package/QuickCheck-2.11.3/docs/src/Test-QuickCheck-Test.html#quickCheckWithResult >>> _______________________________________________ >>> 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 S.J.Thompson at kent.ac.uk Sun Jun 17 10:40:08 2018 From: S.J.Thompson at kent.ac.uk (Simon Thompson) Date: Sun, 17 Jun 2018 11:40:08 +0100 Subject: [Haskell-cafe] the purpose of QuickCheck's size parameter In-Reply-To: References: Message-ID: <5F7B3622-3041-4E10-92D6-C7E19C14C28A@kent.ac.uk> Because it works by increasing size, yes, it doesn’t need guidance about the order. On the other hand, you’re exploring a different part of the space of possible inputs. There’s also Lazy SmallCheck, too. Which is best? There’s no clear answer to this, but a reasonable principle is to try a bundle of approaches if you want to argue that you have used a limited amount of testing resource in as prudent as possible a way. Simon > On 17 Jun 2018, at 11:28, Oliver Charles wrote: > > Is SmallCheck more principled in this regard, or would people consider that equally hacky? > > On Sun, 17 Jun 2018, 10:18 am Petr Pudlák, > wrote: > PS: Just to make clear, it's not that I have something against QuickCheck or similar libraries, on the contrary, they're great! I'm just playing the devil's advocate to analyze and understand the concept. > > ne 17. 6. 2018 v 4:05 odesílatel Oleg Grenrus > napsal: > Not only avoid extremely large trees, but in general guarantee termination of the generation process > > Sent from my iPhone > > On 15 Jun 2018, at 0.31, David Feuer > wrote: > >> data Foo a = Leaf a | Node [Foo a] >> >> Without the size parameter, it's a bit tricky to control the distribution to avoid generating extremely large trees. I certainly agree, however, that the size parameter is an ugly and ill-specified hack. >> >> On Thu, Jun 14, 2018, 4:20 PM Petr Pudlák > wrote: >> Hi everyone, >> >> I'd like to better understand the principles behind the 'size' parameter. Looking at quickCheckWithResult [1], its computation seems to be somewhat non-trivial, or even arbitrary. As far as I understand it, the size is varied throughout tests, increasing from small to larger values. I see two main purposes: >> >> - Test on smaller as well as larger values. But with generators having proper distribution of values, this should happen anyway, just as if we had a constant, larger 'size' parameter. >> - Starting with smaller sizes allows to find smaller count-examples first. But with shrinking, it doesn't matter that much, big counter-examples are shrunk to smaller ones anyway in most cases. >> >> So is this parameter actually necessary? Would anything change considerably if it was dropped? >> >> Thanks, >> Petr >> >> [1] http://hackage.haskell.org/package/QuickCheck-2.11.3/docs/src/Test-QuickCheck-Test.html#quickCheckWithResult _______________________________________________ >> 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. Simon Thompson | Professor of Logic and Computation School of Computing | University of Kent | Canterbury, CT2 7NF, UK s.j.thompson at kent.ac.uk | M +44 7986 085754 | W www.cs.kent.ac.uk/~sjt -------------- next part -------------- An HTML attachment was scrubbed... URL: From zocca.marco at gmail.com Sun Jun 17 12:47:53 2018 From: zocca.marco at gmail.com (Marco Zocca) Date: Sun, 17 Jun 2018 14:47:53 +0200 Subject: [Haskell-cafe] DataHaskell Newsletter #1, June 2018 Message-ID: Hi all, I'd like to share with you a few of the things that happened during the past months on and around DataHaskell (DH), and a summary of the current state of things. Time permitting, this will become a regular newsletter, with the idea to keep up to date those who don't usually hang out on our Gitter chatroom [1]. ---------------------------------------------------------------------------------------------------------------- * Outreach activities and related meetings ICFP 2017 : Early September 2017 we had an hour-long lunch mini-workshop at ICFP during which a few people presented how they use Haskell in their numerical and data-crunching work. Mostly positive opinions, as well as a "contrarian" viewpoint (from an expert practitioner) who lamented the low-performance of native Haskell numerical code (e.g. the large memory footprint of boxed data). Michal Gajda presented how he uses IHaskell for interactive data exploration (btw, it's a thing and you can try it today!), Trevor McDonell introduced Accelerate (the high-performance array library that can target CUDA GPUs), Adam Scibior presented `monad-bayes` and Praveen Narayan presented `hakaru` (two probabilistic progamming laguages embedded in Haskell). ZuriHac 2018 : community bonding mostly (read: no hacking was done). Received more feedback of the usual sort "how do I do X in Haskell?" "I was expecting a more advanced state of machine learning capabilities in Haskell", etc. There may or may not be a set of Haskell bindings for Apache Arrow in the works, stay tuned! ICFP 2018 : There will be two very interesting workshops (FHPC, functional programming in high-performance computing and NPFL, numerical programming in functional languages), for those who will be attending the conference. One of the workshop chairs of NPFL is Dominic Steinitz of Tweag, author of the excellent idontgetoutmuch.wordpress.com blog. ---------------------------------------------------------------------------------------------------------------- * DH survey On April 5 I've published a survey [2], that tried to gauge the community interest and pain points related to doing "data science" in our beloved language. The survey is still open but I won't be collecting data anymore (70 people have taken the questionnaire and 62 have completed it), and I've scraped and formatted the dataset (you can find it at https://github.com/DataHaskell/surveys). Some of the free text answers are particularly interesting. I don't have much time currently to create the plots and publish a blog post about it, but it would be a Good Thing to have, if anyone wants to step up. The project backbone is ready for new contributors! ---------------------------------------------------------------------------------------------------------------- * Contributors wanted : External projects At regular intervals, new exciting projects appear and it's becoming quite hard to keep track of everything that's happening in this area. I'd like to highlight here a few that are seeing significant activity as of late and have large impact potential. ** General-purpose (e.g. numerics-related) `numhask` [3] is an experiment at replacing the numerical typeclasses of `base`, in particular those related to `Num`, in favor of a finer-grained and more principled hierarchy. It is already available and receiving quite a bit of attention recently, but there still are a number of areas that could use some help, for example property checking, test coverage, the `accelerate` bindings, etc. ** Data science `boke-hs` [4] : a native Haskell interface to generate Bokeh plots. The project was mostly developed during the ZuriHac weekend; currently it's functional and you can create line plots with it, but helping out with the domain mapping would be a very valuable contribution. In particular, the library emits JSON blobs that are interpreted in the browser by BokehJS ; "domain mapping" means creating the Haskell data that will serialize into JSON appropriately. A currently-unnamed library for linking databases and Haskell dataframes. This is Gagandeep Bhatia's ongoing Summer of Haskell project, and you can find a writeup and links to his current work (which uses `beam` as a database binding library and `Frames` as type-safe in-memory representation) here: https://www.gagandeepbhatia.com/blog/ . `haskell.do` [5] : a native Haskell notebook/interactive editor/IDE for the browser. The project started well, has a website and a few initial releases, but currently needs some love to achieve its full potential. Interactive development with visual feedback is a crucial part of data science work, and contributions to this project will be very valuable. ** Machine learning `hasktorch` [6] is in developer beta ! This is a set of Haskell bindings for `torch` (the deep learning C library), and comes wrapped in a typed interface that provide statically-checked vector dimensions, and the like. ** Probabilistic programming languages `deanie` [7] is a probabilistic EDSL. Currently it's lacking code for its general-purpose inference engine (see https://github.com/jtobin/deanie/blob/master/lib/Deanie/Inference/Comonadic.hs). The implementation technique is related to "Co-Free for interpreters" as shown in [8]. ---------------------------------------------------------------------------------------------------------------- * Contributors wanted : DataHaskell internal projects We do have a few projects set up that could use some collaborators. If you are willing to contribute to any of these, please open a ticket on the project issue tracker and the maintainers will be in touch shortly. * `type-providers` : a unified code generation library for accessing structured data in a type-safe way : https://github.com/DataHaskell/type-providers . Michal Gajda is willing to mentor a student who wants to translate his own `json-autotype` to a new library that can generate type-safe code for XML, and can be queried in-memory via Frames. Contributing to this library will likely require some knowledge of Template Haskell. * A fork of the venerable `statistics` library, that separates the dense linear algebra library as a standalone library : https://github.com/DataHaskell/statistics . There is currently a PR to the upstream library (https://github.com/bos/statistics/pull/143); longer-term plans include giving it a typeclass-based interface, for example based on `numhask`. * `numhask-linear-algebra` : this is a longer shot at unifying native linear algebra libraries under a single typeclass representation, as provided by `numhask` (project at https://github.com/DataHaskell/numhask-linear-algebra ). This is something that's currently unavailable in the Haskell ecosystem and will be a highly relevant contribution to many. ---------------------------------------------------------------------------------------------------------------- * DataHaskell internal administration In addition to helping out with the survey blogpost, some help in the following areas would be much appreciated ** Knowledge base : testers wanted ! The knowledge base ( http://www.datahaskell.org/docs/community/current-environment.html ) is a growing curated collection of libraries for doing data science-related tasks; anything from manipulating storable data to statistical inference. It's pretty useful as it is, but I think the entries should be annotated with additional information, such as the degree of completeness and developer- and user-friendliness. For this, some help in testing out the libraries and reporting back would be very useful. Ultimately, it would be very useful to contribute such an assessment back to the "state of the ecosystem" document [9], which is highly visible but not so much up to date on the data-science related things. ** Maintainers wanted ! Currently, Nikita and I are the only owners of the github organization. It would be great if additional people stepped up for "tending the garden", e.g. keeping track of issue tickets, filling out the documentation, lending a hand on the gitter channel to address newcomers' issues, etc. Historically, data science and numerical computing have been underserved niches of the Haskell ecosystem, and while things are steadily improving, together we can bring about this change soon ! ---------------------------------------------------------------------------------------------------------------- That's it for now, I hope you enjoyed this Newsletter; don't hesitate to share your thoughts either here or on our Gitter chatroom! [1] Marco github.com/ocramz ---------------------------------------------------------------------------------------------------------------- References : [1] DH Gitter chatroom : https://gitter.im/dataHaskell/Lobby [2] DH user survey April 2018: https://www.surveymonkey.com/r/3FBBJWR [3] numhask : github.com/tonyday567/numhask [4] boke-hs , native Haskell bindings for Bokeh : https://github.com/ahaym/boke-hs [5] HaskellDO, the interactive Haskell editor: http://haskell.do/ , https://github.com/theam/haskell-do [6] hasktorch, the Haskell bindings to Torch : https://github.com/hasktorch/hasktorch [7] deanie , probabilistic programming language : https://github.com/jtobin/deanie [8] "Free for DSLs, co-free for interpreters" http://dlaing.org/cofun/posts/free_and_cofree.html [9] State of the Haskell ecosystem : https://github.com/Gabriel439/post-rfc/blob/master/sotu.md From allbery.b at gmail.com Sun Jun 17 16:10:53 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Sun, 17 Jun 2018 12:10:53 -0400 Subject: [Haskell-cafe] ghc_ticker not checking return code? In-Reply-To: References: Message-ID: I'd suspect it's mishandling the error return from a read(). Or not handling, but if the error it gets back is for some reason EAGAIN then it's kinda difficult to handle this sanely except by adding extra instrumentation to catch the loop. On Sun, Jun 17, 2018 at 5:28 AM Jon Fairbairn wrote: > I’ve just been rebuilding something I wrote ages ago, using > stack with lts-11.6 (so that I can use a recent Conduit). > > Part (not a part I was modifying) of the code runs as a CGI > script, and I was horrified to find that when run by httpd it > soaked up CPU like nobody’s business without producing any > output. Running it at the command line worked fine, so I traced > the problem via audit: > > type=AVC msg=audit(1529223103.790:1705516): avc: denied { read } for > pid=36764 comm="ghc_ticker" path="[timerfd]" dev=anon_inodefs ino=4597 > scontext=system_u:system_r:httpd_sys_script_t:s0 > tcontext=system_u:object_r:anon_inodefs_t:s0 tclass=file > type=AVC msg=audit(1529223103.790:1705517): avc: denied { read } for > pid=36764 comm="ghc_ticker" path="[timerfd]" dev=anon_inodefs ino=4597 > scontext=system_u:system_r:httpd_sys_script_t:s0 > tcontext=system_u:object_r:anon_inodefs_t:s0 tclass=file > > The solution is to add an audit rule to allow that, but surely > ghc_ticker shouldn’t be trying again so fast when whatever it is > trying to do isn’t permitted? > > I don’t know what component ghc_ticker belongs to, so where > should I report the problem? > > -- > Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk > > _______________________________________________ > 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 sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From jon.fairbairn at cl.cam.ac.uk Mon Jun 18 08:48:28 2018 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Mon, 18 Jun 2018 09:48:28 +0100 Subject: [Haskell-cafe] ghc_ticker not checking return code? References: Message-ID: Brandon Allbery writes: > I'd suspect it's mishandling the error return from a read(). Or not > handling, but if the error it gets back is for some reason EAGAIN then it's > kinda difficult to handle this sanely except by adding extra > instrumentation to catch the loop. If a selinux denial is producing EAGAIN, something is very wrong. I doubt that that’s what’s happening. If I knew where to go I could create a ticket… From Graham.Hutton at nottingham.ac.uk Mon Jun 18 13:45:42 2018 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Mon, 18 Jun 2018 13:45:42 +0000 Subject: [Haskell-cafe] Announcement: MPC 2019, Porto, Portugal Message-ID: <30088734-8CD3-4E64-9F83-E9F686EE8727@exmail.nottingham.ac.uk> Dear all, I'm delighted to announce that the next Mathematics of Program Construction (MPC) conference will be held in the historic city of Porto, Portugal in October 2019, co-located with Formal Methods (FM). Please share, and submit your best papers! Best wishes, Graham ====================================================================== 13th International Conference on Mathematics of Program Construction 7-9 October 2019, Porto, Portugal Co-located with FM 2019 https://tinyurl.com/MPC-Porto ====================================================================== 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. IMPORTANT DATES: 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 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 . PROGRAM COMMITTEE: Graham Hutton University of Nottingham, UK (chair) The full committee will be announced as soon as it is available. 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 Duoro. 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 allbery.b at gmail.com Mon Jun 18 15:14:27 2018 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 18 Jun 2018 11:14:27 -0400 Subject: [Haskell-cafe] ghc_ticker not checking return code? In-Reply-To: References: Message-ID: Yeh, that was why "for some reason" — in that case I'd blame the audit framework, not the program. ghc_ticker is an internal thread of the ghc runtime, so you want the ghc Trac, rts component. https://ghc.haskell.org/trac/ghc/newticket?type=bug (you will need to create an account). On Mon, Jun 18, 2018 at 4:48 AM Jon Fairbairn wrote: > Brandon Allbery writes: > > > I'd suspect it's mishandling the error return from a read(). Or not > > handling, but if the error it gets back is for some reason EAGAIN then > it's > > kinda difficult to handle this sanely except by adding extra > > instrumentation to catch the loop. > > If a selinux denial is producing EAGAIN, something is very > wrong. I doubt that that’s what’s happening. If I knew where to > go I could create a ticket… > > > _______________________________________________ > 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 sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From mblazevic at stilo.com Mon Jun 18 20:25:30 2018 From: mblazevic at stilo.com (=?UTF-8?Q?Mario_Bla=c5=beevi=c4=87?=) Date: Mon, 18 Jun 2018 16:25:30 -0400 Subject: [Haskell-cafe] Anybody interested in Dart? Maintainer needed. Message-ID: There is package named language-dart on Hackage by Kwang Yul Seo. The package includes the Dart AST and pretty-printer, but no parser. It hasn't been updated in 2 years. I have implemented a parser in a pull request (https://github.com/kseo/language-dart/pull/1) but the original author says he doesn't have time to maintain this package at the moment and is willing to transfer its maintainance. As for myself, I'd be happy to help as a co-maintainer but I feel that a proper feeding and care of the package requires somebody with interest in Google Dart per se. Does anybody here fit this description? From kitttoran at gmail.com Tue Jun 19 18:36:50 2018 From: kitttoran at gmail.com (=?UTF-8?B?0J3QuNC60LjRgtCwINCk0YPRhNCw0LXQsg==?=) Date: Tue, 19 Jun 2018 21:36:50 +0300 Subject: [Haskell-cafe] Memory leak in infinite recursion Message-ID: Hello everyone In C you can't implement main loop with recursion like void mainLoop() { doSomething(); mainLoop(); } because without optimisations stack will overflow. In haskell it's common to write mainLoop = doSomething >> mainLoop, and it doesn't leak memory because of haskell's evaluation model. Does memory leak or argument stack overflow happen in this case? mainLoop = doSomething >> mainLoop >> exit ExitSuccess What about this case? mainLoopModeA = do doSomething when condition mainLoopModeB mainLoopModeA mainLoopModeB = do doSomethingElse when anotherCondition mainLoopModeA mainLoopModeB or this case? mainLoopModeA = do doSomething if condition then mainLoopModeB else mainLoopModeA mainLoopModeB = do doSomethingElse if anotherCondition then mainLoopModeA else mainLoopModeB -- Nikita Fufaev -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Tue Jun 19 19:52:51 2018 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Tue, 19 Jun 2018 21:52:51 +0200 Subject: [Haskell-cafe] Lattice and calculation of Least Upper Bounds Message-ID: Aaron, the lattices package provides some modules to extend a given lattice by some elements, e.g. new top and bottoms. There are also derived typeclass instances for combinations like tuples, endomorphisms and so forth. But the way of choice really depends on what you know about your multiple inheritance hierarchy. In universal algebra one powerful method of constructing (semi-)lattices is by generators and relations. That means you define the lattice as a quotient of a free lattice. The quotient itself is defined as a set of ineqalities on the generators. I don't know how one would implement that without dependent types, though, as the type would be another type together with a function. To make things worse, the word problem is undecidable in general. Looking at Algebra.Lattice.Free I'm surprised that the free (semi-)lattice types don't have a Monad instance. Does anyone know why they are not implemented? Under the hood the free lattice types are identical to the continuation monad. Olaf >Hi, > >I am trying to work out how to use the Algebra.Lattice family of Lattice >data structures. > >Firstly how do I construct a lattice ? > >What I am wanting to do is to be able to construct a lattice to represent a >multiple inheritance hierarchy. Then I to be able to find the Least Upper >Bound of a set of classes/types. This is in order to find the type of a >multiple case expression. > >I am not sure if the Haskell classes are actually applicable ? but if they >are how do I apply them to the following problem please ? From siddu.druid at gmail.com Tue Jun 19 20:13:53 2018 From: siddu.druid at gmail.com (Siddharth Bhat) Date: Tue, 19 Jun 2018 22:13:53 +0200 Subject: [Haskell-cafe] Lattice and calculation of Least Upper Bounds In-Reply-To: References: Message-ID: I'd love a reference for the last sentence - free lattice ~= continuation monad? Thanks, Siddharth On Tue 19 Jun, 2018, 21:53 Olaf Klinke, wrote: > Aaron, > > the lattices package provides some modules to extend a given lattice by > some elements, e.g. new top and bottoms. There are also derived typeclass > instances for combinations like tuples, endomorphisms and so forth. But the > way of choice really depends on what you know about your multiple > inheritance hierarchy. > In universal algebra one powerful method of constructing (semi-)lattices > is by generators and relations. That means you define the lattice as a > quotient of a free lattice. The quotient itself is defined as a set of > ineqalities on the generators. I don't know how one would implement that > without dependent types, though, as the type would be another type together > with a function. To make things worse, the word problem is undecidable in > general. > Looking at Algebra.Lattice.Free I'm surprised that the free (semi-)lattice > types don't have a Monad instance. Does anyone know why they are not > implemented? Under the hood the free lattice types are identical to the > continuation monad. > > Olaf > > >Hi, > > > >I am trying to work out how to use the Algebra.Lattice family of Lattice > >data structures. > > > >Firstly how do I construct a lattice ? > > > >What I am wanting to do is to be able to construct a lattice to represent > a > >multiple inheritance hierarchy. Then I to be able to find the Least Upper > >Bound of a set of classes/types. This is in order to find the type of a > >multiple case expression. > > > >I am not sure if the Haskell classes are actually applicable ? but if they > >are how do I apply them to the following problem please ? > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Sending this from my phone, please excuse any typos! -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Tue Jun 19 22:16:17 2018 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Wed, 20 Jun 2018 00:16:17 +0200 Subject: [Haskell-cafe] Lattice and calculation of Least Upper Bounds In-Reply-To: References: Message-ID: Well, free lattice ~= continuation monad is not entirely true, since Cont a x = (x -> a) -> a and FreeLattice x = forall a. Lattice a => (x -> a) -> a So in the latter the a is qualified and a rank-2 type. But the types are similar in structure. Thinking of it some more, the unit should be identical but the monad bind could be different. I'm just throwing in the first thing that type-checks; I haven't proven the monad laws for this. But at this abstraction level, the chances are good that the first thing that type-checks is the one you want. Consider the following. (I shortened the type names a bit.) {-# LANGUAGE Rank2Types #-} class Lat a where v :: a -> a -> a -- add more operations if you wish newtype F x = F {free :: forall a. Lat a => (x -> a) -> a} instance Lat (F x) where v x y = F (\f -> v (free x f) (free y f)) returnLat :: x -> F x returnLat x = F (\f -> f x) -- ^ same as for continuation monad bindF :: F x -> (x -> F y) -> F y bindF phi k = free phi k -- ^ uses the fact that F y is a Lat instance. Maybe also a blog post by Dan Doel [1] is relevant, where the free monoid is considered. -- Olaf [1] http://comonad.com/reader/2015/free-monoids-in-haskell/ > > Am 19.06.2018 um 22:13 schrieb Siddharth Bhat : > > I'd love a reference for the last sentence - free lattice ~= continuation monad? > > Thanks, > Siddharth From mwotton at gmail.com Wed Jun 20 00:02:41 2018 From: mwotton at gmail.com (Mark Wotton) Date: Tue, 19 Jun 2018 20:02:41 -0400 Subject: [Haskell-cafe] Memory leak in infinite recursion In-Reply-To: References: Message-ID: Any mutually recursive set of functions calling in tail position should be fine - all your examples are ok. On Tue, Jun 19, 2018, 2:37 PM Никита Фуфаев wrote: > Hello everyone > > In C you can't implement main loop with recursion like > void mainLoop() { > doSomething(); > mainLoop(); > } > because without optimisations stack will overflow. > In haskell it's common to write > mainLoop = doSomething >> mainLoop, and it doesn't leak memory because of > haskell's evaluation model. > Does memory leak or argument stack overflow happen in this case? > mainLoop = doSomething >> mainLoop >> exit ExitSuccess > What about this case? > mainLoopModeA = do > doSomething > when condition mainLoopModeB > mainLoopModeA > mainLoopModeB = do > doSomethingElse > when anotherCondition mainLoopModeA > mainLoopModeB > > or this case? > mainLoopModeA = do > doSomething > if condition > then mainLoopModeB > else mainLoopModeA > mainLoopModeB = do > doSomethingElse > if anotherCondition > then mainLoopModeA > else mainLoopModeB > > -- > Nikita Fufaev > _______________________________________________ > 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 david.feuer at gmail.com Wed Jun 20 00:06:40 2018 From: david.feuer at gmail.com (David Feuer) Date: Tue, 19 Jun 2018 20:06:40 -0400 Subject: [Haskell-cafe] Memory leak in infinite recursion In-Reply-To: References: Message-ID: Actually, only the second set is tail recursive. The first set could be trouble. On Tue, Jun 19, 2018, 8:03 PM Mark Wotton wrote: > Any mutually recursive set of functions calling in tail position should be > fine - all your examples are ok. > > On Tue, Jun 19, 2018, 2:37 PM Никита Фуфаев wrote: > >> Hello everyone >> >> In C you can't implement main loop with recursion like >> void mainLoop() { >> doSomething(); >> mainLoop(); >> } >> because without optimisations stack will overflow. >> In haskell it's common to write >> mainLoop = doSomething >> mainLoop, and it doesn't leak memory because of >> haskell's evaluation model. >> Does memory leak or argument stack overflow happen in this case? >> mainLoop = doSomething >> mainLoop >> exit ExitSuccess >> What about this case? >> mainLoopModeA = do >> doSomething >> when condition mainLoopModeB >> mainLoopModeA >> mainLoopModeB = do >> doSomethingElse >> when anotherCondition mainLoopModeA >> mainLoopModeB >> >> or this case? >> mainLoopModeA = do >> doSomething >> if condition >> then mainLoopModeB >> else mainLoopModeA >> mainLoopModeB = do >> doSomethingElse >> if anotherCondition >> then mainLoopModeA >> else mainLoopModeB >> >> -- >> Nikita Fufaev >> _______________________________________________ >> 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 mwotton at gmail.com Wed Jun 20 00:08:57 2018 From: mwotton at gmail.com (Mark Wotton) Date: Tue, 19 Jun 2018 20:08:57 -0400 Subject: [Haskell-cafe] Memory leak in infinite recursion In-Reply-To: References: Message-ID: Oops, yes, you are right - if it keeps switching back and forth the stack will build up. Apologies, written while wrangling a toddler. On Tue, Jun 19, 2018, 8:06 PM David Feuer wrote: > Actually, only the second set is tail recursive. The first set could be > trouble. > > > On Tue, Jun 19, 2018, 8:03 PM Mark Wotton wrote: > >> Any mutually recursive set of functions calling in tail position should >> be fine - all your examples are ok. >> >> On Tue, Jun 19, 2018, 2:37 PM Никита Фуфаев wrote: >> >>> Hello everyone >>> >>> In C you can't implement main loop with recursion like >>> void mainLoop() { >>> doSomething(); >>> mainLoop(); >>> } >>> because without optimisations stack will overflow. >>> In haskell it's common to write >>> mainLoop = doSomething >> mainLoop, and it doesn't leak memory because >>> of haskell's evaluation model. >>> Does memory leak or argument stack overflow happen in this case? >>> mainLoop = doSomething >> mainLoop >> exit ExitSuccess >>> What about this case? >>> mainLoopModeA = do >>> doSomething >>> when condition mainLoopModeB >>> mainLoopModeA >>> mainLoopModeB = do >>> doSomethingElse >>> when anotherCondition mainLoopModeA >>> mainLoopModeB >>> >>> or this case? >>> mainLoopModeA = do >>> doSomething >>> if condition >>> then mainLoopModeB >>> else mainLoopModeA >>> mainLoopModeB = do >>> doSomethingElse >>> if anotherCondition >>> then mainLoopModeA >>> else mainLoopModeB >>> >>> -- >>> Nikita Fufaev >>> _______________________________________________ >>> 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 vanessa.mchale at iohk.io Wed Jun 20 00:11:04 2018 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Tue, 19 Jun 2018 19:11:04 -0500 Subject: [Haskell-cafe] Memory leak in infinite recursion In-Reply-To: References: Message-ID: <2f890231-7562-e3c2-e0cb-604e466863b1@iohk.io> Have you profiled it? I wouldn't worry about recursion until I've seen the problem. I believe GHC defaults to infinite stack size. Have you tried using hp2ps and/or looking at the code via threadscope? On 06/19/2018 01:36 PM, Никита Фуфаев wrote: > Hello everyone > > In C you can't implement main loop with recursion like > void mainLoop() { >   doSomething(); >   mainLoop(); > }   > because without optimisations stack will overflow. > In haskell it's common to write > mainLoop = doSomething >> mainLoop, and it doesn't leak memory because > of haskell's evaluation model. > Does memory leak or argument stack overflow happen in this case? > mainLoop = doSomething >> mainLoop >> exit ExitSuccess > What about this case? > mainLoopModeA = do >   doSomething >   when condition mainLoopModeB >   mainLoopModeA > mainLoopModeB = do >   doSomethingElse >   when anotherCondition mainLoopModeA >   mainLoopModeB > > or this case? > mainLoopModeA = do >   doSomething >   if condition >     then mainLoopModeB >     else mainLoopModeA > mainLoopModeB = do >   doSomethingElse >   if anotherCondition  >     then mainLoopModeA >     else mainLoopModeB > > -- > Nikita Fufaev > > > _______________________________________________ > 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 drkoster at qq.com Wed Jun 20 01:54:22 2018 From: drkoster at qq.com (=?gb18030?B?RHIuS29zdGVy?=) Date: Wed, 20 Jun 2018 09:54:22 +0800 Subject: [Haskell-cafe] Memory leak in infinite recursion Message-ID: In general infinite monadic recursion will leak, since the tail position is always >> or >>= instead of your own recursive function, but under certain situations, e.g. IO without arguments, the compiler will figure there's no need to push new stack frame. But anyway it's better to checkout yourself rather relying on some weak assumptions. 发自我的iPhone ------------------ Original ------------------ From: Никита Фуфаев Date: Wed,Jun 20,2018 2:37 AM To: haskell-cafe Subject: Re: [Haskell-cafe] Memory leak in infinite recursion Hello everyone In C you can't implement main loop with recursion like void mainLoop() { doSomething(); mainLoop(); } because without optimisations stack will overflow. In haskell it's common to write mainLoop = doSomething >> mainLoop, and it doesn't leak memory because of haskell's evaluation model. Does memory leak or argument stack overflow happen in this case? mainLoop = doSomething >> mainLoop >> exit ExitSuccess What about this case? mainLoopModeA = do doSomething when condition mainLoopModeB mainLoopModeA mainLoopModeB = do doSomethingElse when anotherCondition mainLoopModeA mainLoopModeB or this case? mainLoopModeA = do doSomething if condition then mainLoopModeB else mainLoopModeA mainLoopModeB = do doSomethingElse if anotherCondition then mainLoopModeA else mainLoopModeB -- Nikita Fufaev -------------- next part -------------- An HTML attachment was scrubbed... URL: From hilco.wijbenga at gmail.com Wed Jun 20 04:35:02 2018 From: hilco.wijbenga at gmail.com (Hilco Wijbenga) Date: Tue, 19 Jun 2018 21:35:02 -0700 Subject: [Haskell-cafe] How to use Reader? Message-ID: Hi all, I think I'm pretty close but not quite there yet. Let's say I have the following: {-# LANGUAGE OverloadedStrings #-} module Main where import Prelude (IO) import Data.Text (Text, append) import Data.Text.IO (putStrLn) main :: IO () main = putStrLn (showText "Hello World!" config) where config :: Config config = Config (A "Boo") data A = A Text data Config = Config { a :: A } showText :: Text -> Config -> Text showText text config = "[" `append` text `append` (showA config) `append` "]" showA :: Config -> Text showA config = "'" `append` text `append` "'" where A text = a config Now I want to use Reader. This is as close as I can get: {-# LANGUAGE OverloadedStrings #-} module Main where import Prelude (IO, return, ($)) import Data.Text (Text, append) import Data.Text.IO (putStrLn) import Control.Monad.Reader (Reader, asks, runReader) main :: IO () main = putStrLn (runReader (showText "Hello World!") config) where config :: Config config = Config (A "Boo") data A = A Text data Config = Config { a :: A } showText :: Text -> Reader Config Text showText text = return $ "[" `append` text `append` showA `append` "]" showA :: Reader Config Text showA = do A text <- asks a return $ "'" `append` text `append` "'" This is almost correct, except for the showA invocation in showText. It wants a Text but it's getting a Reader Config Text. What is the magic to make this work? Cheers, Hilco From hilco.wijbenga at gmail.com Wed Jun 20 04:46:55 2018 From: hilco.wijbenga at gmail.com (Hilco Wijbenga) Date: Tue, 19 Jun 2018 21:46:55 -0700 Subject: [Haskell-cafe] How to use Reader? In-Reply-To: References: Message-ID: Ah, quite simple. Thanks! On Tue, Jun 19, 2018 at 9:39 PM, Matt wrote: > showText text = do > a <- showA > return ("[" `append` text `append` a `append` "]") > > > Matt Parsons > > On Tue, Jun 19, 2018 at 10:35 PM, Hilco Wijbenga > wrote: >> >> Hi all, >> >> I think I'm pretty close but not quite there yet. Let's say I have the >> following: >> >> {-# LANGUAGE OverloadedStrings #-} >> >> module Main where >> >> import Prelude (IO) >> import Data.Text (Text, append) >> import Data.Text.IO (putStrLn) >> >> main :: IO () >> main = >> putStrLn (showText "Hello World!" config) >> where >> config :: Config >> config = Config (A "Boo") >> >> data A = A Text >> >> data Config = Config { a :: A } >> >> showText :: Text -> Config -> Text >> showText text config = >> "[" `append` text `append` (showA config) `append` "]" >> >> showA :: Config -> Text >> showA config = >> "'" `append` text `append` "'" >> where >> A text = a config >> >> Now I want to use Reader. This is as close as I can get: >> >> {-# LANGUAGE OverloadedStrings #-} >> >> module Main where >> >> import Prelude (IO, return, ($)) >> import Data.Text (Text, append) >> import Data.Text.IO (putStrLn) >> import Control.Monad.Reader (Reader, asks, runReader) >> >> main :: IO () >> main = >> putStrLn (runReader (showText "Hello World!") config) >> where >> config :: Config >> config = Config (A "Boo") >> >> data A = A Text >> >> data Config = Config { a :: A } >> >> showText :: Text -> Reader Config Text >> showText text = >> return $ >> "[" `append` text `append` showA `append` "]" >> >> showA :: Reader Config Text >> showA = do >> A text <- asks a >> return $ >> "'" `append` text `append` "'" >> >> This is almost correct, except for the showA invocation in showText. >> It wants a Text but it's getting a Reader Config Text. What is the >> magic to make this work? >> >> Cheers, >> Hilco >> _______________________________________________ >> 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 aquagnu at gmail.com Wed Jun 20 07:16:30 2018 From: aquagnu at gmail.com (PY) Date: Wed, 20 Jun 2018 10:16:30 +0300 Subject: [Haskell-cafe] How to define CPP macro definition with stack? Message-ID: Hello all, I'm using conditional compilation: #ifdef BLAH   blahBlah   #endif And I want to define BLAH, but not in *.hs file. For example, with `stack` option or as environment variable... How can I do it? For example, `stack -DBLAH=1 build` or something else. I tried   stack build --flag='*:BLAH' - no effect. Also I tried   stack build --flag=my-library:BLAH and get error that my-library package does not define flag BLAH. So, it's total secret for me how to make such thing (like we can do with gcc, make, etc)  :-) === Best regards, Paul From aquagnu at gmail.com Wed Jun 20 07:57:06 2018 From: aquagnu at gmail.com (PY) Date: Wed, 20 Jun 2018 10:57:06 +0300 Subject: [Haskell-cafe] How to define CPP macro definition with stack? In-Reply-To: References: Message-ID: <88259e59-a5e0-91f4-41b1-020f80e1cf3a@gmail.com> Solution was found: https://stackoverflow.com/questions/48157516/conditional-compilation-in-haskell-submodule Question is closing :) 20.06.2018 10:16, PY wrote: > Hello all, > > I'm using conditional compilation: > > #ifdef BLAH >   blahBlah >   #endif > > And I want to define BLAH, but not in *.hs file. For example, with > `stack` option or as environment variable... How can I do it? For > example, `stack -DBLAH=1 build` or something else. > I tried > >   stack build --flag='*:BLAH' > > - no effect. > > Also I tried > >   stack build --flag=my-library:BLAH > > and get error that my-library package does not define flag BLAH. So, > it's total secret for me how to make such thing (like we can do with > gcc, make, etc)  :-) > > === > > Best regards, Paul > From vanessa.mchale at iohk.io Wed Jun 20 10:13:28 2018 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Wed, 20 Jun 2018 05:13:28 -0500 Subject: [Haskell-cafe] How to define CPP macro definition with stack? In-Reply-To: References: Message-ID: You'll need to change the `cpp-options` field in your .cabal file. You can do this conditionally by using a cabal flag. On 06/20/2018 02:16 AM, PY wrote: > Hello all, > > I'm using conditional compilation: > > #ifdef BLAH >   blahBlah >   #endif > > And I want to define BLAH, but not in *.hs file. For example, with > `stack` option or as environment variable... How can I do it? For > example, `stack -DBLAH=1 build` or something else. > I tried > >   stack build --flag='*:BLAH' > > - no effect. > > Also I tried > >   stack build --flag=my-library:BLAH > > and get error that my-library package does not define flag BLAH. So, > it's total secret for me how to make such thing (like we can do with > gcc, make, etc)  :-) > > === > > Best regards, Paul > > _______________________________________________ > 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: 488 bytes Desc: OpenPGP digital signature URL: From david.feuer at gmail.com Wed Jun 20 10:54:32 2018 From: david.feuer at gmail.com (David Feuer) Date: Wed, 20 Jun 2018 06:54:32 -0400 Subject: [Haskell-cafe] Memory leak in infinite recursion In-Reply-To: References: Message-ID: On Tue, Jun 19, 2018, 9:54 PM Dr.Koster wrote: > In general infinite monadic recursion will leak, since the tail position > is always >> or >>= instead of your own recursive function > That seems a bit strong. Monadic recursion *can* leak, but it need not. >>= is typically lazy in its second argument, so it can produce structure lazily. Consider the free monad, for example: data Free f a = Pure a | Wrap (f (Free f a)) instance Functor f => Monad (Free f) where Pure a >>= f = f a Wrap ff >>= f = Wrap $ fmap (>>= f) ff See how we can produce Wrap without using f? As long as the base functor isn't too large, this shouldn't leak. , but under certain situations, e.g. IO without arguments, the compiler > will figure there's no need to push new stack frame. But anyway it's better > to checkout yourself rather relying on some weak assumptions. > > 发自我的iPhone > > > ------------------ Original ------------------ > *From:* Никита Фуфаев > *Date:* Wed,Jun 20,2018 2:37 AM > *To:* haskell-cafe > *Subject:* Re: [Haskell-cafe] Memory leak in infinite recursion > > Hello everyone > > In C you can't implement main loop with recursion like > void mainLoop() { > doSomething(); > mainLoop(); > } > because without optimisations stack will overflow. > In haskell it's common to write > mainLoop = doSomething >> mainLoop, and it doesn't leak memory because of > haskell's evaluation model. > Does memory leak or argument stack overflow happen in this case? > mainLoop = doSomething >> mainLoop >> exit ExitSuccess > What about this case? > mainLoopModeA = do > doSomething > when condition mainLoopModeB > mainLoopModeA > mainLoopModeB = do > doSomethingElse > when anotherCondition mainLoopModeA > mainLoopModeB > > or this case? > mainLoopModeA = do > doSomething > if condition > then mainLoopModeB > else mainLoopModeA > mainLoopModeB = do > doSomethingElse > if anotherCondition > then mainLoopModeA > else mainLoopModeB > > -- > Nikita Fufaev > _______________________________________________ > 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 drkoster at qq.com Wed Jun 20 11:56:39 2018 From: drkoster at qq.com (winter) Date: Wed, 20 Jun 2018 19:56:39 +0800 Subject: [Haskell-cafe] Memory leak in infinite recursion In-Reply-To: References: Message-ID: +A5AD15E6340F72CB Well, Yes, If the consumer side consume the result properly (not getting in the way of GC),  a space leak could be avoided. On 2018年06月20日 18:54, David Feuer wrote: > On Tue, Jun 19, 2018, 9:54 PM Dr.Koster > wrote: > > In general infinite monadic recursion will leak, since the tail > position is always >> or >>= instead of your own recursive function > > > That seems a bit strong. Monadic recursion *can* leak, but it need > not. >>= is typically lazy in its second argument, so it can produce > structure lazily. Consider the free monad, for example: > > data Free f a = Pure a | Wrap (f (Free f a)) > > instance Functor f => Monad (Free f) where >   Pure a >>= f = f a >   Wrap ff >>= f = Wrap $ fmap (>>= f) ff > > See how we can produce Wrap without using f? As long as the base > functor isn't too large, this shouldn't leak. > > , but under certain situations, e.g. IO without arguments, the > compiler will figure there's no need to push new stack frame. But > anyway it's better to checkout yourself rather relying on some > weak assumptions. > > 发自我的iPhone > > > ------------------ Original ------------------ > *From:* Никита Фуфаев > > *Date:* Wed,Jun 20,2018 2:37 AM > *To:* haskell-cafe > > *Subject:* Re: [Haskell-cafe] Memory leak in infinite recursion > > Hello everyone > > In C you can't implement main loop with recursion like > void mainLoop() { >   doSomething(); >   mainLoop(); > } > because without optimisations stack will overflow. > In haskell it's common to write > mainLoop = doSomething >> mainLoop, and it doesn't leak memory > because of haskell's evaluation model. > Does memory leak or argument stack overflow happen in this case? > mainLoop = doSomething >> mainLoop >> exit ExitSuccess > What about this case? > mainLoopModeA = do >   doSomething >   when condition mainLoopModeB >   mainLoopModeA > mainLoopModeB = do >   doSomethingElse >   when anotherCondition mainLoopModeA >   mainLoopModeB > > or this case? > mainLoopModeA = do > doSomething > if condition >   then mainLoopModeB >   else mainLoopModeA > mainLoopModeB = do > doSomethingElse > if anotherCondition >   then mainLoopModeA >   else mainLoopModeB > > -- > Nikita Fufaev > _______________________________________________ > 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 aquagnu at gmail.com Wed Jun 20 12:43:57 2018 From: aquagnu at gmail.com (PY) Date: Wed, 20 Jun 2018 15:43:57 +0300 Subject: [Haskell-cafe] GHCi: how to load another file than .ghci ? Message-ID: <919c257f-e092-ec05-3071-560e257d3802@gmail.com> Hello, Cafe! If I have typical .ghci file, but it's called somefile.txt, how to call "stack exec ghci" to load and exec this "somefile.txt" (as it does with ".ghci" usual)? === Best regards, Paul From a.pelenitsyn at gmail.com Wed Jun 20 13:21:16 2018 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Wed, 20 Jun 2018 15:21:16 +0200 Subject: [Haskell-cafe] GHCi: how to load another file than .ghci ? In-Reply-To: <919c257f-e092-ec05-3071-560e257d3802@gmail.com> References: <919c257f-e092-ec05-3071-560e257d3802@gmail.com> Message-ID: Hello Paul, You can supply arguments for commands run by stack like this: stack exec CMD -- ARGS In your case the argument you're interested in is -ghci-script. So the answer is stack exec ghci -- -ghci-script path/to/somefile.txt -- Best wishes, Artem On Wed, 20 Jun 2018 at 14:44 PY wrote: > Hello, Cafe! If I have typical .ghci file, but it's called somefile.txt, > how to call "stack exec ghci" to load and exec this "somefile.txt" (as > it does with ".ghci" usual)? > > > === > > Best regards, Paul > > _______________________________________________ > 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 a.pelenitsyn at gmail.com Wed Jun 20 14:33:07 2018 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Wed, 20 Jun 2018 16:33:07 +0200 Subject: [Haskell-cafe] GHCi: how to load another file than .ghci ? In-Reply-To: <773d1b38-64ed-36a5-469c-ff7ec576e335@gmail.com> References: <919c257f-e092-ec05-3071-560e257d3802@gmail.com> <773d1b38-64ed-36a5-469c-ff7ec576e335@gmail.com> Message-ID: It worked for me on a dummy project, but I may miss something. Maybe, it is `stack ghci` you want to use, not `stack exec ghci`. But I wasn't able to convince stack to catch `-ghci-script` for some reason. My best bet was: stack ghci --ghci-options="-ghci-script ~/my-ghci" PS You probably want to reply not just to me but to the whole mailing-list, so that people know that your problem hasn't been resolved. -- Best, Artem On Wed, 20 Jun 2018 at 16:08 PY wrote: > strange, because result is different (I got a lot of errors about not > found modules, etc). > > 20.06.2018 16:21, Artem Pelenitsyn пишет: > > Hello Paul, > > You can supply arguments for commands run by stack like this: stack exec > CMD -- ARGS > In your case the argument you're interested in is -ghci-script. So the > answer is > > stack exec ghci -- -ghci-script path/to/somefile.txt > > -- > Best wishes, Artem > > > On Wed, 20 Jun 2018 at 14:44 PY wrote: > >> Hello, Cafe! If I have typical .ghci file, but it's called somefile.txt, >> how to call "stack exec ghci" to load and exec this "somefile.txt" (as >> it does with ".ghci" usual)? >> >> >> === >> >> Best regards, Paul >> >> _______________________________________________ >> 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 bulat.ziganshin at gmail.com Wed Jun 20 15:09:59 2018 From: bulat.ziganshin at gmail.com (Bulat Ziganshin) Date: Wed, 20 Jun 2018 18:09:59 +0300 Subject: [Haskell-cafe] Looking for simple C statements parser for Parsec, MegaParsec or Happy Message-ID: <465467626.20180620180959@gmail.com> Hello all, I develop a preprocessor transpiling subset of C statements into gcc _asm statements. For this project, I will be happy to reuse existing C statements parser written with any popular Haskell technology, or just start with some simple C subset parser in order to avoid redoing existing work. Unfortunately, so far I found grammars just for everything but C. And while I can start with Parsec grammars for Java/Go, it seems that MegaParsec now is better choice? I can quickly develop grammar for small C subset, but ready-to-use grammar for larger C subset will allow me to completely skip the development of C statement parser and focus on the meat of project - asm code generation. Eventually, it may turn into LLVM pass transpiling parts of C++ code, but for quick prototype, I prefer Haskell, especially if I can find ready-to-use parser. PS: It was the first time I ever asked at SO, but it turned out to be offtopic there: https://stackoverflow.com/questions/50949118/simple-c-grammar-for-haskell-parsec-megaparsec-or-happy -- Best regards, Bulat mailto:Bulat.Ziganshin at gmail.com From Andrew.Butterfield at scss.tcd.ie Wed Jun 20 15:23:27 2018 From: Andrew.Butterfield at scss.tcd.ie (Andrew Butterfield) Date: Wed, 20 Jun 2018 16:23:27 +0100 Subject: [Haskell-cafe] Looking for simple C statements parser for Parsec, MegaParsec or Happy In-Reply-To: <465467626.20180620180959@gmail.com> References: <465467626.20180620180959@gmail.com> Message-ID: <9EE784F6-B2D6-476A-86CA-CAEC54C6A933@scss.tcd.ie> Hi Bulat, will the c-language package do ? Its parser seems to be based on Happy? http://hackage.haskell.org/package/language-c-0.8.1/docs/Language-C-Parser.html Regards, Andrew > On 20 Jun 2018, at 16:09, Bulat Ziganshin wrote: > > Hello all, > > I develop a preprocessor transpiling subset of C statements into gcc > _asm statements. For this project, I will be happy to reuse existing C > statements parser written with any popular Haskell technology, or just > start with some simple C subset parser in order to avoid redoing > existing work. > > Unfortunately, so far I found grammars just for everything but C. And > while I can start with Parsec grammars for Java/Go, it seems that > MegaParsec now is better choice? > > I can quickly develop grammar for small C subset, but ready-to-use > grammar for larger C subset will allow me to completely skip the > development of C statement parser and focus on the meat of project - > asm code generation. > > Eventually, it may turn into LLVM pass transpiling parts of C++ code, > but for quick prototype, I prefer Haskell, especially if I can find > ready-to-use parser. > > PS: It was the first time I ever asked at SO, but it turned out > to be offtopic there: > https://stackoverflow.com/questions/50949118/simple-c-grammar-for-haskell-parsec-megaparsec-or-happy > > -- > Best regards, > Bulat mailto:Bulat.Ziganshin 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. -------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero at TCD, Head of Foundations & Methods Research Group School of Computer Science and Statistics, Room G.39, O'Reilly Institute, Trinity College, University of Dublin http://www.scss.tcd.ie/Andrew.Butterfield/ -------------------------------------------------------------------- -------------- next part -------------- An HTML attachment was scrubbed... URL: From bulat.ziganshin at gmail.com Wed Jun 20 15:58:08 2018 From: bulat.ziganshin at gmail.com (Bulat Ziganshin) Date: Wed, 20 Jun 2018 18:58:08 +0300 Subject: [Haskell-cafe] Looking for simple C statements parser for Parsec, MegaParsec or Happy In-Reply-To: <9EE784F6-B2D6-476A-86CA-CAEC54C6A933@scss.tcd.ie> References: <465467626.20180620180959@gmail.com> <9EE784F6-B2D6-476A-86CA-CAEC54C6A933@scss.tcd.ie> Message-ID: <1627027323.20180620185808@gmail.com> An HTML attachment was scrubbed... URL: From hilco.wijbenga at gmail.com Thu Jun 21 04:03:50 2018 From: hilco.wijbenga at gmail.com (Hilco Wijbenga) Date: Wed, 20 Jun 2018 21:03:50 -0700 Subject: [Haskell-cafe] How to use Reader? In-Reply-To: References: Message-ID: I'm not quite there yet. How can I create a fold over [Reader Config Text]? myFold :: [Reader Config Text] -> Reader Config Text (using `append` and "") I can easily handle [] and singleton but I'm lost when I get to longer lists. In any case, there must be a better way to do this. Maybe something with foldM? I tried implementing the more explicit [Config -> Text] -> (Config -> Text) but I didn't get any further. Can someone give me a hint? From jon.fairbairn at cl.cam.ac.uk Thu Jun 21 09:13:21 2018 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Thu, 21 Jun 2018 10:13:21 +0100 Subject: [Haskell-cafe] (New to Conduits) mixing lazy lists and Conduits? Message-ID: Suppose I’m writing some code using Conduits, but need to use some old function f::[a]->[b] (defined in a library somewhere) that transforms a lazy list. Is there a way of turning f into a Conduit without ending up with all of the list being in memory? ie something that looks like toConduit:: ([a]->[b]) -> ConduitT a b m () I’ve got nowhere with Hoogle or Hayoo -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From lysxia at gmail.com Thu Jun 21 10:30:21 2018 From: lysxia at gmail.com (Li-yao Xia) Date: Thu, 21 Jun 2018 06:30:21 -0400 Subject: [Haskell-cafe] (New to Conduits) mixing lazy lists and Conduits? In-Reply-To: References: Message-ID: <9254d1a1-3e47-005b-8083-fdda7a82f80b@gmail.com> On 06/21/2018 05:13 AM, Jon Fairbairn wrote: > > Suppose I’m writing some code using Conduits, but need to use > some old function f::[a]->[b] (defined in a library somewhere) > that transforms a lazy list. > > Is there a way of turning f into a Conduit without ending up > with all of the list being in memory? Constructing a list in such a streaming fashion only seems possible with unsafePerformIO trickery: define the input list lazily by reading a mutable reference, which gets populated whenever the conduit 'await's a new value. Li-yao From michael at snoyman.com Thu Jun 21 10:46:10 2018 From: michael at snoyman.com (Michael Snoyman) Date: Thu, 21 Jun 2018 13:46:10 +0300 Subject: [Haskell-cafe] (New to Conduits) mixing lazy lists and Conduits? In-Reply-To: References: Message-ID: You can use Data.Conduit.Lazy for this. https://www.stackage.org/haddock/lts-11.14/conduit-extra-1.3.0/Data-Conduit-Lazy.html On Thu, Jun 21, 2018, 12:13 PM Jon Fairbairn wrote: > > Suppose I’m writing some code using Conduits, but need to use > some old function f::[a]->[b] (defined in a library somewhere) > that transforms a lazy list. > > Is there a way of turning f into a Conduit without ending up > with all of the list being in memory? ie something that looks > like > > toConduit:: ([a]->[b]) -> ConduitT a b m () > > I’ve got nowhere with Hoogle or Hayoo > -- > Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk > > _______________________________________________ > 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 luke_lau at icloud.com Thu Jun 21 13:07:42 2018 From: luke_lau at icloud.com (Luke Lau) Date: Thu, 21 Jun 2018 14:07:42 +0100 Subject: [Haskell-cafe] Timeouts inside a ConduitParser Message-ID: I have a ConduitParser (a Sink with some parsing state) with a version of satisfy that can time out: satisfy :: MonadIO m => (a -> Bool) -> ConduitParser a m a satisfy pred = do tId <- liftIO myThreadId timeoutThread <- liftIO $ forkIO $ do threadDelay 1000000 throwTo tId TimeoutException x <- await liftIO $ killThread timeoutThread if pred x then return x else empty However I would rather not deal with the risks involved with handling concurrency myself and use a system library like System.Timeout: satisfy :: MonadIO m => (a -> Bool) -> ConduitParser a m a satisfy pred = do x <- timeout 1000000 await if pred x then return x else empty This doesn’t work though since I need to be able to both lift and unlift await from IO, and ConduitParser lies on top of ConduitT, which is one of the types of monads that UnliftIO cannot be an instance of . Are there any better approaches to this? -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Thu Jun 21 14:00:06 2018 From: michael at snoyman.com (Michael Snoyman) Date: Thu, 21 Jun 2018 17:00:06 +0300 Subject: [Haskell-cafe] Timeouts inside a ConduitParser In-Reply-To: References: Message-ID: Due to the coroutine-based nature of conduit, this kind of approach isn't possible. In short, when you're inside the `ConduitT` transformer, you cannot use `timeout` on a `ConduitT` action because you need to yield control of execution to a different coroutine. Instead, you should move the `timeout` call to _outside_ the `ConduitT` parts, e.g.: timeout foo $ runConduit $ src .| satisfy .| sink It seems like in this case, that kind of timeout usage is going to be too coarse-grained. I haven't used it personally, but the `stm-conduit` package probably has something in the direction you're looking for. Alternatively, I put together an example of how this might be done using some standard Haskell libraries like stm and async here: https://gist.github.com/snoyberg/7e5dd52109b03c8bf1aa8fe1a7e522b9 The basic idea is to have two sibling threads: one running the original source and writing its values to a queue, and another running the full conduit pipeline with a modified source that will time out on reads from that queue. On Thu, Jun 21, 2018 at 4:08 PM Luke Lau wrote: > I have a ConduitParser > (a > Sink with some parsing state) with a version of satisfy that can time out: > > satisfy :: MonadIO m => (a -> Bool) -> ConduitParser a m a > satisfy pred = do > tId <- liftIO myThreadId > timeoutThread <- liftIO $ forkIO $ do > threadDelay 1000000 > throwTo tId TimeoutException > x <- await > liftIO $ killThread timeoutThread > if pred x > then return x > else empty > > However I would rather not deal with the risks involved with handling > concurrency myself and use a system library like System.Timeout: > > satisfy :: MonadIO m => (a -> Bool) -> ConduitParser a m a > satisfy pred = do > x <- timeout 1000000 await > if pred x > then return x > else empty > > This doesn’t work though since I need to be able to both lift and unlift > await from IO, and ConduitParser lies on top of ConduitT, which is one of > the types of monads that UnliftIO cannot be an instance of > . Are there any better > approaches to this? > > > > _______________________________________________ > 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 a.pelenitsyn at gmail.com Thu Jun 21 15:29:11 2018 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Thu, 21 Jun 2018 17:29:11 +0200 Subject: [Haskell-cafe] Colored Haskell Listings in LaTeX Message-ID: Dear Cafe, In his recent Stitch manuscript, https://cs.brynmawr.edu/~rae/papers/2018/stitch/stitch.pdf Richard Eisenberg mentions that he uses lhs2TeX to typeset Haskell listings, but I'm not aware of the support for colors in lhs2TeX. Can anyone suggest how to get such a nice code highlighting (presumably with lhs2TeX). -- Best wishes, Artem -------------- next part -------------- An HTML attachment was scrubbed... URL: From ehaussecker at gmail.com Thu Jun 21 16:14:25 2018 From: ehaussecker at gmail.com (Enzo) Date: Thu, 21 Jun 2018 18:14:25 +0200 Subject: [Haskell-cafe] =?utf-8?q?dfinity-radix-tree=3A_A_Merkleized_key?= =?utf-8?q?=E2=80=93value_data_store=2E?= Message-ID: I am pleased to announce the first release of dfinity-radix-tree: A Merkleized key–value data store. The library provides a simple and easy to use data integrity layer for LevelDB. For more information, please see: [1] https://github.com/dfinity-lab/hs-radix-tree [2] https://hackage.haskell.org/package/dfinity-radix-tree Warm regards, Enzo Haussecker DFINITY Stiftung *We're hiring Haskell developers in Palo Alto and Zürich. Apply now:* [3] https://dfinity.org/openings -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg.grenrus at iki.fi Thu Jun 21 17:22:26 2018 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Thu, 21 Jun 2018 20:22:26 +0300 Subject: [Haskell-cafe] Colored Haskell Listings in LaTeX In-Reply-To: References: Message-ID: Hi Artem, I answer with inline lhs2Tex file. Hopefully it helps in your typed-code type-settings! cheers, Oleg. \documentclass{article} %include polycode.fmt \usepackage{hyperref} \hypersetup{pdfborder={0 0 0}} % in lhs2TeX.style there are % % \newcommand{\Conid}[1]{{\mathit #1}} % \newcommand{\Varid}[1]{{\mathit #1}} % \newcommand{\anonymous}{\_} % % We can renew these \usepackage{xcolor} \definecolor{darkred}{rgb}{.5,0,0} \definecolor{darkgreen}{rgb}{0,0.5,0} \definecolor{darkblue}{rgb}{0,0,.5} \definecolor{color4}{rgb}{0,.4,.4} \definecolor{color5}{rgb}{.4,.4,0} \renewcommand{\Conid}[1]{{\color{darkblue}\mathit #1}} % however types and constructors look the same, we can differentiate them though %format Foo = "{\color{darkred}\mathit Foo}" %format MkFoo = "{\color{darkgreen}\mathit Foo}" % Note how I "cheat" making MkFoo render as Foo! % We can also highlight operators %format + = "\mathbin{\color{color4}+}" % or symbols (note I also make thing look prettier)" %format plusFoo = "{\color{color5}\mathit plus_{Foo}}" %format ColorsInLhs2TeX = "{\text{Colors in lhs2\TeX}}" \begin{document} An example of colorful lhs2\TeX\ file. See the source at \url{https://github.com/phadej/gists/blob/master/posts/2018-06-21-colors-in-lhs2tex.tex}% \footnote{It's named tex to trick \emph{Pandoc} in my blog setup}, and the result PDF at \url{https://github.com/phadej/gists/blob/master/pdf/ColorsInLhs2TeX.pdf} \begin{code} module ColorsInLhs2TeX where newtype Foo = MkFoo Int plusFoo :: Foo -> Foo -> Int plusFoo (MkFoo n) (MkFoo m) = n + m \end{code} \end{document} On 21.06.2018 18:29, Artem Pelenitsyn wrote: > Dear Cafe, > > In his recent Stitch manuscript, > https://cs.brynmawr.edu/~rae/papers/2018/stitch/stitch.pdf > > Richard Eisenberg mentions that he uses lhs2TeX to typeset Haskell > listings, but I'm not aware of the support for colors in lhs2TeX. Can > anyone suggest how to get such a nice code highlighting (presumably > with lhs2TeX). > > -- > Best wishes, > Artem > > > _______________________________________________ > 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 a.pelenitsyn at gmail.com Thu Jun 21 21:20:36 2018 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Thu, 21 Jun 2018 23:20:36 +0200 Subject: [Haskell-cafe] Colored Haskell Listings in LaTeX In-Reply-To: References: Message-ID: Dear Oleg, Thanks for the reply! It works modulo line 24 where, it seems, your mail client broke the line which happened to be inside comment and that drives pdflatex mad. The gist is fine though, so I put the link here: https://github.com/phadej/gists/blob/master/posts/2018-06-21-colors-in-lhs2tex.tex Your answer shows the approach one could apply to tune the color of various lexical element. I wonder if there are prebaked set of definitions covering the whole (or most of) grammar: literals, comments, type variables… {- Obviously, RIchard has one :) -} -- Best, Artem On Thu, 21 Jun 2018 at 19:22 Oleg Grenrus wrote: > Hi Artem, > > I answer with inline lhs2Tex file. Hopefully it helps in your typed-code > type-settings! > > cheers, Oleg. > > \documentclass{article} > %include polycode.fmt > > \usepackage{hyperref} > \hypersetup{pdfborder={0 0 0}} > > % in lhs2TeX.style there are > % > % \newcommand{\Conid}[1]{{\mathit #1}} > % \newcommand{\Varid}[1]{{\mathit #1}} > % \newcommand{\anonymous}{\_} > % > % We can renew these > > \usepackage{xcolor} > \definecolor{darkred}{rgb}{.5,0,0} > \definecolor{darkgreen}{rgb}{0,0.5,0} > \definecolor{darkblue}{rgb}{0,0,.5} > \definecolor{color4}{rgb}{0,.4,.4} > \definecolor{color5}{rgb}{.4,.4,0} > > \renewcommand{\Conid}[1]{{\color{darkblue}\mathit #1}} > > % however types and constructors look the same, we can differentiate > them though > > %format Foo = "{\color{darkred}\mathit Foo}" > %format MkFoo = "{\color{darkgreen}\mathit Foo}" > > % Note how I "cheat" making MkFoo render as Foo! > > % We can also highlight operators > %format + = "\mathbin{\color{color4}+}" > > % or symbols (note I also make thing look prettier)" > %format plusFoo = "{\color{color5}\mathit plus_{Foo}}" > %format ColorsInLhs2TeX = "{\text{Colors in lhs2\TeX}}" > > \begin{document} > > An example of colorful lhs2\TeX\ file. > See the source at > \url{ > https://github.com/phadej/gists/blob/master/posts/2018-06-21-colors-in-lhs2tex.tex}% > \footnote{It's named tex to trick \emph{Pandoc} in my blog setup}, > and the result PDF at > \url{https://github.com/phadej/gists/blob/master/pdf/ColorsInLhs2TeX.pdf} > > \begin{code} > module ColorsInLhs2TeX where > > newtype Foo = MkFoo Int > > plusFoo :: Foo -> Foo -> Int > plusFoo (MkFoo n) (MkFoo m) = n + m > \end{code} > \end{document} > > > On 21.06.2018 18:29, Artem Pelenitsyn wrote: > > Dear Cafe, > > > > In his recent Stitch manuscript, > > https://cs.brynmawr.edu/~rae/papers/2018/stitch/stitch.pdf > > > > Richard Eisenberg mentions that he uses lhs2TeX to typeset Haskell > > listings, but I'm not aware of the support for colors in lhs2TeX. Can > > anyone suggest how to get such a nice code highlighting (presumably > > with lhs2TeX). > > > > -- > > Best wishes, > > Artem > > > > > > _______________________________________________ > > 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 ben.franksen at online.de Fri Jun 22 10:46:06 2018 From: ben.franksen at online.de (Benjamin Franksen) Date: Fri, 22 Jun 2018 12:46:06 +0200 Subject: [Haskell-cafe] Type level seq Message-ID: I have observed that type functions seem to be lazy. A type function that is partial does not give me a type error when it is called with an argument for which it is not defined. Is there a 'seq' at the type level? Here is my use case, simplified of course. Suppose we want to statically track the state of a switch with a phantom type parameter: > {-# LANGUAGE DataKinds, TypeFamilies #-} > > data State (s :: Bool) = State Bool deriving Show > > off :: State False > off = State False We want user code to be able to call the function 'turnOff' only if the switch is currently on: > turnOff :: State True -> State False > turnOff (State True) = State False This works fine: *Main> turnOff off :1:9: error: ? Couldn't match type ?'False? with ?'True? Expected type: State 'True Actual type: State 'False But now I want to abstract this pattern and write a (closed) type function > type family TurnOff s where > TurnOff True = False > turnOff' :: State x -> State (TurnOff x) > turnOff' (State True) = State False > bad = turnOff' off *Main> :t bad bad :: State (TurnOff 'False) *Main> bad *** Exception: TypeLevelSeq.lhs:37:3-37: Non-exhaustive patterns in function turnOff' From k-bx at k-bx.com Fri Jun 22 13:03:43 2018 From: k-bx at k-bx.com (Kostiantyn Rybnikov) Date: Fri, 22 Jun 2018 16:03:43 +0300 Subject: [Haskell-cafe] Call for a maintainer of protocol-buffers Message-ID: Hey everyone, I'm looking for a person who would become the major maintainer of the protocol-buffers package. Details here: https://github.com/k-bx/protocol-buffers/issues/64 Please comment on the issue or send me an email if you'd like to apply. Thank you -------------- next part -------------- An HTML attachment was scrubbed... URL: From a.pelenitsyn at gmail.com Fri Jun 22 18:22:56 2018 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Fri, 22 Jun 2018 20:22:56 +0200 Subject: [Haskell-cafe] Type level seq In-Reply-To: References: Message-ID: Dear Benjamin, I'm not sure I quite get your problem. My guess: you want a type-level guarantee that `turnOff'` function will only be applied to the terms of type `State True`, and so, you expect a compile-time error from `turnOff' off`. Am I get it right? In your solution you seem to over engineer the solution. You try to relate type-level informaton (the value of of the type parameter `s` of `State`) to the term-level one (the value of the field stored in the `State` datatype). I think you'd better read how this task is solved with the technique known as singletons ( https://cs.brynmawr.edu/~rae/papers/2012/singletons/paper.pdf). But I bet you don't need to solve that task to just address the problem at hand, if I understand the problem correctly. Please, tell me if the simpler solution below suits you: it doesn't use term-level (field of State) information at all. {-# LANGUAGE DataKinds, TypeFamilies #-} data State (s :: Bool) = State deriving Show off :: State False off = State type family TurnOff s where TurnOff True = False turnOff :: State True -> State False turnOff State = State bad = turnOff off -- <-- error: Couldn't match type ‘'False’ with ‘'True’ main = print bad https://ideone.com/boWN1q -- Best, Artem On Fri, 22 Jun 2018 at 12:46 Benjamin Franksen wrote: > I have observed that type functions seem to be lazy. A type function > that is partial does not give me a type error when it is called with an > argument for which it is not defined. > > Is there a 'seq' at the type level? > > Here is my use case, simplified of course. Suppose we want to statically > track the state of a switch with a phantom type parameter: > > > {-# LANGUAGE DataKinds, TypeFamilies #-} > > > > data State (s :: Bool) = State Bool deriving Show > > > > off :: State False > > off = State False > > We want user code to be able to call the function 'turnOff' only if the > switch is currently on: > > > turnOff :: State True -> State False > > turnOff (State True) = State False > > This works fine: > > *Main> turnOff off > > :1:9: error: > ? Couldn't match type ?'False? with ?'True? > Expected type: State 'True > Actual type: State 'False > > But now I want to abstract this pattern and write a (closed) type function > > > type family TurnOff s where > > TurnOff True = False > > > turnOff' :: State x -> State (TurnOff x) > > turnOff' (State True) = State False > > > bad = turnOff' off > > *Main> :t bad > bad :: State (TurnOff 'False) > *Main> bad > *** Exception: TypeLevelSeq.lhs:37:3-37: Non-exhaustive patterns in > function turnOff' > > _______________________________________________ > 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 parsonsmatt at gmail.com Fri Jun 22 18:40:46 2018 From: parsonsmatt at gmail.com (Matt) Date: Fri, 22 Jun 2018 12:40:46 -0600 Subject: [Haskell-cafe] Type level seq In-Reply-To: References: Message-ID: Haskell's type families are strict -- they evaluate (or, try to evaluate) all of their arguments before they compute the result. When a type family doesn't have a matching equation, it is "stuck", and GHC just carries the applied type family around. This can be pretty confusing. If you want a type family to work on defined cases, and error otherwise, you must write a manual TypeError message: type family TurnOff (s :: Bool) where TurnOff True = False TurnOff _ = TypeError (Text "You tried to use TurnOff with False, but it can only be used with True.") Where TypError etc comes from `GHC.TypeLits` Matt Parsons On Fri, Jun 22, 2018 at 12:22 PM, Artem Pelenitsyn wrote: > Dear Benjamin, > > I'm not sure I quite get your problem. My guess: you want a type-level > guarantee that `turnOff'` function will only be applied to the terms of > type `State True`, and so, you expect a compile-time error from `turnOff' > off`. Am I get it right? > > In your solution you seem to over engineer the solution. You try to relate > type-level informaton (the value of of the type parameter `s` of `State`) > to the term-level one (the value of the field stored in the `State` > datatype). I think you'd better read how this task is solved with the > technique known as singletons (https://cs.brynmawr.edu/~rae/ > papers/2012/singletons/paper.pdf). > > But I bet you don't need to solve that task to just address the problem at > hand, if I understand the problem correctly. Please, tell me if the simpler > solution below suits you: it doesn't use term-level (field of State) > information at all. > > {-# LANGUAGE DataKinds, TypeFamilies #-} > > data State (s :: Bool) = State deriving Show > > off :: State False > off = State > > type family TurnOff s where > TurnOff True = False > > turnOff :: State True -> State False > turnOff State = State > > bad = turnOff off -- <-- error: Couldn't match type ‘'False’ with ‘'True’ > > main = print bad > https://ideone.com/boWN1q > > -- > Best, Artem > > > > On Fri, 22 Jun 2018 at 12:46 Benjamin Franksen > wrote: > >> I have observed that type functions seem to be lazy. A type function >> that is partial does not give me a type error when it is called with an >> argument for which it is not defined. >> >> Is there a 'seq' at the type level? >> >> Here is my use case, simplified of course. Suppose we want to statically >> track the state of a switch with a phantom type parameter: >> >> > {-# LANGUAGE DataKinds, TypeFamilies #-} >> > >> > data State (s :: Bool) = State Bool deriving Show >> > >> > off :: State False >> > off = State False >> >> We want user code to be able to call the function 'turnOff' only if the >> switch is currently on: >> >> > turnOff :: State True -> State False >> > turnOff (State True) = State False >> >> This works fine: >> >> *Main> turnOff off >> >> :1:9: error: >> ? Couldn't match type ?'False? with ?'True? >> Expected type: State 'True >> Actual type: State 'False >> >> But now I want to abstract this pattern and write a (closed) type function >> >> > type family TurnOff s where >> > TurnOff True = False >> >> > turnOff' :: State x -> State (TurnOff x) >> > turnOff' (State True) = State False >> >> > bad = turnOff' off >> >> *Main> :t bad >> bad :: State (TurnOff 'False) >> *Main> bad >> *** Exception: TypeLevelSeq.lhs:37:3-37: Non-exhaustive patterns in >> function turnOff' >> >> _______________________________________________ >> 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 ben.franksen at online.de Fri Jun 22 20:21:31 2018 From: ben.franksen at online.de (Benjamin Franksen) Date: Fri, 22 Jun 2018 22:21:31 +0200 Subject: [Haskell-cafe] Type level seq In-Reply-To: References: Message-ID: On 06/22/2018 08:40 PM, Matt wrote: > Haskell's type families are strict -- they evaluate (or, try to evaluate) > all of their arguments before they compute the result. When a type family > doesn't have a matching equation, it is "stuck", and GHC just carries the > applied type family around. This can be pretty confusing. > > If you want a type family to work on defined cases, and error otherwise, > you must write a manual TypeError message: > > type family TurnOff (s :: Bool) where > TurnOff True = False > TurnOff _ = TypeError (Text "You tried to use TurnOff with False, but it > can only be used with True.") > > Where TypError etc comes from `GHC.TypeLits` Thanks! That was exactly the missing piece. Cheers Ben From rae at cs.brynmawr.edu Sat Jun 23 03:06:01 2018 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Fri, 22 Jun 2018 23:06:01 -0400 Subject: [Haskell-cafe] Type level seq In-Reply-To: References: Message-ID: <55CB3BFF-667E-43FD-8363-107071AB037C@cs.brynmawr.edu> On Jun 22, 2018, at 2:40 PM, Matt wrote: > Haskell's type families are strict Not quite. Haskell's type families have no specific order of operation, at all. Here's a telling example: > data Nat = Zero | Succ Nat > > type family Inf where > Inf = Succ Inf > > type family F a b where > F True x = Int > F False x = Char > > type family Not a where > Not True = False > Not False = True > > x :: F True Inf > x = 5 > > y :: F False Inf > y = 'a' > > z :: F (Not False) Inf > z = 42 Any attempt to evaluate Inf will cause GHC's evaluation stack to overflow and will result in an error. But x and y are accepted, because GHC can reduce F right away. z, on the other hand, causes this stack overflow, because GHC needs to reduce arguments in order to reduce F. GHC is not clever enough to notice that it needs to reduce only the first argument. This is silly, but it's unclear how to performantly do better. Richard From rae at cs.brynmawr.edu Sat Jun 23 03:32:22 2018 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Fri, 22 Jun 2018 23:32:22 -0400 Subject: [Haskell-cafe] Colored Haskell Listings in LaTeX In-Reply-To: References: Message-ID: The source code for my thesis is public, and it includes this file: https://github.com/goldfirere/thesis/blob/master/tex/rae.fmt But there weren't colors in my thesis. (Or, at least, the code wasn't syntax highlighted with colors.) These days, I use that fmt file with these definitions in the tex file: > \newcommand{\keyword}[1]{\textcolor{BlueViolet}{\textbf{#1}}} > \newcommand{\id}[1]{\textsf{\textsl{#1}}} > \newcommand{\varid}[1]{\textcolor{Sepia}{\id{#1}}} > \newcommand{\conid}[1]{\textcolor{OliveGreen}{\id{#1}}} I hope this is helpful! Richard > On Jun 21, 2018, at 5:20 PM, Artem Pelenitsyn wrote: > > Dear Oleg, > > Thanks for the reply! It works modulo line 24 where, it seems, your mail client broke the line which happened to be inside comment and that drives pdflatex mad. The gist is fine though, so I put the link here: > https://github.com/phadej/gists/blob/master/posts/2018-06-21-colors-in-lhs2tex.tex > > Your answer shows the approach one could apply to tune the color of various lexical element. I wonder if there are prebaked set of definitions covering the whole (or most of) grammar: literals, comments, type variables… {- Obviously, RIchard has one :) -} > > -- > Best, Artem > > On Thu, 21 Jun 2018 at 19:22 Oleg Grenrus > wrote: > Hi Artem, > > I answer with inline lhs2Tex file. Hopefully it helps in your typed-code > type-settings! > > cheers, Oleg. > > \documentclass{article} > %include polycode.fmt > > \usepackage{hyperref} > \hypersetup{pdfborder={0 0 0}} > > % in lhs2TeX.style there are > % > % \newcommand{\Conid}[1]{{\mathit #1}} > % \newcommand{\Varid}[1]{{\mathit #1}} > % \newcommand{\anonymous}{\_} > % > % We can renew these > > \usepackage{xcolor} > \definecolor{darkred}{rgb}{.5,0,0} > \definecolor{darkgreen}{rgb}{0,0.5,0} > \definecolor{darkblue}{rgb}{0,0,.5} > \definecolor{color4}{rgb}{0,.4,.4} > \definecolor{color5}{rgb}{.4,.4,0} > > \renewcommand{\Conid}[1]{{\color{darkblue}\mathit #1}} > > % however types and constructors look the same, we can differentiate > them though > > %format Foo = "{\color{darkred}\mathit Foo}" > %format MkFoo = "{\color{darkgreen}\mathit Foo}" > > % Note how I "cheat" making MkFoo render as Foo! > > % We can also highlight operators > %format + = "\mathbin{\color{color4}+}" > > % or symbols (note I also make thing look prettier)" > %format plusFoo = "{\color{color5}\mathit plus_{Foo}}" > %format ColorsInLhs2TeX = "{\text{Colors in lhs2\TeX}}" > > \begin{document} > > An example of colorful lhs2\TeX\ file. > See the source at > \url{https://github.com/phadej/gists/blob/master/posts/2018-06-21-colors-in-lhs2tex.tex}% > \footnote{It's named tex to trick \emph{Pandoc} in my blog setup}, > and the result PDF at > \url{https://github.com/phadej/gists/blob/master/pdf/ColorsInLhs2TeX.pdf } > > \begin{code} > module ColorsInLhs2TeX where > > newtype Foo = MkFoo Int > > plusFoo :: Foo -> Foo -> Int > plusFoo (MkFoo n) (MkFoo m) = n + m > \end{code} > \end{document} > > > On 21.06.2018 18:29, Artem Pelenitsyn wrote: > > Dear Cafe, > > > > In his recent Stitch manuscript, > > https://cs.brynmawr.edu/~rae/papers/2018/stitch/stitch.pdf > > > > > Richard Eisenberg mentions that he uses lhs2TeX to typeset Haskell > > listings, but I'm not aware of the support for colors in lhs2TeX. Can > > anyone suggest how to get such a nice code highlighting (presumably > > with lhs2TeX). > > > > -- > > Best wishes, > > Artem > > > > > > _______________________________________________ > > 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 a.pelenitsyn at gmail.com Sat Jun 23 11:29:58 2018 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Sat, 23 Jun 2018 13:29:58 +0200 Subject: [Haskell-cafe] Colored Haskell Listings in LaTeX In-Reply-To: References: Message-ID: Thanks, RIchard! I talked about your Stitch paper, not the thesis. But thanks for the reference: the %format things from there are also useful to me. The newcommands you gave almost worked for me. There are a couple of points: - newcommand{\varid} → \renewcommand{\Varid}, and the same for conid (thanks to Oleg again, for leading me to that); otherwise it does nothing; - keyword: again, it does nothing to me as is given; I wasn't able to find TeX'y way to do that, so I went to %subst: %subst keyword a = "\textcolor{BlueViolet}{\textbf{" a "}}" The resulting minimal-working-example is on this gist: https://gist.github.com/ulysses4ever/c2374d35326b8644e27d0018b12d8ae3 Still, I would be happy to look at the whole preamble of Stitch: I believe, there could be something more to steal :) -- Best wishes, Artem On Sat, 23 Jun 2018 at 05:32 Richard Eisenberg wrote: > The source code for my thesis is public, and it includes this file: > https://github.com/goldfirere/thesis/blob/master/tex/rae.fmt > > But there weren't colors in my thesis. (Or, at least, the code wasn't > syntax highlighted with colors.) > > These days, I use that fmt file with these definitions in the tex file: > > \newcommand{\keyword}[1]{\textcolor{BlueViolet}{\textbf{#1}}} > \newcommand{\id}[1]{\textsf{\textsl{#1}}} > \newcommand{\varid}[1]{\textcolor{Sepia}{\id{#1}}} > \newcommand{\conid}[1]{\textcolor{OliveGreen}{\id{#1}}} > > > I hope this is helpful! > Richard > > On Jun 21, 2018, at 5:20 PM, Artem Pelenitsyn > wrote: > > Dear Oleg, > > Thanks for the reply! It works modulo line 24 where, it seems, your mail > client broke the line which happened to be inside comment and that drives > pdflatex mad. The gist is fine though, so I put the link here: > > https://github.com/phadej/gists/blob/master/posts/2018-06-21-colors-in-lhs2tex.tex > > Your answer shows the approach one could apply to tune the color of > various lexical element. I wonder if there are prebaked set of definitions > covering the whole (or most of) grammar: literals, comments, type > variables… {- Obviously, RIchard has one :) -} > > -- > Best, Artem > > On Thu, 21 Jun 2018 at 19:22 Oleg Grenrus wrote: > >> Hi Artem, >> >> I answer with inline lhs2Tex file. Hopefully it helps in your typed-code >> type-settings! >> >> cheers, Oleg. >> >> \documentclass{article} >> %include polycode.fmt >> >> \usepackage{hyperref} >> \hypersetup{pdfborder={0 0 0}} >> >> % in lhs2TeX.style there are >> % >> % \newcommand{\Conid}[1]{{\mathit #1}} >> % \newcommand{\Varid}[1]{{\mathit #1}} >> % \newcommand{\anonymous}{\_} >> % >> % We can renew these >> >> \usepackage{xcolor} >> \definecolor{darkred}{rgb}{.5,0,0} >> \definecolor{darkgreen}{rgb}{0,0.5,0} >> \definecolor{darkblue}{rgb}{0,0,.5} >> \definecolor{color4}{rgb}{0,.4,.4} >> \definecolor{color5}{rgb}{.4,.4,0} >> >> \renewcommand{\Conid}[1]{{\color{darkblue}\mathit #1}} >> >> % however types and constructors look the same, we can differentiate >> them though >> >> %format Foo = "{\color{darkred}\mathit Foo}" >> %format MkFoo = "{\color{darkgreen}\mathit Foo}" >> >> % Note how I "cheat" making MkFoo render as Foo! >> >> % We can also highlight operators >> %format + = "\mathbin{\color{color4}+}" >> >> % or symbols (note I also make thing look prettier)" >> %format plusFoo = "{\color{color5}\mathit plus_{Foo}}" >> %format ColorsInLhs2TeX = "{\text{Colors in lhs2\TeX}}" >> >> \begin{document} >> >> An example of colorful lhs2\TeX\ file. >> See the source at >> \url{ >> https://github.com/phadej/gists/blob/master/posts/2018-06-21-colors-in-lhs2tex.tex}% >> \footnote{It's named tex to trick \emph{Pandoc} in my blog setup}, >> and the result PDF at >> \url{https://github.com/phadej/gists/blob/master/pdf/ColorsInLhs2TeX.pdf} >> >> \begin{code} >> module ColorsInLhs2TeX where >> >> newtype Foo = MkFoo Int >> >> plusFoo :: Foo -> Foo -> Int >> plusFoo (MkFoo n) (MkFoo m) = n + m >> \end{code} >> \end{document} >> >> >> On 21.06.2018 18:29, Artem Pelenitsyn wrote: >> > Dear Cafe, >> > >> > In his recent Stitch manuscript, >> > https://cs.brynmawr.edu/~rae/papers/2018/stitch/stitch.pdf >> > >> > Richard Eisenberg mentions that he uses lhs2TeX to typeset Haskell >> > listings, but I'm not aware of the support for colors in lhs2TeX. Can >> > anyone suggest how to get such a nice code highlighting (presumably >> > with lhs2TeX). >> > >> > -- >> > Best wishes, >> > Artem >> > >> > >> > _______________________________________________ >> > 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 leah at vuxu.org Sat Jun 23 16:49:08 2018 From: leah at vuxu.org (Leah Neukirchen) Date: Sat, 23 Jun 2018 18:49:08 +0200 Subject: [Haskell-cafe] Munich Haskell Meeting, 2018-06-26 @ 19:30 Message-ID: <8736xdwirf.fsf@vuxu.org> Dear all, Next week, our monthly Munich Haskell Meeting will take place again on Tuesday, June 26 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-jun-2018/ Everybody is welcome! cu, -- Leah Neukirchen http://leah.zone From evan at evanrutledgeborden.dreamhosters.com Sun Jun 24 00:10:10 2018 From: evan at evanrutledgeborden.dreamhosters.com (evan@evan-borden.com) Date: Sat, 23 Jun 2018 20:10:10 -0400 Subject: [Haskell-cafe] ANN: network-2.7.0.1 Message-ID: Announcing network-2.7.0.1 * A new API: socketPortSafe. [#319](https://github.com/haskell/network/pull/319) * Fixing a drain bug of sendAll. [#320](https://github.com/haskell/network/pull/320) * Porting the new CALLCONV convention from master. [#313](https://github.com/haskell/network/pull/313) * Withdrawing the deprecations of packFamily and unpackFamily. [#324](https://github.com/haskell/network/pull/324) Thank you to network contributors for bug reports in the push to 3.0.0.0. As well as the continued effort to increase windows reliability and support. -- Evan Borden -------------- next part -------------- An HTML attachment was scrubbed... URL: From kei at lanl.gov Mon Jun 25 22:13:11 2018 From: kei at lanl.gov (Kei Davis) Date: Mon, 25 Jun 2018 16:13:11 -0600 Subject: [Haskell-cafe] Call for Presentations and Demonstrations: Workshop on Functional High-Performance Computing 2018 at ICFP Message-ID: <3fbc746b-bfdd-8f70-b038-bd64b5a6402d@lanl.gov> 7th ACM SIGPLAN Workshop on Functional High-Performance Computing September 29, 2018, St. Louis, Missouri, USA https://icfp18.sigplan.org/track/FHPC-2018-papers The 7th ACM SIGPLAN Workshop on Functional High-Performance Computing (FHPC 2018) is being held as in previous years in conjunction with the International Conference on Functional Programming (ICFP 2018) together with numerous other workshops/symposia, and as a first, colocated with Strange Loop, in St. Louis, MO, USA. Workshop Objectives The FHPC 2018 workshop seeks to bring together researchers and practitioners exploring uses of functional (or more generally, declarative or high-level) programming systems or concepts in application domains where high performance is essential. The aim of the meeting is to enable sharing of results, experiences, and novel ideas about how high-level, declarative specifications of computationally challenging problems can serve as maintainable and portable code that approaches (or even exceeds) the performance of machine-oriented (low-level) imperative implementations. All aspects of performance-critical programming and parallel programming are in scope for the workshop, irrespective of hardware target. This includes both traditional large-scale distributed-memory scientific computing (HPC), as well as work targeting single node systems with SMPs, GPUs, FPGAs, or embedded processors. FHPC 2018 seeks to encourage a range of submissions, focusing on work in progress and facilitating early exchange of ideas and open discussion on innovative and/or emerging results. Original research, experience reports, case studies, and evaluations of programming systems are all welcome. Work on incorporation of functional programming concepts into more traditional (imperative) HPC applications is explicitly solicited. Papers, Presentations, and Demonstrations The refereed paper deadline has passed. In the workshop spirit, the refereed paper presentation program is being augmented to include less formally reviewed presentations in the form of talks not based on accepted papers, and software demonstrations. Topic areas of interest include research or development in progress, experience reports, and position/white paper statements. Proposals will be subject to a mild reviewing process to insure relevance and general interest to FHPC. We expect time slots to be between one-half and one hour. Prospective presenters are requested to submit an abstract describing their proposed contribution via the paper submission site. The deadline is July 29, 2018, midnight anywhere on Earth, but the PC reserves the right to accept proposals at any time after submission. As such, early submission is strongly encouraged. Important Dates - Submission Deadline: Midnight July 29, 2018 Anywhere on Earth. - Notification: early-mid August (TBD) - FHPC 2018: Saturday Sept. 29, 2018. Official website, submissions, registration details https://icfp18.sigplan.org/track/FHPC-2018-papers Previous FHPC websites https://icfp17.sigplan.org/track/FHPC-2017-papers https://sites.google.com/site/fhpcworkshops/ ICFP and related workshops https://conf.researchr.org/home/icfp-2018 https://icfp18.sigplan.org Strange Loop https://www.thestrangeloop.com/ Questions or comments? fhpc18 at gmail.com From dennis.raddle at gmail.com Thu Jun 28 05:22:46 2018 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Wed, 27 Jun 2018 22:22:46 -0700 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads Message-ID: I'm writing a program with several functions, some of which depend on certain fields in a state monad, others of which depend on others, but no routine needs all the fields. So I thought I would declare a two classes, one for each type of data need that a function has: -- as an aside, here's an example of data which is parameterized by two types. data ReportData t1 t2 = ... -- this is rolling my own state monad with a random generator class Monad m => RandMonad m where getGen :: m StdGen putGen :: StdGen -> () -- this is a class of state monad which logs ReportData: class Monad m => LogMonad m where putReport :: ReportData t1 t2 -> m () For a particular use case, I declare a type of State monad: data MyStateData t1 t2 = MyStateData t1 t2 { theGen :: StdGen , theReports :: [StepReport t1 t2] } type MyState t1 t2 = State (MyStateData t1 t2) And I try to define my instances: instance RandMonad (MyState t1 t2) where getGen = gets theGen putGen g = modify (\s -> s { theGen = g}) instance LogMonad (MyState t1 t2) where putReport r = modify (\s -> s { theReports = r : theReports s}) I get an error on the LogMonad instance, saying that there's no instance for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) Identity)) I guess I don't really understand typeclasses once you start using higher kinded types, so please enlighten me. Any reading on this subject would be helpful, too. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Thu Jun 28 05:41:44 2018 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 28 Jun 2018 06:41:44 +0100 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: References: Message-ID: <20180628054144.tbrv6k3uklu2fldo@weber> Your sample code has a few bugs which make it not compile, for example the following is not valid syntax data MyStateData t1 t2 = MyStateData t1 t2 { theGen :: StdGen , theReports :: [StepReport t1 t2] } and you use "StepReport" when I think you mean "ReportData". Could you post a version which is completely working besides the error you are trying to solve? Otherwise it's rather hard to help. Tom On Wed, Jun 27, 2018 at 10:22:46PM -0700, Dennis Raddle wrote: > I'm writing a program with several functions, some of which depend on > certain fields in a state monad, others of which depend on others, but no > routine needs all the fields. > > So I thought I would declare a two classes, one for each type of data need > that a function has: > > -- as an aside, here's an example of data which is parameterized by two > types. > > data ReportData t1 t2 = ... > > -- this is rolling my own state monad with a random generator > class Monad m => RandMonad m where > getGen :: m StdGen > putGen :: StdGen -> () > > -- this is a class of state monad which logs ReportData: > > class Monad m => LogMonad m where > putReport :: ReportData t1 t2 -> m () > > For a particular use case, I declare a type of State monad: > > data MyStateData t1 t2 = MyStateData t1 t2 > { theGen :: StdGen > , theReports :: [StepReport t1 t2] > } > > type MyState t1 t2 = State (MyStateData t1 t2) > > And I try to define my instances: > > instance RandMonad (MyState t1 t2) where > getGen = gets theGen > putGen g = modify (\s -> s { theGen = g}) > > instance LogMonad (MyState t1 t2) where > putReport r = modify (\s -> s { theReports = r : theReports s}) > > I get an error on the LogMonad instance, saying that there's no instance > for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) Identity)) > > I guess I don't really understand typeclasses once you start using higher > kinded types, so please enlighten me. Any reading on this subject would be > helpful, too. > _______________________________________________ > 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 dennis.raddle at gmail.com Thu Jun 28 05:43:52 2018 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Wed, 27 Jun 2018 22:43:52 -0700 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: <20180628054144.tbrv6k3uklu2fldo@weber> References: <20180628054144.tbrv6k3uklu2fldo@weber> Message-ID: okay, will do. It has a lot of details that aren't really necessary to ask the question, but now that I think about it, all that's required of you is to download and try to compile it. D On Wed, Jun 27, 2018 at 10:41 PM, Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > Your sample code has a few bugs which make it not compile, for example the > following is not valid syntax > > data MyStateData t1 t2 = MyStateData t1 t2 > { theGen :: StdGen > , theReports :: [StepReport t1 t2] > } > > and you use "StepReport" when I think you mean "ReportData". Could you > post > a version which is completely working besides the error you are trying to > solve? Otherwise it's rather hard to help. > > Tom > > > On Wed, Jun 27, 2018 at 10:22:46PM -0700, Dennis Raddle wrote: > > I'm writing a program with several functions, some of which depend on > > certain fields in a state monad, others of which depend on others, but no > > routine needs all the fields. > > > > So I thought I would declare a two classes, one for each type of data > need > > that a function has: > > > > -- as an aside, here's an example of data which is parameterized by two > > types. > > > > data ReportData t1 t2 = ... > > > > -- this is rolling my own state monad with a random generator > > class Monad m => RandMonad m where > > getGen :: m StdGen > > putGen :: StdGen -> () > > > > -- this is a class of state monad which logs ReportData: > > > > class Monad m => LogMonad m where > > putReport :: ReportData t1 t2 -> m () > > > > For a particular use case, I declare a type of State monad: > > > > data MyStateData t1 t2 = MyStateData t1 t2 > > { theGen :: StdGen > > , theReports :: [StepReport t1 t2] > > } > > > > type MyState t1 t2 = State (MyStateData t1 t2) > > > > And I try to define my instances: > > > > instance RandMonad (MyState t1 t2) where > > getGen = gets theGen > > putGen g = modify (\s -> s { theGen = g}) > > > > instance LogMonad (MyState t1 t2) where > > putReport r = modify (\s -> s { theReports = r : theReports s}) > > > > I get an error on the LogMonad instance, saying that there's no instance > > for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) Identity)) > > > > I guess I don't really understand typeclasses once you start using higher > > kinded types, so please enlighten me. Any reading on this subject would > be > > helpful, too. > > > _______________________________________________ > > 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 dennis.raddle at gmail.com Thu Jun 28 05:54:02 2018 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Wed, 27 Jun 2018 22:54:02 -0700 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: References: <20180628054144.tbrv6k3uklu2fldo@weber> Message-ID: I created a minimal example of what I'm trying to do --- in fact, I think this will be better than what I wrote in the first place --- but now I'm baffled by a different error entirely, which is some identifiers not in scope. I'm going to post this anyway, because I suspect the error is related to what the compiler can infer about my instance, which is something I need to understand better. Once you get past that error, either it will be working (yay!) or you'll encounter the error about no instance for MonadState which was my original problem. {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-} import Control.Monad.State import System.Random data ReportData t1 t2 = ReportData t1 t2 -- this is rolling my own state monad with a random generator class Monad m => RandMonad m where getGen :: m StdGen putGen :: StdGen -> () -- this is a class of state monad which logs ReportData: class Monad m => LogMonad m where putReport :: ReportData t1 t2 -> m () -- For a particular use case, I declare a type of State monad: data MyStateData t1 t2 = MyStateData t1 t2 { theGen :: StdGen , theReports :: [ReportData t1 t2] } type MyState t1 t2 = State (MyStateData t1 t2) -- And I try to define my instances: instance RandMonad (MyState t1 t2) where getGen = gets theGen putGen g = modify (\s -> s { theGen = g}) -- ERROR : theGen not in scope instance LogMonad (MyState t1 t2) where putReport r = modify (\s -> s { theReports = r : theReports s}) -- ERROR: theReports not in scope On Wed, Jun 27, 2018 at 10:43 PM, Dennis Raddle wrote: > okay, will do. It has a lot of details that aren't really necessary to ask > the question, but now that I think about it, all that's required of you is > to download and try to compile it. > > D > > On Wed, Jun 27, 2018 at 10:41 PM, Tom Ellis jaguarpaw.co.uk> wrote: > >> Your sample code has a few bugs which make it not compile, for example the >> following is not valid syntax >> >> data MyStateData t1 t2 = MyStateData t1 t2 >> { theGen :: StdGen >> , theReports :: [StepReport t1 t2] >> } >> >> and you use "StepReport" when I think you mean "ReportData". Could you >> post >> a version which is completely working besides the error you are trying to >> solve? Otherwise it's rather hard to help. >> >> Tom >> >> >> On Wed, Jun 27, 2018 at 10:22:46PM -0700, Dennis Raddle wrote: >> > I'm writing a program with several functions, some of which depend on >> > certain fields in a state monad, others of which depend on others, but >> no >> > routine needs all the fields. >> > >> > So I thought I would declare a two classes, one for each type of data >> need >> > that a function has: >> > >> > -- as an aside, here's an example of data which is parameterized by two >> > types. >> > >> > data ReportData t1 t2 = ... >> > >> > -- this is rolling my own state monad with a random generator >> > class Monad m => RandMonad m where >> > getGen :: m StdGen >> > putGen :: StdGen -> () >> > >> > -- this is a class of state monad which logs ReportData: >> > >> > class Monad m => LogMonad m where >> > putReport :: ReportData t1 t2 -> m () >> > >> > For a particular use case, I declare a type of State monad: >> > >> > data MyStateData t1 t2 = MyStateData t1 t2 >> > { theGen :: StdGen >> > , theReports :: [StepReport t1 t2] >> > } >> > >> > type MyState t1 t2 = State (MyStateData t1 t2) >> > >> > And I try to define my instances: >> > >> > instance RandMonad (MyState t1 t2) where >> > getGen = gets theGen >> > putGen g = modify (\s -> s { theGen = g}) >> > >> > instance LogMonad (MyState t1 t2) where >> > putReport r = modify (\s -> s { theReports = r : theReports s}) >> > >> > I get an error on the LogMonad instance, saying that there's no instance >> > for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) Identity)) >> > >> > I guess I don't really understand typeclasses once you start using >> higher >> > kinded types, so please enlighten me. Any reading on this subject would >> be >> > helpful, too. >> >> > _______________________________________________ >> > 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 kane at kane.cx Thu Jun 28 06:05:59 2018 From: kane at kane.cx (David Kraeutmann) Date: Thu, 28 Jun 2018 02:05:59 -0400 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: References: <20180628054144.tbrv6k3uklu2fldo@weber> Message-ID: <12488d46-76f4-9897-4baf-8ac66dc21dcd@kane.cx> Apart from a bunch of minor errors, the crux here is that class Monad m => LogMonad m where    putReport :: ReportData t1 t2 -> m () has locally quantified type variables t1, t2, and thus the `r` in `putReport r` has type `ReportData a b` while the state type expects `ReportData x y`. On 06/28/2018 01:54 AM, Dennis Raddle wrote: > I created a minimal example of what I'm trying to do --- in fact, I > think this will be better than what I wrote in the first place --- but > now I'm baffled by a different error entirely, which is some > identifiers not in scope. I'm going to post this anyway, because I > suspect the error is related to what the compiler can infer about my > instance, which is something I need to understand better. > > Once you get past that error, either it will be working (yay!) or > you'll encounter the error about no instance for MonadState which was > my original problem. > > {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, > FlexibleContexts #-} > > > import Control.Monad.State > import System.Random > > data ReportData t1 t2 = ReportData t1 t2 > > -- this is rolling my own state monad with a random generator > class Monad m => RandMonad m where >    getGen :: m StdGen >    putGen :: StdGen -> () > > -- this is a class of state monad which logs ReportData: > > class Monad m => LogMonad m where >    putReport :: ReportData t1 t2 -> m () > > -- For a particular use case, I declare a type of State monad: > > data MyStateData t1 t2 = MyStateData t1 t2 >   { theGen     :: StdGen >   , theReports :: [ReportData t1 t2] >   } > > type MyState t1 t2 = State (MyStateData t1 t2) > > -- And I try to define my instances: > > instance RandMonad (MyState t1 t2) where >   getGen   = gets theGen >   putGen g = modify (\s -> s { theGen = g})   -- ERROR : theGen not in > scope > > instance LogMonad (MyState t1 t2) where >   putReport r = modify (\s -> s { theReports = r : theReports s}) -- > ERROR: theReports not in scope > > > On Wed, Jun 27, 2018 at 10:43 PM, Dennis Raddle > > wrote: > > okay, will do. It has a lot of details that aren't really > necessary to ask the question, but now that I think about it, all > that's required of you is to download and try to compile it. > > D > > On Wed, Jun 27, 2018 at 10:41 PM, Tom Ellis > > wrote: > > Your sample code has a few bugs which make it not compile, for > example the > following is not valid syntax > >     data MyStateData t1 t2 = MyStateData t1 t2 >       { theGen :: StdGen >       , theReports :: [StepReport t1 t2] >       } > > and you use "StepReport" when I think you mean "ReportData".  > Could you post > a version which is completely working besides the error you > are trying to > solve? Otherwise it's rather hard to help. > > Tom > > > On Wed, Jun 27, 2018 at 10:22:46PM -0700, Dennis Raddle wrote: > > I'm writing a program with several functions, some of which > depend on > > certain fields in a state monad, others of which depend on > others, but no > > routine needs all the fields. > > > > So I thought I would declare a two classes, one for each > type of data need > > that a function has: > > > > -- as an aside, here's an example of data which is > parameterized by two > > types. > > > > data ReportData t1 t2 = ... > > > > -- this is rolling my own state monad with a random generator > > class Monad m => RandMonad m where > >    getGen :: m StdGen > >    putGen :: StdGen -> () > > > > -- this is a class of state monad which logs ReportData: > > > > class Monad m => LogMonad m where > >    putReport :: ReportData t1 t2 -> m () > > > > For a particular use case, I declare a type of State monad: > > > > data MyStateData t1 t2 = MyStateData t1 t2 > >   { theGen :: StdGen > >   , theReports :: [StepReport t1 t2] > >   } > > > > type MyState t1 t2 = State (MyStateData t1 t2) > > > > And I try to define my instances: > > > > instance RandMonad (MyState t1 t2) where > >   getGen = gets theGen > >   putGen g = modify (\s -> s { theGen = g}) > > > > instance LogMonad (MyState t1 t2) where > >   putReport r = modify (\s -> s { theReports = r : > theReports s}) > > > > I get an error on the LogMonad instance, saying that there's > no instance > > for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) > Identity)) > > > > I guess I don't really understand typeclasses once you start > using higher > > kinded types, so please enlighten me. Any reading on this > subject would be > > helpful, too. > > > _______________________________________________ > > 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 hilco.wijbenga at gmail.com Thu Jun 28 06:22:51 2018 From: hilco.wijbenga at gmail.com (Hilco Wijbenga) Date: Wed, 27 Jun 2018 23:22:51 -0700 Subject: [Haskell-cafe] Alternative Preludes Message-ID: Hi all, I've been looking for a different Prelude to, at minimum, default to Text instead of String but I'm sure there are other things that would be helpful. E.g., less focus on lists. I had a look at [1] and protolude, classy-prelude, basic-prelude, foundation, safe-prelude, and rio all seem interesting. Maybe even base-noprelude? I'm an advanced beginner (I don't think I qualify as intermediate yet). Going by [1], classy-prelude might not be such a good idea because of "scary error messages". And, I'm guessing, I would need to know Haskell better to take advantage of base-noprelude? I would like to know your thoughts/suggestions/opinions/ideas. Also, if there are other preludes that might be of interest, do tell! Cheers, Hilco [1] https://guide.aelve.com/haskell/alternative-preludes-zr69k1hc From dennis.raddle at gmail.com Thu Jun 28 09:15:08 2018 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Thu, 28 Jun 2018 02:15:08 -0700 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: <12488d46-76f4-9897-4baf-8ac66dc21dcd@kane.cx> References: <20180628054144.tbrv6k3uklu2fldo@weber> <12488d46-76f4-9897-4baf-8ac66dc21dcd@kane.cx> Message-ID: So, does that mean I'm trying to do something impossible? I'm often not clear on what higher-kinded types are doing, and I'm aware that sometimes I'm asking the compiler to do something that is logically impossible. Or is there a correct way to do this? On Wed, Jun 27, 2018 at 11:05 PM, David Kraeutmann wrote: > Apart from a bunch of minor errors, the crux here is that > > class Monad m => LogMonad m where > putReport :: ReportData t1 t2 -> m () > > has locally quantified type variables t1, t2, and thus the `r` in > `putReport r` has type `ReportData a b` while the state type expects > `ReportData x y`. > > > On 06/28/2018 01:54 AM, Dennis Raddle wrote: > > I created a minimal example of what I'm trying to do --- in fact, I > > think this will be better than what I wrote in the first place --- but > > now I'm baffled by a different error entirely, which is some > > identifiers not in scope. I'm going to post this anyway, because I > > suspect the error is related to what the compiler can infer about my > > instance, which is something I need to understand better. > > > > Once you get past that error, either it will be working (yay!) or > > you'll encounter the error about no instance for MonadState which was > > my original problem. > > > > {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, > > FlexibleContexts #-} > > > > > > import Control.Monad.State > > import System.Random > > > > data ReportData t1 t2 = ReportData t1 t2 > > > > -- this is rolling my own state monad with a random generator > > class Monad m => RandMonad m where > > getGen :: m StdGen > > putGen :: StdGen -> () > > > > -- this is a class of state monad which logs ReportData: > > > > class Monad m => LogMonad m where > > putReport :: ReportData t1 t2 -> m () > > > > -- For a particular use case, I declare a type of State monad: > > > > data MyStateData t1 t2 = MyStateData t1 t2 > > { theGen :: StdGen > > , theReports :: [ReportData t1 t2] > > } > > > > type MyState t1 t2 = State (MyStateData t1 t2) > > > > -- And I try to define my instances: > > > > instance RandMonad (MyState t1 t2) where > > getGen = gets theGen > > putGen g = modify (\s -> s { theGen = g}) -- ERROR : theGen not in > > scope > > > > instance LogMonad (MyState t1 t2) where > > putReport r = modify (\s -> s { theReports = r : theReports s}) -- > > ERROR: theReports not in scope > > > > > > On Wed, Jun 27, 2018 at 10:43 PM, Dennis Raddle > > > wrote: > > > > okay, will do. It has a lot of details that aren't really > > necessary to ask the question, but now that I think about it, all > > that's required of you is to download and try to compile it. > > > > D > > > > On Wed, Jun 27, 2018 at 10:41 PM, Tom Ellis > > > > wrote: > > > > Your sample code has a few bugs which make it not compile, for > > example the > > following is not valid syntax > > > > data MyStateData t1 t2 = MyStateData t1 t2 > > { theGen :: StdGen > > , theReports :: [StepReport t1 t2] > > } > > > > and you use "StepReport" when I think you mean "ReportData". > > Could you post > > a version which is completely working besides the error you > > are trying to > > solve? Otherwise it's rather hard to help. > > > > Tom > > > > > > On Wed, Jun 27, 2018 at 10:22:46PM -0700, Dennis Raddle wrote: > > > I'm writing a program with several functions, some of which > > depend on > > > certain fields in a state monad, others of which depend on > > others, but no > > > routine needs all the fields. > > > > > > So I thought I would declare a two classes, one for each > > type of data need > > > that a function has: > > > > > > -- as an aside, here's an example of data which is > > parameterized by two > > > types. > > > > > > data ReportData t1 t2 = ... > > > > > > -- this is rolling my own state monad with a random generator > > > class Monad m => RandMonad m where > > > getGen :: m StdGen > > > putGen :: StdGen -> () > > > > > > -- this is a class of state monad which logs ReportData: > > > > > > class Monad m => LogMonad m where > > > putReport :: ReportData t1 t2 -> m () > > > > > > For a particular use case, I declare a type of State monad: > > > > > > data MyStateData t1 t2 = MyStateData t1 t2 > > > { theGen :: StdGen > > > , theReports :: [StepReport t1 t2] > > > } > > > > > > type MyState t1 t2 = State (MyStateData t1 t2) > > > > > > And I try to define my instances: > > > > > > instance RandMonad (MyState t1 t2) where > > > getGen = gets theGen > > > putGen g = modify (\s -> s { theGen = g}) > > > > > > instance LogMonad (MyState t1 t2) where > > > putReport r = modify (\s -> s { theReports = r : > > theReports s}) > > > > > > I get an error on the LogMonad instance, saying that there's > > no instance > > > for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) > > Identity)) > > > > > > I guess I don't really understand typeclasses once you start > > using higher > > > kinded types, so please enlighten me. Any reading on this > > subject would be > > > helpful, too. > > > > > _______________________________________________ > > > 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 adam at bergmark.nl Thu Jun 28 09:23:15 2018 From: adam at bergmark.nl (Adam Bergmark) Date: Thu, 28 Jun 2018 11:23:15 +0200 Subject: [Haskell-cafe] Alternative Preludes In-Reply-To: References: Message-ID: I think rio looks very reasonable, it just reuses common libs. foundation is a cool project but they e.g. implement their own text type which probably means you will have to do conversions as soon as you try to use other libs. base-noprelude is only useful if you want to avoid having access to the default prelude and/or if you want to create your own. classy prelude seems a bit overkill, the author later released rio so i’m not sure if classy should be considered deprecated. Cheers, Adam On Thu, 28 Jun 2018 at 08:23, Hilco Wijbenga wrote: > Hi all, > > I've been looking for a different Prelude to, at minimum, default to > Text instead of String but I'm sure there are other things that would > be helpful. E.g., less focus on lists. > > I had a look at [1] and protolude, classy-prelude, basic-prelude, > foundation, safe-prelude, and rio all seem interesting. Maybe even > base-noprelude? > > I'm an advanced beginner (I don't think I qualify as intermediate > yet). Going by [1], classy-prelude might not be such a good idea > because of "scary error messages". And, I'm guessing, I would need to > know Haskell better to take advantage of base-noprelude? > > I would like to know your thoughts/suggestions/opinions/ideas. Also, > if there are other preludes that might be of interest, do tell! > > Cheers, > Hilco > > [1] https://guide.aelve.com/haskell/alternative-preludes-zr69k1hc > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanuki at gmail.com Thu Jun 28 09:27:03 2018 From: tanuki at gmail.com (Theodore Lief Gannon) Date: Thu, 28 Jun 2018 02:27:03 -0700 Subject: [Haskell-cafe] Alternative Preludes In-Reply-To: References: Message-ID: I highly recommend Rio. It's current and very pragmatic. On Wed, Jun 27, 2018, 11:23 PM Hilco Wijbenga wrote: > Hi all, > > I've been looking for a different Prelude to, at minimum, default to > Text instead of String but I'm sure there are other things that would > be helpful. E.g., less focus on lists. > > I had a look at [1] and protolude, classy-prelude, basic-prelude, > foundation, safe-prelude, and rio all seem interesting. Maybe even > base-noprelude? > > I'm an advanced beginner (I don't think I qualify as intermediate > yet). Going by [1], classy-prelude might not be such a good idea > because of "scary error messages". And, I'm guessing, I would need to > know Haskell better to take advantage of base-noprelude? > > I would like to know your thoughts/suggestions/opinions/ideas. Also, > if there are other preludes that might be of interest, do tell! > > Cheers, > Hilco > > [1] https://guide.aelve.com/haskell/alternative-preludes-zr69k1hc > _______________________________________________ > 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 Thu Jun 28 09:33:54 2018 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 28 Jun 2018 10:33:54 +0100 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: References: <20180628054144.tbrv6k3uklu2fldo@weber> <12488d46-76f4-9897-4baf-8ac66dc21dcd@kane.cx> Message-ID: <20180628093354.zrkrypaczflqecrd@weber> You're not trying to do something impossible but in my experience it's really only very, very rare cases where it's good design to introduce your own typeclasses. What problem are you trying to solve where introducing new typeclasses is the solution? (And FYI these are not higher-kinded types, they're multiparameter type classes.) Tom On Thu, Jun 28, 2018 at 02:15:08AM -0700, Dennis Raddle wrote: > So, does that mean I'm trying to do something impossible? > > I'm often not clear on what higher-kinded types are doing, and I'm aware > that sometimes I'm asking the compiler to do something that is logically > impossible. > > Or is there a correct way to do this? > > On Wed, Jun 27, 2018 at 11:05 PM, David Kraeutmann wrote: > > > Apart from a bunch of minor errors, the crux here is that > > > > class Monad m => LogMonad m where > > putReport :: ReportData t1 t2 -> m () > > > > has locally quantified type variables t1, t2, and thus the `r` in > > `putReport r` has type `ReportData a b` while the state type expects > > `ReportData x y`. > > > > > > On 06/28/2018 01:54 AM, Dennis Raddle wrote: > > > I created a minimal example of what I'm trying to do --- in fact, I > > > think this will be better than what I wrote in the first place --- but > > > now I'm baffled by a different error entirely, which is some > > > identifiers not in scope. I'm going to post this anyway, because I > > > suspect the error is related to what the compiler can infer about my > > > instance, which is something I need to understand better. > > > > > > Once you get past that error, either it will be working (yay!) or > > > you'll encounter the error about no instance for MonadState which was > > > my original problem. > > > > > > {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, > > > FlexibleContexts #-} > > > > > > > > > import Control.Monad.State > > > import System.Random > > > > > > data ReportData t1 t2 = ReportData t1 t2 > > > > > > -- this is rolling my own state monad with a random generator > > > class Monad m => RandMonad m where > > > getGen :: m StdGen > > > putGen :: StdGen -> () > > > > > > -- this is a class of state monad which logs ReportData: > > > > > > class Monad m => LogMonad m where > > > putReport :: ReportData t1 t2 -> m () > > > > > > -- For a particular use case, I declare a type of State monad: > > > > > > data MyStateData t1 t2 = MyStateData t1 t2 > > > { theGen :: StdGen > > > , theReports :: [ReportData t1 t2] > > > } > > > > > > type MyState t1 t2 = State (MyStateData t1 t2) > > > > > > -- And I try to define my instances: > > > > > > instance RandMonad (MyState t1 t2) where > > > getGen = gets theGen > > > putGen g = modify (\s -> s { theGen = g}) -- ERROR : theGen not in > > > scope > > > > > > instance LogMonad (MyState t1 t2) where > > > putReport r = modify (\s -> s { theReports = r : theReports s}) -- > > > ERROR: theReports not in scope > > > > > > > > > On Wed, Jun 27, 2018 at 10:43 PM, Dennis Raddle > > > > wrote: > > > > > > okay, will do. It has a lot of details that aren't really > > > necessary to ask the question, but now that I think about it, all > > > that's required of you is to download and try to compile it. > > > > > > D > > > > > > On Wed, Jun 27, 2018 at 10:41 PM, Tom Ellis > > > > > > wrote: > > > > > > Your sample code has a few bugs which make it not compile, for > > > example the > > > following is not valid syntax > > > > > > data MyStateData t1 t2 = MyStateData t1 t2 > > > { theGen :: StdGen > > > , theReports :: [StepReport t1 t2] > > > } > > > > > > and you use "StepReport" when I think you mean "ReportData". > > > Could you post > > > a version which is completely working besides the error you > > > are trying to > > > solve? Otherwise it's rather hard to help. > > > > > > Tom > > > > > > > > > On Wed, Jun 27, 2018 at 10:22:46PM -0700, Dennis Raddle wrote: > > > > I'm writing a program with several functions, some of which > > > depend on > > > > certain fields in a state monad, others of which depend on > > > others, but no > > > > routine needs all the fields. > > > > > > > > So I thought I would declare a two classes, one for each > > > type of data need > > > > that a function has: > > > > > > > > -- as an aside, here's an example of data which is > > > parameterized by two > > > > types. > > > > > > > > data ReportData t1 t2 = ... > > > > > > > > -- this is rolling my own state monad with a random generator > > > > class Monad m => RandMonad m where > > > > getGen :: m StdGen > > > > putGen :: StdGen -> () > > > > > > > > -- this is a class of state monad which logs ReportData: > > > > > > > > class Monad m => LogMonad m where > > > > putReport :: ReportData t1 t2 -> m () > > > > > > > > For a particular use case, I declare a type of State monad: > > > > > > > > data MyStateData t1 t2 = MyStateData t1 t2 > > > > { theGen :: StdGen > > > > , theReports :: [StepReport t1 t2] > > > > } > > > > > > > > type MyState t1 t2 = State (MyStateData t1 t2) > > > > > > > > And I try to define my instances: > > > > > > > > instance RandMonad (MyState t1 t2) where > > > > getGen = gets theGen > > > > putGen g = modify (\s -> s { theGen = g}) > > > > > > > > instance LogMonad (MyState t1 t2) where > > > > putReport r = modify (\s -> s { theReports = r : > > > theReports s}) > > > > > > > > I get an error on the LogMonad instance, saying that there's > > > no instance > > > > for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) > > > Identity)) > > > > > > > > I guess I don't really understand typeclasses once you start > > > using higher > > > > kinded types, so please enlighten me. Any reading on this > > > subject would be > > > > helpful, too. > > > > > > > _______________________________________________ > > > > 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. From vanessa.mchale at iohk.io Thu Jun 28 12:10:22 2018 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Thu, 28 Jun 2018 07:10:22 -0500 Subject: [Haskell-cafe] Alternative Preludes In-Reply-To: References: Message-ID: <10039582-8dfe-9a1f-4452-c414b9a72622@iohk.io> I would suggest just using the text package and importing it qualified. Foundation has its own text type which is supposedly fast, but it introduces some complications as well. rio looks too involved to me. This all depends on your project - plenty of libraries have no need to depend on mtl or vector, so adding them as dependencies just makes your builds more fragile.  Lots of these libraries break cross-compilation too (or just make it more difficult). But if you're writing an application for use on your computer only, none of this matters. Also you shouldn't be afraid of lists. They have their place in functional programming and Haskell. On 06/28/2018 01:22 AM, Hilco Wijbenga wrote: > Hi all, > > I've been looking for a different Prelude to, at minimum, default to > Text instead of String but I'm sure there are other things that would > be helpful. E.g., less focus on lists. > > I had a look at [1] and protolude, classy-prelude, basic-prelude, > foundation, safe-prelude, and rio all seem interesting. Maybe even > base-noprelude? > > I'm an advanced beginner (I don't think I qualify as intermediate > yet). Going by [1], classy-prelude might not be such a good idea > because of "scary error messages". And, I'm guessing, I would need to > know Haskell better to take advantage of base-noprelude? > > I would like to know your thoughts/suggestions/opinions/ideas. Also, > if there are other preludes that might be of interest, do tell! > > Cheers, > Hilco > > [1] https://guide.aelve.com/haskell/alternative-preludes-zr69k1hc > _______________________________________________ > 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: 488 bytes Desc: OpenPGP digital signature URL: From ian at skybluetrades.net Thu Jun 28 12:25:53 2018 From: ian at skybluetrades.net (Ian Ross) Date: Thu, 28 Jun 2018 14:25:53 +0200 Subject: [Haskell-cafe] Alternative Preludes In-Reply-To: References: Message-ID: I'd put in a vote for protolude. I just started using it on a new project that promises to get quite big, and it's turning out to make life a lot easier. Two things I'd suggest: 1. Don't use a custom prelude for libraries, especially if you're planning to publish them publicly -- only use custom preludes for applications. 2. Treat whatever custom prelude you choose as a starting point, not as something that's fixed in stone. I've been using our custom prelude as a way to provide common utility functions, to work around limitations in some of the dependencies we're using, and so on. If I find myself repeatedly importing a library module into application code, I move it into one of our prelude modules. I'm really liking the approach and wish I'd tried it a long time ago. Cheers, Ian. On Thu, Jun 28, 2018 at 8:22 AM, Hilco Wijbenga wrote: > Hi all, > > I've been looking for a different Prelude to, at minimum, default to > Text instead of String but I'm sure there are other things that would > be helpful. E.g., less focus on lists. > > I had a look at [1] and protolude, classy-prelude, basic-prelude, > foundation, safe-prelude, and rio all seem interesting. Maybe even > base-noprelude? > > I'm an advanced beginner (I don't think I qualify as intermediate > yet). Going by [1], classy-prelude might not be such a good idea > because of "scary error messages". And, I'm guessing, I would need to > know Haskell better to take advantage of base-noprelude? > > I would like to know your thoughts/suggestions/opinions/ideas. Also, > if there are other preludes that might be of interest, do tell! > > Cheers, > Hilco > > [1] https://guide.aelve.com/haskell/alternative-preludes-zr69k1hc > _______________________________________________ > 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. -- Ian Ross Tel: +43(0)6804451378 ian at skybluetrades.net www.skybluetrades.net PGP Key: 0x04490CC0/F4D6 027F 2661 745C 83A5 297D FCCC 0AE6 0449 0CC0 -------------- next part -------------- An HTML attachment was scrubbed... URL: From paolo.veronelli at gmail.com Thu Jun 28 13:28:09 2018 From: paolo.veronelli at gmail.com (Paolino) Date: Thu, 28 Jun 2018 15:28:09 +0200 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: References: Message-ID: All you need is the state to have different "aspects" You can express this with parameters to your stateful computations Here's an (uncompiled) sketch covering part of your case, using lenses {-# language TemplateHaskell #-} import Control.Lens (Lens', set, makeLenses) import System.Random import Control.Monad.State -- a user of any state 's' which has a StdGen aspect, see the 's' is free here so putGen is polymorphic in it putGen :: Lens' s StdGen -> StdGen -> State s () putGen l g = modify $ set l g -- or for shorter see Control.Lens.Setter -- putGen = (.=) ... ... -- a state as a record with all aspects data S = S { .... :: .... , _generator :: StdGen ..... :: .. } makeLenses ''S -- automatically derive the lenses for you (generator function in example) -- equivalent at least to something like -- generator f g s = (\g' -> s{_generator = g'}) <$> f g main = do g0 <- newStdGen print $ evalState (putGen generator g >> ....) $ S ... g0 .. (This leaves you the burden of passing lenses around (one for each aspect) which you could alleviate with different techniques, if this is ever a concern) As Tom said, typeclasses are not that good for this cases as it might seem at first glance HTH Best paolino On Thu, 28 Jun 2018 at 07:23, Dennis Raddle wrote: > I'm writing a program with several functions, some of which depend on > certain fields in a state monad, others of which depend on others, but no > routine needs all the fields. > > So I thought I would declare a two classes, one for each type of data need > that a function has: > > -- as an aside, here's an example of data which is parameterized by two > types. > > data ReportData t1 t2 = ... > > -- this is rolling my own state monad with a random generator > class Monad m => RandMonad m where > getGen :: m StdGen > putGen :: StdGen -> () > > -- this is a class of state monad which logs ReportData: > > class Monad m => LogMonad m where > putReport :: ReportData t1 t2 -> m () > > For a particular use case, I declare a type of State monad: > > data MyStateData t1 t2 = MyStateData t1 t2 > { theGen :: StdGen > , theReports :: [StepReport t1 t2] > } > > type MyState t1 t2 = State (MyStateData t1 t2) > > And I try to define my instances: > > instance RandMonad (MyState t1 t2) where > getGen = gets theGen > putGen g = modify (\s -> s { theGen = g}) > > instance LogMonad (MyState t1 t2) where > putReport r = modify (\s -> s { theReports = r : theReports s}) > > I get an error on the LogMonad instance, saying that there's no instance > for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) Identity)) > > I guess I don't really understand typeclasses once you start using higher > kinded types, so please enlighten me. Any reading on this subject would be > helpful, too. > _______________________________________________ > 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 paolo.veronelli at gmail.com Thu Jun 28 15:04:29 2018 From: paolo.veronelli at gmail.com (Paolino) Date: Thu, 28 Jun 2018 17:04:29 +0200 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: References: Message-ID: A compiled example where you can taste value level selection of aspect. https://lpaste.net/57731722032185344 - p On Thu, 28 Jun 2018 at 15:28, Paolino wrote: > All you need is the state to have different "aspects" > > You can express this with parameters to your stateful computations > > Here's an (uncompiled) sketch covering part of your case, using lenses > > {-# language TemplateHaskell #-} > > import Control.Lens (Lens', set, makeLenses) > import System.Random > import Control.Monad.State > > -- a user of any state 's' which has a StdGen aspect, see the 's' is free > here so putGen is polymorphic in it > putGen :: Lens' s StdGen -> StdGen -> State s () > putGen l g = modify $ set l g > -- or for shorter see Control.Lens.Setter > -- putGen = (.=) > > ... > ... > > -- a state as a record with all aspects > data S = S { > .... :: .... > , _generator :: StdGen > ..... :: .. > } > > makeLenses ''S -- automatically derive the lenses for you (generator > function in example) > -- equivalent at least to something like > -- generator f g s = (\g' -> s{_generator = g'}) <$> f g > > main = do > g0 <- newStdGen > print $ evalState (putGen generator g >> ....) $ S ... g0 .. > > (This leaves you the burden of passing lenses around (one for each aspect) > which you could alleviate with different techniques, if this is ever a > concern) > > As Tom said, typeclasses are not that good for this cases as it might seem > at first glance > > HTH > > Best > > paolino > > On Thu, 28 Jun 2018 at 07:23, Dennis Raddle > wrote: > >> I'm writing a program with several functions, some of which depend on >> certain fields in a state monad, others of which depend on others, but no >> routine needs all the fields. >> >> So I thought I would declare a two classes, one for each type of data >> need that a function has: >> >> -- as an aside, here's an example of data which is parameterized by two >> types. >> >> data ReportData t1 t2 = ... >> >> -- this is rolling my own state monad with a random generator >> class Monad m => RandMonad m where >> getGen :: m StdGen >> putGen :: StdGen -> () >> >> -- this is a class of state monad which logs ReportData: >> >> class Monad m => LogMonad m where >> putReport :: ReportData t1 t2 -> m () >> >> For a particular use case, I declare a type of State monad: >> >> data MyStateData t1 t2 = MyStateData t1 t2 >> { theGen :: StdGen >> , theReports :: [StepReport t1 t2] >> } >> >> type MyState t1 t2 = State (MyStateData t1 t2) >> >> And I try to define my instances: >> >> instance RandMonad (MyState t1 t2) where >> getGen = gets theGen >> putGen g = modify (\s -> s { theGen = g}) >> >> instance LogMonad (MyState t1 t2) where >> putReport r = modify (\s -> s { theReports = r : theReports s}) >> >> I get an error on the LogMonad instance, saying that there's no instance >> for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) Identity)) >> >> I guess I don't really understand typeclasses once you start using higher >> kinded types, so please enlighten me. Any reading on this subject would be >> helpful, too. >> _______________________________________________ >> 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 jon.fairbairn at cl.cam.ac.uk Thu Jun 28 21:05:21 2018 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Thu, 28 Jun 2018 22:05:21 +0100 Subject: [Haskell-cafe] Using Wai with Conduit and ResourceT (was Re: (New to Conduits) mixing lazy lists and Conduits?) References: Message-ID: Michael Snoyman writes: > You can use Data.Conduit.Lazy for this. Thanks. Not as straightforward as I had hoped, but I can see why. On a different note, still attempting to learn, I am trying to use Network.Wai.Conduit with a conduit that has effects (ie involves sourceFile), and so lives in (ResourceT IO). eg example:: ConduitT i (Flush Builder) (ResourceT IO) () Now, responseSource expects IO, not ResourceT IO, so I don’t think I can use that, so I wrote this: > responseSourceRes status headers res_conduit > = responseStream status200 headers > (\send flush -> runConduitRes $ res_conduit > .| mapM_ (\e->lift $ > case e of > Chunk c -> send c > Flush -> flush )) which runs, but (rather to my surprise) doesn’t produce output (not even headers) until all the effects have completed. That gives rise to two questions: Why does that not stream output? What should I do instead? -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From byorgey at gmail.com Thu Jun 28 21:17:37 2018 From: byorgey at gmail.com (Brent Yorgey) Date: Thu, 28 Jun 2018 16:17:37 -0500 Subject: [Haskell-cafe] Deadline extension for FARM 2018 (now July 8) - Workshop on Functional Art, Music, Modelling, and Design Message-ID: The FARM submission deadline for papers and demo proposals has been extended to July 8 (the same as the performance submission deadline). 6th ACM SIGPLAN International Workshop on Functional Art, Music, Modelling and Design St. Louis, Missouri, USA, September 29th 2018 Call for Papers and Performances Key Dates ========= Paper submission deadline (extended) July 8 Performance submission deadline July 8 Author Notification July 21 Camera Ready August 5 Workshop September 29 About FARM ========== The ACM SIGPLAN International Workshop on Functional Art, Music, Modelling and Design (FARM) gathers together people who are harnessing functional techniques in the pursuit of creativity and expression. It is co-located with ICFP 2018, the 23rd ACM SIGPLAN International Conference on Functional Programming, and with Strange Loop, in St. Louis, Missouri, USA. Functional Programming has emerged as a mainstream software development paradigm, and its artistic and creative use is booming. A growing number of software toolkits, frameworks and environments for art, music and design now employ functional programming languages and techniques. FARM is a forum for exploration and critical evaluation of these developments, for example to consider potential benefits of greater consistency, tersity, and closer mapping to a problem domain. FARM encourages submissions from across art, craft and design, including textiles, visual art, music, 3D sculpture, animation, GUIs, video games, 3D printing and architectural models, choreography, poetry, and even VLSI layouts, GPU configurations, or mechanical engineering designs. Theoretical foundations, language design, implementation issues, and applications in industry or the arts are all within the scope of the workshop. The language used need not be purely functional (“mostly functional” is fine), and may be manifested as a domain specific language or tool. Moreover, submissions focusing on questions or issues about the use of functional programming are within the scope. FARM 2018 website : http://functional-art.org/2018/ Call for Performances ===================== Submission deadline: July 8, 2018. Submission URL: https://easychair.org/conferences/?conf=farm2018 . FARM also hosts a traditional evening of performances. For this year’s event, FARM 2018 is seeking proposals for live performances which employ functional programming techniques, in whole or in part. We would like to support a diverse range of performing arts, including music, dance, video animation, and performance art. We encourage both risk-taking proposals which push forward the state of the art and refined presentations of highly-developed practice. In either case, please support your submission with a clear description of your performance including how your performance employs functional programming and a discussion of influences and prior art as appropriate. Call for Papers and Demos ========================= Submission deadline (extended): July 8 Submission URL: https://easychair.org/conferences/?conf=farm2018 . We welcome submissions from academic, professional, and independent programmers and artists. Submissions are invited in three categories: 1) Original papers We solicit original papers in the following categories: - Original research - Overview / state of the art - Technology tutorial All submissions must propose an original contribution to the FARM theme. FARM is an interdisciplinary conference, so a wide range of approaches are encouraged. An original paper should have 5 to 12 pages, be in portable document format (PDF), using the ACM SIGPLAN style guidelines and the ACM SIGPLAN template. [ http://www.sigplan.org/Resources/Author/ -- use the 'sigplan' sub-format. ] Accepted papers will be published in the ACM Digital Library as part of the FARM 2018 proceedings. See http://authors.acm.org/main.cfm for information on the options available to authors. Authors are encouraged to submit auxiliary material for publication along with their paper (source code, data, videos, images, etc.); authors retain all rights to the auxiliary material. 2) Demo proposals Demo proposals should describe a demonstration to be given at the FARM workshop and its context, connecting it with the themes of FARM. A demo could be in the form of a short (10-20 minute) tutorial, presentation of work-in-progress, an exhibition of some work, or even a performance. Demo proposals should be in plain text, HTML or Markdown format, and not exceed 2000 words. A demo proposal should be clearly marked as such, by prepending Demo Proposal: to the title. Demo proposals will be published on the FARM website. A summary of the demo performances will also be published as part of the conference proceedings, to be prepared by the program chair. 3) Calls for collaboration Calls for collaboration should describe a need for technology or expertise related to the FARM theme. Examples may include but are not restricted to: - art projects in need of realization - existing software or hardware that may benefit from functional programming - unfinished projects in need of inspiration Calls for collaboration should be in plain text, HTML or Markdown format, and not exceed 5000 words. A call for collaboration should be clearly marked as such, by prepending Call for Collaboration: to the title. Calls for collaboration will be published on the FARM website. Authors take note ================= The official publication date is the date the proceedings are made available in the ACM Digital Library. This date may be up to two weeks prior to the first day of your conference. The official publication date affects the deadline for any patent filings related to published work. All presentations at FARM 2018 will be recorded. Permission to publish the resulting video (in all probability on YouTube, along with the videos of ICFP itself and the other ICFP-colocated events) will be requested on-site. Questions ========= If you have any questions about what type of contributions that might be suitable, or anything else regarding submission or the workshop itself, please contact the organisers at: farm-2018 at functional-art.org Workshop Organization ==================== Brent Yorgey (general chair) Donya Quick (program chair) Tom Murphy (performance chair) Program Committee ================= Heinrich Apfelmus (self-employed) Chuck Jee Chau (Hong Kong University of Science and Technology, Hong Kong) Brian Heim (Yale, USA) Can Ince (ince.io) Chris Martens (NC State University, USA) Eduardo Miranda (University of Plymouth, UK) Ivan Perez Dominguez (University of Nottingham, UK) Iris Ren (Utrecht University, Netherlands) Henning Thielemann (self-employed) Didier Verna (EPITA, France) Dan Winograd-Cort (Target, USA) Halley Young (University of Pennsylvania, USA) Code of Conduct =============== FARM adheres to ICFP 2018's Code of Conduct: http://icfp18.sigplan.org/attending/code-of-conduct -------------- next part -------------- An HTML attachment was scrubbed... URL: From dennis.raddle at gmail.com Thu Jun 28 22:23:18 2018 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Thu, 28 Jun 2018 15:23:18 -0700 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: References: Message-ID: ​Thanks, Paolino. I will study this. I'll explain my larger goal. Probably should have started with that. I'm writing algorithms to optimize data structures by backtracking search. More specifically, I'm optimizing musical compositions. But I have several possible representations of a composition and I'd like to swap them in and out. I also have several ideas for a search algorithm. The search will function kind of like a chess program, adding notes to the composition one at a time and looking ahead N notes, then using some kind of fitness evaluation function to find the best "next move." There are variations on this algorithm possible. The fitness function will be computed by summing the fitness from "evaluation units" which, individually, look at only one aspect of good music. Together they have a more comprehensive view. I can easily try variations on the search by adding or removing "evaluation units". For another source of variation, I may use a fully deterministic algorithm, or I may use some pseudorandomness in choosing what paths to search, in various combinations. So how do I write a search algorithm when I don't know the type of the data structure or the evaluation units? My idea was to create a typeclass, Comp, parameterized on the the composition data structure ('comp'), the data type of a single "move" or step to be added, ('step'), and the type of an evaluation units ('eu'). class Comp comp eu step | comp -> eu, comp -> step where listPossibleSteps :: comp -> [step] addStep :: comp -> step -> comp evalComp :: eu -> comp -> comp This should offer all the necessary computations to implement backtracking search of many flavors. There's a lot more to how I want to implement this algorithm, mainly that I want to log "analytics" to be able to examine its behavior, so that's where the ReportLog data type and State (or possibly Writer) monad came into it, but never mind that for now. I'm probably not even on the right track with this much. D -------------- next part -------------- An HTML attachment was scrubbed... URL: From aaronngray.lists at gmail.com Fri Jun 29 00:15:29 2018 From: aaronngray.lists at gmail.com (Aaron Gray) Date: Fri, 29 Jun 2018 01:15:29 +0100 Subject: [Haskell-cafe] Lattice and calculation of Least Upper Bounds In-Reply-To: References: Message-ID: Olaf, Thanks for the reply. Answer inline. On Tue, 19 Jun 2018 at 20:53, Olaf Klinke wrote: > Aaron, > > the lattices package provides some modules to extend a given lattice by > some elements, e.g. new top and bottoms. There are also derived typeclass > instances for combinations like tuples, endomorphisms and so forth. But the > way of choice really depends on what you know about your multiple > inheritance hierarchy AFAICS all that needs to be known about the inheritance hierarchy in order to create the lattice is the sub type relations, and also top and bottom reference types. Ideally I would like to iterate through the hierarchy starting with top and then the base classes and add them incrementally with their subtype dependencies through to bottom. . > In universal algebra one powerful method of constructing (semi-)lattices > is by generators and relations. That means you define the lattice as a > quotient of a free lattice. The quotient itself is defined as a set of > ineqalities on the generators. I don't know how one would implement that > without dependent types, though, as the type would be another type together > with a function. To make things worse, the word problem is undecidable in > general. > Looking at Algebra.Lattice.Free I'm surprised that the free (semi-)lattice > types don't have a Monad instance. Does anyone know why they are not > implemented? Under the hood the free lattice types are identical to the > continuation monad. I think the Lattice classes may well be still in flux as I looked about a month ago ad there seemed to be AFAICR a Least Upper Bound operation taking a list of elements and returning an element. > > Olaf > > >Hi, > > > >I am trying to work out how to use the Algebra.Lattice family of Lattice > >data structures. > > > >Firstly how do I construct a lattice ? > > > >What I am wanting to do is to be able to construct a lattice to represent > a > >multiple inheritance hierarchy. Then I to be able to find the Least Upper > >Bound of a set of classes/types. This is in order to find the type of a > >multiple case expression. > > > >I am not sure if the Haskell classes are actually applicable ? but if they > >are how do I apply them to the following problem please ? -- Aaron Gray Independent Open Source Software Engineer, Computer Language Researcher, Information Theorist, and amateur computer scientist. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Fri Jun 29 06:51:22 2018 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 29 Jun 2018 07:51:22 +0100 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: References: Message-ID: <20180629065122.fukh7paiafi4xf46@weber> On Thu, Jun 28, 2018 at 03:23:18PM -0700, Dennis Raddle wrote: > My idea was to create a typeclass, Comp, parameterized on the the > composition data structure ('comp'), the data type of a single "move" or > step to be added, ('step'), and the type of an evaluation units ('eu'). > > class Comp comp eu step | comp -> eu, comp -> step where > listPossibleSteps :: comp -> [step] > addStep :: comp -> step -> comp > evalComp :: eu -> comp -> comp Have you considered just making a record? data Comp comp eu step = Comp { listPossibleSteps :: comp -> [step], addStep :: comp -> step -> comp, evalComp :: eu -> comp -> comp } If you make it a class then you end up in the bizarre situation where you can only have one collection of functionality for each type `comp`. Tom From ryan.reich at gmail.com Fri Jun 29 07:43:23 2018 From: ryan.reich at gmail.com (Ryan Reich) Date: Fri, 29 Jun 2018 03:43:23 -0400 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: <20180629065122.fukh7paiafi4xf46@weber> References: <20180629065122.fukh7paiafi4xf46@weber> Message-ID: On Fri, Jun 29, 2018 at 2:51 AM, Tom Ellis < tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote: > On Thu, Jun 28, 2018 at 03:23:18PM -0700, Dennis Raddle wrote: > > My idea was to create a typeclass, Comp, parameterized on the the > > composition data structure ('comp'), the data type of a single "move" or > > step to be added, ('step'), and the type of an evaluation units ('eu'). > > > > class Comp comp eu step | comp -> eu, comp -> step where > > listPossibleSteps :: comp -> [step] > > addStep :: comp -> step -> comp > > evalComp :: eu -> comp -> comp > > Have you considered just making a record? > > data Comp comp eu step = Comp { > listPossibleSteps :: comp -> [step], > addStep :: comp -> step -> comp, > evalComp :: eu -> comp -> comp > } > > If you make it a class then you end up in the bizarre situation where you > can only have one collection of functionality for each type `comp`. > > Tom This in turn can be worked around using a newtype wrapper for each alternate instance you want. I like this but I understand why it is often seen as awkward. Ryan -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Fri Jun 29 09:12:28 2018 From: michael at snoyman.com (Michael Snoyman) Date: Fri, 29 Jun 2018 12:12:28 +0300 Subject: [Haskell-cafe] Using Wai with Conduit and ResourceT (was Re: (New to Conduits) mixing lazy lists and Conduits?) In-Reply-To: References: Message-ID: I'd have to see a complete repro to know why the program in question doesn't stream. But I _can_ explain how best to do something like this. To frame this: why is something like ResourceT needed here? The issue is we want to ensure exception safety around the open file handle, and guarantee that the handle is closed regardless of any exceptions being thrown. ResourceT solves this problem by letting you register cleanup actions. This allows for solving some really complicated dynamic allocation problems, but for most cases it's overkill. Instead, a simple use of the bracket pattern is sufficient. You can do that with `withSourceFile`: ``` #!/usr/bin/env stack -- stack --resolver lts-11.10 script import Network.Wai import Network.Wai.Handler.Warp import Network.Wai.Conduit import Network.HTTP.Types import Conduit import Data.ByteString.Builder (byteString) main :: IO () main = run 3000 app app :: Application app _req respond = withSourceFile "Main.hs" $ \src -> respond $ responseSource status200 [] $ src .| mapC (Chunk . byteString) ``` You can also do this by sticking with ResourceT, which requires jumping through some hoops with monad transformers to ensure the original ResourceT context is used. I don't recommend this approach unless you really need it: it's complicated, and slightly slower than the above. But in case you're curious: ``` #!/usr/bin/env stack -- stack --resolver lts-11.10 script import Network.Wai import Network.Wai.Handler.Warp import Network.Wai.Conduit import Network.HTTP.Types import Conduit import Data.ByteString.Builder (byteString) import Control.Monad.Trans.Resource main :: IO () main = run 3000 app app :: Application app _req respond = runResourceT $ withInternalState $ \is -> respond $ responseSource status200 [] $ transPipe (`runInternalState` is) (sourceFile "Main.hs") .| mapC (Chunk . byteString) ``` On Fri, Jun 29, 2018 at 12:05 AM Jon Fairbairn wrote: > Michael Snoyman writes: > > > You can use Data.Conduit.Lazy for this. > > Thanks. Not as straightforward as I had hoped, but I can see > why. > > On a different note, still attempting to learn, I am trying to > use Network.Wai.Conduit with a conduit that has effects (ie > involves sourceFile), and so lives in (ResourceT IO). eg > > example:: ConduitT i (Flush Builder) (ResourceT IO) () > > Now, responseSource expects IO, not ResourceT IO, so I don’t > think I can use that, so I wrote this: > > > > responseSourceRes status headers res_conduit > > = responseStream status200 headers > > (\send flush -> runConduitRes $ res_conduit > > .| mapM_ (\e->lift $ > > case e of > > Chunk c -> send c > > Flush -> flush )) > > which runs, but (rather to my surprise) doesn’t produce output > (not even headers) until all the effects have completed. That > gives rise to two questions: > > Why does that not stream output? > What should I do instead? > > -- > Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk > > _______________________________________________ > 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 jon.fairbairn at cl.cam.ac.uk Fri Jun 29 09:41:02 2018 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Fri, 29 Jun 2018 10:41:02 +0100 Subject: [Haskell-cafe] Using Wai with Conduit and ResourceT (was Re: (New to Conduits) mixing lazy lists and Conduits?) References: Message-ID: Michael Snoyman writes: > I'd have to see a complete repro to know why the program in question > doesn't stream. Thanks. Here’s a fairly small example ``` module Main where import Prelude hiding (mapM_) import Conduit import Data.Conduit.List (mapM_) import System.FilePath import Data.ByteString.UTF8 import Data.Binary.Builder import GHC.IO.Exception (IOException) import Network.Wai.Handler.FastCGI (run) import Network.Wai.Conduit (Application, responseStream) import Network.HTTP.Types.Status import Network.HTTP.Types.Header data_directory = "./test-data/" main = run $ app app:: Application app request respond = do respond $ responseSourceRes status200 [(hContentType, fromString "text/plain; charset=UTF-8")] $ do yieldCBS "\nBEGIN\n" yield Flush wrapSourceFile $ data_directory "file1" wrapSourceFile $ data_directory "a_pipe" yieldCBS "END\n" yield Flush wrapSourceFile:: (MonadUnliftIO m, MonadResource m) => FilePath -> ConduitM a (Flush Builder) m () wrapSourceFile path = do yieldCBS ("\n" ++ path ++ ":\n") catchC (sourceFile path .| mapC (Chunk . fromByteString)) (\e -> yieldCBS $ "Error: " ++ show (e::IOException) ++ "\n") yieldCBS "\n" yield Flush yieldCBS:: Monad m => String -> ConduitT i (Flush Builder) m () yieldCBS = yield . Chunk . fromByteString . fromString responseSourceRes status headers res_conduit = responseStream status200 headers (\send flush -> runConduitRes $ res_conduit .| mapM_ (\e->liftIO $ case e of Chunk c -> send c Flush -> flush )) ``` The various flushes in there were attempts to make something come out. > But I _can_ explain how best to do something like this. > To frame this: why is something like ResourceT needed here? The issue is we > want to ensure exception safety around the open file handle, and guarantee > that the handle is closed regardless of any exceptions being thrown. > ResourceT solves this problem by letting you register cleanup actions. This > allows for solving some really complicated dynamic allocation problems, but > for most cases it's overkill. Instead, a simple use of the bracket pattern > is sufficient. You can do that with `withSourceFile`: > > ``` > #!/usr/bin/env stack > -- stack --resolver lts-11.10 script > import Network.Wai > import Network.Wai.Handler.Warp > import Network.Wai.Conduit > import Network.HTTP.Types > import Conduit > import Data.ByteString.Builder (byteString) > > main :: IO () > main = run 3000 app > > app :: Application > app _req respond = > withSourceFile "Main.hs" $ \src -> > respond $ responseSource status200 [] > $ src .| mapC (Chunk . byteString) I don’t think that will work for what I’m trying to do as the decision to open which file is made within the conduit. > You can also do this by sticking with ResourceT, which requires jumping > through some hoops with monad transformers to ensure the original ResourceT > context is used. I don't recommend this approach unless you really need it: > it's complicated, and slightly slower than the above. But in case you're > curious: Thanks. I think that may be what I want, but it’ll take a while to digest -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From vlatko.basic at gmail.com Fri Jun 29 12:31:51 2018 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Fri, 29 Jun 2018 14:31:51 +0200 Subject: [Haskell-cafe] Measuring memory usage Message-ID: <5e82210c-6aa4-a7d0-fce6-2668df343214@gmail.com> Hello, I've come to some strange results using Weigh package. It shows that HashMap inside 'data' is using much, much more memory. The strange thing is that I'm seeing too large mem usage in my app as well (several "MapData" like in records), and trying to figure out with 'weigh' what's keeping the mem. Noticed that when I change the code to use HashMap directly (not inside 'data', that's the only change), the mem usage observed with top drops down for ~60M, from 850M to 790M. These are the test results for 10K, 5K and 3.3K items for "data MapData k v = MapData (HashMap k v)" (at the end is the full runnable example.) Case           Allocated  GCs HashMap          262,824    0 HashMap half      58,536    0 HashMap third     17,064    0 MapData        4,242,208    4 I tested by changing the order, disabling all but one etc., and the results were the same. Same 'weigh' behaviour with IntMap and Map. So, if anyone knows and has some experience with such issues, my questions are: 1. Is 'weigh' package reliable/usable, at least to some extent? (the results do show diff between full, half and third) 2. How do you measure mem consumptions of your large data/records? 3. If the results are even approximately valid, what could cause such large discrepancies with 'data'? 4. Is there a way to see if some record has been freed from memory, GCed? module Main where import Prelude import Control.DeepSeq     (NFData) import Data.HashMap.Strict (HashMap, fromList) import GHC.Generics        (Generic) import Weigh               (mainWith, value) data MapData k v = MapData (HashMap k v) deriving Generic instance (NFData k, NFData v) => NFData (MapData k v) full, half, third :: Int full  = 10000 half  =  5000 third =  3333 main :: IO () main = mainWith $ do   value "HashMap"       (          mkHMList full)   value "HashMap half"  (          mkHMList half)   value "HashMap third" (          mkHMList third)   value "MapData"       (MapData $ mkHMList full) mkHMList :: Int -> HashMap Int String mkHMList n = fromList . zip [1..n] $ replicate n "some text" -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Fri Jun 29 12:47:17 2018 From: michael at snoyman.com (Michael Snoyman) Date: Fri, 29 Jun 2018 15:47:17 +0300 Subject: [Haskell-cafe] Using Wai with Conduit and ResourceT (was Re: (New to Conduits) mixing lazy lists and Conduits?) In-Reply-To: References: Message-ID: I'm not set up to run a FastCGI script easily on my system, but replacing your example with Warp as the handler works just fine on my machine. On Fri, Jun 29, 2018 at 12:41 PM Jon Fairbairn wrote: > Michael Snoyman writes: > > > I'd have to see a complete repro to know why the program in question > > doesn't stream. > > Thanks. Here’s a fairly small example > > ``` > module Main where > > import Prelude hiding (mapM_) > import Conduit > import Data.Conduit.List (mapM_) > import System.FilePath > import Data.ByteString.UTF8 > import Data.Binary.Builder > import GHC.IO.Exception (IOException) > > import Network.Wai.Handler.FastCGI (run) > import Network.Wai.Conduit (Application, responseStream) > import Network.HTTP.Types.Status > import Network.HTTP.Types.Header > > data_directory = "./test-data/" > > main = run $ app > > app:: Application > app request respond > = do respond > $ responseSourceRes status200 > [(hContentType, fromString "text/plain; charset=UTF-8")] > $ do yieldCBS "\nBEGIN\n" > yield Flush > wrapSourceFile $ data_directory "file1" > wrapSourceFile $ data_directory "a_pipe" > yieldCBS "END\n" > yield Flush > > wrapSourceFile:: (MonadUnliftIO m, MonadResource m) => FilePath -> > ConduitM a (Flush Builder) m () > wrapSourceFile path = do > yieldCBS ("\n" ++ path ++ ":\n") > catchC (sourceFile path .| mapC (Chunk . fromByteString)) (\e -> > yieldCBS $ "Error: " ++ show (e::IOException) ++ "\n") > yieldCBS "\n" > yield Flush > > yieldCBS:: Monad m => String -> ConduitT i (Flush Builder) m () > yieldCBS = yield . Chunk . fromByteString . fromString > > responseSourceRes status headers res_conduit > = responseStream status200 headers > (\send flush -> runConduitRes $ res_conduit > .| mapM_ (\e->liftIO $ > case e of > Chunk c -> send c > Flush -> flush )) > > ``` > > The various flushes in there were attempts to make something > come out. > > > But I _can_ explain how best to do something like this. > > > To frame this: why is something like ResourceT needed here? The issue is > we > > want to ensure exception safety around the open file handle, and > guarantee > > that the handle is closed regardless of any exceptions being thrown. > > ResourceT solves this problem by letting you register cleanup actions. > This > > allows for solving some really complicated dynamic allocation problems, > but > > for most cases it's overkill. Instead, a simple use of the bracket > pattern > > is sufficient. You can do that with `withSourceFile`: > > > > ``` > > #!/usr/bin/env stack > > -- stack --resolver lts-11.10 script > > import Network.Wai > > import Network.Wai.Handler.Warp > > import Network.Wai.Conduit > > import Network.HTTP.Types > > import Conduit > > import Data.ByteString.Builder (byteString) > > > > main :: IO () > > main = run 3000 app > > > > app :: Application > > app _req respond = > > withSourceFile "Main.hs" $ \src -> > > respond $ responseSource status200 [] > > $ src .| mapC (Chunk . byteString) > > I don’t think that will work for what I’m trying to do as the > decision to open which file is made within the conduit. > > > You can also do this by sticking with ResourceT, which requires jumping > > through some hoops with monad transformers to ensure the original > ResourceT > > context is used. I don't recommend this approach unless you really need > it: > > it's complicated, and slightly slower than the above. But in case you're > > curious: > > Thanks. I think that may be what I want, but it’ll take a while > to digest > > -- > Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk > > _______________________________________________ > 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 jon.fairbairn at cl.cam.ac.uk Fri Jun 29 13:22:11 2018 From: jon.fairbairn at cl.cam.ac.uk (Jon Fairbairn) Date: Fri, 29 Jun 2018 14:22:11 +0100 Subject: [Haskell-cafe] Using Wai with Conduit and ResourceT (was Re: (New to Conduits) mixing lazy lists and Conduits?) References: Message-ID: Michael Snoyman writes: > I'm not set up to run a FastCGI script easily on my system, but replacing > your example with Warp as the handler works just fine on my machine. You beat me to it. I have been away from my machine and was part way through testing that when your message arrived. My original version works here too with warp, but not with FastCGI, so it’s something to do with using FastCGI. -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk From vanessa.mchale at iohk.io Fri Jun 29 13:34:40 2018 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Fri, 29 Jun 2018 08:34:40 -0500 Subject: [Haskell-cafe] Measuring memory usage In-Reply-To: <5e82210c-6aa4-a7d0-fce6-2668df343214@gmail.com> References: <5e82210c-6aa4-a7d0-fce6-2668df343214@gmail.com> Message-ID: You might consider profiling your application or making an event log instead. The event log should show GC activity and the heap profile should show memory usage more accurately. On 06/29/2018 07:31 AM, Vlatko Basic wrote: > > Hello, > > I've come to some strange results using Weigh package. > > It shows that HashMap inside 'data' is using much, much more memory. > > The strange thing is that I'm seeing too large mem usage in my app as > well (several "MapData" like in records), and trying to figure out > with 'weigh' what's keeping the mem. > > Noticed that when I change the code to use HashMap directly (not > inside 'data', that's the only change), the mem usage observed with > top drops down for ~60M, from 850M to 790M. > > > These are the test results for 10K, 5K and 3.3K items for "data > MapData k v = MapData (HashMap k v)" (at the end is the full runnable > example.) > > Case           Allocated  GCs > HashMap          262,824    0 > HashMap half      58,536    0 > HashMap third     17,064    0 > MapData        4,242,208    4 > > I tested by changing the order, disabling all but one etc., and the > results were the same. Same 'weigh' behaviour with IntMap and Map. > > > So, if anyone knows and has some experience with such issues, my > questions are: > > 1. Is 'weigh' package reliable/usable, at least to some extent? (the > results do show diff between full, half and third) > > 2. How do you measure mem consumptions of your large data/records? > > 3. If the results are even approximately valid, what could cause such > large discrepancies with 'data'? > > 4. Is there a way to see if some record has been freed from memory, GCed? > > > > module Main where > > import Prelude > > import Control.DeepSeq     (NFData) > import Data.HashMap.Strict (HashMap, fromList) > import GHC.Generics        (Generic) > import Weigh               (mainWith, value) > > > data MapData k v = MapData (HashMap k v) deriving Generic > instance (NFData k, NFData v) => NFData (MapData k v) > > full, half, third :: Int > full  = 10000 > half  =  5000 > third =  3333 > > main :: IO () > main = mainWith $ do >   value "HashMap"       (          mkHMList full) >   value "HashMap half"  (          mkHMList half) >   value "HashMap third" (          mkHMList third) >   value "MapData"       (MapData $ mkHMList full) > > mkHMList :: Int -> HashMap Int String > mkHMList n = fromList . zip [1..n] $ replicate n "some text" > > > > > > _______________________________________________ > 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 claude at mathr.co.uk Fri Jun 29 13:37:45 2018 From: claude at mathr.co.uk (Claude Heiland-Allen) Date: Fri, 29 Jun 2018 14:37:45 +0100 Subject: [Haskell-cafe] Measuring memory usage In-Reply-To: <5e82210c-6aa4-a7d0-fce6-2668df343214@gmail.com> References: <5e82210c-6aa4-a7d0-fce6-2668df343214@gmail.com> Message-ID: Hi Vlatko, On 29/06/18 13:31, Vlatko Basic wrote: > > Hello, > > I've come to some strange results using Weigh package. > > It shows that HashMap inside 'data' is using much, much more memory. > This seems to be astrictness issue - you may be measuring the size of a thunk instead of the resulting evaluated data. To confirm that this is the case, you can replace: data MapData k v = MapData (HashMap k v) deriving Generic with data MapData k v = MapData !(HashMap k v) deriving Generic Or replace:   value "MapData"       (MapData $ mkHMList full) with   value "MapData"       (MapData $! mkHMList full) Either of these changes gave me results like this: Case           Allocated  GCs HashMap          262,824    0 HashMap half      58,536    0 HashMap third     17,064    0 MapData          263,416    0 The real issue seems to be NFData not doing what you expect. I'm not sure what the generic NFData instance is supposed to do, as there is no instance Generic (HashMap k v), so maybe you need to write your own rnf if you don't like either of the above workarounds. Claude > > The strange thing is that I'm seeing too large mem usage in my app as > well (several "MapData" like in records), and trying to figure out > with 'weigh' what's keeping the mem. > > Noticed that when I change the code to use HashMap directly (not > inside 'data', that's the only change), the mem usage observed with > top drops down for ~60M, from 850M to 790M. > > > These are the test results for 10K, 5K and 3.3K items for "data > MapData k v = MapData (HashMap k v)" (at the end is the full runnable > example.) > > Case           Allocated  GCs > HashMap          262,824    0 > HashMap half      58,536    0 > HashMap third     17,064    0 > MapData        4,242,208    4 > > I tested by changing the order, disabling all but one etc., and the > results were the same. Same 'weigh' behaviour with IntMap and Map. > > > So, if anyone knows and has some experience with such issues, my > questions are: > > 1. Is 'weigh' package reliable/usable, at least to some extent? (the > results do show diff between full, half and third) > > 2. How do you measure mem consumptions of your large data/records? > > 3. If the results are even approximately valid, what could cause such > large discrepancies with 'data'? > > 4. Is there a way to see if some record has been freed from memory, GCed? > > > > module Main where > > import Prelude > > import Control.DeepSeq     (NFData) > import Data.HashMap.Strict (HashMap, fromList) > import GHC.Generics        (Generic) > import Weigh               (mainWith, value) > > > data MapData k v = MapData (HashMap k v) deriving Generic > instance (NFData k, NFData v) => NFData (MapData k v) > > full, half, third :: Int > full  = 10000 > half  =  5000 > third =  3333 > > main :: IO () > main = mainWith $ do >   value "HashMap"       (          mkHMList full) >   value "HashMap half"  (          mkHMList half) >   value "HashMap third" (          mkHMList third) >   value "MapData"       (MapData $ mkHMList full) > > mkHMList :: Int -> HashMap Int String > mkHMList n = fromList . zip [1..n] $ replicate n "some text" > > -- https://mathr.co.uk From vlatko.basic at gmail.com Fri Jun 29 14:02:22 2018 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Fri, 29 Jun 2018 16:02:22 +0200 Subject: [Haskell-cafe] Measuring memory usage In-Reply-To: References: <5e82210c-6aa4-a7d0-fce6-2668df343214@gmail.com> Message-ID: <11826c09-3815-aec9-2981-7a3e991da4a1@gmail.com> Good advice for eventlog. I read about it long ago and completely forgot we have it. :-) > -------- Original Message -------- > Subject: Re: [Haskell-cafe] Measuring memory usage > From: Vanessa McHale > To: haskell-cafe at haskell.org > Date: 29/06/18 15:34 > > > You might consider profiling your application or making an event log instead. > The event log should show GC activity and the heap profile should show memory > usage more accurately. > > > On 06/29/2018 07:31 AM, Vlatko Basic wrote: >> >> Hello, >> >> I've come to some strange results using Weigh package. >> >> It shows that HashMap inside 'data' is using much, much more memory. >> >> The strange thing is that I'm seeing too large mem usage in my app as well >> (several "MapData" like in records), and trying to figure out with 'weigh' >> what's keeping the mem. >> >> Noticed that when I change the code to use HashMap directly (not inside >> 'data', that's the only change), the mem usage observed with top drops down >> for ~60M, from 850M to 790M. >> >> >> These are the test results for 10K, 5K and 3.3K items for "data MapData k v = >> MapData (HashMap k v)" (at the end is the full runnable example.) >> >> Case           Allocated  GCs >> HashMap          262,824    0 >> HashMap half      58,536    0 >> HashMap third     17,064    0 >> MapData        4,242,208    4 >> >> I tested by changing the order, disabling all but one etc., and the results >> were the same. Same 'weigh' behaviour with IntMap and Map. >> >> >> So, if anyone knows and has some experience with such issues, my questions are: >> >> 1. Is 'weigh' package reliable/usable, at least to some extent? (the results >> do show diff between full, half and third) >> >> 2. How do you measure mem consumptions of your large data/records? >> >> 3. If the results are even approximately valid, what could cause such large >> discrepancies with 'data'? >> >> 4. Is there a way to see if some record has been freed from memory, GCed? >> >> >> >> module Main where >> >> import Prelude >> >> import Control.DeepSeq     (NFData) >> import Data.HashMap.Strict (HashMap, fromList) >> import GHC.Generics        (Generic) >> import Weigh               (mainWith, value) >> >> >> data MapData k v = MapData (HashMap k v) deriving Generic >> instance (NFData k, NFData v) => NFData (MapData k v) >> >> full, half, third :: Int >> full  = 10000 >> half  =  5000 >> third =  3333 >> >> main :: IO () >> main = mainWith $ do >>   value "HashMap"       (          mkHMList full) >>   value "HashMap half"  (          mkHMList half) >>   value "HashMap third" (          mkHMList third) >>   value "MapData"       (MapData $ mkHMList full) >> >> mkHMList :: Int -> HashMap Int String >> mkHMList n = fromList . zip [1..n] $ replicate n "some text" >> >> >> >> >> >> _______________________________________________ >> 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 vlatko.basic at gmail.com Fri Jun 29 14:14:18 2018 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Fri, 29 Jun 2018 16:14:18 +0200 Subject: [Haskell-cafe] Measuring memory usage In-Reply-To: References: <5e82210c-6aa4-a7d0-fce6-2668df343214@gmail.com> Message-ID: <3c92991e-1882-3e32-a313-c40282ab3cc6@gmail.com> Indeed bang solves the issue. I didn't try it because the docs says value doesn't have to be forced for validateFunc (which is used for value), but obviously only to whnf. Thanks. :-) Been wasting whole morning on this. -------- Original Message -------- Subject: Re: [Haskell-cafe] Measuring memory usage From: Claude Heiland-Allen To: haskell-cafe at haskell.org Date: 29/06/18 15:37 > Hi Vlatko, > > On 29/06/18 13:31, Vlatko Basic wrote: >> >> Hello, >> >> I've come to some strange results using Weigh package. >> >> It shows that HashMap inside 'data' is using much, much more memory. >> > This seems to be astrictness issue - you may be measuring the size of a thunk > instead of the resulting evaluated data. > > To confirm that this is the case, you can replace: > > data MapData k v = MapData (HashMap k v) deriving Generic > > with > > data MapData k v = MapData !(HashMap k v) deriving Generic > > Or replace: > >   value "MapData"       (MapData $ mkHMList full) > > with > >   value "MapData"       (MapData $! mkHMList full) > > Either of these changes gave me results like this: > > Case           Allocated  GCs > HashMap          262,824    0 > HashMap half      58,536    0 > HashMap third     17,064    0 > MapData          263,416    0 > > The real issue seems to be NFData not doing what you expect. I'm not sure what > the generic NFData instance is supposed to do, as there is no instance Generic > (HashMap k v), so maybe you need to write your own rnf if you don't like either > of the above workarounds. > > Claude >> >> The strange thing is that I'm seeing too large mem usage in my app as well >> (several "MapData" like in records), and trying to figure out with 'weigh' >> what's keeping the mem. >> >> Noticed that when I change the code to use HashMap directly (not inside >> 'data', that's the only change), the mem usage observed with top drops down >> for ~60M, from 850M to 790M. >> >> >> These are the test results for 10K, 5K and 3.3K items for "data MapData k v = >> MapData (HashMap k v)" (at the end is the full runnable example.) >> >> Case           Allocated  GCs >> HashMap          262,824    0 >> HashMap half      58,536    0 >> HashMap third     17,064    0 >> MapData        4,242,208    4 >> >> I tested by changing the order, disabling all but one etc., and the results >> were the same. Same 'weigh' behaviour with IntMap and Map. >> >> >> So, if anyone knows and has some experience with such issues, my questions are: >> >> 1. Is 'weigh' package reliable/usable, at least to some extent? (the results >> do show diff between full, half and third) >> >> 2. How do you measure mem consumptions of your large data/records? >> >> 3. If the results are even approximately valid, what could cause such large >> discrepancies with 'data'? >> >> 4. Is there a way to see if some record has been freed from memory, GCed? >> >> >> >> module Main where >> >> import Prelude >> >> import Control.DeepSeq     (NFData) >> import Data.HashMap.Strict (HashMap, fromList) >> import GHC.Generics        (Generic) >> import Weigh               (mainWith, value) >> >> >> data MapData k v = MapData (HashMap k v) deriving Generic >> instance (NFData k, NFData v) => NFData (MapData k v) >> >> full, half, third :: Int >> full  = 10000 >> half  =  5000 >> third =  3333 >> >> main :: IO () >> main = mainWith $ do >>   value "HashMap"       (          mkHMList full) >>   value "HashMap half"  (          mkHMList half) >>   value "HashMap third" (          mkHMList third) >>   value "MapData"       (MapData $ mkHMList full) >> >> mkHMList :: Int -> HashMap Int String >> mkHMList n = fromList . zip [1..n] $ replicate n "some text" >> >> From claude at mathr.co.uk Fri Jun 29 18:34:01 2018 From: claude at mathr.co.uk (Claude Heiland-Allen) Date: Fri, 29 Jun 2018 19:34:01 +0100 Subject: [Haskell-cafe] Measuring memory usage In-Reply-To: <3c92991e-1882-3e32-a313-c40282ab3cc6@gmail.com> References: <5e82210c-6aa4-a7d0-fce6-2668df343214@gmail.com> <3c92991e-1882-3e32-a313-c40282ab3cc6@gmail.com> Message-ID: <13af408bce83dfdf0f97ce0935d5e5ba@mathr.co.uk> On 2018-06-29 15:14, Vlatko Basic wrote: > Indeed bang solves the issue. I didn't try it because the docs says > value doesn't have to be forced for validateFunc (which is used for > value), but obviously only to whnf. I think the issue is something to do with the two default implementations for rnf in the NFData class. Historically, `rnf a = seq a ()` was the default implementation (ie just WHNF), but more recently there is a Generic-based version that should automatically reduce to normal form. I don't know why the Generic version is either 1. not used at all, or 2. not working properly, but I suspect lack of instance Generic (HashMap k v), or possibly instance Generic1/2 MapData (if they are things?), may have something to do with it. I don't know why there is no instance, but maybe it would allow breaking internal data structure invariants? Claude > > Thanks. :-) > Been wasting whole morning on this. > > > -------- Original Message -------- > Subject: Re: [Haskell-cafe] Measuring memory usage > From: Claude Heiland-Allen > To: haskell-cafe at haskell.org > Date: 29/06/18 15:37 > >> Hi Vlatko, >> >> On 29/06/18 13:31, Vlatko Basic wrote: >>> >>> Hello, >>> >>> I've come to some strange results using Weigh package. >>> >>> It shows that HashMap inside 'data' is using much, much more memory. >>> >> This seems to be astrictness issue - you may be measuring the size of >> a thunk instead of the resulting evaluated data. >> >> To confirm that this is the case, you can replace: >> >> data MapData k v = MapData (HashMap k v) deriving Generic >> >> with >> >> data MapData k v = MapData !(HashMap k v) deriving Generic >> >> Or replace: >> >>   value "MapData"       (MapData $ mkHMList full) >> >> with >> >>   value "MapData"       (MapData $! mkHMList full) >> >> Either of these changes gave me results like this: >> >> Case           Allocated  GCs >> HashMap          262,824    0 >> HashMap half      58,536    0 >> HashMap third     17,064    0 >> MapData          263,416    0 >> >> The real issue seems to be NFData not doing what you expect. I'm not >> sure what the generic NFData instance is supposed to do, as there is >> no instance Generic (HashMap k v), so maybe you need to write your own >> rnf if you don't like either of the above workarounds. >> >> Claude >>> >>> The strange thing is that I'm seeing too large mem usage in my app as >>> well (several "MapData" like in records), and trying to figure out >>> with 'weigh' what's keeping the mem. >>> >>> Noticed that when I change the code to use HashMap directly (not >>> inside 'data', that's the only change), the mem usage observed with >>> top drops down for ~60M, from 850M to 790M. >>> >>> >>> These are the test results for 10K, 5K and 3.3K items for "data >>> MapData k v = MapData (HashMap k v)" (at the end is the full runnable >>> example.) >>> >>> Case           Allocated  GCs >>> HashMap          262,824    0 >>> HashMap half      58,536    0 >>> HashMap third     17,064    0 >>> MapData        4,242,208    4 >>> >>> I tested by changing the order, disabling all but one etc., and the >>> results were the same. Same 'weigh' behaviour with IntMap and Map. >>> >>> >>> So, if anyone knows and has some experience with such issues, my >>> questions are: >>> >>> 1. Is 'weigh' package reliable/usable, at least to some extent? (the >>> results do show diff between full, half and third) >>> >>> 2. How do you measure mem consumptions of your large data/records? >>> >>> 3. If the results are even approximately valid, what could cause such >>> large discrepancies with 'data'? >>> >>> 4. Is there a way to see if some record has been freed from memory, >>> GCed? >>> >>> >>> >>> module Main where >>> >>> import Prelude >>> >>> import Control.DeepSeq     (NFData) >>> import Data.HashMap.Strict (HashMap, fromList) >>> import GHC.Generics        (Generic) >>> import Weigh               (mainWith, value) >>> >>> >>> data MapData k v = MapData (HashMap k v) deriving Generic >>> instance (NFData k, NFData v) => NFData (MapData k v) >>> >>> full, half, third :: Int >>> full  = 10000 >>> half  =  5000 >>> third =  3333 >>> >>> main :: IO () >>> main = mainWith $ do >>>   value "HashMap"       (          mkHMList full) >>>   value "HashMap half"  (          mkHMList half) >>>   value "HashMap third" (          mkHMList third) >>>   value "MapData"       (MapData $ mkHMList full) >>> >>> mkHMList :: Int -> HashMap Int String >>> mkHMList n = fromList . zip [1..n] $ replicate n "some text" >>> >>> -- https://mathr.co.uk From dennis.raddle at gmail.com Fri Jun 29 21:52:38 2018 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Fri, 29 Jun 2018 14:52:38 -0700 Subject: [Haskell-cafe] need help understanding how to specify constraints on monads In-Reply-To: <20180629065122.fukh7paiafi4xf46@weber> References: <20180629065122.fukh7paiafi4xf46@weber> Message-ID: Hi Tom, Sounds like a good idea. I'll make it a record and see how that works out. ​ -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Sat Jun 30 21:26:34 2018 From: ben at well-typed.com (Ben Gamari) Date: Sat, 30 Jun 2018 17:26:34 -0400 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.6.1-alpha1 available Message-ID: <87fu14ufsp.fsf@smart-cactus.org> The GHC development team is pleased to announce the first alpha release leading up to GHC 8.6.1. The usual release artifacts are available from https://downloads.haskell.org/~ghc/8.6.1-alpha1 This is the first release (partially) generated using our new CI infrastructure. One known issue is that the haddock documentation is currently unavailable. This will be fixed in the next alpha release. Do let us know if you spot anything else amiss. As always, do let us know if you encounter any trouble in the course of testing. Thanks for your help! Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From ben at well-typed.com Sat Jun 30 21:33:10 2018 From: ben at well-typed.com (Ben Gamari) Date: Sat, 30 Jun 2018 17:33:10 -0400 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.6.1-alpha1 available In-Reply-To: <87fu14ufsp.fsf@smart-cactus.org> References: <87fu14ufsp.fsf@smart-cactus.org> Message-ID: <87d0w8ufhn.fsf@smart-cactus.org> Small correction inline. Ben Gamari writes: > The GHC development team is pleased to announce the first > alpha release leading up to GHC 8.6.1. The usual release artifacts > are available from > > https://downloads.haskell.org/~ghc/8.6.1-alpha1 > > This is the first release (partially) generated using our new CI > infrastructure. One known issue is that the haddock documentation is > currently unavailable. Correction: the issue is not restricted only to haddock documentation; the users guide is also not present. -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From simon at joyful.com Sat Jun 30 21:33:15 2018 From: simon at joyful.com (Simon Michael) Date: Sat, 30 Jun 2018 22:33:15 +0100 Subject: [Haskell-cafe] ANN: hledger-1.10 Message-ID: <9A1F2792-8703-4C09-B6C9-3F0FF96D4A6F@joyful.com> hledger (http://hledger.org) is a friendly, robust, cross-platform program for tracking money, time or other commodities, using double-entry accounting, simple plain text file formats, and command-line, curses or web UIs. I'm very pleased to announce hledger 1.10, including work by release contributors: Alex Chen, Everett Hildenbrandt, Jakub Zárybnický, Nolan Darilek, Dmitry Astapov, Jacob Weisz, Peter Simons, Stephen Morgan, Pavlo Kerestey, Trevor Riles, Léo Gaspard, Mykola Orliuk, Wad, Nana Amfo. You'll note this is not 2.0 as previously planned - we will spend a bit more time on that. The next major release is expected to be on 2018/09/30. Please see http://hledger.org/release-notes#hledger-1.10 for the changes (as soon as I can get to those; until then, the package changelogs): http://hackage.haskell.org/package/hledger-1.10/changelog http://hackage.haskell.org/package/hledger-ui-1.10/changelog http://hackage.haskell.org/package/hledger-web-1.10/changelog http://hackage.haskell.org/package/hledger-api-1.10/changelog http://hackage.haskell.org/package/hledger-lib-1.10/changelog How to get started: ------------------- See http://hledger.org/download for all install methods. One of the easiest is the hledger-install script, which requires only bash and will build and install the hledger tools in $HOME/.local/bin/: $ curl -O https://raw.githubusercontent.com/simonmichael/hledger/master/hledger-install/hledger-install.sh $ less hledger-install.sh # (do security review) $ bash hledger-install.sh # (add -v for more detail; use bash -x to show commands being run) or (insecure): $ curl https://raw.githubusercontent.com/simonmichael/hledger/master/hledger-install/hledger-install.sh | bash After installation, ensure $HOME/.local/bin is in your $PATH, and try some commands: $ hledger -h # quick help $ hledger help # list built-in manuals $ hledger add # record some transactions $ hledger # list available commands Next, I encourage you to at least skim the tutorials and docs at http://hledger.org. Say hello and ask questions in the #hledger IRC channel on Freenode: http://irc.hledger.org. New users and contributors are always welcome! Give feedback, report bugs, send pull requests, write, evangelise, donate. Best! -Simon From vanessa.mchale at iohk.io Sat Jun 30 23:26:17 2018 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Sat, 30 Jun 2018 18:26:17 -0500 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.6.1-alpha1 available In-Reply-To: <87fu14ufsp.fsf@smart-cactus.org> References: <87fu14ufsp.fsf@smart-cactus.org> Message-ID: <2c30ad4c-7dfd-9b08-6972-022a7f3933af@iohk.io> The parser seems to be broken. Attempting to build basement yields: Basement/Nat.hs:15:46: error: parse error on input ‘*’ | 15 | , type (<=), type (<=?), type (+), type (*), type (^), type (-) | ^ I'm not 100% sure where to report bugs for the alpha. On 06/30/2018 04:26 PM, Ben Gamari wrote: > The GHC development team is pleased to announce the first > alpha release leading up to GHC 8.6.1. The usual release artifacts > are available from > > https://downloads.haskell.org/~ghc/8.6.1-alpha1 > > This is the first release (partially) generated using our new CI > infrastructure. One known issue is that the haddock documentation is > currently unavailable. This will be fixed in the next alpha release. Do > let us know if you spot anything else amiss. > > As always, do let us know if you encounter any trouble in the course of > testing. Thanks for your help! > > Cheers, > > - Ben > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 488 bytes Desc: OpenPGP digital signature URL: From rae at cs.brynmawr.edu Sat Jun 30 23:33:11 2018 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Sat, 30 Jun 2018 19:33:11 -0400 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.6.1-alpha1 available In-Reply-To: <2c30ad4c-7dfd-9b08-6972-022a7f3933af@iohk.io> References: <87fu14ufsp.fsf@smart-cactus.org> <2c30ad4c-7dfd-9b08-6972-022a7f3933af@iohk.io> Message-ID: I've created a ticket for this: https://ghc.haskell.org/trac/ghc/ticket/15329 Thanks for letting us know! > On Jun 30, 2018, at 7:26 PM, Vanessa McHale wrote: > > The parser seems to be broken. Attempting to build basement yields: > > Basement/Nat.hs:15:46: error: parse error on input ‘*’ | 15 | , type (<=), type (<=?), type (+), type (*), type (^), type (-) | ^ > > I'm not 100% sure where to report bugs for the alpha. > > On 06/30/2018 04:26 PM, Ben Gamari wrote: >> The GHC development team is pleased to announce the first >> alpha release leading up to GHC 8.6.1. The usual release artifacts >> are available from >> >> https://downloads.haskell.org/~ghc/8.6.1-alpha1 >> >> This is the first release (partially) generated using our new CI >> infrastructure. One known issue is that the haddock documentation is >> currently unavailable. This will be fixed in the next alpha release. Do >> let us know if you spot anything else amiss. >> >> As always, do let us know if you encounter any trouble in the course of >> testing. Thanks for your help! >> >> Cheers, >> >> - Ben >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From vanessa.mchale at iohk.io Sat Jun 30 23:34:14 2018 From: vanessa.mchale at iohk.io (Vanessa McHale) Date: Sat, 30 Jun 2018 18:34:14 -0500 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.6.1-alpha1 available In-Reply-To: References: <87fu14ufsp.fsf@smart-cactus.org> <2c30ad4c-7dfd-9b08-6972-022a7f3933af@iohk.io> Message-ID: <5e4edb8e-9a3a-7213-e908-cb87776d105b@iohk.io> Great, thanks! On 06/30/2018 06:33 PM, Richard Eisenberg wrote: > I've created a ticket for > this: https://ghc.haskell.org/trac/ghc/ticket/15329 > > Thanks for letting us know! > >> On Jun 30, 2018, at 7:26 PM, Vanessa McHale > > wrote: >> >> The parser seems to be broken. Attempting to build basement >> yields: >> >> Basement/Nat.hs:15:46: error: parse error on input ‘*’ | 15 | , type >> (<=), type (<=?), type (+), type (*), type (^), type (-) | ^ >> >> I'm not 100% sure where to report bugs for the alpha. >> >> On 06/30/2018 04:26 PM, Ben Gamari wrote: >>> The GHC development team is pleased to announce the first >>> alpha release leading up to GHC 8.6.1. The usual release artifacts >>> are available from >>> >>> https://downloads.haskell.org/~ghc/8.6.1-alpha1 >>> >>> This is the first release (partially) generated using our new CI >>> infrastructure. One known issue is that the haddock documentation is >>> currently unavailable. This will be fixed in the next alpha release. Do >>> let us know if you spot anything else amiss. >>> >>> As always, do let us know if you encounter any trouble in the course of >>> testing. Thanks for your help! >>> >>> Cheers, >>> >>> - Ben >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> _______________________________________________ >> 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 matthewtpickering at gmail.com Sat Jun 30 23:38:02 2018 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Sun, 1 Jul 2018 00:38:02 +0100 Subject: [Haskell-cafe] [ANNOUNCE] GHC 8.6.1-alpha1 available In-Reply-To: <87fu14ufsp.fsf@smart-cactus.org> References: <87fu14ufsp.fsf@smart-cactus.org> Message-ID: Users of nix can test their package using the instructions in this gist. It should be straightforward as the 8.6.1 alpha will be downloaded from the binary cache. https://gist.github.com/mpickering/fd26e9f03d6cb88cbb91b90b6019f3dd The compiler will use patches form head.hackage in order to build dependencies. Any problems, let me know. Matt On Sat, Jun 30, 2018 at 10:26 PM, Ben Gamari wrote: > > The GHC development team is pleased to announce the first > alpha release leading up to GHC 8.6.1. The usual release artifacts > are available from > > https://downloads.haskell.org/~ghc/8.6.1-alpha1 > > This is the first release (partially) generated using our new CI > infrastructure. One known issue is that the haddock documentation is > currently unavailable. This will be fixed in the next alpha release. Do > let us know if you spot anything else amiss. > > As always, do let us know if you encounter any trouble in the course of > testing. Thanks for your help! > > Cheers, > > - Ben > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >