Way cool. I have gained newfound respect for what I don't know. :)

Can there ever be more than one (observably different) valid definition of pure for a given <*> that obeys all the laws? I would imagine that there could be at most one.

Dan

Ryan Ingram wrote:
(I'm going to play fast and loose with constructors for this post,
treating MyList and ZipList as if they were [])

On Thu, Jul 16, 2009 at 4:10 PM, Dan Weston<weston...@imageworks.com> wrote:
-- different from [], sum rather than product
instance Applicative MyList where
 pure x = x ::: Nil
 (<*>) (f ::: fs) (x ::: xs) = f x ::: (fs <*> xs)
 (<*>) _ _ = Nil

Unfortunately, this instance doesn't fulfill this Applicative law:
     pure id <*> f = f

pure id <*> [1,2,3]
= [id] <*> [1,2,3]
= [id 1]
= [1]

Fortunately, the solution already exists in Control.Applicative:

-- | Lists, but with an 'Applicative' functor based on zipping, so that
--
-- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f 
xs1 ... xsn)@
--
newtype ZipList a = ZipList { getZipList :: [a] }

instance Functor ZipList where
        fmap f (ZipList xs) = ZipList (map f xs)

instance Applicative ZipList where
        pure x = ZipList (repeat x)
        ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)

In this case:

pure id <*> [1,2,3]
= [id, id, ...] <*> [1,2,3]
= [id 1, id 2, id 3]
= [1,2,3]

  -- ryan



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to