Remove unused Applicative import

<$> is exported by Prelude!!
This commit is contained in:
rnhmjoj 2015-04-11 19:15:25 +02:00
parent de4e010021
commit 470e336e0a
4 changed files with 1 additions and 4 deletions

View File

@ -10,7 +10,6 @@ import Web.Simple
import Web.Simple.Static (serveStatic) import Web.Simple.Static (serveStatic)
import Web.Simple.Templates (render) import Web.Simple.Templates (render)
import Control.Applicative
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Text.Printf (printf) import Text.Printf (printf)
import Data.Aeson import Data.Aeson

View File

@ -3,7 +3,6 @@ module Breve.Common where
import Paths_breve (getDataFileName) import Paths_breve (getDataFileName)
import Control.Applicative
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Text.Printf (printf) import Text.Printf (printf)
import System.Environment (lookupEnv) import System.Environment (lookupEnv)

View File

@ -5,7 +5,6 @@ module Breve.Generator
, Url , Url
) where ) where
import Control.Applicative
import Control.Monad.State import Control.Monad.State
import System.Random import System.Random
import Crypto.Hash.SHA256 (hash) import Crypto.Hash.SHA256 (hash)

View File

@ -18,7 +18,7 @@ type UrlTable = H.CuckooHashTable Name Url
sync :: UrlTable -> FilePath -> IO () sync :: UrlTable -> FilePath -> IO ()
sync table file = forever $ do sync table file = forever $ do
threadDelay (round 3.0e8) threadDelay (round 3.0e8)
content <- fmap show (H.toList table) content <- show <$> H.toList table
writeFile file content writeFile file content
-- Load a url table from a file -- Load a url table from a file