"maybe"-like function for Bool and List? - haskell

Sometimes i find myself progamming the pattern "if the Bool is not false" or "if the list is not empty use it, otherwise use something else".
I am looking for functions for Bool and List that are what the "maybe" function is to Maybe. Are there any?
Update: I meant to use the Bool-case as a generalization of the List-case. For example when working with Data.Text as T:
if T.null x then x else foo x
I am looking to reduce such boiler plate code.

maybe is the catamorphism of the Maybe type.
foldr is the catamorphism of the list type.
Data.Bool.bool is the catamorphism of the Bool type.
If you had used maybe like: maybe x (const y)
You could use: foldr (const (const y)) x
Your example if T.null x then x else foo x could be written with bool as
bool foo id (T.null x) x
(it takes the False case first, the opposite of if)

I think the answer is probably that there isn't such a generic function. As djv says, you can perhaps build on Data.Monoid to write one, something like:
maybe' :: (Eq a, Monoid a) => b -> (a -> b) -> a -> b
maybe' repl f x = if x == mempty then repl else f x
But I don't know of any functions in the standard library like that (or any that could easily be composed together to do so).

Check Data.Monoid, it's a typeclass describing data types which have a designated empty value and you can pattern-match on it to write your generic function. There are instances for Bool with empty value False and for List with empty value [].

Related

Pattern matching with Alternative empty or Applicative pure

I know it is possible, to pattern match against (named) constructors like so:
f1 :: Maybe a -> Bool
f1 Nothing = False
f1 (Just x) = True -- in reality have something that uses x here
f2 :: [a] -> Int
f2 [] = False
f2 x = True
How can I write such a function for general Alternatives similar to
f :: (Alternative m) => m a -> Bool
f empty = False
f x = True
If I try this, I get the error Parse error in pattern: empty. Which makes sense, I guess, as empty as a function here and not a constructor. But how can I accomplish this for general Alternatives idiomatically?
Edit 1:
My actual goal is to define a Monad instance (and probably also a MonadPlus instance) for a custom result type. Instead of the basic Either Error Result type, it should support a Maybe Error (and if possible also other Alternatives like [Error]) as error type and also some Applicative as result type in order to support lazy evaluation, for example with the result type (Maybe Error, [Tokens]) of a tokenizer.
I'd like something similar to
instance (Alterantive mErr, Applicative mRes) => Monad (mErr e, mRes a) where
return x = (empty, pure x)
(empty, pure x) >>= f = f x
(err, x) >>= f = (err, x)
The best you can do is:
f :: (Eq (m a), Alternative m) => m a -> Bool
f x | x == empty = False
| otherwise = True
It is in fact possible using -XPatternSynonyms and -XViewPatterns:
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
import Control.Applicative (empty)
pattern Empty :: (Eq (m a), Alternative m) => m a
pattern Empty <- ((==) empty -> True)
f :: (Eq (m a), Alternative m) => m a -> Bool
f Empty = False
f _ = True
Slipping in an Eq constraint, as in mithrandi's answer, is indeed the best that can be done. In any case, it is worth emphasising that it comes at a cost: we are now stuck with an Eq constant that would be unnecessary were we merely pattern match against, say, [] or Nothing. A common way to avoid this problem is using null :: Foldable t => t a -> Bool. Here, however, that option is not great either, as Foldable is largely unrelated to Alternative and rather alien to your use case. In particular, there is no guarantee that, in the general case, there will be just one value for which null holds, which means it might conceivably hold for values that aren't the empty of the relevant Alternative instance.
Ultimately, then, the only tool that would fully fit the requirements might well be some Alternative subclass with an isEmpty method. I don't think that exists anywhere, and the power-to-weight ratio doesn't seem encouraging when it comes to conjuring such a thing.

Getting all function arguments in haskel as list

