📜 ⬆️ ⬇️

Why do we need all these functors and monads?

Very often in articles about Haskell pretty often there are functors and especially monads.
So often that sometimes the comments “how much is possible about some new monads” and “write about something useful” are not less frequent.
In my opinion, this indicates that people sometimes do not understand why we need all these functors and monads.

This article is an attempt to show that the power of functional languages, and especially Haskell, is also the power of functors and monads.


Clean data


I will try to show this with an example of a rather artificial and probably useless, however, the emphasis will be placed on the importance of using a common code and reuse.

The term “clean” is overloaded in programming.
For example, the phrase “Ruby is a purely objective language” we understand as “Ruby is a language, where everything is objects”.
But the phrase "Haskell is a pure functional language" should be understood as "Haskell is a functional language without side effects."
In this article we will use the term “pure” in another context.
“Net data” is the data I want to get.
Mostly primitive types are numbers, strings, sometimes more complex ones, for example, a picture or several values.
Accordingly, “dirty data” is data that contains, in addition to what I want, additional information.
')
Here's a program:
module Main where foo = undefined --   main :: IO () main = do putStrLn "Input a: " a <- getLine --  1    putStrLn "Input b: " b <- getLine --  2    print (foo ab) --    

The program is simple to disgrace - we ask the user to enter 2 lines, and then output the result of the calculation.
We see that our foo function is not yet defined (it always causes the program to crash), although Haskel can already compile our code.

Now we will rewrite our function in more detail using only “pure” data:
 pure1arg :: Int -> Int pure1arg = (+ 1) --   ,   1  pure2args :: Int -> Int -> Int pure2args = (+) --  ,   2  unsafe2args :: Int -> Int -> Int unsafe2args = div --   ,   2  foo :: String -> String -> Int foo ab = unsafe2args extraUnsafeE unsafeC --     ,     where unsafeA :: Int unsafeA = read a --           unsafeB :: Int unsafeB = read b --  unsafeA    unsafeC :: Int unsafeC = pure1arg unsafeB --    1     reallyUnsafeD :: Int reallyUnsafeD = pure2args unsafeA unsafeC --    2     extraUnsafeE :: Int extraUnsafeE = unsafe2args unsafeA reallyUnsafeD --    2 .  2   . 

As you can see, it is also clear here, the function foo is essentially [no matter what] a mixture of integer division and sums.
Most functional programming languages ​​make it easy to create functions based on pure data.

It would seem that everything is great - a simple and elegant program. But netushki!
The result of the function is much more complicated than we would like.
As we understand, it is impossible to divide by 0 , and the user can enter not the numbers, but the left strings, and when converting strings to numbers can throw out an error. Our code is not safe.
The imperative approach to solving such problems is divided into 2 groups: either use branching, or use exceptions. Often, both approaches are combined.
These approaches are so effective that they are mainly used in functional languages.
Let's face it - there are exceptions in Haskell, but they are underdeveloped, need to be reformed, are not caught in the best way. And most importantly - in most cases they are simply not needed.
But it is no less - possible.
Therefore, we will try to rewrite our code using branches and exceptions.
 module Main where import Control.Exception (IOException, catch) printError :: IOException -> IO () printError = print pure2args :: Int -> Int -> Int pure2args = (+) pure1arg :: Int -> Int pure1arg = (+ 1) unsafe2args :: Int -> Int -> Int unsafe2args ab = if b == 0 then error "Error 'unsafe2args' : wrong 2nd argument = 0" --unsafe source of IOException else div ab foo :: String -> String -> Int foo ab = unsafe2args extraUnsafeE unsafeC where unsafeA :: Int unsafeA = read a --unsafe source of IOException unsafeB :: Int unsafeB = read b --unsafe source of IOException unsafeC :: Int unsafeC = pure1arg unsafeB reallyUnsafeD :: Int reallyUnsafeD = pure2args unsafeA unsafeC extraUnsafeE :: Int extraUnsafeE = unsafe2args unsafeA reallyUnsafeD main :: IO () main = do putStrLn "Input a: " a <- getLine putStrLn "Input b: " b <- getLine catch (print (foo ab)) printError --      IOException 

Dirty data


In Haskell (and in many functional languages) there is a worthy answer to such problems.
The main strength lies in Algebraic Data Types.

If we consider the above example, it is clear that our functions may fall.
The solution is to use plain data types.
In ML languages ​​and Scala, this type is called Option , in Haskell, it is called Maybe a .
 import Prelude hiding (Maybe) --       .       data Maybe a = Nothing | Just a deriving Show 

We do not pay attention to the deriving part, we simply say that we ask the compiler to be able to translate our data type into a string.
Namely,
 show Nothing == "Nothing" show (Just 3) == "Just 3" 

The data type is Nothing if we have no data, and Just a if it has one.
As you can see, the data type is “dirty” because it contains extra information.
Let's rewrite our functions more correctly, more safely and without exceptions.

