module Data.MemoCombinators
( Memo
, wrap
, memo2, memo3, memoSecond, memoThird
, bool, char, list, boundedList, either, maybe, unit, pair
, enum, integral, bits
, switch
, RangeMemo
, arrayRange, unsafeArrayRange, chunks
)
where
import Prelude hiding (either, maybe)
import Data.Bits
import qualified Data.Array as Array
import Data.Char (ord,chr)
import qualified Data.IntTrie as IntTrie
type Memo a = forall r. (a -> r) -> (a -> r)
wrap :: (a -> b) -> (b -> a) -> Memo a -> Memo b
wrap i j m f = m (f . i) . j
memo2 :: Memo a -> Memo b -> (a -> b -> r) -> (a -> b -> r)
memo2 a b = a . (b .)
memo3 :: Memo a -> Memo b -> Memo c -> (a -> b -> c -> r) -> (a -> b -> c -> r)
memo3 a b c = a . (memo2 b c .)
memoSecond :: Memo b -> (a -> b -> r) -> (a -> b -> r)
memoSecond b = (b .)
memoThird :: Memo c -> (a -> b -> c -> r) -> (a -> b -> c -> r)
memoThird c = (memoSecond c .)
bool :: Memo Bool
bool f = cond (f True) (f False)
where
cond t f True = t
cond t f False = f
list :: Memo a -> Memo [a]
list m f = table (f []) (m (\x -> list m (f . (x:))))
where
table nil cons [] = nil
table nil cons (x:xs) = cons x xs
char :: Memo Char
char = wrap chr ord integral
boundedList :: Int -> Memo a -> Memo [a]
boundedList 0 m f = f
boundedList n m f = table (f []) (m (\x -> boundedList (n1) m (f . (x:))))
where
table nil cons [] = nil
table nil cons (x:xs) = cons x xs
either :: Memo a -> Memo b -> Memo (Either a b)
either m m' f = table (m (f . Left)) (m' (f . Right))
where
table l r (Left x) = l x
table l r (Right x) = r x
maybe :: Memo a -> Memo (Maybe a)
maybe m f = table (f Nothing) (m (f . Just))
where
table n j Nothing = n
table n j (Just x) = j x
unit :: Memo ()
unit f = let m = f () in \() -> m
pair :: Memo a -> Memo b -> Memo (a,b)
pair m m' f = uncurry (m (\x -> m' (\y -> f (x,y))))
enum :: (Enum a) => Memo a
enum = wrap toEnum fromEnum integral
integral :: (Integral a) => Memo a
integral = wrap fromInteger toInteger bits
bits :: (Num a, Ord a, Bits a) => Memo a
bits f = IntTrie.apply (fmap f IntTrie.identity)
switch :: (a -> Bool) -> Memo a -> Memo a -> Memo a
switch p m m' f = table (m f) (m' f)
where
table t f x | p x = t x
| otherwise = f x
type RangeMemo a = (a,a) -> Memo a
arrayRange :: (Array.Ix a) => RangeMemo a
arrayRange rng = switch (Array.inRange rng) (unsafeArrayRange rng) id
unsafeArrayRange :: (Array.Ix a) => RangeMemo a
unsafeArrayRange rng f = (Array.listArray rng (map f (Array.range rng)) Array.!)
chunks :: (Array.Ix a) => RangeMemo a -> [(a,a)] -> Memo a
chunks rmemo cs f = lookup (cs `zip` map (\rng -> rmemo rng f) cs)
where
lookup [] _ = error "Element non in table"
lookup ((r,c):cs) x | Array.inRange r x = c x
| otherwise = lookup cs x