Skip to content

Commit 3e714b1

Browse files
committed
Add File clock
1 parent 22f0349 commit 3e714b1

File tree

2 files changed

+76
-0
lines changed

2 files changed

+76
-0
lines changed

rhine/rhine.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -85,6 +85,7 @@ library
8585
exposed-modules:
8686
FRP.Rhine
8787
FRP.Rhine.Clock
88+
FRP.Rhine.Clock.File
8889
FRP.Rhine.Clock.FixedStep
8990
FRP.Rhine.Clock.Periodic
9091
FRP.Rhine.Clock.Proxy

rhine/src/FRP/Rhine/Clock/File.hs

Lines changed: 75 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,75 @@
1+
module FRP.Rhine.Clock.File where
2+
3+
-- base
4+
import Data.Bifunctor (first)
5+
import System.IO
6+
import System.IO.Error
7+
8+
-- transformers
9+
import Control.Monad.Trans.Class
10+
import Control.Monad.Trans.Except
11+
12+
-- rhine
13+
14+
import Data.Void
15+
import FRP.Rhine.Clock
16+
import FRP.Rhine.Clock.Proxy
17+
18+
-- | A clock that opens a file in read mode and extracts data of type @a@ from it.
19+
data File e a = File
20+
{ filename :: FilePath
21+
-- ^ The path of the file to be opened
22+
, action :: Handle -> IO (Either e a)
23+
-- ^ The action to be performed on the file handle,
24+
-- e.g. a line being read
25+
}
26+
27+
{- | Read a line of text from a text file.
28+
29+
For higher performance, you will typically want to use a 'Text' or 'ByteString' version,
30+
see https://github.com/turion/rhine/issues/257.
31+
-}
32+
type TextFile = File Void String
33+
34+
{- | Create a 'TextFile' from a file path.
35+
36+
It ticks at every line of the file.
37+
Its 'Tag' will be 'String', the current line.
38+
-}
39+
textFile :: FilePath -> TextFile
40+
textFile filename =
41+
File
42+
{ filename
43+
, action = fmap Right . hGetLine
44+
}
45+
46+
instance GetClockProxy (File e a)
47+
48+
{- | The only non-error exception that the 'File' clock can throw.
49+
50+
It is thrown when the file reaches its end.
51+
52+
To handle this exception outside of @rhine@,
53+
lift all other signal components to the 'ExceptT' transformer,
54+
call 'flow' on the whole 'Rhine',
55+
and then 'runExceptT'.
56+
57+
To handle this exception inside of @rhine@,
58+
you will probably want to use 'eraseClock' on the 'Rhine' containing the 'File',
59+
and then add the result to another signal network.
60+
-}
61+
data FileException = EndOfFile
62+
deriving (Show)
63+
64+
instance Clock (ExceptT (Either e FileException) IO) (File e a) where
65+
type Time (File e a) = Integer
66+
type Tag (File e a) = a
67+
initClock File {filename, action} = lift $ do
68+
handle <- openFile filename ReadMode
69+
let getLineHandle = arrM $ const $ ExceptT $ do
70+
catchIOError (Data.Bifunctor.first Left <$> action handle) $ \e -> do
71+
hClose handle
72+
if isEOFError e
73+
then return $ Left $ Right EndOfFile
74+
else ioError e
75+
return (count &&& getLineHandle, 0)

0 commit comments

Comments
 (0)