From two functions create a tuple transform - haskell

What I am trying to do is that from a function, f, returning a pair. I want to make a pair of two functions, pf. And than implement the transform f2p.
f :: a -> (b,c)
pf :: (a->b,a->c)
f2p :: (a -> (b,c)) -> (a->b,a->c)
I find this suprisingly difficult, I think I should use function composition in some manner but the question seems so strangely formulated. What I have tried is just to create a dummy function for f looking like this.
f n = (n,n+1)
just to be able to work with the two other functions. But when I come to write the function pf, whatever I do I can not make it work like the defenition want it to. For example,
pf = (fst a, snd a)
where a = f 3
This just makes it into pf :: (Integer, Integer), wich is not really what I want. If I try to force it with pf :: (Num t) => (t->t,t->t) I get
Could not deduce (Num (t -> t)) arising from a use of ‘f’
I could really need some guidance!

If a = f x and f :: T -> (B, C), then a is already a (B, C) and not a function anymore. We only get a B or a C out of it, but we cannot plug in another T.
So we need to build two functions from f instead, such that
firstF x = fst (f x)
secondF x = snd (f x)
Actually, we're done at that point:
pf = (firstF, secondF)
We can now write f2p:
f2p :: (a -> (b,c)) -> (a -> b, a -> c)
f2p f = (fst . f, snd . f)

Related

Explanation of <$> and <*> when used with functions

