I've got this fizzbuzz project I am using for a blog series, among other things. In this version, the fizzbuzz function is fed from a Fibonacci generator. I'm particularly concerned with the efficiency of the Fibonacci generator, but all scrutiny is welcomed.

I'll included a link to the entire project, but below are the parts I think would be sufficient to spot trouble with how I am generating Fibonacci numbers.

-- Driver function performs following
-- (1) checks that input is proper
-- (2) creates integer list for fibonacci generator
-- (3) calculates first x in fibonnaci sequence
-- (4) generates fizzbuzz output using (3)

fizzBuzzFib :: [Text] -> Either FizzError [Text]
fizzBuzzFib str =
mapM fizzbuzz          =<<
mapM fibb              =<< -- Possible problem here
(\x -> Right [1 .. x]) =<<
convertToPInt          =<<
mustHaveOne str

fibb :: Integer -> Either FizzError Integer
fibb n = Right $ snd . foldl' fib' (1, 0) . map (toEnum . fromIntegral) $ unfoldl divs n
  where
    unfoldl f x =
      case f x of
        Nothing     -> []
        Just (u, v) -> unfoldl f v ++ [u]

    divs 0 = Nothing
    divs k = Just (uncurry (flip (,)) (k `divMod` 2))

    fib' (f, g) p
      | p = (f*(f+c*g), f^c + g^c)
      | otherwise = (f^c+g^c, g*(c*f-g))
      where
        c :: Integer -- See codebase for reasons
        c = 2

The whole project, for your critiquing eye: https://github.com/mlitchard/swiftfizz