[vector] #60: Add support for additional implementations of fusible functions

vector vector at projects.haskell.org
Tue Aug 23 22:47:23 BST 2011


#60: Add support for additional implementations of fusible functions
------------------------+---------------------------------------------------
Reporter:  rl           |       Owner:     
    Type:  enhancement  |      Status:  new
Priority:  major        |   Milestone:     
 Version:               |    Keywords:     
------------------------+---------------------------------------------------
 The prime example is `replicate`: if it doesn't fuse, we really want it to
 use `basicSet` rather than `unstream`. There are many other functions like
 this. We don't really want to rely on rules for this because that would
 require an additional simplifier phase to work reliably. Rather, we'd want
 to implement `replicate` roughly like this:

 {{{
 unstreamOrElse :: Stream a -> v a -> v a
 {-# INLINE_STREAM unstreamOrElse #-}
 unstreamOrElse s x = x

 {-# RULES

 "stream/unstreamOrElse"
   stream (unstreamOrElse s x) = s

   #-}

 replicate n x = unstreamOrElse (Stream.replicate n x)
                                (new (Mutable.replicate n x))
 }}}

 We'll probably also want `streamOrElse`:

 {{{
 streamOrElse :: (Stream a -> b) -> (v a -> b) -> v a -> b
 {-# INLINE_STREAM streamOrElse #-}
 streamOrElse f g = g

 {-# RULES

 "streamOrElse/unstream"
   streamOrElse f g (unstream s) = f s

 "streamOrElse/unstreamOrElse"
   streamOrElse f g (unstreamOrElse s x) = f s
 }}}

 There are ways to keep the number of rules manageable (e.g., by making
 `streamOrElse` and `unstreamOrElse` the only streaming combinators.

-- 
Ticket URL: <http://trac.haskell.org/vector/ticket/60>
vector <http://trac.haskell.org/vector>
Package vector


More information about the vector mailing list