I am learning haskell currently and I am having a really hard time wrapping my head around how to explain <$> and <*>'s behavior.
For some context this all came from searching how to use an or operation when using takeWhile and the answer I found was this
takeWhile ((||) <$> isDigit <*> (=='.'))
In most of the documentation I have seen, <*> is used with a container type.
show <*> Maybe 10
By looking at
(<$>) :: Functor f => (a -> b) -> f a -> f b
It tells me that <*> keeps the outer container if its contents and applies the right to the inside, then wraps it back into the container
a b f a f b
([Int] -> String) -> [Just]([Int]) -> [Just]([String])
This makes sense to me, in my mind the f a is essentially happening inside the container, but when I try the same logic, I can make sense to me but I cant correlate the logic
f = (+) <$> (read)
so for f it becomes
a b f a f b
([Int] -> [Int -> Int]) -> ([String] -> [Int]) -> ([String] -> [Int -> Int])
So f being the container really confuses me when I try and work out what this code is going to do. I understand when I write it out like this, I can work it out and see its basically equivalent to the .
(.) :: (b -> c) -> (a -> b) -> a -> c
b c a b a c
([Int] -> [Int -> Int]) -> ([String] -> [Int]) -> ([String] -> [Int -> Int])
so it can be written as
f = (+) . read
Why not just write it as just that? Why wasn't the original snippet just written as
takeWhile ((||) . isDigit <*> (=='.'))
or does <$> imply something in this context that . des not?
Now looking at <*>, it seems like it is basicly exactly the same as the <$> except it takes two containers, uses the inner of both, then puts it pack in the container
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
so
Just show <*> Just 10
f a b f a f b
[Just]([Int->Int]->[Int]) -> [Just]([Int->Int]) -> [Just]([Int])
However with functions, it becomes murky how things are being passed around to each other.
Looking at the original snippit and breaking it up
f1 :: Char -> Bool -> Bool
f1 = (||) . isDigit
f2 :: Char -> Bool
f2 = f1 <*> (== '.')
<*> behavior in f2 is
f a b f a f b
([Char] -> [Bool] -> [Bool]) -> ([Char] -> [Bool]) -> ([Char] -> [Bool])
So using previous logic, I see it as Char -> is the container, but its not very useful for me when working out what's happening.
It looks to me as if <*> is passing the function parameter into right side, then passing the same function parameter, and the return value into the left?
So to me, it looks equivalent to
f2 :: Char -> Bool
f2 x = f1 x (x=='_')
Its a bit of mental gymnastics for me to work out where the data is flowing when I see <*> and <$>. I guess im just looking for how an experienced haskell-er would read these operations in their head.
The applicative instance for functions is quite simple:
f <*> g = \x -> f x (g x)
You can verify for yourself that the types match up. And as you said,
(<$>) = (.)
(Ignoring fixity)
So you can rewrite your function:
(||) <$> isDigit <*> (=='.')
(||) . isDigit <*> (=='.')
\x -> ((||) . isDigit) x ((=='.') x)
-- Which can simply be rewritten as:
\x -> isDigit x || x == '.'
But it's important to understand why the function instance is as it is and how it works. Let's begin with Maybe:
instance Applicative Maybe where
pure :: a -> Maybe a
pure x = Just x
(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b
Nothing <*> _ = Nothing
_ <*> Nothing = Nothing
(Just f) <*> (Just x) = Just (f x)
Ignore the implementation here and just look at the types. First, notice that we've made Maybe an instance of Applicative. What exactly is Maybe? You might say that it's a type, but that isn't true - I can't write something like
x :: Maybe
- that doesn't make sense. Instead, I need to write
x :: Maybe Int
-- Or
x :: Maybe Char
or any other type after Maybe. So we give Maybe a type like Int or Char, and it suddenly becomes a type itself! That's why Maybe is what's known as a type constructor.
And that's exactly what the Applicative typeclass expects - a type constructor, which you can put any other type inside. So, using your analogy, we can think of giving Applicative a container type.
Now, what do I mean by
a -> b
?
We can rewrite it using prefix notation (the same way 1 + 2 = (+) 1 2)
(->) a b
And here we see that the arrow (->) itself is also just a type constructor - but unlike Maybe, it takes two types. But Applicative only wants a type constructor which takes one type. So we give it this:
instance Applicative ((->) r)
Which means that for any r, (->) r is an Applicative. Continuing the container analogy, (->) r is now a container for any type b such that the resulting type is r -> b. What that means is that the contained type is actually the future result of the function on giving it an r.
Now for the actual instance:
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
Substituting (->) r as the applicative,
(<*>) :: ((->) r (a -> b)) -> ((->) r a) ((->) r b)
-- Rewriting it in infix notation:
(<*>) :: (r -> (a -> b)) -> (r -> a) -> (r -> b)
How would we go about writing the instance? Well, we need a way to get the contained type out of the container - but we can't use pattern matching like we did with Maybe. So, we use a lambda:
(f :: r -> (a -> b)) <*> (g :: r -> a) = \(x :: r) -> f x (g x)
And the type of f x (g x) is b, so the entire lambda has type r -> b, which is exactly what we were looking for!
EDIT: I noticed that I didn't talk about the implementation of pure for functions - I could update the answer, but try seeing if you can use the type signature to work it out yourself!

How are monoid and applicative connected?

I am reading in the haskellbook about applicative and trying to understand it.
In the book, the author mentioned:
So, with Applicative, we have a Monoid for our structure and function
application for our values!
How is monoid connected to applicative?
Remark: I don't own the book (yet), and IIRC, at least one of the authors is active on SO and should be able to answer this question. That being said, the idea behind a monoid (or rather a semigroup) is that you have a way to create another object from two objects in that monoid1:
mappend :: Monoid m => m -> m -> m
So how is Applicative a monoid? Well, it's a monoid in terms of its structure, as your quote says. That is, we start with an f something, continue with f anotherthing, and we get, you've guessed it a f resulthing:
amappend :: f (a -> b) -> f a -> f b
Before we continue, for a short, a very short time, let's forget that f has kind * -> *. What do we end up with?
amappend :: f -> f -> f
That's the "monodial structure" part. And that's the difference between Applicative and Functor in Haskell, since with Functor we don't have that property:
fmap :: (a -> b) -> f a -> f b
-- ^
-- no f here
That's also the reason we get into trouble if we try to use (+) or other functions with fmap only: after a single fmap we're stuck, unless we can somehow apply our new function in that new structure. Which brings us to the second part of your question:
So, with Applicative, we have [...] function application for our values!
Function application is ($). And if we have a look at <*>, we can immediately see that they are similar:
($) :: (a -> b) -> a -> b
(<*>) :: f (a -> b) -> f a -> f b
If we forget the f in (<*>), we just end up with ($). So (<*>) is just function application in the context of our structure:
increase :: Int -> Int
increase x = x + 1
five :: Int
five = 5
increaseA :: Applicative f => f (Int -> Int)
increaseA = pure increase
fiveA :: Applicative f => f Int
fiveA = pure 5
normalIncrease = increase $ five
applicativeIncrease = increaseA <*> fiveA
And that's, I guessed, what the author meant with "function application". We suddenly can take those functions that are hidden away in our structure and apply them on other values in our structure. And due to the monodial nature, we stay in that structure.
That being said, I personally would never call that monodial, since <*> does not operate on two arguments of the same type, and an applicative is missing the empty element.
1 For a real semigroup/monoid that operation should be associative, but that's not important here
Although this question got a great answer long ago, I would like to add a bit.
Take a look at the following class:
class Functor f => Monoidal f where
unit :: f ()
(**) :: f a -> f b -> f (a, b)
Before explaining why we need some Monoidal class for a question about Applicatives, let us first take a look at its laws, abiding by which gives us a monoid:
f a (x) is isomorphic to f ((), a) (unit ** x), which gives us the left identity. (** unit) :: f a -> f ((), a), fmap snd :: f ((), a) -> f a.
f a (x) is also isomorphic f (a, ()) (x ** unit), which gives us the right identity. (unit **) :: f a -> f (a, ()), fmap fst :: f (a, ()) -> f a.
f ((a, b), c) ((x ** y) ** z) is isomorphic to f (a, (b, c)) (x ** (y ** z)), which gives us the associativity. fmap assoc :: f ((a, b), c) -> f (a, (b, c)), fmap assoc' :: f (a, (b, c)) -> f ((a, b), c).
As you might have guessed, one can write down Applicative's methods with Monoidal's and the other way around:
unit = pure ()
f ** g = (,) <$> f <*> g = liftA2 (,) f g
pure x = const x <$> unit
f <*> g = uncurry id <$> (f ** g)
liftA2 f x y = uncurry f <$> (x ** y)
Moreover, one can prove that Monoidal and Applicative laws are telling us the same thing. I asked a question about this a while ago.

Haskell write your version of (.) function

Can someone help me with writing my own version of a (.) function in Haskell?
From this post Haskell write your version of a ($) function I know how to determine a type of this function, but I still have the problem with its body.
I also do not know why ghci refuses to use the name (..).
($$$) :: (b -> c) -> (a -> b) -> a -> c
($$$) f (g x) = ((f g) $) x
infixr 9 $$$
Another idea of mine was for instance this one:
($$$) :: (b -> c) -> (a -> b) -> a -> c
($$$) f (g x) = map (f) (g x)
infixr 9 $$$
The error message says that "Parse error in pattern: g".
From the signature:
($$$) :: (b -> c) -> (a -> b) -> a -> c
your function needs 3 arguments. So I would start:
($$$) f g x = ...
| | \
| \ a
| \
| a->b
b->c
Update
This attempt at defining ($$$) does not work:
($$$) (f g) x = ...
It says that ($$$) takes two arguments. The way I've started to define ($$$) says that the function takes three arguments.
Are you coming from Lisp? You still seem to assume lists everywhere...
As I already said in the other thread, lists have nothing to do with this task, so neither of (:), foldr or map can possibly be useful here.
More to the point, the occurence of (g x) in the left-hand side of the definition doesn't make sense. (This is not a list, but apparently you think it should be a kind of “argument list”).
As a matter of fact, you could define ($$$) in un-curried form this way:
($$$) :: (b->c) -> (a->b, a) -> c
($$$) f (g, x) = ...
...which is exactly the same thing as the more elegant
f $$$ (g, x) = ...
In this case, you have an argument tuple (g, x), which is more or less equivalent to a Lisp list.
In Haskell, we like to write functions curried though. The signature
($$$) :: (b -> c) -> (a -> b) -> a -> c
is in fact parsed as
($$$) :: (b -> c) -> ( (a -> b) -> (a -> c) )
Hence the way to define such a function is, at the most fundamental level
($$$) = \f -> (\g -> (\x -> ... ))
Which can be written short as
($$$) f g x = ...
or
(f $$$ g) x = ...
In the actual definition part, you should similarly get the grasp of how things are actually parsed. As you have by now figured out, the composition operator can be defined as
($$$) f g x = f(g(x))
In fact, only the outer parentheses are necessary here: the preferred form is
($$$) f g x = f (g x)
or indeed
($$$) f g x = f $ g x
If something like g x or (f g) appears on its own in an expression, it always means that the left function is applied to the right argument. For f g this doesn't make sense, because though f is a function it can not take another function as its argument, only the result of such a function. Well, to get such a result you need to apply g to an argument!
Many thanks for your patience. I used brackets where I should not have. I still have problems with looking at everything (including mathematical operators) as a function. Now the idea of (.) is clear.
($$$) :: (b -> c) -> (a -> b) -> a -> c
($$$) f g x = f(g x)
infixr 9 $$$

How can I apply an arbitrary function under an existential wrapper?

I'm trying to write a function (called hide here), which can apply a sufficiently polymorphic function inside an existential wrapper (or lift functions to work on wrappers with hidden types; hence "hide"):
{-# LANGUAGE GADTs
, RankNTypes
#-}
data Some f
where Some :: f a -> Some f
hide :: (forall a. f a -> g b) -> Some f -> Some g
hide f (Some x) = Some (f x)
data Phantom a = Phantom
cast :: Phantom a -> Phantom b
cast Phantom = Phantom
works :: Some Phantom -> Some Phantom
works = hide cast
doesn't :: Functor f => Some f -> Some f
doesn't = hide (fmap $ \x -> [x])
{-
foo.hs:23:17:
Couldn't match type ‘b0’ with ‘[a]’
because type variable ‘a’ would escape its scope
This (rigid, skolem) type variable is bound by
a type expected by the context: f a -> f b0
at foo.hs:23:11-33
Expected type: f a -> f b0
Actual type: f a -> f [a]
In the first argument of ‘hide’, namely ‘(fmap $ \ x -> [x])’
In the expression: hide (fmap $ \ x -> [x])
In an equation for ‘doesn't’: doesn't = hide (fmap $ \ x -> [x])
Failed, modules loaded: none.
-}
but :: Functor f => Some f -> Some f
but = hide' (fmap $ \x -> [x])
where hide' :: (forall a. f a -> g [a]) -> Some f -> Some g
hide' f (Some x) = Some (f x)
So I pretty much understand why this is happening; works shows that hide does in fact work when the return type is completely unrelated to the input type, but in doesn't I'm calling hide with an argument of type a -> [a]. hide is supposed to get to "choose" the type a (RankNTypes), but b is ordinarily polymorphic. When b in fact depends on a, a could leak out.
But in the context where I'm actually calling it, a doesn't in fact leak out; I immediately wrap it up in Some. And in fact I can write an alternate hide' that accepts specifically a -> [a] functions and works with the exact same implementation, just a different type signature.
Is there any way I can type the implementation hide f (Some x) = Some (f x) so that it works more generally? Really I'm interested in lifting functions with type a -> q a, where q is some arbitrary type function; i.e. I expect the return type to depend on a, but I don't care how it does so. There probably are use cases where q a is a constant (i.e. the return type doesn't depend on a), but I imagine they'll be much rarer.
This example is pretty silly, obviously. In my real use case I have a GADT Schema a that roughly speaking represents types in an external type system; the phantom parameter gives a Haskell type that could be used to represent values in the external type system. I need that phantom parameter to keep everything type safe, but sometimes I construct Schemas based on runtime data, in which case I don't know what that parameter type is.
So I appear to need another type which is agnostic about the type parameter. Rather than make (yet) another parallel type, I was hoping to use a simple existential wrapper like Some to construct it from Schema, and be able to lift functions of type forall a. Schema a -> Schema b to Some Schema -> Some Schema. So if I have an XY problem and I'd be better of using some other means of passing around Schema a for unknown a, that would also solve my problem.
As David Young says, you can write
hide' :: (forall a. f a -> g (q a)) -> Some f -> Some g
hide' f (Some x) = Some (f x)
does :: Functor f => Some f -> Some f
does = hide' (fmap (:[]))
but instead of making hide fmap-like, you can make it bind-like:
hide'' :: (forall a. f a -> Some g) -> Some f -> Some g
hide'' f (Some x) = f x
does :: Functor f => Some f -> Some f
does = hide'' (Some . fmap (:[]))
But this is a bit boilerplateable.
Or, more generally
elim :: (forall a. f a -> c) -> Some f -> c
elim f (Some x) = f x
I'm not sure how useful this is for your larger use-case as you'd have to refactor all your existing operations to use continuation passing style, but continuations can be used to implement a hide that works for both of your examples and keeps b completely generic.
hide :: (forall r a. f a -> (forall b. g b -> r g) -> r g) -> Some f -> Some g
hide f (Some x) = f x Some
cast :: Phantom a -> (forall b. Phantom b -> r Phantom) -> r Phantom
cast Phantom f = f Phantom
works :: Some Phantom -> Some Phantom
works = hide cast
alsoWorks :: Functor f => Some f -> Some f
alsoWorks = hide (\a f -> f $ fmap (\x -> [x]) a)
You can make it somewhat nicer by factoring out the CPS-conversion which allows you to more easily use existing functions like your original cast:
hide :: (forall r a. f a -> (forall b. g b -> r g) -> r g) -> Some f -> Some g
hide f (Some x) = f x Some
cps :: (f a -> g b) -> (f a -> (forall c. g c -> r) -> r)
cps f a c = c (f a)
cast :: Phantom a -> Phantom b
cast Phantom = Phantom
works :: Some Phantom -> Some Phantom
works = hide $ cps cast
alsoWorks :: Functor f => Some f -> Some f
alsoWorks = hide $ cps $ fmap (\x -> [x])

using mplus for list of functions

In Using the Maybe Monad in “reverse” acfoltzer nicely shows how to use mplus. I want to have a similar effect but with the list of functions as a parameter:
tryFuncs :: [a -> Maybe b] -> a -> Maybe b
...
so a call like
tryFuncs [f, g, h] x
would become possible and do the same as
(f x) `mplus` (g x) `mplus` (h x)
How can one achieve this?
The simplest is to use msum (a list version of mplus) together with map:
tryFuncs fs x = msum $ map ($ x) fs
(In the end, this solution will be identical to Ørjan Johansen's answer, since Maybes MonadPlus is equivalent to the First Monoid's behaviour. It's a neat little application of the a -> b monoid though, which is easily overlooked.)
Conceptually, the function you're looking for is ... mconcat!
tryFuncs' :: Monoid b => [a -> Maybe b] -> a -> Maybe b
tryFuncs' = mconcat
Unfortunately, the default Monoid instance for Maybe is not what you want here ("ignore Nothing, mappend Just contents"), otherwise that solution would have been truly neat.
But there's the First wrapper around Maybe that gives you the "retain first Just" behaviour, so that
-- newtype First a = First (Maybe a)
tryFuncsFirst :: [a -> First b] -> a -> First b
tryFuncsFirst = mconcat
What's left for you is to wrap/unwrap the Maybes to Firsts.
firstify :: (a -> Maybe b) -> (a -> First b)
firstify f = First . f
firstifyList :: [a -> Maybe b] -> [a -> First b]
firstifyList = map firstify
getFirst :: First a -> Maybe a -- Defined in Data.Monoid
So now you can recover your desired function by wrapping-mconcat-unwrapping,
[a -> Maybe b] -> a -> Maybe b
tryFuncs fs x = getFirst (mconcat (firstifyList xs) x)
But how does this work? Well, there are two monoids at work here, First a and Monoid b => (a -> b), and the latter one is where the magic happens. To spell the instance out a little, using <> for mappend,
(a <> b) x = a x <> b c
-- and therefore
mconcat [a,b,c] x = mconcat [a x, b x, c x] -- (1)
So now the above code can be understood:
First-wrap all the input functions to take them from a -> Maybe b to a -> First b, which is the same, but has a different Maybe Monoid instance.
mconcat the list of functions, this uses the Monoid b => (a -> b) instance I just mentioned. All functions in the created list are applied to x, leaving you with a list of First b, which is then concatenated again, just as in (1).
Extract the resulting Maybe value out of the First wrapper again.

Resources