\documentclass[10pt,letterpaper]{article} \usepackage[utf8]{inputenc} \usepackage{listings} \lstnewenvironment{code}{\lstset{language=Haskell,basicstyle=\small}}{} \author{Alexander Schaap} \title{Input} \begin{document} \maketitle \section{Thoughts} Input takes input in some format, encapsulates/converts it piece by piece in words and groups these into lines before it enters those into a storage (which might be a passthrough in the case of pipe and filter). It will need to 'connect' to some input and some storage. A choice of word to enter into the storage is also necessary. Incrementality (for the pipe-and-filter architecture) is not an issue for this module. The data will likely be converted and/or split into pieces, so it will have to pass through this module. Perhaps it can be brought closer to storage. The changes possible here are the input format, what word implementation is used, how this input is converted into the specified words, and which storage implementations are chosen for lines and the first line storage. \begin{code} {-# 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 \end{code} \end{document}