Should folds in containers package remain INLINE

wren ng thornton wren at freegeek.org
Tue May 8 03:11:50 CEST 2012


On 5/7/12 4:02 AM, Simon Peyton-Jones wrote:
> |> Can you give a concrete example.  It's hard to be certain but what you
> |> describe sounds like exactly what INLINABLE does.
>
> Your example didn't use any type classes, so GHC won't specialise it.

In order to give a sense of why it matters I only presented the general 
recurrence rather than the actual Haskell code; in the recurrence the 
type class is left implicit, but covers (Probability,(*),sum). The 
actual type of the forward algorithm in the Haskell code is:

     forward
         ::  ( Enum i
             , MapLike i map_i
             , MapLike ts map_ts
             , SlidingWindow t ts
             , ExtendedSemiring t sr sr0
             )
         => map_ts Prob
             -- ^ Prior probabilities: @Pr( t_{1-k}^0 )@
         -> (t -> ts -> Prob)
             -- ^ Transition probabilities: @Pr( t_j | t_{j-k}^{j-1} )@
         -> (w -> t  -> Prob)
             -- ^ Emission probabilities: @Pr( w_j | t_j )@
         -> (w -> [t])
             -- ^ A tag dictionary for all words
         -> [w]
             -- ^ The sentence to be tagged: @w_1^N@
         -> (i, map_i (map_ts sr))
             -- ^ The final index and table: @(N, alpha)@

The first four arguments are passed in together, but are dynamically 
defined; and the resulting function will be called on multiple [w]. We 
will almost certainly satisfy:

     i     ~ Nat        -- a newtype of Int
     map_i ~ NatMap     -- a newtype of IntMap; fundep defines i
     t     ~ ID Tag     -- a newtype of Int
     w     ~ ID Word    -- a newtype of Int

and so should definitely specialize on them. That part can be handled by 
SPECIALIZE since it's well-known. But the important things are the types 
which are left abstract but which we want to specialize on:

     ts        -- some n-tuple of @t@ for unknown @n@
     map_ts    -- fundep defines ts
     sr        -- fundep defined by sr0
     sr0       -- the semiring-like structure

-- 
Live well,
~wren



More information about the Libraries mailing list