
I've got this import Data.Maybe data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) whereIsBM Empty = Nothing whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM lx) which I would like to tell me where the Bacon is (index), not just if there's Bacon, which is what it does now. That is, I need this to happen
whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) Empty)))) Just 2
So I need to traverse a BaconOrIndex list and count how deep I went to find the Bacon variable. I get the above code to evaluate error-free, but obviously I'm only returning a Just 1 when it sees Bacon. What I need is to have the last part be . . . else (1 + whereIsBM lx) work; but it keeps giving the error Non type-variable argument in the constraint: Num (Maybe a) (Use FlexibleContexts to permit this) • When checking the inferred type whereIsBM :: forall a. (Num a, Num (Maybe a)) => MyList BaconOrIndex -> Maybe a I haven't a clue what this means. Eventually, I'll wrap this in something that handles the Nothing and does fromJust on the alternative. This whole effort is because if I didn't use the Maybe strategy, and said whereIsBM Empty = 0 ... it would never give back 0 if it didn't find Bacon, rather, it would simply return the whole countdown to Empty. What can I do to make Maybe work here? LB

‘whereIsBM’ returns a Maybe-wrapped value, so applying ‘1 + …’ to it would
require ‘Maybe a’ to be in ‘Num’, hence the error message.
‘FlexibleContexts’ (ditto ‘FlexibleInstances’) is a pretty benign
extension, but it won’t help here, since it just kicks the error down the
road a bit.
The basic thing you need to do is match on the Maybe and return ‘Nothing’
if it was ‘Nothing’, or ‘Just (1 + x)’ if it was ‘Just x’ for some x. That
can be written quite literally as a ‘case’ expression:
case whereIsBM lx of
Just x -> Just (1 + x)
Nothing -> Nothing
Which could also be written with ‘do’:
do
x <- whereIsBM lx
pure (1 + x)
But this pattern is very common, so it’s already packaged up and
generalised as ‘fmap’, a.k.a. ‘<$>’
fmap (1 +) (whereIsBM lx)
-- or
(1 +) <$> whereIsBM lx
On Sun, Mar 28, 2021, 8:13 PM Galaxy Being
I've got this
import Data.Maybe
data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show)
whereIsBM Empty = Nothing whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM lx)
which I would like to tell me where the Bacon is (index), not just if there's Bacon, which is what it does now. That is, I need this to happen
whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) Empty)))) Just 2
So I need to traverse a BaconOrIndex list and count how deep I went to find the Bacon variable. I get the above code to evaluate error-free, but obviously I'm only returning a Just 1 when it sees Bacon. What I need is to have the last part be
. . . else (1 + whereIsBM lx)
work; but it keeps giving the error
Non type-variable argument in the constraint: Num (Maybe a) (Use FlexibleContexts to permit this) • When checking the inferred type whereIsBM :: forall a. (Num a, Num (Maybe a)) => MyList BaconOrIndex -> Maybe a
I haven't a clue what this means. Eventually, I'll wrap this in something that handles the Nothing and does fromJust on the alternative. This whole effort is because if I didn't use the Maybe strategy, and said
whereIsBM Empty = 0 ...
it would never give back 0 if it didn't find Bacon, rather, it would simply return the whole countdown to Empty. What can I do to make Maybe work here?
LB _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Sun, Mar 28, 2021 at 08:37:13PM -0700, Jon Purdy wrote:
fmap (1 +) (whereIsBM lx) -- or (1 +) <$> whereIsBM lx
Or with bounds checks: succ <$> whereIsBM lx but all these variants run out of stack on very long lists due to failure to be tail recursive. A more robust elemIndex implementation would be: elemIndex :: (Integral i, Eq a) => a -> [a] -> Maybe i elemIndex e = go 0 where go !_ [] = Nothing go !acc (x : xs) | x == e = Just acc | otherwise = go (succ acc) xs This is quite pedantic in generalising the index type from `Int` to `Integral`, and then using `succ` rather than (1 +) to ensure that overflow is detected: λ> :set -XBangPatterns λ> import Data.Int (Int8) λ> λ> :{ λ>| elemIndex :: (Integral i, Eq a) => a -> [a] -> Maybe i λ>| elemIndex e = go 0 λ>| where λ>| go !_ [] = Nothing λ>| go !acc (x : xs) | x == e = Just acc λ>| | otherwise = go (succ acc) xs λ>| :} λ> λ> elemIndex 42 [0..] :: Maybe Int8 Just 42 λ> λ> elemIndex 300 [0..] :: Maybe Int8 *** Exception: Enum.succ{Int8}: tried to take `succ' of maxBound More typically/sloppily one would just use "Int" and (+), in the expectation that Ints are 64 bits or more, and no list one could search is longer than 2^63-1 elements. Often that assumption is justified, but the strictly correct implementation is: elemIndex :: Eq a => a -> [a] -> Maybe Integer elemIndex e = go 0 where go !_ [] = Nothing go !acc (x : xs) | x == e = Just acc | otherwise = go (acc + 1) xs and the user would need to check the value for overflow before converting to some narrower integral type. The function is still however /partial/, in that given the infinite list [0..] and a negative target value it would now search forever. Which brings us to the more fundamental observation that if you're using a (linked) list to search through more than a handful of items you're very much in a state of sin. That's simply not the right data structure for the purpose. Linked lists should be used primarily for one shot iteration, rather than indexing, search or repeated traversal. Any appearance of a list index is a strong signal that the wrong data structure is in use. One should probably be using arrays or vectors in these cases, but in `base` we only have `array` in `GHC.Array`, and the interface is not friendly to new users. Thus I applaud Michael Snoyman's quest to address the absense of a basic array type in the `base` library. Perhaps more users would stop abusing lists (memoisable iterators) as an indexed store. -- Viktor.

On Mon, 29 Mar 2021, Viktor Dukhovni wrote:
Thus I applaud Michael Snoyman's quest to address the absense of a basic array type in the `base` library. Perhaps more users would stop abusing lists (memoisable iterators) as an indexed store.
Data.Array actually _was_ part of base-3. However, I think we should split 'base' in more smaller parts rather than making it bigger.

A bit of post-mortem... I got this data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) import Data.Maybe whereIsBM = whereIsBM' 1 whereIsBM' _ Empty = Nothing whereIsBM' !n (Cons Bacon _) = Just n whereIsBM' !n (Cons _ lx) = whereIsBM' (succ n) lx
whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8) Empty)))) Nothing whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons Bacon (Cons (Indx 8) Empty)))) Just 3
to work. Unfortunately, I couldn't get this whereIsBM boiList = go 0 where go !_ Empty = Nothing go !acc (Cons idx lx) | (idx == Bacon) = Just acc | otherwise = go (acc + 1) lx to work. Both are nearly identical, but the latter gives this error
whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8) Empty)))) No instance for (Show (MyList BaconOrIndex -> Maybe Integer)) : arising from a use of `print'
This also failed whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> (1 +) <$> (whereIsBM lx) Couldn't match type `Maybe (MyList BaconOrIndex)' with `MyList BaconOrIndex' Expected type: MyList BaconOrIndex -> Maybe a Actual type: Maybe (MyList BaconOrIndex) -> Maybe a Not sure why this didn't work. Would like to understand the whole fmap idea as applied here, though. On Mon, Mar 29, 2021 at 4:04 AM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 29 Mar 2021, Viktor Dukhovni wrote:
Thus I applaud Michael Snoyman's quest to address the absense of a basic array type in the `base` library. Perhaps more users would stop abusing lists (memoisable iterators) as an indexed store.
Data.Array actually _was_ part of base-3.
However, I think we should split 'base' in more smaller parts rather than making it bigger. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi. In this version
whereIsBM boiList = go 0 where go !_ Empty = Nothing go !acc (Cons idx lx) | (idx == Bacon) = Just acc | otherwise = go (acc + 1) lx
you abstract from boiList but then don't use it. You should either remove boiList on the left hand side or add it as a second argument to the call of the go function. In this version
whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> (1 +) <$> (whereIsBM lx)
you are pattern matching on boiList with Nothing / Just, as if it is of Maybe type, but judging from the other functions and also the recursive call, you're expecting it to be of type MyList. Cheers, Andres

On Mon, Mar 29, 2021 at 12:12:59PM -0500, Galaxy Being wrote:
A bit of post-mortem...
Perhaps the Haskell beginners list: https://mail.haskell.org/cgi-bin/mailman/listinfo/beginners will be more helpful, and a tad more appropriate for such questions? -- Viktor.

For the record, since I suggested this solution (without actually trying it):
whereIsBM boiList = case boiList of
Nothing -> Nothing
Just (Cons idx lx)
| (idx == Bacon) -> Just 1
| otherwise -> (1 +) <$> (whereIsBM lx)
The problem I did not realize here is that lx is of type BaconOrIndex, not Maybe BaconOrIndex. There are two solutions. What someone suggested of just making whereIsBM receive BaconOrIndex all the way (You're also missing the Empty case, I just realized, which maybe you confused with Nothing, so I add that one):
whereIsBM boiList = case boiList of
{
Empty -> Nothing;
Cons idx lx
| (idx == Bacon) -> Just 1
| otherwise -> (1 +) <$> (whereIsBM lx)
}
The other option is to just wrap lx in Just, but that really feels strange and not what you want, plus you'd still need to account for the Empty case.
________________________________
From: Haskell-Cafe
whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8) Empty)))) Nothing whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons Bacon (Cons (Indx 8) Empty)))) Just 3
to work. Unfortunately, I couldn't get this whereIsBM boiList = go 0 where go !_ Empty = Nothing go !acc (Cons idx lx) | (idx == Bacon) = Just acc | otherwise = go (acc + 1) lx to work. Both are nearly identical, but the latter gives this error
whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8) Empty)))) No instance for (Show (MyList BaconOrIndex -> Maybe Integer)) : arising from a use of `print'
This also failed
whereIsBM boiList = case boiList of
Nothing -> Nothing
Just (Cons idx lx)
| (idx == Bacon) -> Just 1
| otherwise -> (1 +) <$> (whereIsBM lx)
Couldn't match type `Maybe (MyList BaconOrIndex)'
with `MyList BaconOrIndex'
Expected type: MyList BaconOrIndex -> Maybe a
Actual type: Maybe (MyList BaconOrIndex) -> Maybe a
Not sure why this didn't work. Would like to understand the whole fmap idea as applied here, though.
On Mon, Mar 29, 2021 at 4:04 AM Henning Thielemann
Thus I applaud Michael Snoyman's quest to address the absense of a basic array type in the `base` library. Perhaps more users would stop abusing lists (memoisable iterators) as an indexed store.
Data.Array actually _was_ part of base-3. However, I think we should split 'base' in more smaller parts rather than making it bigger. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336. Is e buidheann carthannais a th' ann an Oilthigh Dh?n ?ideann, cl?raichte an Alba, ?ireamh cl?raidh SC005336.

I'm not getting past
whereIsBM boiList = case boiList of
Nothing -> Nothing
Just (Cons idx lx)
| (idx == Bacon) -> Just 1
| otherwise -> Just (1 + whereIsBM lx)
...and a few other attempts.
On Sun, Mar 28, 2021 at 10:37 PM Jon Purdy
‘whereIsBM’ returns a Maybe-wrapped value, so applying ‘1 + …’ to it would require ‘Maybe a’ to be in ‘Num’, hence the error message. ‘FlexibleContexts’ (ditto ‘FlexibleInstances’) is a pretty benign extension, but it won’t help here, since it just kicks the error down the road a bit.
The basic thing you need to do is match on the Maybe and return ‘Nothing’ if it was ‘Nothing’, or ‘Just (1 + x)’ if it was ‘Just x’ for some x. That can be written quite literally as a ‘case’ expression:
case whereIsBM lx of Just x -> Just (1 + x) Nothing -> Nothing
Which could also be written with ‘do’:
do x <- whereIsBM lx pure (1 + x)
But this pattern is very common, so it’s already packaged up and generalised as ‘fmap’, a.k.a. ‘<$>’
fmap (1 +) (whereIsBM lx) -- or (1 +) <$> whereIsBM lx
On Sun, Mar 28, 2021, 8:13 PM Galaxy Being
wrote: I've got this
import Data.Maybe
data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show)
whereIsBM Empty = Nothing whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM lx)
which I would like to tell me where the Bacon is (index), not just if there's Bacon, which is what it does now. That is, I need this to happen
whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) Empty)))) Just 2
So I need to traverse a BaconOrIndex list and count how deep I went to find the Bacon variable. I get the above code to evaluate error-free, but obviously I'm only returning a Just 1 when it sees Bacon. What I need is to have the last part be
. . . else (1 + whereIsBM lx)
work; but it keeps giving the error
Non type-variable argument in the constraint: Num (Maybe a) (Use FlexibleContexts to permit this) • When checking the inferred type whereIsBM :: forall a. (Num a, Num (Maybe a)) => MyList BaconOrIndex -> Maybe a
I haven't a clue what this means. Eventually, I'll wrap this in something that handles the Nothing and does fromJust on the alternative. This whole effort is because if I didn't use the Maybe strategy, and said
whereIsBM Empty = 0 ...
it would never give back 0 if it didn't find Bacon, rather, it would simply return the whole countdown to Empty. What can I do to make Maybe work here?
LB _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

As others explained, you still can't do (1 + whereIsBM Ix), you need to unwrap the whereIsBM value or use fmap (<$>).
Here, let me give you a small modification on your code that will do it:
whereIsBM boiList = case boiList of
Nothing -> Nothing
Just (Cons idx lx)
| (idx == Bacon) -> Just 1
| otherwise -> (1 +) <$> (whereIsBM lx)
And as others have explained, what this does is take the result of (whereIsBM Ix), which is a Maybe-wrapped value, and apply the function ((1 +) <$>) (alternatively, (fmap (1 +))), which basically just takes the function (1 +) (add 1 to a number) and applies it to whatever is wrapped inside the Maybe (your numbers), while keeping the Maybe structure. So if the result of (whereIsBM x) is Nothing, then applying ((1 +) <$>) will return Nothing because there's nothing wrapped, whereas if (whereIsBM x) is (Just n), then applying ((1 + ) <$>) to it will return (Just (1 + n)).
You could also, as others explained, case match on the result of (whereIsBM Ix), but that would be more verbose and probably just confuse you. But it is, ultimately, what fmap is actually doing. Unwrapping and re-wrapping.
________________________________
From: Haskell-Cafe
whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) Empty)))) Just 2
So I need to traverse a BaconOrIndex list and count how deep I went to find the Bacon variable. I get the above code to evaluate error-free, but obviously I'm only returning a Just 1 when it sees Bacon. What I need is to have the last part be . . . else (1 + whereIsBM lx) work; but it keeps giving the error Non type-variable argument in the constraint: Num (Maybe a) (Use FlexibleContexts to permit this) • When checking the inferred type whereIsBM :: forall a. (Num a, Num (Maybe a)) => MyList BaconOrIndex -> Maybe a I haven't a clue what this means. Eventually, I'll wrap this in something that handles the Nothing and does fromJust on the alternative. This whole effort is because if I didn't use the Maybe strategy, and said whereIsBM Empty = 0 ... it would never give back 0 if it didn't find Bacon, rather, it would simply return the whole countdown to Empty. What can I do to make Maybe work here? LB _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336. Is e buidheann carthannais a th’ ann an Oilthigh Dhùn Èideann, clàraichte an Alba, àireamh clàraidh SC005336.

A simple solution: data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show) whereIsBM = whereIsBM' 0 whereIsBM' _ Empty = Nothing whereIsBM' !n (Cons Bacon _) = Just n whereIsBM' !n (Cons _ lx) = whereIsBM' (succ n) lx You can omit the ! if you want. The result will be the same, but the computation will use more memory because the program will first construct the unevaluated data structure (called 'thunk') suc (suc (suc (... 0) ...)) and then compute it instead of computing succ 0 to 1, then succ 1 to 2, etc., step by step, in constant memory. succ n is n+1 but faster than the function (+). Best, Antonio Regidor Garcia El Sun, Mar 28, 2021 at 11:27:48PM -0500, Galaxy Being escribió:
I'm not getting past
whereIsBM boiList = case boiList of Nothing -> Nothing Just (Cons idx lx) | (idx == Bacon) -> Just 1 | otherwise -> Just (1 + whereIsBM lx)
...and a few other attempts.
On Sun, Mar 28, 2021 at 10:37 PM Jon Purdy
wrote: ‘whereIsBM’ returns a Maybe-wrapped value, so applying ‘1 + …’ to it would require ‘Maybe a’ to be in ‘Num’, hence the error message. ‘FlexibleContexts’ (ditto ‘FlexibleInstances’) is a pretty benign extension, but it won’t help here, since it just kicks the error down the road a bit.
The basic thing you need to do is match on the Maybe and return ‘Nothing’ if it was ‘Nothing’, or ‘Just (1 + x)’ if it was ‘Just x’ for some x. That can be written quite literally as a ‘case’ expression:
case whereIsBM lx of Just x -> Just (1 + x) Nothing -> Nothing
Which could also be written with ‘do’:
do x <- whereIsBM lx pure (1 + x)
But this pattern is very common, so it’s already packaged up and generalised as ‘fmap’, a.k.a. ‘<$>’
fmap (1 +) (whereIsBM lx) -- or (1 +) <$> whereIsBM lx
On Sun, Mar 28, 2021, 8:13 PM Galaxy Being
wrote: I've got this
import Data.Maybe
data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show) data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show)
whereIsBM Empty = Nothing whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM lx)
which I would like to tell me where the Bacon is (index), not just if there's Bacon, which is what it does now. That is, I need this to happen
whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) Empty)))) Just 2
So I need to traverse a BaconOrIndex list and count how deep I went to find the Bacon variable. I get the above code to evaluate error-free, but obviously I'm only returning a Just 1 when it sees Bacon. What I need is to have the last part be
. . . else (1 + whereIsBM lx)
work; but it keeps giving the error
Non type-variable argument in the constraint: Num (Maybe a) (Use FlexibleContexts to permit this) • When checking the inferred type whereIsBM :: forall a. (Num a, Num (Maybe a)) => MyList BaconOrIndex -> Maybe a
I haven't a clue what this means. Eventually, I'll wrap this in something that handles the Nothing and does fromJust on the alternative. This whole effort is because if I didn't use the Maybe strategy, and said
whereIsBM Empty = 0 ...
it would never give back 0 if it didn't find Bacon, rather, it would simply return the whole countdown to Empty. What can I do to make Maybe work here?
LB _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view 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.

On Mar 29, 2021, at 3:36 AM, Antonio Regidor Garcia
wrote: succ n is n+1 but faster than the function (+).
Because 'succ' typically does bounds checks, while (+) (for Int) just does the underlying CPU instruction, that's not particularly plausible. Indeed running a test (100 million increments) suggests that (+) is noticeably cheaper: (1 +): MUT time 0.035s ( 0.035s elapsed) (succ): MUT time 0.134s ( 0.134s elapsed) The succ function is however safer against uncaught overflow: λ> succ False True λ> succ True *** Exception: Prelude.Enum.Bool.succ: bad argument If the datatype in question is not bounded (Double, Integer, ...) then succ performance is closer to that of (+). I see identical speeds for Double, but (GHC 8.10 on X86_64) succ seems slightly slower for Integer. -- Viktor.

Mmm strange... I thought I read somewhere that succ is faster, but now I'm searching for the reference and don't find it. Anyway, good to know! Best, Antonio Regidor Garcia El Mon, Mar 29, 2021 at 04:22:07AM -0400, Viktor Dukhovni escribió:
On Mar 29, 2021, at 3:36 AM, Antonio Regidor Garcia
wrote: succ n is n+1 but faster than the function (+).
Because 'succ' typically does bounds checks, while (+) (for Int) just does the underlying CPU instruction, that's not particularly plausible.
Indeed running a test (100 million increments) suggests that (+) is noticeably cheaper:
(1 +): MUT time 0.035s ( 0.035s elapsed) (succ): MUT time 0.134s ( 0.134s elapsed)
The succ function is however safer against uncaught overflow:
λ> succ False True λ> succ True *** Exception: Prelude.Enum.Bool.succ: bad argument
If the datatype in question is not bounded (Double, Integer, ...) then succ performance is closer to that of (+). I see identical speeds for Double, but (GHC 8.10 on X86_64) succ seems slightly slower for Integer.
-- 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.
participants (7)
-
Andres Loeh
-
Antonio Regidor Garcia
-
CASANOVA Juan
-
Galaxy Being
-
Henning Thielemann
-
Jon Purdy
-
Viktor Dukhovni