Skip to content

Commit

Permalink
Remove unused imports and stale code.
Browse files Browse the repository at this point in the history
  • Loading branch information
aloiscochard committed Apr 16, 2016
1 parent dabe746 commit d9827c3
Show file tree
Hide file tree
Showing 3 changed files with 4 additions and 8 deletions.
2 changes: 1 addition & 1 deletion sarsi-nvim/Main.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Main where

import Codec.Sarsi (Event(..), Level(..), Location(..), Message(..))
import Data.Machine (ProcessT, (<~), asParts, auto, final, scan, sinkPart_, runT)
import Data.Machine (ProcessT, (<~), asParts, final, scan, sinkPart_, runT)
import Data.MessagePack.Object (Object(..), toObject)
import NVIM.Client (Command(..), runCommand)
import Sarsi (getBroker, getTopic, title)
Expand Down
2 changes: 1 addition & 1 deletion sarsi-sbt/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import System.Exit (ExitCode, exitWith)
import System.Process (StdStream(..), shell, std_in, std_out)
import System.Process.Machine (ProcessMachines, callProcessMachines)
import System.IO (BufferMode(NoBuffering), hSetBuffering, stdin, stdout)
import System.IO.Machine (IOSink, byChunk)
import System.IO.Machine (byChunk)

import qualified Data.List as List
import qualified Data.Text.IO as TextIO
Expand Down
8 changes: 2 additions & 6 deletions src/Sarsi/Consumer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,12 +5,12 @@ import Codec.Sarsi (Event, getEvent)
import Control.Concurrent.MVar (newEmptyMVar, takeMVar, putMVar)
import Control.Exception (IOException, bracket, try)
import Data.Binary.Machine (processGet)
import Data.Machine ((<~), auto, asParts, runT_)
import Data.Machine ((<~), auto, asParts)
import Network.Socket (connect, socketToHandle)
import Sarsi (Broker(..), Topic(..), createSocket, getSockAddr)
import System.FSNotify (eventPath, watchDir, withManager)
import System.IO (IOMode(ReadMode), hClose, hWaitForInput)
import System.IO.Machine (IOSink, IOSource, byChunkOf, sourceHandle)
import System.IO.Machine (IOSource, byChunkOf, sourceHandle)

consumeOrWait :: Topic -> (Maybe s -> IOSource Event -> IO (Either s a)) -> IO a
consumeOrWait topic@(Topic (Broker bp) tp) f = do
Expand All @@ -25,10 +25,6 @@ consumeOrWait topic@(Topic (Broker bp) tp) f = do
consumeOrWait topic f
pred' e = eventPath e == tp

consumeOrWait_ :: Topic -> IOSink Event -> IO a
consumeOrWait_ topic@(Topic _ _) sink =
consumeOrWait topic f where f _ src = fmap (const $ Left ()) $ runT_ $ sink <~ src

consume :: Topic -> (Maybe s -> IOSource Event -> IO (Either s a)) -> IO (Either IOException a)
consume topic f = try $ consume' topic f

Expand Down

0 comments on commit d9827c3

Please sign in to comment.