fastmemo-0.1.0.1: Memoize functions on Generic types
Safe HaskellNone
LanguageHaskell2010

Data.Function.FastMemo

Description

Straightforward function memoization library; see Examples for example usage

Synopsis

Documentation

class Memoizable a where Source #

Minimal complete definition

Nothing

Methods

memoize :: (a -> b) -> a -> b Source #

default memoize :: (Generic a, GMemoize (Rep a)) => (a -> b) -> a -> b Source #

Instances

Instances details
Memoizable Bool Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Bool -> b) -> Bool -> b Source #

Memoizable Char Source # 
Instance details

Defined in Data.Function.FastMemo.Char

Methods

memoize :: (Char -> b) -> Char -> b Source #

Memoizable Int Source # 
Instance details

Defined in Data.Function.FastMemo.Int

Methods

memoize :: (Int -> b) -> Int -> b Source #

Memoizable Int8 Source # 
Instance details

Defined in Data.Function.FastMemo.Int

Methods

memoize :: (Int8 -> b) -> Int8 -> b Source #

Memoizable Int16 Source # 
Instance details

Defined in Data.Function.FastMemo.Int

Methods

memoize :: (Int16 -> b) -> Int16 -> b Source #

Memoizable Int32 Source # 
Instance details

Defined in Data.Function.FastMemo.Int

Methods

memoize :: (Int32 -> b) -> Int32 -> b Source #

Memoizable Int64 Source # 
Instance details

Defined in Data.Function.FastMemo.Int

Methods

memoize :: (Int64 -> b) -> Int64 -> b Source #

Memoizable Integer Source # 
Instance details

Defined in Data.Function.FastMemo.Integer

Methods

memoize :: (Integer -> b) -> Integer -> b Source #

Memoizable Natural Source # 
Instance details

Defined in Data.Function.FastMemo.Natural

Methods

memoize :: (Natural -> b) -> Natural -> b Source #

Memoizable Ordering Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Ordering -> b) -> Ordering -> b Source #

Memoizable Word Source # 
Instance details

Defined in Data.Function.FastMemo.Word

Methods

memoize :: (Word -> b) -> Word -> b Source #

Memoizable Word8 Source # 
Instance details

Defined in Data.Function.FastMemo.Word

Methods

memoize :: (Word8 -> b) -> Word8 -> b Source #

Memoizable Word16 Source # 
Instance details

Defined in Data.Function.FastMemo.Word

Methods

memoize :: (Word16 -> b) -> Word16 -> b Source #

Memoizable Word32 Source # 
Instance details

Defined in Data.Function.FastMemo.Word

Methods

memoize :: (Word32 -> b) -> Word32 -> b Source #

Memoizable Word64 Source # 
Instance details

Defined in Data.Function.FastMemo.Word

Methods

memoize :: (Word64 -> b) -> Word64 -> b Source #

Memoizable () Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (() -> b) -> () -> b Source #

Memoizable Void Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Void -> b) -> Void -> b Source #

Memoizable Version Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Version -> b) -> Version -> b Source #

Memoizable ByteString Source # 
Instance details

Defined in Data.Function.FastMemo.ByteString

Methods

memoize :: (ByteString -> b) -> ByteString -> b Source #

Memoizable ByteString Source # 
Instance details

Defined in Data.Function.FastMemo.ByteString

Methods

memoize :: (ByteString -> b) -> ByteString -> b Source #

Memoizable a => Memoizable [a] Source # 
Instance details

Defined in Data.Function.FastMemo.Class

Methods

memoize :: ([a] -> b) -> [a] -> b Source #

Memoizable a => Memoizable (Maybe a) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Maybe a -> b) -> Maybe a -> b Source #

(Integral a, Memoizable a) => Memoizable (Ratio a) Source # 
Instance details

Defined in Data.Function.FastMemo.Ratio

Methods

memoize :: (Ratio a -> b) -> Ratio a -> b Source #

Memoizable a => Memoizable (Complex a) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Complex a -> b) -> Complex a -> b Source #

Memoizable a => Memoizable (Identity a) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Identity a -> b) -> Identity a -> b Source #

Memoizable a => Memoizable (NonEmpty a) Source # 
Instance details

Defined in Data.Function.FastMemo.Class

Methods

memoize :: (NonEmpty a -> b) -> NonEmpty a -> b Source #

(Unbox a, Memoizable a) => Memoizable (Vector a) Source # 
Instance details

Defined in Data.Function.FastMemo.Vector

Methods

memoize :: (Vector a -> b) -> Vector a -> b Source #

(Storable a, Memoizable a) => Memoizable (Vector a) Source # 
Instance details

Defined in Data.Function.FastMemo.Vector

Methods

memoize :: (Vector a -> b) -> Vector a -> b Source #

Memoizable a => Memoizable (Vector a) Source # 
Instance details

Defined in Data.Function.FastMemo.Vector

Methods

memoize :: (Vector a -> b) -> Vector a -> b Source #

(Memoizable a, Memoizable b) => Memoizable (Either a b) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Either a b -> b0) -> Either a b -> b0 Source #

(Memoizable a, Memoizable b) => Memoizable (a, b) Source # 
Instance details

Defined in Data.Function.FastMemo.Class

Methods

memoize :: ((a, b) -> b0) -> (a, b) -> b0 Source #

Memoizable (Proxy a) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: (Proxy a -> b) -> Proxy a -> b Source #

(Memoizable a, Memoizable b, Memoizable c) => Memoizable (a, b, c) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: ((a, b, c) -> b0) -> (a, b, c) -> b0 Source #

(Memoizable a, Memoizable b, Memoizable c, Memoizable d) => Memoizable (a, b, c, d) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: ((a, b, c, d) -> b0) -> (a, b, c, d) -> b0 Source #

(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e) => Memoizable (a, b, c, d, e) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: ((a, b, c, d, e) -> b0) -> (a, b, c, d, e) -> b0 Source #

(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f) => Memoizable (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: ((a, b, c, d, e, f) -> b0) -> (a, b, c, d, e, f) -> b0 Source #

(Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g) => Memoizable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Function.FastMemo.Instances

Methods

memoize :: ((a, b, c, d, e, f, g) -> b0) -> (a, b, c, d, e, f, g) -> b0 Source #

memoizeFixedLen :: (HasCallStack, Memoizable a) => Int -> ([a] -> b) -> [a] -> b Source #

Memoize a function on a list whose length is predetermined.

If called on a larger list, it will truncate; on a smaller list, it will throw an error

memo1 :: Memoizable a => (a -> b) -> a -> b Source #

memo2 :: (Memoizable a, Memoizable b) => (a -> b -> c) -> a -> b -> c Source #

memo3 :: (Memoizable a, Memoizable b, Memoizable c) => (a -> b -> c -> d) -> a -> b -> c -> d Source #

memo4 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d) => (a -> b -> c -> d -> e) -> a -> b -> c -> d -> e Source #

memo5 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e) => (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> f Source #

memo6 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f) => (a -> b -> c -> d -> e -> f -> g) -> a -> b -> c -> d -> e -> f -> g Source #

memo7 :: (Memoizable a, Memoizable b, Memoizable c, Memoizable d, Memoizable e, Memoizable f, Memoizable g) => (a -> b -> c -> d -> e -> f -> g -> h) -> a -> b -> c -> d -> e -> f -> g -> h Source #