Added fileRead and fileWrite

This commit is contained in:
Gabriel Gonzalez 2015-01-17 19:14:37 -08:00
parent 67b12f49b1
commit 9813046dd9
3 changed files with 37 additions and 2 deletions

View file

@ -2,6 +2,7 @@ module Turtle (
-- * Shell
Shell
, fold
, foldIO
, runShell
-- * Utilities

View file

@ -12,13 +12,18 @@
module Turtle.Shell (
Shell(..)
, fold
, foldIO
, runShell
-- * Re-exports
, Fold(..)
, FoldM(..)
) where
import Control.Applicative (Applicative(..), Alternative(..), liftA2)
import Control.Monad (MonadPlus(..), ap)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Foldl (Fold)
import Control.Foldl (Fold, FoldM)
import qualified Control.Foldl as Foldl
import Data.Monoid (Monoid(..))
import Data.String (IsString(..))
@ -28,7 +33,10 @@ newtype Shell a = Shell
{ foldM_ :: forall r x . (x -> a -> IO x) -> IO x -> (x -> IO r) -> IO r }
fold :: Fold a b -> Shell a -> IO b
fold f s = Foldl.impurely (foldM_ s) (Foldl.generalize f)
fold f = foldIO (Foldl.generalize f)
foldIO :: FoldM IO a b -> Shell a -> IO b
foldIO f s = Foldl.impurely (foldM_ s) f
runShell :: Shell a -> IO ()
runShell = fold (pure ())

View file

@ -2,7 +2,11 @@ module Turtle.Util where
import Control.Applicative (Alternative(..))
import Control.Exception (bracket)
import Control.Monad (guard)
import qualified Data.Text.IO as Text
import System.IO
import Turtle.Parser
import Turtle.Shell
@ -18,3 +22,25 @@ grep p s = do
str <- s
guard (not (null (parse p str)))
return str
fileRead :: FilePath -> Shell Text
fileRead file = Shell (\step begin done -> do
x0 <- begin
x1 <- bracket (openFile file ReadMode) hClose (\handle -> do
let go x = do
eof <- hIsEOF handle
if eof
then return x
else do
str <- Text.hGetLine handle
x' <- step x str
go x'
go x0 )
done x1 )
fileWrite :: FilePath -> FoldM IO Text ()
fileWrite file = FoldM step (openFile file WriteMode) hClose
where
step handle txt = do
Text.hPutStrLn handle txt
return handle