5
votes

I want to have a function q of type:

q :: ([b] -> b) -> ([(a, b)] -> (a, b))

which takes a function that selects a single element from a list, and lifts* that function into the context of selecting a single pair from a pair of lists (completely ignoring the first element of the pairs).

Is it even possible to write such a function? I haven't been able to make any progress on this.

*is 'lift' the right word?


Example use: if I have a function:

safeMaximum :: b -> [b] -> b

> safeMaximum 18 [] 
18
> safeMaximum 18 [4,5,1,4,3]
5

I then want to use safeMaximum to get, from a list of pairs, the pair whose 2nd element is the largest:

liftedSafeMaximum :: (a, b) -> [(a, b)] -> (a, b)
liftedSafeMaximum val = q val safeMaximum

liftedSafeMaximum ("?", 3) []
> ("?", 3)
liftedSafeMaximum ("?", 3) [("xyz", 1), ("123", 3), ("hi", 2)]
> ("123", 3)
5
I'd guess you can't, since, if the [(a, b)] list is empty, you'd need to make an a out of thin air. You could write q :: ([b] -> b) -> ([(a, b)] -> Maybe (a, b)), though.scvalex
@scvalex Or you can not terminate. undefined etc. are ugly and a bad idea, but legal.user395760
Good point, but I need a function that actually works.Matt Fenwick
@scvalex you're right, but even if I change the signature to q :: (a, b) -> ([b] -> b) -> ([(a, b)] -> (a, b)) I'm still stuck.Matt Fenwick

5 Answers

4
votes

You can get something like this to work if you're willing to refine your definition of a selector function slightly. Instead of selecting an element from a list directly, we will have a polymorphic function that, given a projection that allows it to look at the part of each element it's interested in, will select an item from a list.

All q has to do then, is give it snd as the projection to use.

