Reputation: 864
I'm trying to recurse through a directory, processing files and storing the results in a database, but I'm running into a problem.
A simplified example of what I'm trying to do would look like:
{-# LANGUAGE QuasiQuotes, TemplateHaskell, TypeFamilies, OverloadedStrings #-}
{-# LANGUAGE GADTs, FlexibleContexts #-}
import Database.Persist
import Database.Persist.Sqlite
import Database.Persist.TH
import System.Environment (getArgs)
import System.Directory (canonicalizePath, getDirectoryContents, doesDirectoryExist, doesFileExist)
import System.FilePath (combine, takeExtension)
import Control.Monad (filterM, mapM_)
import Control.Monad.IO.Class (liftIO)
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistUpperCase|
File
path String
deriving (Show)
|]
main :: IO ()
main = do
args <- getArgs
path <- canonicalizePath $ head args
runSqlite "files.sqlite" $ do
runMigration migrateAll
liftIO $ processDirectory path
return ()
processDirectory path = files >>= mapM_ processFile >>
directories >>= mapM_ processDirectory
where contents = getDirectoryContents path >>=
return . map (combine path) . filter (`notElem` [".", ".."])
directories = contents >>= filterM doesDirectoryExist
files = contents >>= filterM doesFileExist
processFile path = insert $ File path
The above does not compile however, instead resulting in:
No instance for (PersistStore IO)
arising from a use of `processFile'
Possible fix: add an instance declaration for (PersistStore IO)
In the first argument of `mapM_', namely `processFile'
In the second argument of `(>>=)', namely `mapM_ processFile'
In the first argument of `(>>)', namely
`files >>= mapM_ processFile'
Failed, modules loaded: none.
This makes sense to me, since processFile is just a call to insert, which part of the PersistStore monad (right?) not IO. I think what I need is a monad transformer, but at this point I'm running into a brick wall, which perhaps means I'm barking up the wrong tree.
Upvotes: 2
Views: 342
Reputation: 131
The one thing you do not want enclosed by liftIO is the database action, so you need to rearrange the code to leave processFile outside of it.
About the simplest change to your code which will make it compile is the following. I will leave it to you to tidy it up so that it is clearer what is going on!
{-# LANGUAGE QuasiQuotes, TemplateHaskell, TypeFamilies, OverloadedStrings #-}
{-# LANGUAGE GADTs, FlexibleContexts #-}
import Database.Persist
import Database.Persist.Sqlite
import Database.Persist.TH
import System.Environment (getArgs)
import System.Directory (canonicalizePath, getDirectoryContents, doesDirectoryExist, doesFileExist)
import System.FilePath (combine, takeExtension)
import Control.Monad (filterM, mapM_)
import Control.Monad.IO.Class (liftIO)
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistUpperCase|
File
path String
deriving (Show)
|]
main :: IO ()
main = do
args <- getArgs
path <- canonicalizePath $ head args
runSqlite "files.sqlite" $ do
runMigration migrateAll
processDirectory path
return ()
processDirectory path = liftIO files >>= mapM_ processFile >>
liftIO directories >>= mapM_ processDirectory
where contents = getDirectoryContents path >>=
return . map (combine path) . filter (`notElem` [".", ".."])
directories = contents >>= filterM doesDirectoryExist
files = contents >>= filterM doesFileExist
processFile path = insert $ File path
Upvotes: 7