memo-sqlite-0.1: memoize functions using SQLite3 database

Portabilityportable
Stabilityunstable
Maintainerclaudiusmaximus@goto10.org

Data.Memo.Sqlite

Contents

Description

Memoize functions in a SQLite3 database.

The functions memoized while having type f :: k -> IO v must result in the same output given the same input, otherwise all kinds of wrongness will result.

The cleanup action returned by the memoizers must not be called if you are going to use the memoized function again; beware.

An example program (included in the examples directory) might look like:

 -- fib.hs
 import Data.Memo.Sqlite (memoRec', readShow, table)

 import Control.Monad (liftM2)
 import System.Environment (getArgs)

 fib :: (Integer -> IO Integer) -> Integer -> IO Integer
 fib _fib' n@0 = print n >> return 0
 fib _fib' n@1 = print n >> return 1
 fib  fib' n   = print n >> liftM2 (+) (fib' (n - 1)) (fib' (n - 2))

 main :: IO ()
 main = do
   [file, ts, ns] <- getArgs
   let Just t = table ts
       n = read ns
   (cleanup, fib') <- memoRec' readShow file t fib
   fib' n >>= \nth -> putStrLn $ "fib(" ++ show n ++ ") = " ++ show nth
   cleanup

Example usage:

 ghc --make fib.hs
 ./fib fibs.sqlite3 fibs 10
 ./fib fibs.sqlite3 fibs 10
 ./fib fibs.sqlite3 fibs 100
 ./fib fibs.sqlite3 fibs 100

See also:

  • the data-memocombinators package for pure in-memory memoization.

Synopsis

Database table identifier.

data Table Source

A valid SQLite3 table name.

Instances

table :: String -> Maybe TableSource

Construct a table name.

Database (de)serialization.

class Sqlite t whereSource

Database (de)serialization

Methods

toSqlite :: t -> SQLDataSource

Serialize to SQLite3 data.

fromSqlite :: SQLData -> tSource

Deserialize from SQLite3 data.

Instances

(Read t, Show t) => Sqlite (ReadShow t) 

Wrapper types for control over (de)serialization.

type Wrap s t k v = (k -> IO v) -> s k -> IO (t v)Source

type Unwrap s t k v = (s k -> IO (t v)) -> k -> IO vSource

type Wrapper s t k v = (Wrap s t k v, Unwrap s t k v)Source

Read/Show (de)serialization.

data ReadShow t Source

Use Read and Show for database (de)serialization.

Instances

(Read t, Show t) => Sqlite (ReadShow t) 

readShow :: Wrapper ReadShow ReadShow k vSource

Wrapper using Read and Show for (de)serialization of both keys and values.

Memoizers.

Memoizer types.

type Memo k v = (k -> IO v) -> IO (IO (), k -> IO v)Source

type MemoRec k v = ((k -> IO v) -> k -> IO v) -> IO (IO (), k -> IO v)Source

type MkMemo k v = FilePath -> Table -> Memo k vSource

type MkMemoRec k v = FilePath -> Table -> MemoRec k vSource

Memoizer functions.

memo :: (Sqlite k, Sqlite v) => MkMemo k vSource

Memoize a function using an SQLite3 database.

memoRec :: (Sqlite k, Sqlite v) => MkMemoRec k vSource

Memoize a recursive function using an SQLite3 database.

memo' :: (Sqlite (s k), Sqlite (t v)) => Wrapper s t k v -> MkMemo k vSource

Memoize a function using an SQLite3 database, using the supplied wrapper for control of (de)serialization.

memoRec' :: (Sqlite (s k), Sqlite (t v)) => Wrapper s t k v -> MkMemoRec k vSource

Memoize a recursive function using an SQLite3 database, using the supplied wrapper for control of (de)serialization.

SQLite3 data (re-exported from the direct-sqlite package).