Skip to content

Commit

Permalink
🔧 #61 #80 #72 Properly catch error when history file cannot be deseri…
Browse files Browse the repository at this point in the history
…alized
  • Loading branch information
Romain GERARD committed Apr 11, 2020
1 parent 069b922 commit 922c3fe
Showing 1 changed file with 2 additions and 4 deletions.
6 changes: 2 additions & 4 deletions src/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module Main where
import Protolude hiding (readFile, to, (<&>), (&))

import Control.Monad.Catch (MonadCatch, catchAll)
import Data.Binary (decode, encode)
import Data.Binary (decodeFile, encode)
import qualified Data.ByteString as B
import Data.Hashable (hash)
import Data.List (dropWhileEnd)
Expand Down Expand Up @@ -55,9 +55,7 @@ readFile filepath = bracket (openFile filepath ReadMode) hClose $ \h -> do
getHistory :: (MonadIO m, MonadReader Config m) => m ClipHistory
getHistory = do
storePath <- view $ to (toS . historyPath)
liftIO $ readH storePath `catchAll` const mempty
where
readH filePath = B.readFile filePath <&> V.fromList . decode . toS
liftIO $ (V.fromList <$> decodeFile storePath) `catchAll` const mempty


getStaticHistory :: (MonadIO m, MonadReader Config m) => m ClipHistory
Expand Down

0 comments on commit 922c3fe

Please sign in to comment.