views:

219

answers:

3

Hi

I have the following code to return the length of a cycle in a string:

module Main where
import Data.List

detec ys n | 2*n > (length ys) = error "no cycle"
           | t == h = (2*n - n)
           | otherwise = detec ys (n+1)
            where
                t = ys !! n
                h = if n == 0 then ys !! 1 else  ys !! (n*2)
f x = detec (show x) 0
answer = map f [1/x|x<-[1..100]]

But what I don't know how to do is make it ignore the "no cycle" exception so that the list produced only contains the lengths of the strings which are cyclic.

How can I do this?

+3  A: 

You might use catch from Control.Exception as in

import Prelude hiding (catch)
import Control.Exception

main = do
  print answer `catch` errorMessage
  where
    errorMessage :: SomeException -> IO ()
    errorMessage = putStrLn . ("error: " ++) . show

Catching SomeException is sloppy, and the output is messy:

[error: No cycle

It got partway through printing an array but ran into the exception. Not very nice.

Another answer has covered the fine approach of using the Maybe monad for representing computations that can fail. An even more general approach is MonadError:

{-# LANGUAGE FlexibleContexts #-}

import Control.Applicative
import Control.Monad.Error

detec2 :: (MonadError String m, Eq a) => [a] -> Int -> m Int
detec2 ys n | 2*n >= (length ys) = throwError "No cycle"
            | t == h = return (2*n - n)
            | otherwise = detec2 ys (n+1)
             where
                 t = ys !! n
                 h = if n == 0 then ys !! 1 else  ys !! (n*2)

(Notice this also fixes the bug in your first guard that allows !! to throw exceptions.)

This permits similar but more flexible use, for example:

answer2 = f2 <$> [1/x | x <- [1..100]]

f2 x = detec2 (show x) 0

main = do
  forM_ answer2 $
    \x -> case x of
            Left msg -> putStrLn $ "error: " ++ msg
            Right x  -> print x

Now the first few lines of the output are

error: No cycle
error: No cycle
2
error: No cycle
error: No cycle
3
6
error: No cycle
2

Keep in mind this is still a pure function: you don't have to run it inside IO. To ignore the no-cycle errors, you might use

cycles :: [Int]
cycles = [x | Right x <- answer2]

If you don't care about errors messages at all, then don't generate them. A natural way to do this is with lists where you return the empty list for no cycles and condense the result with concatMap:

detec3 :: (Show a) => a -> [Int]
detec3 x = go 0
  where go :: Int -> [Int]
        go n
          | 2*n >= len = []
          |     t == h = [2*n - n]
          |  otherwise = go (n+1)
          where t = ys !! n
                h | n == 0    = ys !! 1
                  | otherwise = ys !! (n*2)
                len = length ys
                ys = show x

main = do
  print $ concatMap (detec3 . recip) [1..100]

Finally, you may be interested in reading 8 ways to report errors in Haskell.

Greg Bacon
how would I use this?
Jonno_FTW
@Jonno_FTW See update.
Greg Bacon
Clarifying the difference between approaches, note that `Maybe` is also a monad. `MonadError` is the more general approach by virtue of allowing you to attach error messages; if you don't care about error messages, there's not much practical difference, and both can be written either in a "direct" style or using `do` notation.
camccann
+22  A: 

Please don't use error to implement logic where the "erroneous" result is expected to occur.

Instead, why not return Maybe n instead of just n, then use catMaybes to filter out the Nothings?

The changes are easy enough:

module Main where
import Data.List
import Data.Maybe

detec ys n | 2*n > (length ys) = Nothing
           | t == h = Just (2*n - n)
           | otherwise = detec ys (n+1)
            where
                t = ys !! n
                h = if n == 0 then ys !! 1 else  ys !! (n*2)

f x = detec (show x) 0
answer = catMaybes $ map f [1/x|x<-[1..100]]

By the way, you're indexing past the end of the list; perhaps you meant to check 2*n + 1 > length ys? Drifting slightly off topic, I'd like to mention that !! and length are, for the most part, both inefficient and non-idiomatic when applied to lists, especially in an iterating construct like this. The list type is basically a cons cell list, which is an intrinsically recursive data structure, and is emphatically not an array. Ideally you should avoid doing anything with a list that can't be easily expressed with pattern matching, e.g., f (x:xs) = ....

camccann
+1 for discouraging `error`. Note that it isn't even possible to check against the `_|_` it returns! With an evaluated error, the whole program returns undefined.
Dario
+1 for the same, as well as discouraging array indexing, although I would have preferred it if you pointed out that OP's algorithm is faulty to begin with. Well, since you didn't, I did...
ephemient
`catMaybes . map == mapMaybe`
Nefrubyr
Actually, you can catch "error" (and pattern-match failures) in IO. But you don't want to ever get to that point; it's not an exception, it's a bug.
jrockway
+5  A: 
ephemient