
How can I fix it so that `ItDoesnt <*> WhatThisIsCalled` works? I have came up with a solution without WhatThisIsCalled data WhoCares a = ItDoesnt | Matter a deriving (Eq, Show) instance Functor WhoCares where fmap _ ItDoesnt = ItDoesnt fmap f (Matter a) = Matter (f a) instance Applicative WhoCares where pure = Matter Matter f <*> Matter a = Matter (f a) ItDoesnt <*> _ = ItDoesnt _ <*> ItDoesnt = ItDoesnt instance Monad WhoCares where return x = Matter x (Matter x) >>= k = k x ItDoesnt >>= _ = ItDoesnt half x = if even x then Matter (x `div` 2) else ItDoesnt incVal :: (Ord a, Num a) => a -> WhoCares a incVal x | x + 1 <= 10 = return (x + 1) | otherwise = ItDoesnt decVal :: (Ord a, Num a) => a -> WhoCares a decVal x | x - 1 >= 0 = return (x - 1) | otherwise = ItDoesnt main = do -- fmap id == id let funcx = fmap id "Hi Julie" let funcy = id "Hi Julie" print(funcx) print(funcy) print(funcx == funcy) -- fmap (f . g) == fmap f . fmap g let funcx' = fmap ((+1) . (*2)) [1..5] let funcy' = fmap (+1) . fmap (*2) $ [1..5] print(funcx') print(funcy') print(funcx' == funcy') -- pure id <*> v = v print(pure id <*> (Matter 10)) -- pure (.) <*> u <*> v <*> w = u <*> (v <*> w) let appx = pure (.) <*> (Matter (+1)) <*> (Matter (*2)) <*> (Matter 10) let appy = (Matter (+1)) <*> ((Matter (*2)) <*> (Matter 10)) print(appx) print(appy) print(appx == appy) -- pure f <*> pure x = pure (f x) let appx' = pure (+1) <*> pure 1 :: WhoCares Int let appy' = pure ((+1) 1) :: WhoCares Int print(appx') print(appy') print(appx' == appy') -- u <*> pure y = pure ($ y) <*> u let appx'' = Matter (+2) <*> pure 2 let appy'' = pure ($ 2) <*> Matter (+ 2) print(appx'') print(appy'') print(appx'' == appy'') -- m >>= return = m let monx = Matter 20 >>= return let mony = Matter 20 print(monx) print(mony) print(monx == mony) -- return x >>= f = f x let monx' = return 20 >>= half let mony' = half 20 print(monx') print(mony') print(monx' == mony') -- (m >>= f) >>= g = m >>= (\x -> f x >>= g) let monx'' = return 20 >>= half >>= half let mony'' = half 20 >>= half print(monx'') print(mony'') print(monx'' == mony'') print (Matter 7 >>= incVal >>= incVal >>= incVal) print (Matter 7 >>= incVal >>= incVal >>= incVal >>= incVal) print (Matter 7 >>= incVal >>= incVal >>= incVal >>= incVal >>= decVal
= decVal) print (Matter 2 >>= decVal >>= decVal >>= decVal) print (Matter 20 >>= half >>= half)
*Thanks and Best Regards,Ahmad Ismail*
On Sun, Nov 13, 2022 at 5:08 PM Francesco Ariis
Hello Ahmad,
Il 13 novembre 2022 alle 16:33 Ahmad Ismail ha scritto:
Due to lack of examples, I am not understanding how to implement >>= and
.
All you need to implement is (>>=)!
The code I came up with so far is:
instance Monad (WhoCares a) where (>>=) :: Matter a -> (a -> Matter b) -> Matter b (>>) :: Matter a -> Matter b -> Matter b return :: a -> Matter a return = pure
The signature for (>>=) is wrong, `Matter` is a *data* constructor, you need a *type* one instead, so:
(>>=) :: WhoCares a -> (a -> WhoCares b) -> WhoCares b
But let us go back to typeclasses. Your `Applicative` instance
instance Applicative WhoCares where pure = Matter Matter f <*> Matter a = Matter (f a)
is broken:
λ> ItDoesnt <*> WhatThisIsCalled *** Exception: /tmp/prova.hs:11:5-40: Non-exhaustive patterns in function <*>
So we need first to fix that. What behaviour would you expect, what are you trying to model with `WhoCares`? —F _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners