-
Notifications
You must be signed in to change notification settings - Fork 0
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Implement indexed tables as databases (#38)
* Add IndexedTable file * Add singleton Indexed Table * Implement unions of indexed tables * Implement projection * Implement selection on IndexedTables * Implement aggregation in indexed table * Define natural join for indexed tables * Explain natural join for indexed tables
- Loading branch information
Showing
5 changed files
with
91 additions
and
4 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,27 @@ | ||
module Database.IndexedTable where | ||
|
||
import qualified Data.Bag as Bag | ||
import qualified Data.Key as Map | ||
import Data.CMonoid | ||
|
||
empty :: (Map.Key k) => Map.Map k (Bag.Bag v) | ||
empty = Map.empty | ||
|
||
singleton :: (Map.Key k) => (k, v) -> Map.Map k (Bag.Bag v) | ||
singleton (k, v) = Map.single (k, Bag.single v) | ||
|
||
union :: (Map.Key k) => Map.Map k (Bag.Bag v) -> Map.Map k (Bag.Bag v) -> Map.Map k (Bag.Bag v) | ||
union t1 t2 = (fmap (uncurry Bag.union) . Map.merge) (t1, t2) | ||
|
||
projection :: (Map.Key k) => (v -> w) -> Map.Map k (Bag.Bag v) -> Map.Map k (Bag.Bag w) | ||
projection = fmap . fmap | ||
|
||
selection :: (Map.Key k) => (v -> Bool) -> Map.Map k (Bag.Bag v) -> Map.Map k (Bag.Bag v) | ||
selection p = fmap (Bag.filter p) | ||
|
||
aggregation :: (Map.Key k, CMonoid m) => Map.Map k (Bag.Bag m) -> Map.Map k m | ||
aggregation = fmap Bag.reduceBag | ||
|
||
-- Joins on common keys | ||
naturalJoin :: (Map.Key k) => Map.Map k (Bag.Bag v) -> Map.Map k (Bag.Bag w) -> Map.Map k (Bag.Bag (v, w)) | ||
naturalJoin t1 t2 = fmap (uncurry Bag.cp) (Map.merge (t1 , t2)) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,49 @@ | ||
module Database.IndexedTableSpec (spec) where | ||
|
||
import Test.Hspec | ||
import qualified Database.IndexedTable as Table | ||
import qualified Data.Key as Map | ||
import qualified Data.Bag as Bag | ||
import Data.Monoid | ||
|
||
type Name = String | ||
data Person = Person { firstName :: Name, lastName :: Name} deriving (Show, Eq) | ||
|
||
people :: Map.Map () (Bag.Bag Person) | ||
people = Map.Lone (Bag.Bag [Person "John" "Smith", Person "Jane" "Doe", Person "John" "Doe"]) | ||
|
||
spec :: Spec | ||
spec = do | ||
describe "empty" $ do | ||
it "returns an empty map" $ do | ||
(Table.empty :: Map.Map () (Bag.Bag Int)) `shouldBe` (Map.empty :: Map.Map () (Bag.Bag Int)) | ||
describe "singleton" $ do | ||
it "returns a single table" $ do | ||
Table.singleton ((), 3) `shouldBe` Map.Lone (Bag.Bag [3]) | ||
describe "union" $ do | ||
it "can correctly handle union of singletons" $ do | ||
Table.union (Table.singleton ((), 3)) (Table.singleton ((), 4)) `shouldBe` Map.Lone (Bag.Bag [3, 4]) | ||
it "can correctly deal with first element empty" $ do | ||
Table.union (Table.empty :: Map.Map () (Bag.Bag Char)) (Table.singleton ((), 'a')) `shouldBe` Map.Lone (Bag.Bag ['a']) | ||
it "can correctly deal with second element empty" $ do | ||
Table.union (Table.singleton ((), 'a')) (Table.empty :: Map.Map () (Bag.Bag Char)) `shouldBe` Map.Lone (Bag.Bag ['a']) | ||
describe "projection" $ do | ||
it "can correctly do a general projection" $ do | ||
Table.projection firstName people `shouldBe` Map.Lone (Bag.Bag ["John", "Jane", "John"]) | ||
it "can correctly project on an empty map" $ do | ||
Table.projection lastName (Table.empty :: Map.Map () (Bag.Bag Person)) `shouldBe` Map.empty | ||
it "can correctly use the identity projection" $ do | ||
Table.projection id people `shouldBe` people | ||
describe "selection" $ do | ||
it "can correctly select in general" $ do | ||
Table.selection ((== "John") . firstName) people `shouldBe` Map.Lone (Bag.Bag [Person "John" "Smith", Person "John" "Doe"]) | ||
it "can correctly select all elements of a table" $ do | ||
Table.selection (const True) people `shouldBe` people | ||
it "can correctly select no elements of a table" $ do | ||
Table.selection (const False) people `shouldBe` Map.empty | ||
describe "aggregation" $ do | ||
it "can correctly aggregate a table in general" $ do | ||
Table.aggregation (Map.Lone (Bag.Bag [Any True, Any True, Any False])) `shouldBe` Map.Lone (Any True) | ||
describe "natural join" $ do | ||
it "is a local cartesian product" $ do | ||
Table.naturalJoin (Map.Lone (Bag.Bag [1, 2])) (Map.Lone (Bag.Bag [2, 3])) `shouldBe` Map.Lone (Bag.Bag [(1, 2), (1, 3), (2, 2), (2, 3)]) |