module BasicPrelude
(
module CorePrelude
, module Data.List
, module Control.Monad
, Foldable
(
foldMap
, foldr
, foldr'
, foldl
, foldl'
, foldr1
, foldl1
)
, elem
, maximum
, minimum
, traverse_
, sequenceA_
, for_
, maximumBy
, minimumBy
, Traversable
(
traverse
, sequenceA
, mapM
, sequence
)
, for
, map
, empty
, (++)
, concat
, intercalate
, BasicPrelude.sum
, BasicPrelude.product
, tshow
, fromShow
, read
, readIO
, readFile
, writeFile
, appendFile
, Text.lines
, Text.words
, Text.unlines
, Text.unwords
, textToString
, ltextToString
, fpToText
, fpFromText
, fpToString
, encodeUtf8
, decodeUtf8
, getLine
, getContents
, interact
, Prelude.gcd
, Prelude.lcm
, Prelude.Show (..)
, Prelude.ShowS
, Prelude.shows
, Prelude.showChar
, Prelude.showString
, Prelude.showParen
, Prelude.ReadS
, Prelude.readsPrec
, Prelude.readList
, Prelude.reads
, Prelude.readParen
, Prelude.lex
, readMay
, getChar
, putChar
, readLn
) where
import CorePrelude
import Data.List hiding
(
(++)
, concat
, intercalate
, lines
, words
, unlines
, unwords
, map
, sum
, product
, elem
, foldl
, foldl'
, foldl1
, foldr
, foldr1
, maximum
, minimum
, maximumBy
, minimumBy
)
import Control.Monad hiding
(
mapM
, sequence
)
import Data.Foldable (Foldable(..), elem, maximum, minimum, traverse_, sequenceA_, for_)
import Data.Traversable (Traversable(..), for)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import qualified Data.Text.Lazy as LText
import qualified Data.Text.Lazy.IO as LText
import qualified Prelude
import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
import Data.Text.Encoding.Error (lenientDecode)
import qualified Text.Read
#if MIN_VERSION_base(4,10,0)
import Data.Foldable (maximumBy, minimumBy)
#else
maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
maximumBy cmp = foldl1 max'
where max' x y = case cmp x y of
GT -> x
_ -> y
minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
minimumBy cmp = foldl1 min'
where min' x y = case cmp x y of
GT -> y
_ -> x
#endif
map :: (Functor f) => (a -> b) -> f a -> f b
map = fmap
empty :: Monoid w => w
empty = mempty
infixr 5 ++
(++) :: Monoid w => w -> w -> w
(++) = mappend
concat :: Monoid w => [w] -> w
concat = mconcat
intercalate :: Monoid w => w -> [w] -> w
intercalate xs xss = mconcat (Data.List.intersperse xs xss)
sum :: (Foldable f, Num a) => f a -> a
sum = Data.Foldable.foldl' (+) 0
product :: (Foldable f, Num a) => f a -> a
product = Data.Foldable.foldl' (*) 1
tshow :: Show a => a -> Text
tshow = Text.pack . Prelude.show
fromShow :: (Show a, IsString b) => a -> b
fromShow = fromString . Prelude.show
read :: Read a => Text -> a
read = Prelude.read . Text.unpack
readIO :: (MonadIO m, Read a) => Text -> m a
readIO = liftIO . Prelude.readIO . Text.unpack
readFile :: MonadIO m => FilePath -> m Text
readFile = liftIO . Text.readFile
writeFile :: MonadIO m => FilePath -> Text -> m ()
writeFile p = liftIO . Text.writeFile p
appendFile :: MonadIO m => FilePath -> Text -> m ()
appendFile p = liftIO . Text.appendFile p
textToString :: Text -> Prelude.String
textToString = Text.unpack
ltextToString :: LText -> Prelude.String
ltextToString = LText.unpack
fpToText :: FilePath -> Text
fpToText = Text.pack
fpFromText :: Text -> FilePath
fpFromText = Text.unpack
fpToString :: FilePath -> Prelude.String
fpToString = id
decodeUtf8 :: ByteString -> Text
decodeUtf8 = decodeUtf8With lenientDecode
getLine :: MonadIO m => m Text
getLine = liftIO Text.getLine
getContents :: MonadIO m => m LText
getContents = liftIO LText.getContents
interact :: MonadIO m => (LText -> LText) -> m ()
interact = liftIO . LText.interact
readMay :: Read a => Text -> Maybe a
readMay = Text.Read.readMaybe . Text.unpack
getChar :: MonadIO m => m Char
getChar = liftIO Prelude.getChar
putChar :: MonadIO m => Char -> m ()
putChar = liftIO . Prelude.putChar
readLn :: (MonadIO m, Read a) => m a
readLn = liftIO Prelude.readLn