Skip to content

Commit

Permalink
Applying remarks from blog post comments
Browse files Browse the repository at this point in the history
Implementation of a strict readFile (from Mike Tolly).
Using the nicer notation from Erik Hesselink.
  • Loading branch information
bartavelle committed Dec 19, 2012
1 parent 3c35879 commit 1eb0296
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 6 deletions.
10 changes: 6 additions & 4 deletions Puppet/Interpreter/Functions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,20 +12,20 @@ module Puppet.Interpreter.Functions
,pdbresourcequery
) where

import Prelude hiding (catch)
import Control.Exception
import PuppetDB.Rest
import Puppet.Printers
import Puppet.Interpreter.Types
import Puppet.Utils

import Prelude hiding (catch)
import Control.Exception
import Data.Hash.MD5
import qualified Crypto.Hash.SHA1 as SHA1
import qualified Data.ByteString.Char8 as BS
import Data.String.Utils (join,replace)
import Text.RegexPR
import Text.Regex.PCRE.String
import Control.Monad.Error
import System.IO
import qualified Data.ByteString.Base16 as B16
import SafeProcess
import Data.Either (lefts, rights)
Expand Down Expand Up @@ -88,7 +88,9 @@ versioncmp a b | a > b = 1
file :: [String] -> IO (Maybe String)
file [] = return Nothing
-- this is bad, is should be rewritten as a ByteString
file (x:xs) = catch (fmap Just (withFile x ReadMode (\fh -> do { y <- hGetContents fh; evaluate (length y); return y }))) ((\_ -> file xs) :: SomeException -> IO (Maybe String))
file (x:xs) = catch
(fmap Just (readFile' x))
(\SomeException{} -> file xs)

puppetSplit :: String -> String -> IO (Either String [String])
puppetSplit str reg = do
Expand Down
14 changes: 12 additions & 2 deletions Puppet/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,15 @@
{-# LANGUAGE CPP, ForeignFunctionInterface #-}

module Puppet.Utils (mGetExecutablePath) where
module Puppet.Utils (mGetExecutablePath, readFile', readSymbolicLink) where

-- copy pasted from base 4.6.0.0

import Prelude hiding (catch)
import Foreign.C
import Foreign.Marshal.Array
import System.Posix.Internals
import System.IO
import Control.Exception


foreign import ccall unsafe "readlink" c_readlink :: CString -> CString -> CSize -> IO CInt

Expand All @@ -26,3 +29,10 @@ readSymbolicLink file =
mGetExecutablePath :: IO FilePath
mGetExecutablePath = readSymbolicLink $ "/proc/self/exe"

-- | Strict readFile
readFile' f = do
h <- openFile f ReadMode
s <- hGetContents h
evaluate (length s)
return s

0 comments on commit 1eb0296

Please sign in to comment.