{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Safe #-}
module Relude.Print
(
putText
, putTextLn
, putLText
, putLTextLn
, putBS
, putBSLn
, putLBS
, putLBSLn
) where
import Relude.Function ((.))
import Relude.Monad.Reexport (MonadIO (..))
import Relude.String (ByteString, LByteString, LText, Text)
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as LBS
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy.IO as TL
import qualified Relude.Base as Base
putText :: MonadIO m => Text -> m ()
putText :: Text -> m ()
putText = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (Text -> IO ()) -> Text -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> IO ()
T.putStr
{-# SPECIALIZE putText :: Text -> Base.IO () #-}
{-# INLINE putText #-}
putTextLn :: MonadIO m => Text -> m ()
putTextLn :: Text -> m ()
putTextLn = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (Text -> IO ()) -> Text -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> IO ()
T.putStrLn
{-# SPECIALIZE putTextLn :: Text -> Base.IO () #-}
{-# INLINE putTextLn #-}
putLText :: MonadIO m => LText -> m ()
putLText :: LText -> m ()
putLText = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (LText -> IO ()) -> LText -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LText -> IO ()
TL.putStr
{-# SPECIALIZE putLText :: LText -> Base.IO () #-}
{-# INLINE putLText #-}
putLTextLn :: MonadIO m => LText -> m ()
putLTextLn :: LText -> m ()
putLTextLn = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (LText -> IO ()) -> LText -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LText -> IO ()
TL.putStrLn
{-# SPECIALIZE putLTextLn :: LText -> Base.IO () #-}
{-# INLINE putLTextLn #-}
putBS :: MonadIO m => ByteString -> m ()
putBS :: ByteString -> m ()
putBS = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (ByteString -> IO ()) -> ByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> IO ()
BS.putStr
{-# SPECIALIZE putBS :: ByteString -> Base.IO () #-}
{-# INLINE putBS #-}
putBSLn :: MonadIO m => ByteString -> m ()
putBSLn :: ByteString -> m ()
putBSLn = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (ByteString -> IO ()) -> ByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> IO ()
BS.putStrLn
{-# SPECIALIZE putBSLn :: ByteString -> Base.IO () #-}
{-# INLINE putBSLn #-}
putLBS :: MonadIO m => LByteString -> m ()
putLBS :: LByteString -> m ()
putLBS = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (LByteString -> IO ()) -> LByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LByteString -> IO ()
LBS.putStr
{-# SPECIALIZE putLBS :: LByteString -> Base.IO () #-}
{-# INLINE putLBS #-}
putLBSLn :: MonadIO m => LByteString -> m ()
putLBSLn :: LByteString -> m ()
putLBSLn = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (LByteString -> IO ()) -> LByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LByteString -> IO ()
LBS.putStrLn
{-# SPECIALIZE putLBSLn :: LByteString -> Base.IO () #-}
{-# INLINE putLBSLn #-}