Skip to content

Commit

Permalink
Use catch from Control.Exception, avoid warning.
Browse files Browse the repository at this point in the history
  • Loading branch information
John MacFarlane committed Oct 24, 2012
1 parent 5489cef commit 939f87e
Show file tree
Hide file tree
Showing 4 changed files with 38 additions and 11 deletions.
11 changes: 8 additions & 3 deletions Yst/Build.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-
Copyright (C) 2009 John MacFarlane <jgm@berkeley.edu>
Expand Down Expand Up @@ -32,12 +33,14 @@ import System.Time (ClockTime(..))
-- So we use System.IO.UTF8 only if we have an earlier version
#if MIN_VERSION_base(4,2,0)
import System.IO (hPutStrLn)
import Prelude hiding (catch)
#else
import Prelude hiding (readFile, putStrLn, print, writeFile)
import Prelude hiding (readFile, putStrLn, print, writeFile, catch)
import System.IO.UTF8
#endif
import System.IO (stderr)
import Control.Monad
import Control.Exception (catch, SomeException)

findSource :: Site -> FilePath -> IO FilePath
findSource = searchPath . sourceDir
Expand Down Expand Up @@ -79,7 +82,8 @@ updateFile site file = do
let destpath = deployDir site </> file
srcpath <- searchPath (filesDir site) file
srcmod <- getModificationTime srcpath
destmod <- catch (getModificationTime destpath) (\_ -> return $ TOD 0 0)
destmod <- catch (getModificationTime destpath)
(\(_::SomeException) -> return $ TOD 0 0)
if srcmod > destmod
then do
createDirectoryIfMissing True $ takeDirectory destpath
Expand All @@ -98,7 +102,8 @@ updatePage site page = do
hPutStrLn stderr $ "Aborting! Cannot build " ++ destpath
exitWith $ ExitFailure 3
depsmod <- mapM getModificationTime deps
destmod <- catch (getModificationTime destpath) (\_ -> return $ TOD 0 0)
destmod <- catch (getModificationTime destpath)
(\(_::SomeException) -> return $ TOD 0 0)
if maximum depsmod > destmod
then do
createDirectoryIfMissing True $ takeDirectory destpath
Expand Down
12 changes: 9 additions & 3 deletions Yst/CSV.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-
Copyright (C) 2009 John MacFarlane <jgm@berkeley.edu>
Expand All @@ -24,14 +25,19 @@ import Text.CSV
-- Note: ghc >= 6.12 (base >=4.2) supports unicode through iconv
-- So we use System.IO.UTF8 only if we have an earlier version
#if MIN_VERSION_base(4,2,0)
import Prelude hiding (catch)
#else
import Prelude hiding (readFile)
import Prelude hiding (readFile, catch)
import System.IO.UTF8
#endif
import Control.Exception (catch, SomeException)

readCSVFile :: FilePath -> IO Node
readCSVFile f = catch (readFile f >>= return . csvToNode . parseCSV' f . stripBlanks . filter (/='\r'))
(\e -> errorExit 11 ("Error parsing " ++ f ++ ": " ++ show e) >> return NNil)
readCSVFile f = catch (toNode `fmap` readFile f)
(\(e::SomeException) -> do
errorExit 11 ("Error parsing " ++ f ++ ": " ++ show e)
return NNil)
where toNode = csvToNode . parseCSV' f . stripBlanks . filter (/='\r')

parseCSV' :: FilePath -> String -> CSV
parseCSV' f s = case parseCSV f s of
Expand Down
14 changes: 11 additions & 3 deletions Yst/Data.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-}
{-
Copyright (C) 2009 John MacFarlane <jgm@berkeley.edu>
Expand Down Expand Up @@ -30,18 +30,26 @@ import Data.Maybe (fromMaybe)
import Data.List (sortBy, nub, isPrefixOf)
import Text.ParserCombinators.Parsec
import System.FilePath (takeExtension)
import Prelude hiding (catch)
import Control.Exception (catch, SomeException)

findData :: Site -> FilePath -> IO FilePath
findData = searchPath . dataDir

getData :: Site -> DataSpec -> IO Node
getData site (DataFromFile file opts) = do
raw <- catch (findData site file >>= readDataFile)
(\e -> errorExit 15 ("Error reading data from " ++ file ++ ": " ++ show e) >> return undefined)
(\(e::SomeException) -> do
errorExit 15 ("Error reading data from " ++ file ++ ": "
++ show e)
return undefined)
return $ foldl applyDataOption raw opts
getData site (DataFromSqlite3 database query opts) = do
raw <- catch (findData site database >>= \d -> readSqlite3 d query)
(\e -> errorExit 15 ("Error reading Sqlite3 database from " ++ database ++ ": " ++ show e) >> return undefined)
(\(e::SomeException) -> do
errorExit 15 ("Error reading Sqlite3 database from " ++
database ++ ": " ++ show e)
return undefined)
return $ foldl applyDataOption raw opts
getData _ (DataConstant n) = return n

Expand Down
12 changes: 10 additions & 2 deletions Yst/Yaml.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-
Copyright (C) 2009 John MacFarlane <jgm@berkeley.edu>
Expand Down Expand Up @@ -26,6 +27,8 @@ import Data.Time
import System.Locale (defaultTimeLocale)
import Codec.Binary.UTF8.String (encodeString, decodeString)
import qualified Data.ByteString.Char8 as B (ByteString, readFile, filter)
import Prelude hiding (catch)
import Control.Exception (catch, SomeException)

-- Note: Syck isn't unicode aware, so we use parseYamlBytes and do our
-- own encoding and decoding.
Expand All @@ -39,8 +42,13 @@ packBuf :: String -> Buf
packBuf = Data.Yaml.Syck.packBuf . encodeString

readYamlFile :: FilePath -> IO Node
readYamlFile f = catch (B.readFile f >>= parseYamlBytes . B.filter (/='\r') >>= return . yamlNodeToNode)
(\e -> errorExit 11 ("Error parsing " ++ f ++ ": " ++ show e) >> return NNil)
readYamlFile f = catch (B.readFile f
>>= parseYamlBytes . B.filter (/='\r')
>>= return . yamlNodeToNode)
(\(e::SomeException) -> do
errorExit 11 ("Error parsing " ++ f ++ ": " ++
show e)
return NNil)

yamlNodeToNode :: YamlNode -> Node
yamlNodeToNode n =
Expand Down

0 comments on commit 939f87e

Please sign in to comment.