3

I'm writing my homework (CIS194 Haskell course).

I must rewrite the following recursive function to pipeline functions (without obvious recursion).

fun2 :: Integer -> Integer
fun2 1 = 0
fun2 n 
    | even n = n + fun2 ( n ‘div‘ 2 )
    | otherwise = fun2 (3 * n + 1) 

My first try is here:

fun2''' = sum 
          . (filter (even)) 
          . unfoldr (\x -> if (even x) 
                          then Just (x, x `div` 2)
                          else if (x==1) then Nothing 
                               else Just (x, x * 3 + 1))

Is this a normal solution or is it weird?

And how can I rewrite fun2 better?

Now i try write version with takeWhile and iterate

my 2nd try:

fun2'' :: Integer -> Integer
fun2'' = sum 
         . (filter even) 
         . takeWhile (/=1) 
         . iterate (\x -> if even x 
                          then x `div` 2
                          else x * 3 + 1 )

i have little problems with until version now.

Will Ness
  • 70,110
  • 9
  • 98
  • 181
  • 2
    A few unnecessary parentheses, but it's rather good. I'm optimisitc that your `takeWhile` + `iterate` approach will turn out well too. – Daniel Fischer Apr 21 '13 at 16:49
  • 1
    Also instead of returning `x` for the case when it's odd, you could return `Just (0, x * 3 + 1)` and avoid `filter`ing later. – Petr Apr 21 '13 at 16:58
  • What about applying Collatz conjecture and writing as fun2 _ = 0 – Luka Rahne Apr 23 '13 at 07:56
  • @LukaRahne it is not 0. The function sums up all evens in a Collatz sequence for a given number. The conjecture states it's finite, and to be so it must end with a sequence of powers of 2, i.e. evens (up to the finishing 1). – Will Ness Apr 23 '13 at 22:43

2 Answers2

2

Looks not bad, the only thing here that's a bit of a red flag in Haskell is else if. In this case, it can be rewritten nicely in applicative style:

{-# LANGUAGE TupleSections     #-}

import Control.Applicative
import Control.Monad (guard)

fun2''' = sum 
          . filter even
          . unfoldr ( \x -> fmap (x,) $
                   x`div`2 <$ guard(even x)
               <|> x*3 + 1 <$ guard( x/=1 )
             )
leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • 1
    You can read a chain of `a<$guard α <|> b<$guard β <|> ...` much like what you'd write in a procedural language as `if α then return a; if β then return b...`. — It works like this: `guard ψ` is `Just ()` if _ψ_ is true, and `Nothing` if it's false. `<$` replaces the `()` with the value to its left, or leaves the `Nothing` as it is. `<|>` finally picks the first `Just a` it finds, skipping any `Nothing`s. – leftaroundabout Apr 21 '13 at 17:16
  • @groovy: `a <$ b` is just `const a <$> b` or `fmap (const a) b`. Think about it as a special version of `<$>` that ignores the values on the right--that's why the symbol is just like `<$>` without the right `>`. – Tikhon Jelvis Apr 21 '13 at 18:07
  • this code [fails with a type mismatch error on Ideone](http://ideone.com/MNyLKN). [Sticking some `runKleisli` and `Kleisli` in there](http://ideone.com/eScxaq) did the trick. But that's hardly an intuitive or easy-to-read code (for me at least). :) Is there an easier way to mend this code? – Will Ness Apr 22 '13 at 15:52
  • @WillNess: right, that Arrow thing was a bit too much, and with the required kleisli wrapper really not nice anymore. I went back to the [plain applicative version](http://ideone.com/2bi6nK). – leftaroundabout Apr 22 '13 at 16:49
  • thanks! (I could've looked into the edit history, it turns out...) – Will Ness Apr 23 '13 at 07:19
1

Nested ifs can now be written with multi-way IF:

g :: Integer -> Integer
g = sum . 
     unfoldr (\x-> 
          if | even x    -> Just (x, x `div` 2) 
             | x==1      -> Nothing 
             | otherwise -> Just (0, x * 3 + 1))

Or you can define your own if operator,

(??) t (c,a) | t = c | otherwise = a

g = sum . unfoldr (\x-> even x ?? (Just (x, x `div` 2) ,
                        (x==1) ??  (Nothing, Just (0, x * 3 + 1))))

Same function with until, with sum and filter fused into it:

g = fst . until ((==1).snd) 
            (\(s,n) -> if even n then (s+n,n`div`2) else (s,3*n+1)) 
    . ((,)0)

or

g = sum . filter even . f

f :: Integer -> [Integer]
f = (1:) . fst . until ((==1).snd) 
            (\(s,n) -> if even n then (n:s,n`div`2) else (n:s,3*n+1)) 
    . ((,)[])

The last function, f, shows the whole Collatz sequence for a given input number, reversed.

Will Ness
  • 70,110
  • 9
  • 98
  • 181
  • Please, describe (1:) , ((,)0) , ((,)[]) sentences. I never meet it before. – Сергей Кузминский Apr 22 '13 at 18:31
  • @СергейКузминский That's "operator sections", i.e. partially applied operators. `(1:) == (:) 1 == (\y -> 1:y)`. `(,)x == (x ,) == (\y -> (x, y))`. See also http://stackoverflow.com/a/13477198/849891 . – Will Ness Apr 22 '13 at 21:29
  • 1
    @СергейКузминский congrats on reaching the 15 rep! :) You have the power to up-vote now. ;) ;) (and you always had the power to *accept* an answer). – Will Ness Apr 23 '13 at 07:06