Reputation: 20390
I want to get the minimum of two maybe values, or if one is nothing get the non-nothing one, or return nothing if both inputs are nothing. I can write a simple function to do this, but I suspect there is a way to do this without writing a custom function. Sorry, if this is a petty question, but is there a simpler way than using this custom function?
minMaybe :: Ord a => Maybe a -> Maybe a -> Maybe a
minMaybe Nothing b = b
minMaybe a Nothing = a
minMaybe (Just a) (Just b) = Just $ min a b
Upvotes: 8
Views: 2079
Reputation: 48591
I think radomaj had a good idea.
import Data.Ord (Down (..))
import Data.Function (on)
minMaybes mx my =
getDown <$> (max `on` fmap Down) mx my
getDown (Down x) = x
We use max
to prefer Just
to Nothing
, and then use Down
so we actually get the minimum if both are Just
.
Here's another, similar approach that seems a bit cleaner. Maybe
can be seen a way to tack on an extra minimal value, Nothing
, to an arbitrary Ord
type. We can write our own type to tack on a maximal value:
data AddMax a = TheMax | Plain a deriving Eq
instance Ord a => Ord (AddMax a) where
TheMax <= Plain _ = False
_ <= TheMax = True
Plain a <= Plain b = a <= b
maybeToAddMax :: Maybe a -> AddMax a
maybeToAddMax = maybe TheMax Plain
addMaxToMaybe :: AddMax a -> Maybe a
addMaxToMaybe TheMax = Nothing
addMaxToMaybe (Plain a) = Just a
Now you can write
minMaybes mx my = addMaxToMaybe $
(min `on` maybeToAddMax) mx my
You can also pull a little sleight-of-hand:
{-# LANGUAGE ScopedTypeVariables, TypeApplications #-}
import Data.Ord
import Data.Function
import Data.Coerce
newtype AddMax a = AddMax {unAddMax :: Down (Maybe (Down a))}
deriving (Eq, Ord)
Now
minMaybes :: forall a. Ord a => Maybe a -> Maybe a -> Maybe a
minMaybes = coerce (min @(AddMax a))
Upvotes: 0
Reputation: 336
Question is about lifting function min :: Ord a ⇒ a → a → a
to work with Maybe
s context. It's associative so Semigroup
instance does exactly what you want:
min' :: forall a. Ord a => Maybe a -> Maybe a -> Maybe a
min' = coerce ((<>) @(Maybe (Min a)))
This requires ScopedTypeVariables
and TypeApplications
. coerce
comes from Data.Coerce
. More old fashioned solution given below. But version above should be more performant: coerce
doesn't exist at runtime. Although GHC may eliminate fmap
s there's no guarantee:
min'' :: Ord a => Maybe a -> Maybe a -> Maybe a
min'' x y = fmap getMin (fmap Min x <> fmap Min y)
P.S. I would say that your solution is just fine.
Upvotes: 2
Reputation: 43383
It is possible to satisfy the specification using operators from Control.Applicative
.
myMin :: Ord x => Maybe x -> Maybe x -> Maybe x
myMin a b = min <$> a <*> b <|> a <|> b
where the <|>
for Maybe
implements "preference"
Nothing <|> b = b
a <|> _ = a
The thing is
min <$> Just a <*> Just b = Just (min a b)
but
min <$> Just a <*> Nothing = Nothing
which has resulted in some incorrect answers to this question. Using <|>
allows you to prefer the computed min
value when it's available, but recover with either individual when only one is Just
.
But you should ask if it is appropriate to use Maybe
in this way. With the inglorious exception of its Monoid
instance, Maybe
is set up to model failure-prone computations. What you have here is the extension of an existing Ord
with a "top" element.
data Topped x = Val x | Top deriving (Show, Eq, Ord)
and you'll find that min
for Topped x
is just what you need. It's good to think of types as not just the representation of data but the equipment of data with structure. Nothing
usually represents some kind of failure, so it might be better to use a different type for your purpose.
Upvotes: 22
Reputation: 11963
You can write it using the Alternative
instance of Maybe
:
minMaybe a b = liftA2 min a b <|> a <|> b
Alternatively, you could use maxBound
as default, so it'll always choose the other:
minMaybe a b = liftA2 min (d a) (d b)
where d x = x <|> Just maxBound
But I don't recommend that.
Upvotes: 3
Reputation: 105886
You cannot use the Applicative
, or Monad
instance for this, since any Nothing
in those contexts will have your total result being a Nothing
. That being said, the term "simpler" is highly opinionated, and your function is fine as it is.
Upvotes: 3