{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Monoid.Lexical.RunLengthEncoding -- Copyright : (c) Edward Kmett 2009 -- License : BSD-style -- Maintainer : libraries@haskell.org -- Stability : experimental -- Portability : non-portable (MPTCs) -- -- A simple 'Monoid' transformer that turns any monoidal 'Reducer' into a -- a reducer that expects to be supplied both a run length @n@ with each item -- and which efficiently exponentiates the result of 'unit' @n@ times through -- 'replicate'. -- ----------------------------------------------------------------------------- module Data.Monoid.Lexical.RunLengthEncoding ( module Data.Monoid.Reducer , RLE(RLE,getRLE) ) where import Prelude hiding (replicate) import Data.Monoid.Reducer import Data.Monoid.Combinators (replicate) newtype RLE n m = RLE { getRLE :: m } instance (Integral n, Monoid m) => Monoid (RLE n m) where mempty = RLE mempty RLE a `mappend` RLE b = RLE (a `mappend` b) instance (Integral n, Reducer c m) => Reducer (n,c) (RLE n m) where unit ~(n,c) = RLE $ replicate (unit c) n