Dear Haskellers,
while playing with folds and trying to implement `!!` by folding, I came to the conclusion that:
- `foldr` is unsuitable because it counts the elements from the end, while `!!` needs counting from the start (and it's not tail recursive).
- `foldl` is also unsuitable, because it always traverses the whole list.
I came up with the following tail-recursive generalization of `foldl` that allows exiting the computation prematurely:
    foldlE :: (a -> c) -> (a -> b -> Either c a) -> Either c a -> [b] -> c
    foldlE f g = fld
      where
        fld (Left c)  _         = c
        fld (Right a) []        = f a
        fld (Right a) (x:xs)    = fld (g a x) xs
`foldl` can be defined from it  as
    foldl'' :: (a -> b -> a) -> a -> [b] -> a
    foldl'' f z = foldlE id ((Right .) . f) (Right z)
and `!!` as:
    -- Checks for a negative index omitted for brevity.
    index :: Int -> [a] -> a
    index i = foldlE (error $ "No such index") f (Right i)
      where
        f 0 x = Left x
        f n _ = Right (n - 1)
Is something like that already available somewhere?
  Best regards,
  Petr Pudlak