Thanks for the reply.  Here's the decomposition I had in mind.  Start with

    type List a = Maybe (a, List a)

Rewrite a bit

    type List a = Maybe (Id a, List a)

Then make the type *constructor* pairing explicit

    type List a = Maybe ((Id :*: List) a)

where

    newtype (f :*: g) a = Prod { unProd :: (f a, g a) }

Then make the type-constructor composition explicit

    type List = Maybe :. (Id :*: List)

(which isn't legal Haskell, due to the type synonym cycle).  From there use
the Functor and Applicative instances for composition and pairing of type
constructors and for Id.  I think the result is equivalent to ZipList.

To clarify my "cross products" question, I mean fs <*> xs = [f x | f <- fs,
x <- xs], as with lists.

Cheers,  - Conal


On Mon, Mar 24, 2008 at 8:36 AM, apfelmus <[EMAIL PROTECTED]> wrote:

> (Sorry for the late reply)
>
> Conal Elliott wrote:
> > Is there a known deconstruction of the list/backtracking applicative
> functor
> > (AF)?  If I decompose the list type into pieces (Maybe, product,
> > composition), I think I can see where the ZipList AF comes from, but not
> the
> > list/backtracking AF.
>
> So, you mean that the strange thing about the list monad is that the
> "natural" applicative structure for [a] is derived from the "composition"
>
>   [a]  ~  Maybe (a, Maybe (a, ...))  ~  Maybe `O` (a,) `O` Maybe `O`
> (a,) `O` ...
>
> ? Well, this is not quite true since the applicativity you're seeking is
> in the extra argument  a , not in the argument of the composition. In
> fact, this infinite composition doesn't have an argument (that's the
> whole point of taking the fixed point). In other words, every chain like
>
>   Maybe `O` (a,) `O` Maybe `O` (a,)
>   Maybe `O` (a,) `O` Maybe `O` (a,) `O` Maybe `O` (a,)
>
> etc. is an applicative functor in its argument, but not necessarily in
> a  . So, there is more to the "natural" ZipList AF than  Maybe, product
> and composition.
>
> > Is there some construction simpler than lists
> > (non-recursive) that introduces cross products?
>
> What do you mean with "cross products" here? Something with
>
>   sequence :: Applicative f => [f a] -> f [a]
>
> being the cartesian product for the list monad? Or simpler
>
>   pure (,) :: Applicative f => (f a, f b) -> f (a,b)
>
> somehow "crossing" the "elements" of  f a  and  f b ?
>
>
> Regards,
> apfelmus
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to