{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances, FlexibleInstances #-} module Input where import LineStorage import Word import qualified Data.IntMap as IntMap import Data.IORef import Data.Array.Unboxed import Foreign.StablePtr import Data.Array.IO class Input s t e where parse :: (Word e) => FilePath -> IO (s (t e)) instance Input StorageList StorageList WordString where parse filename = do contents <- readFile filename let contentListListString = map words $ lines contents contentListListWords = ListStorage $ map ListStorage $ map (map create) $ contentListListString return contentListListWords instance Input StorageMap StorageMap WordString where parse filename = do contents <- readFile filename let contentListListStrings = map words $ lines contents contentListMapsWords = map ((foldl add IntMap.empty) . (map create)) contentListListStrings contentMapMapsWords = foldl add IntMap.empty contentListMapsWords return contentMapMapsWords --instance Input StorageGrowableArray StorageArray WordString where class InputModule stores inConn outConn where process :: stores -> inConn -> IO outConn instance InputModule (StorageGrowableArray (StablePtr (StorageArray (StablePtr WordString)))) FilePath () where process (SGA r) f = do contents <- readFile f let listListString = map words $ lines contents ioLstLstStPtrWrdStr <- mapM (mapM (newStablePtr . create)) listListString ioLstStArrStPtrWrdStr <- mapM listStArr $ ioLstLstStPtrWrdStr ioLstStPtrStArrStPtrWrdStr <- mapM newStablePtr ioLstStArrStPtrWrdStr ioSGA_SP_SA_SP_WS <- listStGArr $ ioLstStPtrStArrStPtrWrdStr let SGA tmpref = ioSGA_SP_SA_SP_WS tmp <- readIORef tmpref writeIORef r tmp return () where listStArr x = ini_ (length x) x :: IO (StorageArray (StablePtr WordString)) listStGArr x = ini_ (length x) x :: IO (StorageGrowableArray (StablePtr (StorageArray (StablePtr WordString)))) testSGASAProc :: FilePath -> IO () testSGASAProc f = do stores <- emptySGASA process stores f :: IO () t <- listSGASA stores print t return () emptySGASA :: IO (StorageGrowableArray (StablePtr (StorageArray (StablePtr WordString)))) emptySGASA = do {-pw <- newStablePtr (create "empty" :: WordString) apw <- ini_ 0 [] :: IO (StorageArray (StablePtr WordString)) papw <- newStablePtr $ apw-} ini_ 0 [] :: IO (StorageGrowableArray (StablePtr (StorageArray (StablePtr WordString)))) listSGASA :: (StorageGrowableArray (StablePtr (StorageArray (StablePtr WordString)))) -> IO String listSGASA (SGA r) = do a <- readIORef r let elptrs = elems a els <- mapM deRefStablePtr elptrs do a <- readIORef r let elptrs = elems a els <- mapM deRefStablePtr elptrs elselptrs <- mapM getElems els elsels <- mapM (mapM deRefStablePtr) elselptrs return $ show elsels