A list whose "Nil" carries a value?
Asked Answered
F

1

12

Does some standard Haskell library define a data type like this

data ListWithEnd e a = Cons a (ListWithEnd e a)
                     | End e

That is a list whose terminating element carries a value of a designated type?

So ListWithEnd () is isomorphic to [] and ListWithEnd Void is isomorphic to infinite streams. Or, viewed differently, ListWithEnd e a is very close to ConduitM () a Identity e..

Feticide answered 30/3, 2015 at 17:32 Comment(7)
I've not seen it. Perhaps it would be easier (wrt working with predefined functions) to define newtype ListWithEnd e a = LWE ([a], e)?Parkinson
@ThomasM.DuBuisson I need e to be really in the constructor at the end, as I'm experimenting with functions that compute e while constructing the list.Feticide
Trying to express it in terms of standard stuff, type LWE e a = Free ((,) a) e comes to mind.Confrere
Can't you just use ([a],e)?Hannigan
Very similar to a Producer a Identity e from pipes as well. Following the analogy, a function that decoded bytes into chars and returned any undecoded leftovers would have type forall e . ListWithEnd e Word8 -> ListWithEnd (ListWithEnd e Word8) Char.Hertz
@OmarAntolín-Camarena: That wouldn't quite be the same because a list does not have to have an end. Particularly, ([a], Void) would be isomorphic to Void and not to infinite streams.Liselisetta
@AndrásKovács Could you convert your comment to an answer so that I can accept it?Feticide
P
5

We can define ListWithEnd as follows:

import Control.Monad.Free

type LWE a e = Free ((,) a) e

We generally have an expectation that abstract or generic representations should reward us with an overall reduction of boilerplate. Let's see what this representation provides us.

In any case, we shall define a pattern synonym for the cons case:

{-# LANGUAGE PatternSynonyms #-}

pattern x :> xs = Free (x, xs)
infixr 5 :>

We can map, fold and traverse over the end element:

fmap (+1) (0 :> Pure 0) == (0 :> Pure 1)
traverse print (0 :> Pure 1) -- prints 1

The Applicative instance gives us very neat concatenation:

xs = 1 :> 2 :> Pure 10
ys = 3 :> 4 :> Pure 20

xs *> ys          == 1 :> 2 :> 3 :> 4 :> Pure 20 -- use right end
xs <* ys          == 1 :> 2 :> 3 :> 4 :> Pure 10 -- use left end
(+) <$> xs <*> ys == 1 :> 2 :> 3 :> 4 :> Pure 30 -- combine ends

We can map over the list elements, if a bit tortuously:

import Data.Bifunctor -- included in base-4.8!

hoistFree (first (+10)) xs == 11 :> 12 :> Pure 10

And we can make use of iter, of course.

iter (uncurry (+)) (0 <$ xs) == 3 -- sum list elements

It would be nice if LWE could be a Bitraversable (and Bifunctor and Bifoldable), because then we could access the list elements in a more generic and principled way. For this we definitely need a newtype:

newtype LWE a e = LWE (Free ((,) a) e) deriving (lots of things)

instance Bifunctor LWE where bimap = bimapDefault
instance Bifoldable LWE where bifoldMap = bifoldMapDefault
instance Bitraversable LWE where bitraverse = ...

But at this point we might think about just writing the plain ADT out and writing the Applicative, Monad and Bitraversable instances in a couple of lines of code. Alternatively, we could use lens and write a Traversal for the list elements:

import Control.Lens

elems :: Traversal (LWE a e) (LWE b e) a b
elems f (Pure e)  = pure (Pure e)
elems f (x :> xs) = (:>) <$> f x <*> elems f xs

Thinking further along this line, we should make a Lens for the end element. This is a bit of a bonus over the generic Free interface, since we know that every finite LWE must contain exactly one end element, and we can make this explicit by having a Lens for it (rather than a Traversal or Prism).

end :: Lens (LWE a e) (LWE a e') e e'
end f (Pure e)  = Pure <$> f e
end f (x :> xs) = (x :>) <$> end f xs
Prithee answered 31/3, 2015 at 21:3 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.