<div dir="ltr"><div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
> f as alist = [ b | (a, b) <- alist, a `elem` as ]<br>
><br>
> perhaps?<br>
<br>
perhaps.  i have no idea how that works.  but don't spoil it for me though, i'm going to go of and study it :-)<br></blockquote><div><br></div></div><div dir="ltr"><div class="gmail_quote"><div>It's a <a href="https://wiki.haskell.org/List_comprehension" target="_blank">list comprehension</a>. I hope that's not too much of a spoiler :)<br> <br></div></div></div><div dir="ltr"><div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
unsure what the ~(ts, fs) syntax is though, removing the `~` doesn't seem to matter.<br></blockquote><div><br></div></div></div><div dir="ltr"><div class="gmail_quote"><div><a href="http://en.wikibooks.org/wiki/Haskell/Laziness#Lazy_pattern_matching" target="_blank">Makes it lazier</a><br></div></div></div><div dir="ltr"><div class="gmail_quote"><div> </div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
<br>
this seems fairly clean. i noticed that partition simply uses foldr.  it looks like select is just a helper so that partition isn't cluttered.  i'm unsure why select was broken out as a separate function instead of just being in a where clause.  possibly to be able to assign it a an explicit type signature ?<br></blockquote><div><br></div><div>You can assign type signatures in `let` and `where` clauses:
<br><br><pre style="color:#000000;background:#ffffff"><pre>f <span style="color:#808030">=</span> let i <span style="color:#800080">::</span> Int
        i <span style="color:#808030">=</span> <span style="color:#008c00">1</span>
    in increment i
    where
        increment <span style="color:#800080">::</span> Int <span style="color:#808030">-</span><span style="color:#808030">></span> Int
        increment <span style="color:#808030">=</span> <span style="color:#808030">(</span><span style="color:#808030">+</span><span style="color:#808030">)</span> <span style="color:#008c00">1</span></pre></pre>This is often quite a good idea. Type signatures are excellent, machine-checkable documentation.<br></div><div> </div></div></div><div dir="ltr"><div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
extract :: [(String,b)] -> [String] -> ([b], [String])<br>
extract alist l =<br>
  let inList s = lookup (uppercase s) alist<br>
      (l1, l2) = partitionMaybe inList l<br>
  in<br>
   (l1, l2)<br>
<br>
partitionMaybe :: (a -> Maybe b) -> [a] -> ([b],[a])<br>
partitionMaybe p xs = foldr (select p) ([],[]) xs<br>
<br>
select :: (a -> Maybe b) -> a -> ([b], [a]) -> ([b], [a])<br>
select p x ~(ts,fs) | isJust y = ((fromJust y):ts,fs)<br>
                    | otherwise = (ts, x:fs)<br>
  where<br>
    y = p x<br></blockquote><div><br> Couple of things:

<br><br>`fromJust` is a code smell. In general, you should at least consider replacing it with `fromMaybe (error msg)` where `msg` is a more useful error message than '*** Exception: Maybe.fromJust: Nothing'.

<br><br>Of course in this particular case, that will never come up because you can prove that `y` is never Nothing using the guard condition. But in that case, it's better practice to use pattern matching and let the compiler prove it for you:<br><br><pre style="color:#000000;background:#ffffff"><pre><span style="color:#400000">select</span> p y <span style="color:#808030">~</span><span style="color:#808030">(</span>xs<span style="color:#808030">,</span>ys<span style="color:#808030">)</span> <span style="color:#808030">=</span> acc $ p y
    where
        acc <span style="color:#808030">(</span>Just x<span style="color:#808030">)</span> <span style="color:#808030">=</span> <span style="color:#808030">(</span>x<span style="color:#800080">:</span>xs<span style="color:#808030">,</span>   ys<span style="color:#808030">)</span>
        acc Nothing  <span style="color:#808030">=</span> <span style="color:#808030">(</span>  xs<span style="color:#808030">,</span> y<span style="color:#800080">:</span>ys<span style="color:#808030">)<br><br><br></span></pre></pre>The `partitionMaybe` function looks a bit odd to me. The computation you're trying to express is 'If this computation succedes, return whatever value it returned, but if it fails return some default value'. This is not a natural use of the Maybe data type: that's what Either is for. There's even a `partitionEithers` library function. `lookup` returns Maybe, not Either, but we can fix that.
