{-# OPTIONS_GHC -XEmptyDataDecls #-} -- -- (c) 2009, Sigbjorn Finne. -- -- Example of how to create and execute LINQ queries -- from Haskell. -- -- To test, call 'whereQuery' from GHCi. -- module LinqQuery where import Data.Int import NET import NET.System.Collections.Generic.Queue ( Queue, enqueue ) import NET.System.Collections.Generic.List as List ( get_Item ) import NET.System.Linq.Enumerable ( whereQ, toList ) newQueue :: NET.Type a => a -> IO (Queue () a) newQueue a = newGeneric "System.Collections.Generic.Queue" a whereQuery :: IO () whereQuery = do intQ <- newQueue (0::Int32) mapM_ (flip enqueue intQ) [1..5] let queryPred v = do putStrLn ("Predicate passed argument: " ++ show v) return (v>=3) putStrLn "Performing the query..." -- creating the LINQ query, passing it the (Haskell) predicate res <- intQ # whereQ queryPred putStrLn "..query done; predicate not yet invoked.." -- let's force the query by getting out a result list.. ls <- res # getList putStrLn ("Query result: " ++ show ls) 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)]