Skip to content

Commit

Permalink
Add File clock
Browse files Browse the repository at this point in the history
  • Loading branch information
turion committed Oct 9, 2023
1 parent 0ef2901 commit 7a29d5c
Show file tree
Hide file tree
Showing 2 changed files with 76 additions and 0 deletions.
1 change: 1 addition & 0 deletions rhine/rhine.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,7 @@ library
exposed-modules:
FRP.Rhine
FRP.Rhine.Clock
FRP.Rhine.Clock.File
FRP.Rhine.Clock.FixedStep
FRP.Rhine.Clock.Periodic
FRP.Rhine.Clock.Proxy
Expand Down
75 changes: 75 additions & 0 deletions rhine/src/FRP/Rhine/Clock/File.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,75 @@
module FRP.Rhine.Clock.File where

-- base
import Data.Bifunctor (first)
import System.IO
import System.IO.Error

-- transformers
import Control.Monad.Trans.Class
import Control.Monad.Trans.Except

-- rhine

import Data.Void
import FRP.Rhine.Clock
import FRP.Rhine.Clock.Proxy

-- | A clock that opens a file in read mode and extracts data of type @a@ from it.
data File e a = File
{ filename :: FilePath
-- ^ The path of the file to be opened
, action :: Handle -> IO (Either e a)
-- ^ The action to be performed on the file handle,
-- e.g. a line being read
}

{- | Read a line of text from a text file.
For higher performance, you will typically want to use a 'Text' or 'ByteString' version,
see https://github.com/turion/rhine/issues/257.
-}
type TextFile = File Void String

{- | Create a 'TextFile' from a file path.
It ticks at every line of the file.
Its 'Tag' will be 'String', the current line.
-}
textFile :: FilePath -> TextFile
textFile filename =
File
{ filename
, action = fmap Right . hGetLine
}

instance GetClockProxy (File e a)

{- | The only non-error exception that the 'File' clock can throw.
It is thrown when the file reaches its end.
To handle this exception outside of @rhine@,
lift all other signal components to the 'ExceptT' transformer,
call 'flow' on the whole 'Rhine',
and then 'runExceptT'.
To handle this exception inside of @rhine@,
you will probably want to use 'eraseClock' on the 'Rhine' containing the 'File',
and then add the result to another signal network.
-}
data FileException = EndOfFile
deriving (Show)

instance Clock (ExceptT (Either e FileException) IO) (File e a) where
type Time (File e a) = Integer
type Tag (File e a) = a
initClock File {filename, action} = lift $ do
handle <- openFile filename ReadMode
let getLineHandle = arrM $ const $ ExceptT $ do
catchIOError (Data.Bifunctor.first Left <$> action handle) $ \e -> do
hClose handle
if isEOFError e
then return $ Left $ Right EndOfFile
else ioError e
return (count &&& getLineHandle, 0)

0 comments on commit 7a29d5c

Please sign in to comment.