Created
November 23, 2013 12:22
-
-
Save AlexanderAA/7614044 to your computer and use it in GitHub Desktop.
This file contains hidden or 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
{-# LANGUAGE DeriveDataTypeable #-} | |
-- | Merging of indexed types | |
module MergeIx ( | |
main | |
) where | |
import Data.Typeable | |
import qualified Data.Sequence as S | |
import qualified Data.IxSet as IX | |
-------------------------------------------------------------------------------- | |
--Types------------------------------------------------------------------------- | |
data Col = Col Int deriving (Eq, Show, Ord, Typeable) | |
data Row = Row Int deriving (Eq, Show, Ord, Typeable) | |
data Val = Val Int deriving (Eq, Show, Ord, Typeable) | |
data SV = SV Col Row Val deriving (Eq, Show, Typeable) | |
getIxCol :: SV -> [Col] | |
getIxCol (SV col _ _) = [col] | |
getIxRow :: SV -> [Row] | |
getIxRow (SV _ row _) = [row] | |
instance IX.Indexable SV where | |
empty = IX.ixSet [IX.ixFun getIxCol, IX.ixFun getIxRow] | |
instance Ord SV where | |
compare (SV acol arow aval) (SV bcol brow bval) = | |
case ccol of | |
LT -> LT | |
EQ -> crow | |
GT -> GT | |
where | |
ccol = compare acol bcol | |
crow = compare arow brow | |
compareVal :: SV -> SV -> Ordering | |
compareVal a@(SV ac ar av) b@(SV bc br bv) = (compare av bv) | |
mergeSV :: SV -> IX.IxSet SV -> IX.IxSet SV | |
mergeSV el@(SV col row val) svset = do | |
case ex of | |
Nothing -> IX.insert el svset | |
Just ex -> case (compareVal ex el) of | |
LT -> IX.insert el $ IX.delete ex svset | |
EQ -> svset | |
GT -> svset | |
where | |
ex = IX.getOne $ (IX.getEQ col . IX.getEQ row) svset | |
mergeIxSV :: [SV] -> IX.IxSet SV -> IX.IxSet SV | |
mergeIxSV newSV@(x:xs) currentSV = mergeIxSV xs $ mergeSV x currentSV | |
mergeIxSV [] currentSV = currentSV | |
main = do | |
let seq0 = IX.fromList [(SV (Col 1) (Row 2) (Val 3)), | |
(SV (Col 1) (Row 3) (Val 3)), | |
(SV (Col 1) (Row 3) (Val 5)), | |
(SV (Col 1) (Row 5) (Val 3))] :: IX.IxSet SV | |
print $ seq0 | |
let el = (SV (Col 1) (Row 2) (Val 7)) | |
print $ mergeSV el seq0 | |
let seq1 = IX.fromList [(SV (Col 2) (Row 2) (Val 3)), | |
(SV (Col 1) (Row 3) (Val 7)), | |
(SV (Col 1) (Row 5) (Val 0))] :: IX.IxSet SV | |
print seq1 | |
print $ mergeIxSV (IX.toList seq1) seq0 | |
print (IX.stats seq1) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment