Skip to content

Commit

Permalink
Complete the move to ByteString.
Browse files Browse the repository at this point in the history
Also known as RawFilePath.
  • Loading branch information
kolmodin committed May 1, 2016
1 parent b96fde1 commit 106930c
Show file tree
Hide file tree
Showing 7 changed files with 57 additions and 46 deletions.
12 changes: 6 additions & 6 deletions hinotify.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ source-repository head
location: git://github.com/kolmodin/hinotify.git

library
build-depends: base >= 4.5.0.0 && < 5, bytestring, containers, directory, unix
build-depends: base >= 4.5.0.0 && < 5, bytestring, containers, unix
extensions: ForeignFunctionInterface

exposed-modules:
Expand All @@ -34,39 +34,39 @@ library

test-suite test001
type: exitcode-stdio-1.0
build-depends: base, directory, hinotify
build-depends: base, bytestring, directory, hinotify, unix
hs-source-dirs: src tests
main-is: test001-list-dir-contents.hs
other-modules: Utils
ghc-options: -Wall

test-suite test002
type: exitcode-stdio-1.0
build-depends: base, directory, hinotify
build-depends: base, bytestring, directory, hinotify, unix
hs-source-dirs: src tests
main-is: test002-writefile.hs
other-modules: Utils
ghc-options: -Wall

test-suite test003
type: exitcode-stdio-1.0
build-depends: base, directory, hinotify
build-depends: base, bytestring, directory, hinotify, unix
hs-source-dirs: src tests
main-is: test003-removefile.hs
other-modules: Utils
ghc-options: -Wall

test-suite test004
type: exitcode-stdio-1.0
build-depends: base, directory, hinotify
build-depends: base, bytestring, directory, hinotify, unix
hs-source-dirs: src tests
main-is: test004-modify-file.hs
other-modules: Utils
ghc-options: -Wall

test-suite test005
type: exitcode-stdio-1.0
build-depends: base, directory, hinotify
build-depends: base, bytestring, directory, hinotify, unix
hs-source-dirs: src tests
main-is: test005-move-file.hs
other-modules: Utils
Expand Down
32 changes: 16 additions & 16 deletions src/System/INotify.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@ import Prelude hiding (init)
import Control.Monad
import Control.Concurrent
import Control.Exception as E (bracket, catch, mask_, SomeException)
import qualified Data.ByteString as B
import Data.Maybe
import Data.Map (Map)
import qualified Data.Map as Map
Expand All @@ -51,7 +50,8 @@ import System.IO.Error
import GHC.IO.Handle.FD (fdToHandle')
import GHC.IO.Device (IODeviceType(Stream))

import System.Posix.Files
import System.Posix.ByteString.FilePath
import System.Posix.Files.ByteString

import System.INotify.Masks

Expand All @@ -70,45 +70,45 @@ instance Eq INotify where

newtype Cookie = Cookie CUInt deriving (Eq,Ord)

data FDEvent = FDEvent WD Masks CUInt{-Cookie-} (Maybe B.ByteString) deriving (Eq, Show)
data FDEvent = FDEvent WD Masks CUInt{-Cookie-} (Maybe RawFilePath) deriving (Eq, Show)

data Event =
-- | A file was accessed. @Accessed isDirectory file@
Accessed
{ isDirectory :: Bool
, maybeFilePath :: Maybe B.ByteString
, maybeFilePath :: Maybe RawFilePath
}
-- | A file was modified. @Modified isDirectory file@
| Modified
{ isDirectory :: Bool
, maybeFilePath :: Maybe B.ByteString
, maybeFilePath :: Maybe RawFilePath
}
-- | A files attributes where changed. @Attributes isDirectory file@
| Attributes
{ isDirectory :: Bool
, maybeFilePath :: Maybe B.ByteString
, maybeFilePath :: Maybe RawFilePath
}
-- | A file was closed. @Closed isDirectory file wasWriteable@
| Closed
{ isDirectory :: Bool
, maybeFilePath :: Maybe B.ByteString
, maybeFilePath :: Maybe RawFilePath
, wasWriteable :: Bool
}
-- | A file was opened. @Opened isDirectory maybeFilePath@
| Opened
{ isDirectory :: Bool
, maybeFilePath :: Maybe B.ByteString
, maybeFilePath :: Maybe RawFilePath
}
-- | A file was moved away from the watched dir. @MovedFrom isDirectory from cookie@
| MovedOut
{ isDirectory :: Bool
, filePath :: B.ByteString
, filePath :: RawFilePath
, moveCookie :: Cookie
}
-- | A file was moved into the watched dir. @MovedTo isDirectory to cookie@
| MovedIn
{ isDirectory :: Bool
, filePath :: B.ByteString
, filePath :: RawFilePath
, moveCookie :: Cookie
}
-- | The watched file was moved. @MovedSelf isDirectory@
Expand All @@ -118,12 +118,12 @@ data Event =
-- | A file was created. @Created isDirectory file@
| Created
{ isDirectory :: Bool
, filePath :: B.ByteString
, filePath :: RawFilePath
}
-- | A file was deleted. @Deleted isDirectory file@
| Deleted
{ isDirectory :: Bool
, filePath :: B.ByteString
, filePath :: RawFilePath
}
-- | The file watched was deleted.
| DeletedSelf
Expand Down Expand Up @@ -177,17 +177,17 @@ initINotify = do
(tid1, tid2) <- inotify_start_thread h em
return (INotify h fd em tid1 tid2)

addWatch :: INotify -> [EventVariety] -> FilePath -> (Event -> IO ()) -> IO WatchDescriptor
addWatch :: INotify -> [EventVariety] -> RawFilePath -> (Event -> IO ()) -> IO WatchDescriptor
addWatch inotify@(INotify _ fd em _ _) masks fp cb = do
catch_IO (void $
(if (NoSymlink `elem` masks) then getSymbolicLinkStatus else getFileStatus)
fp) $ \_ ->
ioError $ mkIOError doesNotExistErrorType
"can't watch what isn't there!"
Nothing
(Just fp)
(Just (show fp))
let mask = joinMasks (map eventVarietyToMask masks)
wd <- withCString fp $ \fp_c ->
wd <- withFilePath fp $ \fp_c ->
throwErrnoIfMinus1 "addWatch" $
c_inotify_add_watch (fromIntegral fd) fp_c mask
let event = \e -> ignore_failure $ do
Expand Down Expand Up @@ -259,7 +259,7 @@ read_events h =
nameM <- if len == 0
then return Nothing
else do
fmap Just $ B.packCString ((#ptr struct inotify_event, name) ptr)
fmap Just $ peekFilePath ((#ptr struct inotify_event, name) ptr)
let event_size = (#size struct inotify_event) + (fromIntegral len)
event = cEvent2Haskell (FDEvent wd mask cookie nameM)
rest <- read_events' (ptr `plusPtr` event_size) (r - event_size)
Expand Down
33 changes: 21 additions & 12 deletions tests/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,41 +1,50 @@
{-# LANGUAGE OverloadedStrings #-}
module Utils where

import Control.Concurrent.Chan
import Control.Exception

import System.Directory
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC8
import Data.String

import System.Directory ( removeDirectoryRecursive )
import System.Environment
import System.Exit

import System.INotify

testName :: IO String
import System.Posix.ByteString.FilePath
import System.Posix.Directory.ByteString
import System.Posix.Files.ByteString

testName :: IO RawFilePath
testName = do
n <- getProgName
return (n ++ "-playground")
return (fromString n `B.append` "-playground")

withTempDir :: (String -> IO a) -> IO a
withTempDir :: (RawFilePath -> IO a) -> IO a
withTempDir f = do
path <- testName
bracket
( createDirectory path >> return path )
( removeDirectoryRecursive )
( f )
( createDirectory path ownerModes >> return path )
( removeDirectoryRecursive . fromString . BC8.unpack )
f

withWatch :: INotify -> [EventVariety] -> FilePath -> (Event -> IO ()) -> IO a -> IO a
withWatch :: INotify -> [EventVariety] -> RawFilePath -> (Event -> IO ()) -> IO a -> IO a
withWatch inot events path action f =
bracket
( addWatch inot events path action )
removeWatch
( const f )

inTestEnviron :: [EventVariety] -> (String -> IO a) -> ([Event] -> IO b) -> IO b
inTestEnviron events action f = do
inTestEnviron :: [EventVariety] -> (FilePath -> IO a) -> ([Event] -> IO b) -> IO b
inTestEnviron events action f =
withTempDir $ \testPath -> do
inot <- initINotify
chan <- newChan
withWatch inot events testPath (writeChan chan) $ do
_ <- action testPath
_ <- action (fromString . BC8.unpack $ testPath)
events' <- getChanContents chan
f events'

Expand All @@ -56,5 +65,5 @@ explainFailure expected reality = unlines $

testFailure, testSuccess :: IO a
testFailure = exitFailure
testSuccess = exitWith ExitSuccess
testSuccess = exitSuccess

8 changes: 5 additions & 3 deletions tests/test002-writefile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,15 @@ module Main where

import Control.Monad

import qualified Data.ByteString as B

import System.INotify as INotify

import Utils

write :: String -> IO ()
write path = do
writeFile (path ++ "/hello") ""
write :: FilePath -> IO ()
write path =
B.writeFile (path ++ "/hello") ""
-- actually writing any contents gives me two Modified

main :: IO ()
Expand Down
4 changes: 2 additions & 2 deletions tests/test003-removefile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,11 +13,11 @@ file :: String
file = "hello"

write :: String -> IO ()
write path = do
write path =
writeFile (path ++ '/':file) ""

remove :: String -> IO ()
remove path = do
remove path =
removeFile (path ++ '/':file)

action :: String -> IO ()
Expand Down
8 changes: 4 additions & 4 deletions tests/test004-modify-file.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,18 +15,18 @@ file :: String
file = "hello"

write :: String -> IO ()
write path = do
write path =
writeFile (path ++ '/':file) ""

modify :: String -> IO ()
modify path = do
modify path =
bracket
(openFile (path ++ '/':file) AppendMode)
(hClose)
hClose
(\h -> hPutStr h "yarr!")

remove :: String -> IO ()
remove path = do
remove path =
removeFile (path ++ '/':file)

action :: String -> IO ()
Expand Down
6 changes: 3 additions & 3 deletions tests/test005-move-file.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,15 +14,15 @@ file = "hello"
file2 = "hello2"

write :: String -> IO ()
write path = do
write path =
writeFile (path ++ '/':file) ""

move :: String -> IO ()
move path = do
move path =
renameFile (path ++ '/':file) (path ++ '/':file2)

remove :: String -> IO ()
remove path = do
remove path =
removeFile (path ++ '/':file2)

action :: String -> IO ()
Expand Down

0 comments on commit 106930c

Please sign in to comment.