Git Product home page Git Product logo

Comments (4)

gregwebs avatar gregwebs commented on June 28, 2024

oh, and sometimes, but not usually, I see this output:

2012-07-12 09:42 watch[68012] (CarbonCore.framework) FSEventStreamStart(): failed assertion 'streamRef != NULL'

from hfsnotify.

mdittmer avatar mdittmer commented on June 28, 2024

I'm not entirely sure what has gone awry with the code, but the following refactoring works properly with both action and chan (one is commented out and one is called upon in the coffee function).

{-# LANGUAGE OverloadedStrings #-}

import Prelude hiding (FilePath)

import Control.Concurrent
import Control.Monad (forever)
import Data.Text
import Filesystem
import Filesystem.Path.CurrentOS
import System.Cmd (rawSystem)
import System.IO.FSNotify

main :: IO ()
main = do
  wd <- getWorkingDirectory
  withManager $ \man -> coffee man wd
  void

coffee :: WatchManager -> FilePath -> IO ()
coffee man dir = do
  -- guardExt method:
  guardExt man dir "coffee" "js" doAction
  _ <- getLine
  void

  -- guardExtChan method:
  -- tid <- guardExtChan man dir "coffee" "js" doAcdtion
  -- _ <- getLine
  -- killThread tid

void :: IO ()
void = return ()

-- | assumes you are running a compile function that produces a file in the same directory but with a different extension
guardExt :: WatchManager
         -> FilePath -- ^ Directory to watch
         -> Text -- ^ old extension
         -> Text -- ^ new extension
         -> (FilePath -> IO ()) -- ^ compile action to run on file
         -> IO ()
guardExt man dir oldExt newExt action = do
  print $ dir
  watchTreeAction man dir (predicate oldExt) (compile newExt action)
  where

readChanLoop :: Chan Event -> Text -> (FilePath -> IO ()) -> IO ()
readChanLoop chan newExt action = do
  event <- readChan chan
  case event of
    Added    f _ -> actionWrapper newExt action f
    Modified f _ -> actionWrapper newExt action f
    Removed  f _ -> void

-- | for debugging
guardExtChan :: WatchManager
         -> FilePath -- ^ Directory to watch
         -> Text -- ^ old extension
         -> Text -- ^ new extension
         -> (FilePath -> IO ()) -- ^ compile action to run on file
         -> IO ThreadId
guardExtChan man dir oldExt newExt action = do
  chan <- newChan
  watchTreeChan man dir (predicate oldExt) chan
  forkIO $ forever (readChanLoop chan newExt action)


doAction fp =
  -- Debug:
  putStrLn $ "Dispatching on: " ++ show fp

  -- Do stuff:
  -- rawSystem "coffee" ["-c", encodeString fp] >> void

actionWrapper newExt action f = do
  print f
  print $ convert newExt f
  action . (convert newExt) $ f

extFilter oldExt = flip hasExtension oldExt

convert newExt = flip replaceExtension newExt

compile newExt action event = do
  print event
  case event of
    Added    f _ -> actionWrapper newExt action f
    Modified f _ -> actionWrapper newExt action f
    Removed  f _ -> void

predicate oldExt event =
  case event of
    Added    f _ -> extFilter oldExt f
    Modified f _ -> extFilter oldExt f
    Removed  f _ -> extFilter oldExt f

from hfsnotify.

gregwebs avatar gregwebs commented on June 28, 2024

This works great in the root watched directory. However, watchTree is not picking up my recurse directories.

from hfsnotify.

gregwebs avatar gregwebs commented on June 28, 2024

recursive working now also.

from hfsnotify.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.