{-# OPTIONS_GHC -XEmptyDataDecls #-} -- -- (c) 2009, Sigbjorn Finne. -- -- Example of how to create and execute LINQ queries -- from Haskell beyond basic 'where' queries (cf. LinqQuery.hs) -- -- To test, call 'whereSelectIt' from GHCi. -- module LinqSelect where import Data.Int import NET import NET.System.Func import NET.System.Collections.Generic.Queue import NET.System.Collections.Generic.List as List import NET.System.Linq.Enumerable import NET.System.Linq.IOrderedEnumerable instance NET.System.Linq.IOrderedEnumerable.IOrderedEnumerable (Queue_ a b) where instanceName_IOrderedEnumerable _ = "" newQueue :: NET.Type a => a -> IO (Queue () a) newQueue a = newGeneric "System.Collections.Generic.Queue" a whereSelectIt :: IO () whereSelectIt = do dict <- newQueue "" mapM_ (flip enqueue dict) ["Harry", "Dick", "Jan"] -- simple predicate for picking strings longer than the given length. let predicate v = return (length v > 2) putStrLn "Performing the query.." d0 <- dict # whereQ predicate d1 <- (d0 `asTypeOf` dict) # orderBy (\ x -> return (length x)) d <- (d1 `asTypeOf` dict) # select (\ x -> return (x ++ show (length x))) putStrLn "..query done; predicate not yet invoked.." vs <- d # getList putStrLn ("Query result: " ++ show vs) putStrLn "Running some extra LINQ operations over query result.." let showRes c act = d # act >>= \ v -> putStrLn (c ++ ": " ++ show v) showRes "First element" first showRes "Number of elements" NET.System.Linq.Enumerable.count showRes "Contains Jan3?" (NET.System.Linq.Enumerable.contains "Jan3") showRes "Contains Jan4?" (NET.System.Linq.Enumerable.contains "Jan4") showRes "Has Jan4?" (NET.System.Linq.Enumerable.any_1 (\ x -> return (x == "Jan4"))) showRes "Has Jan3?" (NET.System.Linq.Enumerable.any_1 (\ x -> return (x == "Jan3"))) d2 <- NET.System.Linq.Enumerable.concat d d vs <- d2 # getList putStrLn ("Query result: " ++ show vs) dict # enqueue "Bob!" d2 <- NET.System.Linq.Enumerable.union d d vs <- d2 # getList putStrLn ("2nd query result: " ++ show vs) getList :: (Type a, Result a) => Queue () a -> IO [a] getList q = do ls <- q # toList count <- ls # getField "Count" () mapM (\ i -> ls # List.get_Item i) [(0::Int32)..(count-1)]