<br><br>Here's my go (I've changed around the API a little bit as well)<br>
</div><div><pre style="color:#000000;background:#ffffff"><pre>toEither <span style="color:#800080">::</span> a <span style="color:#808030">-</span><span style="color:#808030">></span> <span style="color:#808030">(</span>Maybe b<span style="color:#808030">)</span> <span style="color:#808030">-</span><span style="color:#808030">></span> Either a b
toEither _ <span style="color:#808030">(</span>Just x<span style="color:#808030">)</span> <span style="color:#808030">=</span> Right x
toEither y Nothing  <span style="color:#808030">=</span> Left  y

lookupEither <span style="color:#800080">::</span> Eq a <span style="color:#808030">=</span><span style="color:#808030">></span> a <span style="color:#808030">-</span><span style="color:#808030">></span> <span style="color:#808030">[</span><span style="color:#808030">(</span>a<span style="color:#808030">,</span>b<span style="color:#808030">)</span><span style="color:#808030">]</span> <span style="color:#808030">-</span><span style="color:#808030">></span> Either a b
lookupEither key assocs <span style="color:#808030">=</span> toEither key $ lookup key assocs

uppercase <span style="color:#800080">::</span> <span style="color:#603000">String</span> <span style="color:#808030">-</span><span style="color:#808030">></span> <span style="color:#603000">String</span>
uppercase <span style="color:#808030">=</span> map toUpper

extract <span style="color:#800080">::</span> <span style="color:#808030">[</span><span style="color:#603000">String</span><span style="color:#808030">]</span> <span style="color:#808030">-</span><span style="color:#808030">></span> <span style="color:#808030">[</span><span style="color:#808030">(</span><span style="color:#603000">String</span><span style="color:#808030">,</span>b<span style="color:#808030">)</span><span style="color:#808030">]</span> <span style="color:#808030">-</span><span style="color:#808030">></span> <span style="color:#808030">(</span><span style="color:#808030">[</span><span style="color:#603000">String</span><span style="color:#808030">]</span><span style="color:#808030">,</span><span style="color:#808030">[</span>b<span style="color:#808030">]</span><span style="color:#808030">)</span>
extract xs assocs <span style="color:#808030">=</span>
    let xs' <span style="color:#808030">=</span> map uppercase xs
        eithers <span style="color:#808030">=</span> map <span style="color:#808030">(</span>\x <span style="color:#808030">-</span><span style="color:#808030">></span> lookupEither x assocs<span style="color:#808030">)</span> xs'
        <span style="color:#808030">-</span><span style="color:#808030">-</span> spoilers<span style="color:#800080">:</span> same as <span style="color:#808030">[</span> lookupEither x assocs <span style="color:#808030">|</span> x <span style="color:#808030"><</span><span style="color:#808030">-</span> xs' <span style="color:#808030">]</span>
    in partitionEithers eithers

<span style="color:#400000">main</span> <span style="color:#800080">::</span> IO <span style="color:#808030">(</span><span style="color:#808030">)</span>
<span style="color:#400000">main</span> <span style="color:#808030">=</span> print $ extract <span style="color:#808030">[</span><span style="color:#800000">"</span><span style="color:#0000e6">Foo</span><span style="color:#800000">"</span><span style="color:#808030">,</span> <span style="color:#800000">"</span><span style="color:#0000e6">Bar</span><span style="color:#800000">"</span><span style="color:#808030">]</span> <span style="color:#808030">[</span><span style="color:#808030">(</span><span style="color:#800000">"</span><span style="color:#0000e6">FOO</span><span style="color:#800000">"</span><span style="color:#808030">,</span><span style="color:#008c00">1</span><span style="color:#808030">)</span><span style="color:#808030">,</span> <span style="color:#808030">(</span><span style="color:#800000">"</span><span style="color:#0000e6">BAZ</span><span style="color:#800000">"</span><span style="color:#808030">,</span><span style="color:#008c00">2</span><span style="color:#808030">)</span><span style="color:#808030">]</span><br></pre><br><pre><span style="color:#808030"></span>This differs slightly from your algorithm in that it returns '(["BAR"],[1]), where yours would return (["Bar"],[1]). If preserving the original case in the output, I would either write a `caseInsensitiveLookup` function, or use a <a href="https://hackage.haskell.org/package/case-insensitive-0.2.0.1/docs/Data-CaseInsensitive.html">case insensitive text</a> data type.</pre><br></pre><br></div></div></div></div>