[Haskell-cafe] space-efficient, composable list transformers [was: Re: Reifying case expressions]

Heinrich Apfelmus apfelmus at quantentunnel.de
Mon Jan 2 14:34:34 CET 2012


Sebastian Fischer wrote:
> Your `ListTo` type achieves space efficiency for Applicative composition of
> list functions by executing them in lock-step. Because of the additional
> laziness provided by the `Fmap` constructor, compositions like
> 
>     interpret a . interpret b
> 
> can also be executed in constant space. However, we cannot use the space
> efficient Applicative combinators again to form parallel compositions of
> sequential ones because we are already in the meaning type.
> 
> We could implement composition for the `ListTo` type as follows
> 
>     (<.) :: ListTo b c -> ListTo a [b] -> ListTo a c
>     a <. b = interpret a <$> b
> 
> But if we use a result of this function as argument of <*>, then the
> advantage of using `ListTo` is lost. While
> 
>     interpret ((,) <$> andL <*> andL)
> 
> runs in constant space,
> 
>     interpret ((,) <$> (andL <. idL) <*> (andL <. idL))
> 
> does not.
>
> The ListTransformer type supports composition in lock-step via a category
> instance. The meaning of `ListTransformer a b` is `[a] -> [b]` with the
> additional restriction that all functions `f` in the image of the
> interpretation function are incremental:
> 
>     xs `isPrefixOf` ys  ==>  f xs `isPrefixOf` f ys
> 
> [..]
> 
> The Applicative instance for `ListTransformer` is different from the
> Applicative instance for `ListTo` (or `ListConsumer`). While
> 
>     interpret ((,) <$> idL <*> idL)
> 
> is of type `[a] -> ([a],[a])`
> 
>     transformList ((,) <$> idL <*> idL)
> 
> is of type `[a] -> [(a,a)]`. 
> [..]

Ah, so  ListTransformer  is actually quite different from  ListTo 
because the applicative instance yields a different type. Then again, 
the former can be obtained form the latter via  unzip .

> I have a gut feeling that the laziness provided by the `Fmap` constructor
> is too implicit to be useful for the kind of lock-step composition provided
> by ListTransformer. So I don't have high hopes that we can unify
> `ListConsumer` and `ListTransformer` into a single type.
> 
> Do you have an idea?

Well, the simple solution would be to restrict the type of  (<.)  to

     (<.) :: ListTo b c -> ListTransformer a b -> ListTo a c

so that the second argument is guaranteed to be incremental. Of course, 
this is rather unsatisfactory.

Fortunately, there is a nicer solution that keeps everything in the 
ListTo  type. The main problem with  Fmap  is that it can be far from 
incremental, because we can plug in any function we like:

     example :: ListTo a [a]
     example = Fmap reverse

Without an explicit guarantee that the function is incremental, we can't 
do anything here. But we can just add another constructor to that effect 
if we turn  ListTo  into a GADT:

     data ListTo a b where
         CaseOf   :: b ->  (a -> ListTo a b)  -> ListTo a b
         Fmap     :: (b -> c) -> ListTo a b   -> ListTo a c

         FmapCons :: b -> ListTo a [b] -> ListTo a [b]

The interpretation for this case is given by the morphism

     interpret (FmapCons x g) = fmap (x:) $ interpret g

and sequential composition reads

     -- sequential composition
     -- interpret (a <. b) = interpret $ interpret a <$> b
     (<.) :: ListTo b c -> ListTo a [b] -> ListTo a c
     (CaseOf _ cons) <. (FmapCons y b) = cons y <. b
     (Fmap f a)      <. (FmapCons y b) = Fmap f     $ a <. (FmapCons y b)
     (FmapCons x a)  <. (FmapCons y b) = FmapCons x $ a <. (FmapCons y b)
     a <. (CaseOf nil cons) = CaseOf (interpret a nil) ((a <.) . cons)
     a <. (Fmap f b)        = fmap (interpret a . f) b

Of course, the identity has to be redefined to make use of the new guarantee

     idL :: ListTo a [a]
     idL = caseOf [] $ \x -> FmapCons x idL

I'm going to omit the new definition for the applicative instance, the 
full code can be found here:

     https://gist.github.com/1550676

With all these combinators in place, even examples like

     liftA2 (,) (andL <. takeL 3) (andL <. idL)

should work as expected.


While nice, the above solution is not perfect. One thing we can do with 
  ListTransformer  type is to perform an apply first and then do a 
sequential composition.

     a <. (b <*> c)

This only works because the result of  <*>  is already zipped.


And there is an even more worrisome observation: all this work would 
have been superfluous if we had *partial evaluation*, i.e. if it were 
possible to evaluate expressions like  \xs -> f (4:xs)  beneath the 
lambda. Then we could dispense with all the constructor yoga above and 
simply use a plain

      type ListTo a b = [a] -> b

with the applicative instance

      instance Applicative (ListTo a) where
          pure b = const b
          (f <*> x) cs = case cs of
              []     -> f [] $ x []
              (c:cs) -> let f' = f . (c:); x; = x . (c:) in
                        f' `partialseq` x' `partialseq` (f' <*> x')

to obtain space efficient parallel and sequential composition. In fact, 
by using constructors, we are essentially doing partial evaluation by hand.


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com




More information about the Haskell-Cafe mailing list