First of all, let's replace the functions that caused the drop on safe analogues:
 maybeResult2args :: Int -> Int -> Maybe Int maybeResult2args ab = if b == 0 then Nothing --safe else Just (div ab) ... maybeA :: Maybe Int maybeA = readMaybe a --safe maybeB :: Maybe Int maybeB = readMaybe b --safe 

Now, these functions instead of falling give the result Nothing , if everything is in order, then Just .

But the rest of the code depends on these functions. We will have to change almost all the functions, including those that have been tested many times.
 pure2args :: Int -> Int -> Int pure2args = (+) safePure2args :: Maybe Int -> Maybe Int -> Maybe Int safePure2args ab = case a of Nothing -> Nothing Just a' -> case b of Nothing -> Nothing Just b' -> Just (pure2args a' b') pure1arg :: Int -> Int pure1arg = (+ 1) safePure1arg :: Maybe Int -> Maybe Int safePure1arg a = case a of Nothing -> Nothing Just a' -> Just (pure1arg a') maybeResult2args :: Int -> Int -> Maybe Int maybeResult2args ab = if b == 0 then Nothing else Just (div ab) foo :: String -> String -> Maybe Int foo ab = case maybeE of Nothing -> Nothing Just e -> case maybeC of Nothing -> Nothing Just c -> maybeResult2args ec where maybeA :: Maybe Int maybeA = readMaybe a maybeB :: Maybe Int maybeB = readMaybe b maybeC :: Maybe Int maybeC = safePure1arg maybeB maybeD :: Maybe Int maybeD = safePure2args maybeA maybeC maybeE = case maybeA of Nothing -> Nothing Just a1 -> case maybeD of Nothing -> Nothing Just d -> maybeResult2args a1 d printMaybe :: Show a => Maybe a -> IO () printMaybe Nothing = print "Something Wrong" printMaybe (Just a) = print a main :: IO () main = do putStrLn "Input a: " a <- getLine putStrLn "Input b: " b <- getLine printMaybe (foo ab) 

As you can see a simple program has turned into a rather monstro-shaped code.
A lot of wrapper functions, a lot of redundant code, a lot has been changed.
But this is where many functional programming languages ​​stop.
Now you can understand why in those languages, despite the possibility of creating a lot of ADT, ADT is not so often used in the code.

You can live with ATD, but without a similar orgy? It turns out you can.

Functors


Functors come to our aid in the beginning.

Functors are those data types for which the fmap function exists.
 class Functor f where fmap :: (a -> b) -> fa -> fb 

as well as his infix synonym:
 (<$>) :: Functor f => (a -> b) -> fa -> fb (<$>) = fmap 

such that for all values ​​of the data type the following conditions are always met:

Identity condition:
fmap id == id
Composition condition:
fmap (f . g) == fmap f . fmap g

Where id is an identity function
  id :: a -> a id x = x 

And (.) - functional composition
  (.) :: (b -> c) -> (a -> b) -> a -> c f . g = \x -> f (gx) 

The functor is a type class where we have created a special function fmap . Let's look at its arguments - it takes one “pure” function a -> b , we take the “dirty” functor value fa and get the output functor value fb .

The data type Maybe is a functor. Create an instance (instance) for the type Maybe , so that the laws of the functors are not violated:
 instance Functor Maybe where fmap _ Nothing = Nothing fmap f (Just a) = Just (fa) 

How do we use a pure function with the Maybe functor? Very simple:
 safePure1arg :: Maybe Int -> Maybe Int safePure1arg = fmap pure1arg 

We see the most important thing here - we did not rewrite our pure1arg function, which means we don’t have to test it again for bugs and everything remained universal and clean, but we easily created its safe version, which accepts not numbers for input, but simple ones numbers

However, if we want to use a functor, trying to rewrite safePure2args , we’ll be a fiasco.
Functors work only with functions with a single functor-dirty argument.
What to do for functions with several parameters?

Applicative Functors


Here applicative functors come to the rescue:

Applicative functors are such functors for which 2 functions are defined: pure and (<*>)
 class Functor f => Applicative f where pure :: a -> fa (<*>) :: f (a -> b) -> fa -> fb 

Such that for them for any values ​​of one data type the following rules are always executed:

Identity condition:
pure id <*> v == v
Composition condition:
pure (.) <*> u <*> v <*> w == u <*> (v <*> w)
The homomorphism condition:
pure f <*> pure x == pure (fx)
Exchange condition:
u <*> pure y == pure ($ y) <*> u

The main distinction of the funtor from the applicative funtor is that the funder pulls a pure function through the functor value, while the applicator allows us to drag the functor function f (a -> b) through the functor value.

Maybe is an applicative functor and is defined as follows:
 instance Applicative Maybe where pure = Just Nothing <*> _ = Nothing _ <*> Nothing = Nothing (Just f) <*> (Just a) = Just (fa) 

It's time to rewrite safePure2args .
Basically, the function is rewritten, combining the functor fmap for the first argument, and the applicative stringing of the remaining arguments:
 safePure2args :: Maybe Int -> Maybe Int -> Maybe Int safePure2args ab = pure2args <$> a <*> b 

