{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses #-} -- You'll need these language extensions when defining a type you want to be in an IxSet {- This file should be loaded into ghci for your personal experiments. Try looking at all the different values that start with "ex" and hopefully you should get some definite intuition for using IxSet. -} import Happstack.Data.IxSet -- We need to import Data.Map, Data.Set, and Data.Typeable in order to set up a type to work with IxSet import qualified Data.Map as Map import Data.Map (Map) import Data.Set (Set) import Data.Typeable import Data.Data {- Indexing is done by dispatch over the actual type, so it isn't possible to have a working IxSet with multiple indexes of the same type. The standard trick, then, is to use newtypes. -} newtype Id = Id Int deriving (Ord,Eq,Show,Typeable,Data) newtype Val = Val Int deriving (Ord,Eq,Show,Typeable,Data) newtype Name = Name String deriving (Ord,Eq,Show,Typeable,Data) newtype Calc = Calc Int deriving (Ord,Eq,Data,Typeable) {- Now we define the actual data type that we'll be storing in the IxSet -} data Example1 = Example1 { uid :: Id, name :: Name, val :: Val, unindexed :: Int } deriving (Ord,Eq,Data,Typeable,Show) {- In order to actually use the IxSet interface with a type, that type needs to be made an instance of Indexable. The actual instance is extremely straight forward, however, in that all we need is to make the list of Maps in empty contain an Ix (Map.empty :: Map a (Set Example)) for each type a that we want to index, which in this case means Id, Name, and Val. Now the calcs method is actually something quite interesting. It provides a calculated index, not actually stored in the type, that you can use as an index just like the ones you define in the empty instance. Notice that we need to include the -} instance Indexable Example1 Calc where empty = IxSet [Ix (Map.empty :: Map Id (Set Example1)), Ix (Map.empty :: Map Name (Set Example1)), Ix (Map.empty :: Map Val (Set Example1)), Ix (Map.empty :: Map Calc (Set Example1))] calcs e = let (Val v) = val e u = unindexed e in Calc (u+v) exEmpty :: IxSet Example1 exEmpty = empty exInsert1 :: IxSet Example1 exInsert1 = insert (Example1 (Id 1) (Name "Foo") (Val 10) 0) empty exInsert2 :: IxSet Example1 exInsert2 = insert (Example1 (Id 3) (Name "Bar") (Val 20) 3) $ insert (Example1 (Id 2) (Name "Baz") (Val 10) 0) exInsert1 exDelete :: IxSet Example1 exDelete = delete (Example1 (Id 3) (Name "Bar") (Val 20) 3) exInsert2 -- There exist both fromList and fromSet functions for building -- up IxSets from simpler containers. fromList in particular is -- convenient because of the syntax for lists. exFromList :: IxSet Example1 exFromList = fromList [Example1 (Id 4) (Name "Blah") (Val 30) 5, Example1 (Id 5) (Name "Blah") (Val 40) 0, Example1 (Id 6) (Name "Blah") (Val 10) 0] -- The (|||) operator is used for creating unions of IxSets. -- Conversely the (&&&) operator is used for intersecting IxSets. exUnion :: IxSet Example1 exUnion = exFromList ||| exInsert2 exQuery1 :: IxSet Example1 exQuery1 = exUnion @= Name "Blah" exQuery2 :: IxSet Example1 exQuery2 = exUnion @< Val 40 exQuery3 :: IxSet Example1 exQuery3 = exUnion @>< ((Id 0),(Id 20)) -- the @+ function takes a list of indices and returns the IxSet that -- matches one of the indices. The @* function returns the IxSet that -- matches all of the indices. In this case, we pick out the examples -- that have Id 1 or Id 6 exQuery4 :: IxSet Example1 exQuery4 = exUnion @+ [(Id 1),(Id 6)] -- Again, we can treat the type Calc just as if it was actually contained -- in Example1 for the purposes of queries and updates. exCalcQuery :: IxSet Example1 exCalcQuery = exUnion @= Calc 35 {- The following query passes in a String to the query operator @=. Since we have no index of type String, what do you expect to happen? The behavior of the IxSet library in this case is going to be to return an empty IxSet. Something I think you should take away from this is that the compiler can not check that you are providing a valid index to an IxSet. -} exBadQuery :: IxSet Example1 exBadQuery = exUnion @= "ham" {- To modify a particular item in the ixset, you can use the updateIx function; however, it only works if the index is unique. Otherwise, it'll only modify one of the items that matches the index. -} exUpdateIx :: IxSet Example1 exUpdateIx = updateIx (Id 1) (Example1 (Id 1) (Name "Bar") (Val 20) 3) exUnion