module Effectful.Console.ByteString
(
Console
, runConsole
, getLine
, getContents
, putStr
, putStrLn
, interact
) where
import Prelude hiding
( getContents
, getLine
, interact
, putStr
, putStrLn
)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as BS8
import Effectful
import Effectful.Console.Effect
import Effectful.Dispatch.Static
getLine :: Console :> es => Eff es ByteString
getLine :: forall (es :: [Effect]). (Console :> es) => Eff es ByteString
getLine = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO ByteString
BS8.getLine
getContents :: Console :> es => Eff es ByteString
getContents :: forall (es :: [Effect]). (Console :> es) => Eff es ByteString
getContents = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO ByteString
BS8.getContents
putStr :: Console :> es => ByteString -> Eff es ()
putStr :: forall (es :: [Effect]). (Console :> es) => ByteString -> Eff es ()
putStr = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> IO ()
BS8.putStr
putStrLn :: Console :> es => ByteString -> Eff es ()
putStrLn :: forall (es :: [Effect]). (Console :> es) => ByteString -> Eff es ()
putStrLn = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> IO ()
BS8.putStrLn
interact :: Console :> es => (ByteString -> ByteString) -> Eff es ()
interact :: forall (es :: [Effect]).
(Console :> es) =>
(ByteString -> ByteString) -> Eff es ()
interact = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> ByteString) -> IO ()
BS8.interact