[Haskell-cafe] exceptions vs. Either

David Menendez zednenem at psualum.com
Tue Aug 3 22:06:11 EDT 2004


David Menendez writes:

> MR K P SCHUPKE writes:
> 
> > I would suggest using the type system as I said earlier so:
> > 
> > toNonEmptyList :: [a] -> Maybe (NonEmpty a)
> > toNonEmptyList (a0:_) = Just (NonEmpty a)
> > toNonEmptyList _ = Nothing
> > 
> > Then redefine head:
> > 
> > head :: NonEmpty a -> a
> > head (NonEmpty (a0:_)) = a0
> 
> Oleg described a similar technique a few months ago.
> 
> From <http://haskell.org/pipermail/haskell/2004-June/014271.html>:
> 
> |> newtype NonEmpty a = NonEmpty [a] -- the NonEmpty constructor
should
> |> -- be hidden (not exported from its module)
> |>
> |> head' (NonEmpty a) = head a -- no error can occur! Can use unsafe
> version
> |> tail' (NonEmpty a) = tail a -- no error can occur! Can use unsafe
> version
> |>
> |> -- trusted function: the only one that can use NonEmpty
constructor.
> |> fork_list_len f g x = if null x then f else g (NonEmpty x)
> |>
> |> revers x  = revers' x []
> |>  where
> |>    revers' x accum = fork_list_len accum (g accum) x
> |>    g accum x = revers' (tail' x) ((head' x):accum)
> 
> We have these equivalences:
> 
>     toNonEmptyList    == fork_list_len Nothing Just
>     fork_list_len d f == maybe d f . toNonEmptyList
> 
> I think defining 'toNonEmptyList' in terms of 'fork_list_len' is
> cleaner, but that's just my personal taste. (As it happens, I ended up
> defining a very similar function 'cons' in my recursion module[1]).
> 
> [1]
> <http://www.eyrie.org/~zednenem/2004/hsce/Control.Recursion.html#v%
> 3Acons>
-- 
David Menendez <zednenem at psualum.com> <http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list