{-# LANGUAGE Rank2Types #-}

import Data.Ord (comparing)
import Data.List (maximumBy)

q :: (forall c. (c -> b) -> c -> [c] -> c) -> (a, b) -> [(a, b)] -> (a, b)
q select = select snd

safeMaximumOn :: Ord b => (a -> b) -> a -> [a] -> a
safeMaximumOn proj x xs = maximumBy (comparing proj) (x:xs)

liftedSafeMaximum :: Ord b => (a, b) -> [(a, b)] -> (a, b)
liftedSafeMaximum = q safeMaximumOn

This is essentially the same idea from a previous answer of mine.

3
votes

You describe this as wanting to "lift a function into a context", so let's see what that works out to mean. Starting from the desired type:

q :: (a, b) -> ([b] -> b) -> ([(a, b)] -> (a, b))

...we can optimistically abstract over the desired context:

q :: f b -> ([b] -> b) -> ([f b] -> f b)

Assuming that f is a Functor--which it is, in the motivating example--we could lift [b] -> b to f [b] -> f b. We could get from that to the desired type if we had a function of type [f b] -> f [b], which looks a lot like sequence.

Consider the case where f is ((->) a) instead: given a function [b] -> b and a list [a -> b], we can return a function a -> b that applies its argument of type a to every function in the list, uses the selector function, then returns the result of type b. That sounds like what you're after!

Unfortunately it doesn't work for your specific example--the Monad involved is the writer monad, which would add a Monoid constraint on a and always return the monoid sum of every a value in the list.

The reason it fails is that we have only an opaque selection function for b values, which by necessity must be used without any context, which entails using something like sequence to extract (and in the process merge) all the individual contexts. To write the function you want, you'd need a way to merge contexts without losing information associating a context to each element.

The reader monad works where others don't because the "merge" process involved is unique--applying a single argument to multiple functions is based on a contravariant use of the canonical comonoid given by \x -> () and \x -> (x, x), where each result element uniquely determines the original input.

To get the same property in covariant position, we would need a monoid where each input element uniquely determines the resulting sum, which implies that every input must be the same, which implies that they must be of a type with only one value. Based on that, we can indeed write a version of your function with a slightly more restricted type:

q' :: ([b] -> b) -> ([((), b)] -> ((), b))

But I suppose that's not very satisfying. :]

2
votes

Isn't this trivial now, with the new signature/interface?

import Data.List (elemIndex)

q v f [] = v
q v f xs = let ys = map snd xs; x = f (snd v) ys in
           case elemIndex x ys of Just i -> xs !! i ; _ -> v 
                                               -- or (fst v, x) if you prefer

There can be no safeMaximum without the Ord constraint, right? So was that an omission, or by design?

1
votes

Not with that exact type signature, no. For example, if you choose type b = Double->Double and your function [b]->b is foldr (.) id, then your polymorphic function q cannot use the value produced there to select from the pairs, but I think that's misinterpreting your problem as seeking a specific type sig, rather than promoting/lifting a means of selection from elements to pairs.

Solving the raw selection problem

If your original function is used simply to select an element from a list, you could tell Haskell how to select between two, instead.

This solution is safe in the sense that it enforces using a selection from the original list or your fallback element, by using a helper function b -> b -> Bool, where True indicates you prefer the first argument.

We can use that to select from a pair:

selectPair :: (a -> a -> Bool) -> (a,c) -> (a,c) -> (a,c)
selectPair f (a,c) (a',c') 
    | f a a'    = (a,c)
    | otherwise = (a',c')

And then fold to select from a list:

selectList :: (a -> a -> Bool) -> (a,c) -> [(a,c)] -> (a,c)
selectList f = foldr (selectPair f)

Notice that this doesn't require any instances on the type a, so might be what you need in a general setting.

Solving the maximum problem

Of course (b -> b -> Bool) feels very like > from an Ord instance, and your example used a function suggesting maximum, but if you've got an Ord instance, it would would be simplest to use import Data.List and Data.Function to do

safePairMaximum :: Ord b => (a, b) -> [(a, b)] -> (a, b)
safePairMaximum m bs = maximumBy (compare `on` snd) $ m:bs

This is a more basic, less cool version of part of hammar's solution.

Maybe you're stuck-with [b]->b, but do have equality on b

This gets as close to your type signature as I think is sensible whilst still solving your stated problem: If using a selection function ::[b]->b is crucial, then you'll need at least an Eq context:

chooseLike :: Eq b => (a, b) -> ([b] -> b) -> ([(a, b)] -> (a, b))
chooseLike m selectb pairs = let wanted = selectb $ map snd pairs in
    case filter ((==wanted).snd) pairs of
      [] -> m
      (p:_) -> p

(You can of course replace the Eq context with a (b -> b -> Bool) argument, this time indicating equality.)

This isn't ideal, because you traverse the [b] list seperately to the [(a,b)] list, which seems inefficient.

Conclusion

Although I believe there's no useful function of exactly the type you specify, there are various ways of solving the problem you stated. It was an interesting question, thanks.

1
votes

I don't believe this is possible in a meaningful way. Since this is just intuition, and I can't prove it, I'll just give a counterexample:

Let's say I have the function sum :: Num a => [a] -> a. I can apply it to a list:

sum [1 .. 4]
> 10

But let's say I wanted to apply my 'lifted' sum:

liftedSum [("abc", 1), ("def", 2), ("ghi", 3), ("jkl", 4)]
> (??WTF??, 10)

What meaningful value should ??WTF?? have? I can't think of one.

The problem was I interpreted [b] -> b as "pick one" when really, it can also mean "aggregate". And there's no meaningful way to 'lift' an aggregate function into tuples, as I was trying to do.

But another problem is that, even if [b] -> b means "pick one", you can't use that to uniquely pick from [(a, b)], if there are duplicate b values. Example:

liftedMax [("abc", 1), ("def", 2), ("ghi", 2)]
> (>> is this "def" or "ghi"? <<, 2)

So I don't think that my function can be reasonably implemented, and I think it's cool that Haskell's type system made it hard for me to shoot myself in the foot.