{-# LANGUAGE CPP #-}
module Language.Rust.Data.InputStream (
InputStream,
countLines,
inputStreamEmpty,
readInputStream,
hReadInputStream,
inputStreamFromString,
inputStreamToString,
takeByte,
takeChar,
peekChars,
) where
import Data.Word ( Word8 )
import Data.Coerce ( coerce )
import Data.String ( IsString(..) )
import System.IO
#ifdef USE_BYTESTRING
import qualified Data.ByteString as BS
import qualified Data.ByteString.UTF8 as BE
#else
import qualified Data.Char as Char
#endif
readInputStream :: FilePath -> IO InputStream
{-# INLINE readInputStream #-}
hReadInputStream :: Handle -> IO InputStream
{-# INLINE hReadInputStream #-}
inputStreamToString :: InputStream -> String
{-# INLINE inputStreamToString #-}
inputStreamFromString :: String -> InputStream
{-# INLINE inputStreamFromString #-}
instance IsString InputStream where fromString = inputStreamFromString
takeByte :: InputStream -> (Word8, InputStream)
{-# INLINE takeByte #-}
takeChar :: InputStream -> (Char, InputStream)
{-# INLINE takeChar #-}
inputStreamEmpty :: InputStream -> Bool
{-# INLINE inputStreamEmpty #-}
peekChars :: Int -> InputStream -> String
{-# INLINE peekChars #-}
countLines :: InputStream -> Int
{-# INLINE countLines #-}
#ifdef USE_BYTESTRING
newtype InputStream = IS BS.ByteString deriving (Eq, Ord)
takeByte bs = (BS.head (coerce bs), coerce (BS.tail (coerce bs)))
takeChar bs = maybe (error "takeChar: no char left") coerce (BE.uncons (coerce bs))
inputStreamEmpty = BS.null . coerce
peekChars n = BE.toString . BE.take n . coerce
readInputStream f = coerce <$> BS.readFile f
hReadInputStream h = coerce <$> BS.hGetContents h
inputStreamToString = BE.toString . coerce
inputStreamFromString = IS . BE.fromString
countLines = length . BE.lines . coerce
instance Show InputStream where
show (IS bs) = show bs
#else
newtype InputStream = IS String deriving (Eq, Ord)
takeByte (IS ~(c:str))
| Char.isLatin1 c = let b = fromIntegral (Char.ord c) in b `seq` (b, IS str)
| otherwise = error "takeByte: not a latin-1 character"
takeChar (IS ~(c:str)) = (c, IS str)
inputStreamEmpty (IS str) = null str
peekChars n (IS str) = take n str
readInputStream f = IS <$> readFile f
hReadInputStream h = IS <$> hGetContents h
inputStreamToString = coerce
inputStreamFromString = IS
countLines (IS str) = length . lines $ str
instance Show InputStream where
show (IS bs) = show bs
#endif