Is there a way in haskell to get all function arguments as a list.
Let's supose we have the following program, where we want to add the two smaller numbers and then subtract the largest. Suppose, we can't change the function definition of foo :: Int -> Int -> Int -> Int. Is there a way to get all function arguments as a list, other than constructing a new list and add all arguments as an element of said list? More importantly, is there a general way of doing this independent of the number of arguments?
Example:
module Foo where
import Data.List
foo :: Int -> Int -> Int -> Int
foo a b c = result!!0 + result!!1 - result!!2 where result = sort ([a, b, c])
is there a general way of doing this independent of the number of arguments?
Not really; at least it's not worth it. First off, this entire idea isn't very useful because lists are homogeneous: all elements must have the same type, so it only works for the rather unusual special case of functions which only take arguments of a single type.
Even then, the problem is that “number of arguments” isn't really a sensible concept in Haskell, because as Willem Van Onsem commented, all functions really only have one argument (further arguments are actually only given to the result of the first application, which has again function type).
That said, at least for a single argument- and final-result type, it is quite easy to pack any number of arguments into a list:
{-# LANGUAGE FlexibleInstances #-}
class UsingList f where
usingList :: ([Int] -> Int) -> f
instance UsingList Int where
usingList f = f []
instance UsingList r => UsingList (Int -> r) where
usingList f a = usingList (f . (a:))
foo :: Int -> Int -> Int -> Int
foo = usingList $ (\[α,β,γ] -> α + β - γ) . sort
It's also possible to make this work for any type of the arguments, using type families or a multi-param type class. What's not so simple though is to write it once and for all with variable type of the final result. The reason being, that would also have to handle a function as the type of final result. But then, that could also be intepreted as “we still need to add one more argument to the list”!
With all respect, I would disagree with #leftaroundabout's answer above. Something being
unusual is not a reason to shun it as unworthy.
It is correct that you would not be able to define a polymorphic variadic list constructor
without type annotations. However, we're not usually dealing with Haskell 98, where type
annotations were never required. With Dependent Haskell just around the corner, some
familiarity with non-trivial type annotations is becoming vital.
So, let's take a shot at this, disregarding worthiness considerations.
One way to define a function that does not seem to admit a single type is to make it a method of a
suitably constructed class. Many a trick involving type classes were devised by cunning
Haskellers, starting at least as early as 15 years ago. Even if we don't understand their
type wizardry in all its depth, we may still try our hand with a similar approach.
Let us first try to obtain a method for summing any number of Integers. That means repeatedly
applying a function like (+), with a uniform type such as a -> a -> a. Here's one way to do
it:
class Eval a where
eval :: Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval i = \y -> eval (i + y)
instance Eval Integer where
eval i = i
And this is the extract from repl:
λ eval 1 2 3 :: Integer
6
Notice that we can't do without explicit type annotation, because the very idea of our approach is
that an expression eval x1 ... xn may either be a function that waits for yet another argument,
or a final value.
One generalization now is to actually make a list of values. The science tells us that
we may derive any monoid from a list. Indeed, insofar as sum is a monoid, we may turn arguments to
a list, then sum it and obtain the same result as above.
Here's how we can go about turning arguments of our method to a list:
class Eval a where
eval2 :: [Integer] -> Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [Integer] where
eval2 is i = i:is
This is how it would work:
λ eval2 [] 1 2 3 4 5 :: [Integer]
[5,4,3,2,1]
Unfortunately, we have to make eval binary, rather than unary, because it now has to compose two
different things: a (possibly empty) list of values and the next value to put in. Notice how it's
similar to the usual foldr:
λ foldr (:) [] [1,2,3,4,5]
[1,2,3,4,5]
The next generalization we'd like to have is allowing arbitrary types inside the list. It's a bit
tricky, as we have to make Eval a 2-parameter type class:
class Eval a i where
eval2 :: [i] -> i -> a
instance (Eval a i) => Eval (i -> a) i where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [i] i where
eval2 is i = i:is
It works as the previous with Integers, but it can also carry any other type, even a function:
(I'm sorry for the messy example. I had to show a function somehow.)
λ ($ 10) <$> (eval2 [] (+1) (subtract 2) (*3) (^4) :: [Integer -> Integer])
[10000,30,8,11]
So far so good: we can convert any number of arguments into a list. However, it will be hard to
compose this function with the one that would do useful work with the resulting list, because
composition only admits unary functions − with some trickery, binary ones, but in no way the
variadic. Seems like we'll have to define our own way to compose functions. That's how I see it:
class Ap a i r where
apply :: ([i] -> r) -> [i] -> i -> a
apply', ($...) :: ([i] -> r) -> i -> a
($...) = apply'
instance Ap a i r => Ap (i -> a) i r where
apply f xs x = \y -> apply f (x:xs) y
apply' f x = \y -> apply f [x] y
instance Ap r i r where
apply f xs x = f $ x:xs
apply' f x = f [x]
Now we can write our desired function as an application of a list-admitting function to any number
of arguments:
foo' :: (Num r, Ord r, Ap a r r) => r -> a
foo' = (g $...)
where f = (\result -> (result !! 0) + (result !! 1) - (result !! 2))
g = f . sort
You'll still have to type annotate it at every call site, like this:
λ foo' 4 5 10 :: Integer
-1
− But so far, that's the best I can do.
The more I study Haskell, the more I am certain that nothing is impossible.

Haskell - Maybe Either

-- | Convert a 'Maybe a' to an equivalent 'Either () a'. Should be inverse
-- to 'eitherUnitToMaybe'.
maybeToEitherUnit :: Maybe a -> Either () a
maybeToEitherUnit a = error "Not yet implemented: maybeToEitherUnit"
-- | Convert a 'Either () a' to an equivalent 'Maybe a'. Should be inverse
-- to 'maybeToEitherUnit'.
eitherUnitToMaybe :: Either () a -> Maybe a
eitherUnitToMaybe = error "Not yet implemented: eitherUnitToMaybe"
-- | Convert a pair of a 'Bool' and an 'a' to 'Either a a'. Should be inverse
-- to 'eitherToPairWithBool'.
pairWithBoolToEither :: (Bool,a) -> Either a a
pairWithBoolToEither = undefined -- What should I do here?
-- | Convert an 'Either a a' to a pair of a 'Bool' and an 'a'. Should be inverse
-- to 'pairWithBoolToEither'.
eitherToPairWithBool :: Either a a -> (Bool,a)
eitherToPairWithBool = undefined -- What should I do here?
-- | Convert a function from 'Bool' to 'a' to a pair of 'a's. Should be inverse
-- to 'pairToFunctionFromBool'.
functionFromBoolToPair :: (Bool -> a) -> (a,a)
functionFromBoolToPair = error "Not yet implemented: functionFromBoolToPair"
-- | Convert a pair of 'a's to a function from 'Bool' to 'a'. Should be inverse
-- to 'functionFromBoolToPair'.
pairToFunctionFromBool :: (a,a) -> (Bool -> a)
pairToFunctionFromBool = error "Not yet implemented: pairToFunctionFromBool"
I don't really know what to do. I know what maybe is, but I think I have a problem with either, because Either a a makes no sense in my mind. Either a b would be okay. This is either a or b but Either a a is a?!
I don't have any idea in general how to write these functions.
Given that I think this is homework, I'll not answer, but give important hints:
If you look for the definitions on hoogle (http://www.haskell.org/hoogle/)
you find
data Bool = True | False
data Either a b = Left a | Right b
This means that Bool can only be True or False, but that Either a b can be Left a or Right b.
which means your functions should look like
pairWithBoolToEither :: (Bool,a) -> Either a a
pairWithBoolToEither (True,a) = ....
pairWithBoolToEither (False,a) = ....
and
eitherToPairWithBool :: Either a a -> (Bool,a)
eitherToPairWithBool (Left a) = ....
eitherToPairWithBool (Right a) = ....
Comparing with Maybe
Maybe a is given by
data Maybe a = Just a | Nothing
so something of type Maybe Int could be Just 7 or Nothing.
Similarly, something of type Either Int Char could be Left 5 or Right 'c'.
Something of type Either Int Int could be Left 7 or Right 4.
So something with type Either Int Char is either an Int or a Char, but something of type Either Int Int is either an Int or an Int. You don't get to choose anything other than Int, but you'll know whether it was a Left or a Right.
Why you've been asked this/thinking behind it
If you have something of type Either a a, then the data (eg 5 in Left 5) is always of type a, and you've just tagged it with Left or Right. If you have something of type (Bool,a) the a-data (eg 5 in (True,5)) is always the same type, and you've paired it with False or True.
The maths word for two things which perhaps look different but actually have the same content is "isomorphic". Your instructor has asked you to write a pair of functions which show this isomorphism. Your answer will go down better if pairWithBoolToEither . eitherToPairWithBool and eitherToPairWithBool . pairWithBoolToEither do what id does, i.e. don't change anything. In fact, I've just spotted the comments in your question, where it says they should be inverses. In your write-up, you should show this by doing tests in ghci like
ghci> eitherToPairWithBool . pairWithBoolToEither $ (True,'h')
(True,'h')
and the other way round.
(In case you haven't seen it, $ is defined by f $ x = f x but $ has really low precedence (infixr 0 $), so f . g $ x is (f . g) $ x which is just (f . g) x and . is function composition, so (f.g) x = f (g x). That was a lot of explanation to save one pair of brackets!)
Functions that take or return functions
This can be a bit mind blowing at first when you're not used to it.
functionFromBoolToPair :: (Bool -> a) -> (a,a)
The only thing you can pattern match a function with is just a variable like f, so we'll need to do something like
functionFromBoolToPair f = ...
but what can we do with that f? Well, the easiest thing to do with a function you're given is to apply it to a value. What value(s) can we use f on? Well f :: (Bool -> a) so it takes a Bool and gives you an a, so we can either do f True or f False, and they'll give us two (probably different) values of type a. Now that's handy, because we needed to a values, didn't we?
Next have a look at
pairToFunctionFromBool :: (a,a) -> (Bool -> a)
The pattern match we can do for the type (a,a) is something like (x,y) so we'll need
pairToFunctionFromBool (x,y) = ....
but how can we return a function (Bool -> a) on the right hand side?
There are two ways I think you'll find easiest. One is to notice that since -> is right associative anyway, the type (a,a) -> (Bool -> a) is the same as (a,a) -> Bool -> a so we can actually move the arguments for the function we want to return to before the = sign, like this:
pairToFunctionFromBool (x,y) True = ....
pairToFunctionFromBool (x,y) False = ....
Another way, which feels perhaps a little easier, would to make a let or where clause to define a function called something like f, where f :: Bool -> a< a bit like:
pairToFunctionFromBool (x,y) = f where
f True = ....
f False = ....
Have fun. Mess around.
Perhaps it's useful to note that Either a b is also called the coproduct, or sum, of the types a and b. Indeed it is now common to use
type (+) = Either
You can then write Either a b as a + b.
eitherToPairWithBool :: (a+a) -> (Bool,a)
Now common sense would dictate that we rewrite a + a as something like 2 ⋅ a. Believe it or not, that is exactly the meaning of the tuple type you're transforming to!
To explain: algebraic data types can roughly be seen as "counting1 the number of possible constructions". So
data Bool = True | False
has two constructors. So sort of (this is not valid Haskell!)
type 2 = Bool
Tuples allow all the combinations of constructors from each argument. So for instance in (Bool, Bool), we have the values
(False,False)
(False,True )
(True, False)
(True, True )
You've guessed it: tuples are also called products. So the type (Bool, a) is basically 2 ⋅ a: for every value x :: a, we can create both the (False, x) tuple and the (True, x) tuple, alltogether twice as many as there are x values.
Much the same thing for Either a a: we always have both Left x and Right x as a possible value.
All your functions with "arithmetic types":
type OnePlus = Maybe
maybeToEitherUnit :: OnePlus a -> () + a
eitherUnitToMaybe :: () + a -> OnePlus a
pairWithBoolToEither :: 2 ⋅ a -> a + a
eitherToPairWithBool :: a + a -> 2 ⋅ a
functionFromBoolToPair :: a² -> a⋅a
pairToFunctionFromBool :: a⋅a -> a²
1For pretty much any interesting type there are actually infinitely many possible values, still this kind of naïve arithmetic gets you surprisingly far.
Either a a makes no sense in my mind.
Yes it does. Try to figure out the difference between type a and Either a a. Either is a disjoint union. Once you understand the difference between a and Either a a, your homework should be easy in conjunction with AndrewC's answer.
Note that Either a b means quite literally that a value of such a type can be either an a, or an a. It sounds like you have actually grasped this concept, but the piece you're missing is that the Either type differentiates between values constructed with Left and those constructed with Right.
For the first part, the idea is that Maybe is either Just a thing or Nothing -- Nothing corresponds to () because both are "in essence" data types with only one possible value.
The idea behind converting (Bool, a) pairs to Either a a pairs might seem a little trickier, but just think about the correspondence between True and False and Left and Right.
As for converting functions of type (Bool -> a) to (a, a) pairs, here's a hint: Consider the fact that Bool can only have two types, and write down what that initial function argument might look like.
Hopefully those hints help you to get started.

How to restrict a tuple?

I think tuples in Haskell are like
tuple :: (a,b)
which means a and b can be the same type or can be diffrent types
so if i define a function without giving the type for it then i will get probably (t,t1) or some diffrent types when i write :t function in ghci.
So is it possible to get only the same types without defining it in function.
I heard its not allowed in haskell
so i cant write some function like
function [(x,x)]=[(x,x,x)]
to get the
:t function
function :: [(a,a)]->[(a,a,a)]
This is an exercise that i am trying to do and this exercise want me to write a function without defining a type.For example to get
Bool->(Char,Bool)
when i give
:t function
in ghci. i should ve write--
function True=('A',True)
i am not allowed to define the type part of a function
So i cant write
function::(Eq a)=>[(a,a)]->[(a,a,a)]
or something like that
You can use the function asTypeOf from the Prelude to restrict the type of the second component of your tuple to be the same as the type of the first component. For example, in GHCi:
> let f (x, y) = (x, y `asTypeOf` x, x)
> :t f
f :: (t, t) -> (t, t, t)
You can happily restrict the types to be equivalent .. by writing out the required type.
type Pair a = (a,a)
type Triple a = (a,a,a)
and then:
fn :: [Pair a] -> [Triple a]
will enforce the constraint you want.
You can use type, as Don says. Or, if you don't want to bother with that (perhaps you only need it for one function), you can specify the type signature of the function like this:
function :: [(a,a)] -> [(a,a,a)]
function xs = map (\(a, b) -> (a, b, a)) xs -- just an example
I guess what you're looking for is the asTypeOf function. Using it you can restrict a type of some value to be the same as the one of another value in the function definition. E.g.:
Prelude> :t \(a, b) -> (a, b `asTypeOf` a)
\(a, b) -> (a, b `asTypeOf` a) :: (t, t) -> (t, t)
The following should work without asTypeOf:
trans (a,b) = case [a,b] of _ -> (a,b,a)
function xs = map trans xs
OK, if I've understood this correctly, the problem you're having really has nothing to do with types. Your definition,
function [(x,x)]=[(x,x,x)]
won't work because you're saying, in effect, "if the argument to
function is a list with one element, and that element is a tuple,
then call then bind x to the first part of the tuple and also bind
x to the second part of the tuple".
You can't bind a symbol to two expressions at once.
If what you really want is to ensure that both parts of the tuple
are the same, then you can do something like this:
function [(x,y)] = if x == y then [(x,x,x)] else error "mismatch"
or this:
function2 [(x,y)] | x == y = [(x,x,x)]
...but that will fail when the parts of the tuple don't match.
Now I suspect what you really want is to handle lists with more than
one element. So you might want to do something like:
function3 xs = map f xs
where f (x, y) = if x == y then [(x,x,x)] else error "mismatch"
Any of these functions will have the type you want, Eq t => [(t, t)] -> [(t, t, t)] without you having to specify it.

Shorter way to write this code

The following pattern appears very frequently in Haskell code. Is there a shorter way to write it?
if pred x
then Just x
else Nothing
You're looking for mfilter in Control.Monad:
mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
-- mfilter odd (Just 1) == Just 1
-- mfilter odd (Just 2) == Nothing
Note that if the condition doesn't depend on the content of the MonadPlus, you can write instead:
"foo" <$ guard (odd 3) -- Just "foo"
"foo" <$ guard (odd 4) -- Nothing
Hm... You are looking for a combinator that takes an a, a function a -> Bool and returns a Maybe a. Stop! Hoogle time. There is no complete match, but find is quite close:
find :: (a -> Bool) -> [a] -> Maybe a
I doubt that you can actually find your function somewhere. But why not define it by yourself?
ifMaybe :: (a -> Bool) -> a -> Maybe a
ifMaybe f a | f a = Just a
ifMaybe _ _ = Nothing
You can use guard to achieve this behavior:
guard (pred x) >> return x
This is such a generally useful behavior that I've even defined ensure in my own little suite of code for one-offs (everybody has such a thing, right? ;-):
ensure p x = guard (p x) >> return x
Use:
(?:) (5>2) (Just 5,Nothing)
from Data.Bool.HT.
f pred x = if pred x then Just x else Nothing
Given the above definition, you can simply write:
f pred x
Of course this is no different than Daniel Wagner's ensure or FUZxxl's ifMaybe. But it's name is simply f, making it the shortest, and it's definition is precisely the code you gave, making it the most easily proven correct. ;)
Some ghci, just for fun
ghci> let f pred x = if pred x then Just x else Nothing
ghci> f (5>) 2
Just 2
ghci> f (5>) 6
Nothing
If you couldn't tell, this isn't a very serious answer. The others are a bit more insightful, but I couldn't resist the tongue-in-cheek response to "make this code shorter".
Usually I'm a big fan of very generic code, but I actually find this exact function useful often enough, specialized to Maybe, that I keep it around instead of using guard, mfilter, and the like.
The name I use for it is justIf, and I'd typically use it for doing things like this:
∀x. x ⊢ import Data.List
∀x. x ⊢ unfoldr (justIf (not . null . snd) . splitAt 3) [1..11]
[[1,2,3],[4,5,6],[7,8,9]]
Basically, stuff where some sort of element-wise filtering or checking needs to be done in a compound expression, so Maybe is used to indicate the result of the predicate.
For the specialized version like this, there really isn't much you can do to make it shorter. It's already pretty simple. There's a fine line between being concise, and just golfing your code for character count, and for something this simple I wouldn't really worry about trying to "improve" it...

Resources