But you can rewrite the function using exclusively applicative functions (monad style) - first, we make the pure function purely applicative, and applicatively string the arguments:
 safePure2args :: Maybe Int -> Maybe Int -> Maybe Int safePure2args ab = (pure pure2args) <*> a <*> b 

Wonderful!
Can it be possible at the same time to rewrite the function maybeE with the help of applicative functors? Alas.

Monads


Let's take a look at the signature of the maybeResult2args function:
maybeResult2args :: Int -> Int -> Maybe Int
The function takes as input the "clean" arguments, and gives the output a "dirty" result.
So, for the most part in real programming, it is these functions that are most often encountered - they take “clean” arguments as input, and “dirty” result as output.
And when we have several such functions, monads help to combine them together.

Monads are data types for which there are return and (>>=) functions
 class Monad m where return :: a -> ma (>>=) :: ma -> (a -> mb) -> mb 

such that the rules for any values ​​of type are executed:

Left identity:
return a >>= k == ka
Right Identity:
m >>= return == m
Associativity:
m >>= (\x -> kx >>= h) == (m >>= k) >>= h

For convenience, there is an additional function with the reverse order of the arguments:
 (=<<) :: Monad m => (a -> mb) -> ma -> mb (=<<) = flip (>>=) 

Where
 flip :: (a -> b -> c) -> b -> a -> c flip fab = fba 

We understand that the Maybe type is a monad, which means we can define its instance (instance):
 instance Monad Maybe where return = Just (Just x) >>= k = kx Nothing >>= _ = Nothing 

By the way, if we look closely at the internal content and signatures, we see that:
pure == return
fmap f xs == xs >>= return . f

It's time to rewrite the function maybeE
  maybeE = maybeA >>= (\a1 -> maybeD >>= (maybeResult2args a1)) 

Yeah, it turned out not much more beautiful. This is due to the fact that monads are beautifully written for one variable. Fortunately, there are many additional features.
You can write bind2 function
 bind2 :: Monad m => (a -> b -> mc) -> ma -> mb -> mc bind2 mf mx my = do x <- mx y <- my mf xy 

  maybeE = bind2 maybeResult2args maybeA maybeD 

Or use the liftM2 and join functions
 liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> mr join :: Monad m => m (ma) -> ma maybeE = join $ liftM2 maybeResult2args maybeA maybeD 

In extreme cases, you can use syntax sugar for monads using do notation:
  maybeE = do a1 <- maybeA d <- maybeD maybeResult2args a1 d 

Differences in the use of funtors and monads


If we reduce the basic functions to one type, we will see:
 (<$>) :: Functor f => (a -> b) -> fa -> fb (<*>) :: Applicative f => f (a -> b) -> fa -> fb (=<<) :: Monad f => (a -> fb) -> fa -> fb 

All are used to pass “dirty” values ​​to functions, while functions expect “clean” values ​​at the input.
Funtori use the "clean" function.
Applicative functors are a “pure” function inside “pollution”.
Monads use functions that have a “dirty” meaning at the exit.

Program without routine


Well, finally, you can completely and accurately rewrite the entire program:
 module Main where import Control.Monad import Control.Applicative import Text.Read (readMaybe) bind2 :: Monad m => (a -> b -> mc) -> ma -> mb -> mc bind2 mf mx my = do x <- mx y <- my mf xy pure2args :: Int -> Int -> Int pure2args = (+) pure1arg :: Int -> Int pure1arg = (+ 1) maybeResult2args :: Int -> Int -> Maybe Int maybeResult2args ab = if b == 0 then Nothing --safe else Just (div ab) foo :: String -> String -> Maybe Int foo ab = bind2 maybeResult2args maybeE maybeC where maybeA :: Maybe Int maybeA = readMaybe a --safe maybeB :: Maybe Int maybeB = readMaybe b --safe maybeC :: Maybe Int maybeC = fmap pure1arg maybeB maybeD :: Maybe Int maybeD = pure2args <$> maybeA <*> maybeC maybeE :: Maybe Int maybeE = bind2 maybeResult2args maybeA maybeD printMaybe :: Show a => Maybe a -> IO () printMaybe Nothing = print "Something Wrong" printMaybe (Just a) = print a main :: IO () main = do putStrLn "Input a: " a <- getLine putStrLn "Input b: " b <- getLine printMaybe (foo ab) 

The code became simple and clear again!
At the same time, we did not sacrifice a safety span!
At the same time, we almost did not change the code!
At the same time, the pure functions remained pure!
At the same time avoided the routine!

Conclusion


Is it possible to live in a functional world without functors and monads? Can.
But, if we want to use the full force of Algebraic Data Types with all our might, we will have to use functors and monads for convenient functional composition of various functions.
For this is an excellent remedy for the routine and the path to short, understandable and frequently re-used code!

PS It should be understood that for different types of data, the analogy with the "clean" and "dirty" data types is not quite appropriate.
For example, for lists
fmap = map
And the monad:
  a = do c <- cs d <- ds return (zet cd) 

really is
 a = [zet cd | c <- cs, d <- ds] 

What is not always obvious at first sight.

Source: https://habr.com/ru/post/212955/


All Articles