{-# LANGUAGE CPP, BangPatterns #-}
{-# OPTIONS -Wall #-}
module Language.C.Data.InputStream (
InputStream, readInputStream,inputStreamToString,inputStreamFromString,
takeByte, takeChar, inputStreamEmpty, takeChars,
countLines,
)
where
import Data.Word
#ifndef NO_BYTESTRING
import Data.ByteString (ByteString)
import qualified Data.ByteString as BSW
import qualified Data.ByteString.Char8 as BSC
#else
import qualified Data.Char as Char
#endif
readInputStream :: FilePath -> IO InputStream
inputStreamToString :: InputStream -> String
{-# INLINE inputStreamToString #-}
inputStreamFromString :: String -> InputStream
takeByte :: InputStream -> (Word8, InputStream)
{-# INLINE takeByte #-}
takeChar :: InputStream -> (Char, InputStream)
{-# INLINE takeChar #-}
inputStreamEmpty :: InputStream -> Bool
{-# INLINE inputStreamEmpty #-}
takeChars :: Int -> InputStream -> [Char]
{-# INLINE takeChars #-}
countLines :: InputStream -> Int
#ifndef NO_BYTESTRING
type InputStream = ByteString
takeByte :: InputStream -> (Word8, InputStream)
takeByte InputStream
bs = HasCallStack => InputStream -> Word8
InputStream -> Word8
BSW.head InputStream
bs Word8 -> (Word8, InputStream) -> (Word8, InputStream)
forall a b. a -> b -> b
`seq` (HasCallStack => InputStream -> Word8
InputStream -> Word8
BSW.head InputStream
bs, HasCallStack => InputStream -> InputStream
InputStream -> InputStream
BSW.tail InputStream
bs)
takeChar :: InputStream -> (Char, InputStream)
takeChar InputStream
bs = InputStream -> Char
BSC.head InputStream
bs Char -> (Char, InputStream) -> (Char, InputStream)
forall a b. a -> b -> b
`seq` (InputStream -> Char
BSC.head InputStream
bs, HasCallStack => InputStream -> InputStream
InputStream -> InputStream
BSC.tail InputStream
bs)
inputStreamEmpty :: InputStream -> Bool
inputStreamEmpty = InputStream -> Bool
BSW.null
#ifndef __HADDOCK__
takeChars :: Int -> InputStream -> [Char]
takeChars !Int
n InputStream
bstr = InputStream -> [Char]
BSC.unpack (InputStream -> [Char]) -> InputStream -> [Char]
forall a b. (a -> b) -> a -> b
$ Int -> InputStream -> InputStream
BSC.take Int
n InputStream
bstr
#endif
readInputStream :: [Char] -> IO InputStream
readInputStream = [Char] -> IO InputStream
BSW.readFile
inputStreamToString :: InputStream -> [Char]
inputStreamToString = InputStream -> [Char]
BSC.unpack
inputStreamFromString :: [Char] -> InputStream
inputStreamFromString = [Char] -> InputStream
BSC.pack
countLines :: InputStream -> Int
countLines = [InputStream] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([InputStream] -> Int)
-> (InputStream -> [InputStream]) -> InputStream -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputStream -> [InputStream]
BSC.lines
#else
type InputStream = String
takeByte bs
| Char.isLatin1 c = let b = fromIntegral (Char.ord c) in b `seq` (b, tail bs)
| otherwise = error "takeByte: not a latin-1 character"
where c = head bs
takeChar bs = (head bs, tail bs)
inputStreamEmpty = null
takeChars n str = take n str
readInputStream = readFile
inputStreamToString = id
inputStreamFromString = id
countLines = length . lines
#endif