{-# OPTIONS -XFlexibleInstances -XTypeSynonymInstances -XMagicHash #-} module Esotericbot.BSH where -- Saves time appending things together by sending them directly to the network import System.IO as IO import Data.ByteString.Lazy.Char8 as BS import Data.ByteString.Unsafe import Data.ByteString.Char8 as BSS import Control.Monad.Reader import Control.Monad.Stream as C type BSH = ReaderT Handle IO class BSHAble bsh where send :: bsh -> BSH ( ) instance BSHAble BSS.ByteString where send b = do h <- ask liftIO $ BSS.hPut h b instance BSHAble BS.ByteString where send b = do h <- ask liftIO $ BS.hPut h b instance BSHAble ( BSH ( ) ) where send b = b instance BSHAble ( Handle -> IO ( ) ) where send b = do h <- ask liftIO $ b h instance BSHAble ( IO ( ) ) where send b = liftIO b instance BSHAble Char where send c = do h <- ask liftIO $ IO.hPutStr h [ c ] instance BSHAble BSHString where send ( BSHString s ) = do h <- ask liftIO $ IO.hPutStr h s instance BSHAble b => BSHAble [ b ] where send = C.mapM_ send newtype BSHString = BSHString String hAppend bs1 bs2 = do send bs1 send bs2 hConcat :: BSHAble b => [ b ] -> BSH ( ) hConcat = do C.mapM_ send