Skip to content

Instantly share code, notes, and snippets.

@MSeven
Created May 1, 2011 18:25
Show Gist options
  • Save MSeven/950714 to your computer and use it in GitHub Desktop.
Save MSeven/950714 to your computer and use it in GitHub Desktop.
Patent 5,893,120
{- |
The claims of United States Patent 5,893,120 may be reduced to a set
of mathematical formulae expressed in the Typed Lambda Calculus, also
known as System F. This file contains these formulae. The language
used is Haskell, which is a version of System F with extra "syntactic
sugar" to make it useful for practical purposes.
It happens that formulae expressed in Haskell can also be transated by
a Haskell compiler into executable computer programs. However that
does not make a Haskell function any less of a mathematical formula.
Otherwise the quadratic formula
> x = (b +/- sqrt (-b^2 - 4ac))/2a
would be rendered patentable subject material by the same argument.
-}
module Patent120 where
import Data.Char (ord)
-- The "ord" function defines a bijection between text characters and
-- numbers.
import Data.Map (Map)
import qualified Data.Map as M
-- The Data.Map module is a standard module defined entirely as a set
-- of Haskell formulae, in the same way as this module. The "import"
-- means that these formulae are incorporated with the formulae given
-- here.
{-
Claim 1. An information storage and retrieval system, the system
comprising:
a linked list to store and provide access to records stored in a
memory of the system, at least some of the records automatically
expiring,
a record search means utilizing a search key to access the linked
list,
the record search means including a means for identifying and removing
at least some of the expired ones of the records from the linked list
when the linked list is accessed, and
means, utilizing the record search means, for accessing the linked
list and, at the same time, removing at least some of the expired ones
of the records in the linked list.
-}
-- | A record with Birth value below some threshold is considered "expired".
type Birth = Integer
-- | Records in the list have their birth recorded, and also contain
-- a key and a value.
data Record k a = Record Birth k a
-- | True iff the record is older than the threshold argument.
expired t (Record b _ _) = b < t
-- | True iff the record matches the key.
matches k (Record _ k1 _) = k == k1
-- | The value stored in a record.
value (Record _ _ v) = v
-- | Records are stored in a linked list in the system memory.
type Storage k a = [Record k a]
-- | The "search1" function includes a threshold age parameter.
-- It returns both the items that match the key and the linked list
-- with the expired items removed.
--
-- The recitation of "means" cannot be used to disguise the formula
-- given here. Otherwise any mathematical formula could be patented
-- by reciting e.g. "addition means" and "multiplication means" that are
-- mechanically derived from the formula.
search1 :: (Eq k) => Birth -> k -> Storage k a -> (Storage k a, [a])
search1 t k records = foldr nextItem ([], []) records
where
nextItem r@(Record b k2 v) (retained,found) =
(if b > t then r:retained else retained,
if k == k2 then v:found else found)
{-
Claim 2. The information storage and retrieval system according to
claim 1 further including means for dynamically determining maximum
number for the record search means to remove in the accessed linked
list of records.
-}
-- | Similar to "search1", but with an added parameter for the maximum
-- number of records to remove.
search2 :: (Eq k) => Int -> Birth -> k -> Storage k a -> (Storage k a, [a])
search2 n t k = (\(_,x,y) -> (x,y)) . foldr nextItem (n,[],[])
where
nextItem r@(Record b k2 v) (n2,retained,found) =
(n2-1,
if b > t || n2 == 0 then r:retained else retained,
if k == k2 then v:found else found)
{-
Claim 3. A method for storing and retrieving information records using
a linked list to store and provide access to the records, at least
some of the records automatically expiring, the method comprising the
steps of:
accessing the linked list of records,
identifying at least some of the automatically expired ones of the
records, and
removing at least some of the automatically expired records from the
linked list when the linked list is accessed.
Claim 4. The method according to claim 3 further including the step of
dynamically determining maximum number of expired ones of the records
to remove when the linked list is accessed.
-}
-- | Claim 3 can be reduced to the same formula as Claim 1. The use of
-- a sequence of steps cannot disguise the fact that this represents
-- a mathematical formula. Otherwise it would be possible to patent
-- any mathematical formula simply by reciting the steps in evaluating
-- it. e.g. "step 3: the addition of the results of step 1 and step 2"
search3 :: (Eq k) => Birth -> k -> Storage k a -> (Storage k a, [a])
search3 = search1
-- | Likewise Claim 4 can be reduced to the same formula as Claim 2.
search4 :: (Eq k) => Int -> Birth -> k -> Storage k a -> (Storage k a, [a])
search4 = search2
{-
Claim 5. An information storage and retrieval system, the system
comprising:
a hashing means to provide access to records stored in a memory of the
system and using an external chaining technique to store the records
with same hash address, at least some of the records automatically
expiring,
a record search means utilizing a search key to access a linked list
of records having the same hash address,
the record search means including means for identifying and removing
at least some expired ones of the records from the linked list of
records when the linked list is accessed, and
meals, utilizing the record search means, for inserting, retrieving,
and deleting records from the system and, at the same time, removing
at least some expired ones of the records in the accessed linked list
of records.
-}
-- | Every key has a hash code. Strings of characters may be used as
-- keys.
class (Eq k) => Hashable k where
hash :: k -> Int -- Every key has a hash code.
instance Hashable Char where hash = ord
instance (Hashable a) => Hashable [a] where
hash = foldr (\x h -> ((hash x + h) * 53 + 1) `mod` 1733) 0
type HashedStore k a = Map Int [Record k a]
-- | Access a hashed store with a function that returns the modified list of records.
hashAccess5 :: (Hashable k) =>
(Storage k a -> (Storage k a, [a])) -> Birth -> k -> HashedStore k a -> (HashedStore k a, [a])
hashAccess5 f t k store = (M.insert h retained store, result)
where
h = hash k
(retained, result) = case M.lookup h store of
Just records -> f $ filter (expired t) records
Nothing -> ([], [])
-- | Search using hashAccess.
search5 :: (Hashable k) => Birth -> k -> HashedStore k a -> (HashedStore k a, [a])
search5 t k = hashAccess5 srch t k
where srch store = (store, map value $ filter (matches k) store)
-- | Insert using hashAccess.
insert5 :: (Hashable k) => Birth
-- ^ Expiry threshold for old entries.
-> Birth
-- ^ Birth date for new entry.
-> k -> a -> HashedStore k a -> HashedStore k a
insert5 t b k v = fst . hashAccess5 (\store -> (Record b k v : store, [])) t k
-- | Delete using hashAccess
delete5 :: (Hashable k) => Birth -> k -> HashedStore k a -> HashedStore k a
delete5 t k = fst . hashAccess5 (\store -> (filter (not . deleted) store, [])) t k
where deleted (Record _ k1 _) = (k == k1)
{-
Claim 6. The information storage and retrieval system according to
claim 5 further including means for dynamically determining maximum
number for the record search means to remove in the accessed linked
list of records.
-}
-- | Access a hashed store with a function that returns the modified list of records. The "Int"
-- argument is the maxiumum number of expired records to remove.
hashAccess6 :: (Hashable k) =>
Int -> (Storage k a -> (Storage k a, [a])) -> Birth -> k -> HashedStore k a -> (HashedStore k a, [a])
hashAccess6 n f t k store = (M.insert h retained store, result)
where
h = hash k
(retained, result) = case M.lookup h store of
Just records -> f $ filterN n (expired t) records
Nothing -> ([], [])
filterN _ _ [] = []
filterN n1 p (x:xs) = if n1 <= 0 || p x then x : filterN n1 p xs else filterN (n1-1) p xs
-- | Search using hashAccess.
search6 :: (Hashable k) => Int -> Birth -> k -> HashedStore k a -> (HashedStore k a, [a])
search6 n t k = hashAccess6 n srch t k
where srch store = (store, map value $ filter (matches k) store)
-- | Insert using hashAccess.
insert6 :: (Hashable k) => Int
-> Birth
-- ^ Expiry threshold for old entries.
-> Birth
-- ^ Birth date for new entry.
-> k -> a -> HashedStore k a -> HashedStore k a
insert6 n t b k v = fst . hashAccess6 n (\store -> (Record b k v : store, [])) t k
-- | Delete using hashAccess
delete6 :: (Hashable k) => Int -> Birth -> k -> HashedStore k a -> HashedStore k a
delete6 n t k = fst . hashAccess6 n (\store -> (filter (not . deleted) store, [])) t k
where deleted (Record _ k1 _) = (k == k1)
{-
Claim 7. A method for storing and retrieving information records using
a hashing technique to provide access to the records and using an
external chaining technique to store the records with same hash
address, at least some of the records automatically expiring, the
method comprising the steps of:
accessing a linked list of records having same hash address,
identifying at least some of the automatically expired ones of the records,
removing at least some of the automatically expired records from the
linked list when the linked list is accessed, and
inserting, retrieving or deleting one of the records from the system
following the step of removing.
Claim 8. The method according to claim 7 further including the step of
dynamically determining maximum number of expired ones of the records
to remove when the linked list is accessed.
-}
-- | As with Claim 3 vs Claim 1, the formulae for Claim 7 are the same as for Claim 5
hashAccess7 :: (Hashable k) =>
(Storage k a -> (Storage k a, [a])) -> Birth -> k -> HashedStore k a -> (HashedStore k a, [a])
hashAccess7 = hashAccess5
search7 :: (Hashable k) => Birth -> k -> HashedStore k a -> (HashedStore k a, [a])
search7 = search5
insert7 :: (Hashable k) => Birth
-- ^ Expiry threshold for old entries.
-> Birth
-- ^ Birth date for new entry.
-> k -> a -> HashedStore k a -> HashedStore k a
insert7 = insert5
delete7 :: (Hashable k) => Birth -> k -> HashedStore k a -> HashedStore k a
delete7 = delete5
-- | And the formulae for Claim 8 are the same as for Claim 6
hashAccess8 :: (Hashable k) =>
Int -> (Storage k a -> (Storage k a, [a])) -> Birth -> k -> HashedStore k a -> (HashedStore k a, [a])
hashAccess8 = hashAccess6
search8 :: (Hashable k) => Int -> Birth -> k -> HashedStore k a -> (HashedStore k a, [a])
search8 = search6
insert8 :: (Hashable k) => Int
-> Birth
-- ^ Expiry threshold for old entries.
-> Birth
-- ^ Birth date for new entry.
-> k -> a -> HashedStore k a -> HashedStore k a
insert8 = insert6
delete8 :: (Hashable k) => Int -> Birth -> k -> HashedStore k a -> HashedStore k a
delete8 = delete6
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment