module Effectful.FileSystem.HandleReader.Dynamic
(
HandleReader (..),
hIsEOF,
hGetBuffering,
hIsOpen,
hIsClosed,
hIsReadable,
hIsWritable,
hIsSeekable,
hIsTerminalDevice,
hGetEcho,
hWaitForInput,
hReady,
hGetChar,
hGetLine,
hGetContents,
hGet,
hGetSome,
hGetNonBlocking,
runHandleReader,
hGetLineUtf8,
hGetLineUtf8Lenient,
hGetLineUtf8ThrowM,
hGetContentsUtf8,
hGetContentsUtf8Lenient,
hGetContentsUtf8ThrowM,
hGetUtf8,
hGetUtf8Lenient,
hGetUtf8ThrowM,
hGetSomeUtf8,
hGetSomeUtf8Lenient,
hGetSomeUtf8ThrowM,
hGetNonBlockingUtf8,
hGetNonBlockingUtf8Lenient,
hGetNonBlockingUtf8ThrowM,
ByteString,
Handle,
OsPath,
Text,
UnicodeException,
)
where
import Control.Monad ((>=>))
import Data.ByteString (ByteString)
import Data.Text (Text)
import Data.Text.Encoding.Error (UnicodeException)
import Effectful
( Dispatch (Dynamic),
DispatchOf,
Eff,
Effect,
IOE,
type (:>),
)
import Effectful.Dispatch.Dynamic (HasCallStack, reinterpret_, send)
import Effectful.Dynamic.Utils (ShowEffect (showEffectCons))
import Effectful.FileSystem.HandleReader.Static qualified as Static
import FileSystem.OsPath (OsPath)
import FileSystem.UTF8 qualified as FS.UTF8
import System.IO (BufferMode, Handle)
data HandleReader :: Effect where
HIsEOF :: Handle -> HandleReader m Bool
HGetBuffering :: Handle -> HandleReader m BufferMode
HIsOpen :: Handle -> HandleReader m Bool
HIsClosed :: Handle -> HandleReader m Bool
HIsReadable :: Handle -> HandleReader m Bool
HIsWritable :: Handle -> HandleReader m Bool
HIsSeekable :: Handle -> HandleReader m Bool
HIsTerminalDevice :: Handle -> HandleReader m Bool
HGetEcho :: Handle -> HandleReader m Bool
HWaitForInput :: Handle -> Int -> HandleReader m Bool
HReady :: Handle -> HandleReader m Bool
HGetChar :: Handle -> HandleReader m Char
HGetLine :: Handle -> HandleReader m ByteString
HGetContents :: Handle -> HandleReader m ByteString
HGet :: Handle -> Int -> HandleReader m ByteString
HGetSome :: Handle -> Int -> HandleReader m ByteString
HGetNonBlocking :: Handle -> Int -> HandleReader m ByteString
type instance DispatchOf HandleReader = Dynamic
instance ShowEffect HandleReader where
showEffectCons :: forall (m :: * -> *) a. HandleReader m a -> String
showEffectCons = \case
HIsEOF Handle
_ -> String
"HIsEOF"
HGetBuffering Handle
_ -> String
"HGetBuffering"
HIsOpen Handle
_ -> String
"HIsOpen"
HIsClosed Handle
_ -> String
"HIsClosed"
HIsReadable Handle
_ -> String
"HIsReadable"
HIsWritable Handle
_ -> String
"HIsWritable"
HIsSeekable Handle
_ -> String
"HIsSeekable"
HIsTerminalDevice Handle
_ -> String
"HIsTerminalDevice"
HGetEcho Handle
_ -> String
"HGetEcho"
HWaitForInput Handle
_ Int
_ -> String
"HWaitForInput"
HReady Handle
_ -> String
"HReady"
HGetChar Handle
_ -> String
"HGetChar"
HGetLine Handle
_ -> String
"HGetLine"
HGetContents Handle
_ -> String
"HGetContents"
HGet Handle
_ Int
_ -> String
"HGet"
HGetSome Handle
_ Int
_ -> String
"HGetSome"
HGetNonBlocking Handle
_ Int
_ -> String
"HGetNonBlocking"
runHandleReader ::
( HasCallStack,
IOE :> es
) =>
Eff (HandleReader : es) a ->
Eff es a
runHandleReader :: forall (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, IOE :> es) =>
Eff (HandleReader : es) a -> Eff es a
runHandleReader = (Eff (HandleReader : es) a -> Eff es a)
-> EffectHandler_ HandleReader (HandleReader : es)
-> Eff (HandleReader : es) a
-> Eff es a
forall (e :: (* -> *) -> * -> *)
(handlerEs :: [(* -> *) -> * -> *]) a (es :: [(* -> *) -> * -> *])
b.
(HasCallStack, DispatchOf e ~ 'Dynamic) =>
(Eff handlerEs a -> Eff es b)
-> EffectHandler_ e handlerEs -> Eff (e : es) a -> Eff es b
reinterpret_ Eff (HandleReader : es) a -> Eff es a
forall (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, IOE :> es) =>
Eff (HandleReader : es) a -> Eff es a
Static.runHandleReader (EffectHandler_ HandleReader (HandleReader : es)
-> Eff (HandleReader : es) a -> Eff es a)
-> EffectHandler_ HandleReader (HandleReader : es)
-> Eff (HandleReader : es) a
-> Eff es a
forall a b. (a -> b) -> a -> b
$ \case
HIsEOF Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hIsEOF Handle
h
HGetBuffering Handle
h -> Handle -> Eff (HandleReader : es) BufferMode
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es BufferMode
Static.hGetBuffering Handle
h
HIsOpen Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hIsOpen Handle
h
HIsClosed Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hIsClosed Handle
h
HIsReadable Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hIsReadable Handle
h
HIsWritable Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hIsWritable Handle
h
HIsSeekable Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hIsSeekable Handle
h
HIsTerminalDevice Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hIsTerminalDevice Handle
h
HGetEcho Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hGetEcho Handle
h
HWaitForInput Handle
h Int
i -> Handle -> Int -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es Bool
Static.hWaitForInput Handle
h Int
i
HReady Handle
h -> Handle -> Eff (HandleReader : es) Bool
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
Static.hReady Handle
h
HGetChar Handle
h -> Handle -> Eff (HandleReader : es) Char
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Char
Static.hGetChar Handle
h
HGetLine Handle
h -> Handle -> Eff (HandleReader : es) ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
Static.hGetLine Handle
h
HGetContents Handle
h -> Handle -> Eff (HandleReader : es) ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
Static.hGetContents Handle
h
HGet Handle
h Int
i -> Handle -> Int -> Eff (HandleReader : es) ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
Static.hGet Handle
h Int
i
HGetSome Handle
h Int
i -> Handle -> Int -> Eff (HandleReader : es) ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
Static.hGetSome Handle
h Int
i
HGetNonBlocking Handle
h Int
i -> Handle -> Int -> Eff (HandleReader : es) ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
Static.hGetNonBlocking Handle
h Int
i
hIsEOF :: (HandleReader :> es, HasCallStack) => Handle -> Eff es Bool
hIsEOF :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hIsEOF = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HIsEOF
hGetBuffering ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es BufferMode
hGetBuffering :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es BufferMode
hGetBuffering = HandleReader (Eff es) BufferMode -> Eff es BufferMode
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) BufferMode -> Eff es BufferMode)
-> (Handle -> HandleReader (Eff es) BufferMode)
-> Handle
-> Eff es BufferMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) BufferMode
forall (m :: * -> *). Handle -> HandleReader m BufferMode
HGetBuffering
hIsOpen ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Bool
hIsOpen :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hIsOpen = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HIsOpen
hIsClosed ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Bool
hIsClosed :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hIsClosed = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HIsClosed
hIsReadable ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Bool
hIsReadable :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hIsReadable = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HIsReadable
hIsWritable ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Bool
hIsWritable :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hIsWritable = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HIsWritable
hIsSeekable ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Bool
hIsSeekable :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hIsSeekable = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HIsSeekable
hIsTerminalDevice ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Bool
hIsTerminalDevice :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hIsTerminalDevice = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HIsTerminalDevice
hGetEcho ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Bool
hGetEcho :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hGetEcho = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HGetEcho
hWaitForInput ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es Bool
hWaitForInput :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es Bool
hWaitForInput Handle
h = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Int -> HandleReader (Eff es) Bool) -> Int -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> Int -> HandleReader m Bool
HWaitForInput Handle
h
hReady ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Bool
hReady :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Bool
hReady = HandleReader (Eff es) Bool -> Eff es Bool
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Bool -> Eff es Bool)
-> (Handle -> HandleReader (Eff es) Bool) -> Handle -> Eff es Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Bool
forall (m :: * -> *). Handle -> HandleReader m Bool
HReady
hGetChar ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Char
hGetChar :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Char
hGetChar = HandleReader (Eff es) Char -> Eff es Char
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) Char -> Eff es Char)
-> (Handle -> HandleReader (Eff es) Char) -> Handle -> Eff es Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) Char
forall (m :: * -> *). Handle -> HandleReader m Char
HGetChar
hGetLine ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es ByteString
hGetLine :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
hGetLine = HandleReader (Eff es) ByteString -> Eff es ByteString
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) ByteString -> Eff es ByteString)
-> (Handle -> HandleReader (Eff es) ByteString)
-> Handle
-> Eff es ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) ByteString
forall (m :: * -> *). Handle -> HandleReader m ByteString
HGetLine
hGetContents ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es ByteString
hGetContents :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
hGetContents = HandleReader (Eff es) ByteString -> Eff es ByteString
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) ByteString -> Eff es ByteString)
-> (Handle -> HandleReader (Eff es) ByteString)
-> Handle
-> Eff es ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> HandleReader (Eff es) ByteString
forall (m :: * -> *). Handle -> HandleReader m ByteString
HGetContents
hGet ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es ByteString
hGet :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGet Handle
h = HandleReader (Eff es) ByteString -> Eff es ByteString
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) ByteString -> Eff es ByteString)
-> (Int -> HandleReader (Eff es) ByteString)
-> Int
-> Eff es ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> HandleReader (Eff es) ByteString
forall (m :: * -> *). Handle -> Int -> HandleReader m ByteString
HGet Handle
h
hGetSome ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es ByteString
hGetSome :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGetSome Handle
h = HandleReader (Eff es) ByteString -> Eff es ByteString
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) ByteString -> Eff es ByteString)
-> (Int -> HandleReader (Eff es) ByteString)
-> Int
-> Eff es ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> HandleReader (Eff es) ByteString
forall (m :: * -> *). Handle -> Int -> HandleReader m ByteString
HGetSome Handle
h
hGetNonBlocking ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es ByteString
hGetNonBlocking :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGetNonBlocking Handle
h = HandleReader (Eff es) ByteString -> Eff es ByteString
forall (e :: (* -> *) -> * -> *) (es :: [(* -> *) -> * -> *]) a.
(HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) =>
e (Eff es) a -> Eff es a
send (HandleReader (Eff es) ByteString -> Eff es ByteString)
-> (Int -> HandleReader (Eff es) ByteString)
-> Int
-> Eff es ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> HandleReader (Eff es) ByteString
forall (m :: * -> *). Handle -> Int -> HandleReader m ByteString
HGetNonBlocking Handle
h
hGetLineUtf8 ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es (Either UnicodeException Text)
hGetLineUtf8 :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es (Either UnicodeException Text)
hGetLineUtf8 = (ByteString -> Either UnicodeException Text)
-> Eff es ByteString -> Eff es (Either UnicodeException Text)
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Either UnicodeException Text
FS.UTF8.decodeUtf8 (Eff es ByteString -> Eff es (Either UnicodeException Text))
-> (Handle -> Eff es ByteString)
-> Handle
-> Eff es (Either UnicodeException Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
hGetLine
hGetLineUtf8Lenient ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Text
hGetLineUtf8Lenient :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Text
hGetLineUtf8Lenient = (ByteString -> Text) -> Eff es ByteString -> Eff es Text
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
FS.UTF8.decodeUtf8Lenient (Eff es ByteString -> Eff es Text)
-> (Handle -> Eff es ByteString) -> Handle -> Eff es Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
hGetLine
hGetLineUtf8ThrowM ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Text
hGetLineUtf8ThrowM :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Text
hGetLineUtf8ThrowM = Handle -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
hGetLine (Handle -> Eff es ByteString)
-> (ByteString -> Eff es Text) -> Handle -> Eff es Text
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> ByteString -> Eff es Text
forall (m :: * -> *).
(HasCallStack, MonadThrow m) =>
ByteString -> m Text
FS.UTF8.decodeUtf8ThrowM
hGetContentsUtf8 ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es (Either UnicodeException Text)
hGetContentsUtf8 :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es (Either UnicodeException Text)
hGetContentsUtf8 = (ByteString -> Either UnicodeException Text)
-> Eff es ByteString -> Eff es (Either UnicodeException Text)
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Either UnicodeException Text
FS.UTF8.decodeUtf8 (Eff es ByteString -> Eff es (Either UnicodeException Text))
-> (Handle -> Eff es ByteString)
-> Handle
-> Eff es (Either UnicodeException Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
hGetContents
hGetContentsUtf8Lenient ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Text
hGetContentsUtf8Lenient :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Text
hGetContentsUtf8Lenient = (ByteString -> Text) -> Eff es ByteString -> Eff es Text
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
FS.UTF8.decodeUtf8Lenient (Eff es ByteString -> Eff es Text)
-> (Handle -> Eff es ByteString) -> Handle -> Eff es Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
hGetContents
hGetContentsUtf8ThrowM ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Eff es Text
hGetContentsUtf8ThrowM :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es Text
hGetContentsUtf8ThrowM = Handle -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Eff es ByteString
hGetContents (Handle -> Eff es ByteString)
-> (ByteString -> Eff es Text) -> Handle -> Eff es Text
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> ByteString -> Eff es Text
forall (m :: * -> *).
(HasCallStack, MonadThrow m) =>
ByteString -> m Text
FS.UTF8.decodeUtf8ThrowM
hGetUtf8 ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es (Either UnicodeException Text)
hGetUtf8 :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es (Either UnicodeException Text)
hGetUtf8 Handle
h = (ByteString -> Either UnicodeException Text)
-> Eff es ByteString -> Eff es (Either UnicodeException Text)
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Either UnicodeException Text
FS.UTF8.decodeUtf8 (Eff es ByteString -> Eff es (Either UnicodeException Text))
-> (Int -> Eff es ByteString)
-> Int
-> Eff es (Either UnicodeException Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGet Handle
h
hGetUtf8Lenient ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es Text
hGetUtf8Lenient :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es Text
hGetUtf8Lenient Handle
h = (ByteString -> Text) -> Eff es ByteString -> Eff es Text
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
FS.UTF8.decodeUtf8Lenient (Eff es ByteString -> Eff es Text)
-> (Int -> Eff es ByteString) -> Int -> Eff es Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGet Handle
h
hGetUtf8ThrowM ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es Text
hGetUtf8ThrowM :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es Text
hGetUtf8ThrowM Handle
h = Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGet Handle
h (Int -> Eff es ByteString)
-> (ByteString -> Eff es Text) -> Int -> Eff es Text
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> ByteString -> Eff es Text
forall (m :: * -> *).
(HasCallStack, MonadThrow m) =>
ByteString -> m Text
FS.UTF8.decodeUtf8ThrowM
hGetSomeUtf8 ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es (Either UnicodeException Text)
hGetSomeUtf8 :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es (Either UnicodeException Text)
hGetSomeUtf8 Handle
h = (ByteString -> Either UnicodeException Text)
-> Eff es ByteString -> Eff es (Either UnicodeException Text)
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Either UnicodeException Text
FS.UTF8.decodeUtf8 (Eff es ByteString -> Eff es (Either UnicodeException Text))
-> (Int -> Eff es ByteString)
-> Int
-> Eff es (Either UnicodeException Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGetSome Handle
h
hGetSomeUtf8Lenient ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es Text
hGetSomeUtf8Lenient :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es Text
hGetSomeUtf8Lenient Handle
h = (ByteString -> Text) -> Eff es ByteString -> Eff es Text
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
FS.UTF8.decodeUtf8Lenient (Eff es ByteString -> Eff es Text)
-> (Int -> Eff es ByteString) -> Int -> Eff es Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGetSome Handle
h
hGetSomeUtf8ThrowM ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es Text
hGetSomeUtf8ThrowM :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es Text
hGetSomeUtf8ThrowM Handle
h = Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGetSome Handle
h (Int -> Eff es ByteString)
-> (ByteString -> Eff es Text) -> Int -> Eff es Text
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> ByteString -> Eff es Text
forall (m :: * -> *).
(HasCallStack, MonadThrow m) =>
ByteString -> m Text
FS.UTF8.decodeUtf8ThrowM
hGetNonBlockingUtf8 ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es (Either UnicodeException Text)
hGetNonBlockingUtf8 :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es (Either UnicodeException Text)
hGetNonBlockingUtf8 Handle
h = (ByteString -> Either UnicodeException Text)
-> Eff es ByteString -> Eff es (Either UnicodeException Text)
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Either UnicodeException Text
FS.UTF8.decodeUtf8 (Eff es ByteString -> Eff es (Either UnicodeException Text))
-> (Int -> Eff es ByteString)
-> Int
-> Eff es (Either UnicodeException Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGetNonBlocking Handle
h
hGetNonBlockingUtf8Lenient ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es Text
hGetNonBlockingUtf8Lenient :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es Text
hGetNonBlockingUtf8Lenient Handle
h = (ByteString -> Text) -> Eff es ByteString -> Eff es Text
forall a b. (a -> b) -> Eff es a -> Eff es b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Text
FS.UTF8.decodeUtf8Lenient (Eff es ByteString -> Eff es Text)
-> (Int -> Eff es ByteString) -> Int -> Eff es Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGetNonBlocking Handle
h
hGetNonBlockingUtf8ThrowM ::
( HandleReader :> es,
HasCallStack
) =>
Handle ->
Int ->
Eff es Text
hGetNonBlockingUtf8ThrowM :: forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es Text
hGetNonBlockingUtf8ThrowM Handle
h = Handle -> Int -> Eff es ByteString
forall (es :: [(* -> *) -> * -> *]).
(HandleReader :> es, HasCallStack) =>
Handle -> Int -> Eff es ByteString
hGetNonBlocking Handle
h (Int -> Eff es ByteString)
-> (ByteString -> Eff es Text) -> Int -> Eff es Text
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> ByteString -> Eff es Text
forall (m :: * -> *).
(HasCallStack, MonadThrow m) =>
ByteString -> m Text
FS.UTF8.decodeUtf8ThrowM