Add Readable typeclass to simplify safe reading of files

Why?
====

After the introduction of:

    safeReadFile :: FilePath -> IO (Either E.IOException String)

There were places who needed to repack data into the appropriate type.
This is an extra step and, while in these situations not necessarily
*slow*, should be removed.

This introduces a Readable typeclass which dictates implementation of
`readFile'` based on the resulting requested type. This means `safeReadFile`
can be used in various situations without having to `pack`.
This commit is contained in:
Joshua Clayton 2016-07-02 21:17:36 -04:00
parent 752a3b23b9
commit 7618e6cb23
No known key found for this signature in database
GPG Key ID: 5B6558F77E9A8118
3 changed files with 22 additions and 7 deletions

View File

@ -9,7 +9,6 @@ import Data.Csv (FromRecord, ToRecord, HasHeader(..), encode, decode)
import Data.Vector (toList)
import System.Directory (createDirectoryIfMissing)
import qualified Data.ByteString.Lazy as BS
import qualified Data.ByteString.Lazy.Char8 as C
import Unused.Cache.DirectoryFingerprint
import Unused.Util (safeReadFile)
@ -36,7 +35,7 @@ readCache = do
either
(const Nothing)
(processCsv . decode NoHeader . C.pack)
(processCsv . decode NoHeader)
<$> (liftIO $ safeReadFile fileName)
where
processCsv = either (const Nothing) (Just . toList)

View File

@ -4,7 +4,6 @@ module Unused.ResultsClassifier.Config
) where
import qualified Data.Yaml as Y
import qualified Data.ByteString.Char8 as C
import qualified Data.Either as E
import qualified Data.Bifunctor as B
import System.FilePath ((</>))
@ -19,7 +18,7 @@ loadConfig = do
either
(const $ Left "default config not found")
(Y.decodeEither . C.pack)
Y.decodeEither
<$> safeReadFile configFileName
loadAllConfigurations :: IO (Either [ParseConfigError] [LanguageConfiguration])
@ -38,7 +37,7 @@ loadAllConfigurations = do
loadConfigFromFile :: String -> IO (Either ParseConfigError [LanguageConfiguration])
loadConfigFromFile path = do
file <- fmap C.pack <$> safeReadFile path
file <- safeReadFile path
return $ case file of
Left _ -> Right []
Right body -> addSourceToLeft path $ Y.decodeEither body

View File

@ -1,3 +1,6 @@
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
module Unused.Util
( groupBy
, stringToInt
@ -10,6 +13,8 @@ import qualified Control.Exception as E
import qualified Data.List as L
import Data.Function
import Data.Char (digitToInt, isDigit)
import qualified Data.ByteString.Lazy.Char8 as Cl
import qualified Data.ByteString.Char8 as C
groupBy :: (Ord b) => (a -> b) -> [a] -> [(b, [a])]
groupBy f = map (f . head &&& id)
@ -27,5 +32,17 @@ stringToInt xs
where
loop = foldl (\acc x -> acc * 10 + digitToInt x)
safeReadFile :: FilePath -> IO (Either E.IOException String)
safeReadFile = E.try . readFile
class Readable a where
readFile' :: FilePath -> IO a
instance Readable String where
readFile' = readFile
instance Readable C.ByteString where
readFile' = C.readFile
instance Readable Cl.ByteString where
readFile' = Cl.readFile
safeReadFile :: Readable s => FilePath -> IO (Either E.IOException s)
safeReadFile = E.try . readFile'