{- - Module used to read a UTF-8 stream. - UTF-8 is used by the MPD daemon. -} module Hmpf.UTF8Stream where import qualified Data.ByteString.Lazy as L import System.IO ( Handle , hFlush ) import Codec.Binary.UTF8.String import Data.Word (Word8) hGetLine :: Handle -> IO String hGetLine h = do ln <- hGetLine' h return . decode $ ln hGetLine' :: Handle -> IO [Word8] hGetLine' h = do c <- L.hGet h 1 if ( ( fromEnum . head . L.unpack $ c ) == 10 ) then return [] else do rest <- hGetLine' h return ( ( head . L.unpack $ c ) : rest ) hPutStrLn :: Handle -> String -> IO () hPutStrLn h cmd = do L.hPut h bs L.hPut h eol hFlush h where bs = L.pack . encode $ cmd eol = L.pack . encode . (:[]) $ '\n'