module BasicPrelude
  ( 
    module CorePrelude
  , module Data.List
  , module Control.Monad
    
    
  , map
  , empty
  , (++)
  , concat
  , intercalate
    
  , sum
  , product
    
  , show
  , read
  , readIO
    
  , readFile
  , writeFile
  , appendFile
    
    
  , Text.lines
  , Text.words
  , Text.unlines
  , Text.unwords
  , textToString
  , ltextToString
    
  , Text.putStr
  , Text.getLine
  , LText.getContents
  , LText.interact
    
    
  , Prelude.gcd
  , Prelude.lcm
    
  , Prelude.String
  , Prelude.ShowS
  , Prelude.showsPrec
  , Prelude.showList
  , Prelude.shows
  , Prelude.showChar
  , Prelude.showString
  , Prelude.showParen
  , Prelude.ReadS
  , Prelude.readsPrec
  , Prelude.readList
  , Prelude.reads
  , Prelude.readParen
  , Prelude.lex
    
  , Prelude.putChar
  , Prelude.getChar
  , Prelude.readLn
    
  , Prelude.IOError
  , Prelude.ioError
  , Prelude.userError
  ) where
import CorePrelude
import Data.List hiding
  ( 
    (++)
  , concat
  , intercalate
    
  , lines
  , words
  , unlines
  , unwords
    
  , map
    
  , sum
  , product
  )
import Control.Monad
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 Filesystem.Path.CurrentOS as FilePath
import qualified Prelude
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 :: Num a => [a] -> a
sum = foldl' (+) 0
product :: Num a => [a] -> a
product = foldl' (*) 1
show :: Show a => a -> Text
show = Text.pack . Prelude.show
read :: Read a => Text -> a
read = Prelude.read . Text.unpack
readIO :: Read a => Text -> IO a
readIO = Prelude.readIO . Text.unpack
readFile :: FilePath -> IO Text
readFile = Text.readFile . FilePath.encodeString
writeFile :: FilePath -> Text -> IO ()
writeFile = Text.writeFile . FilePath.encodeString
appendFile :: FilePath -> Text -> IO ()
appendFile = Text.appendFile . FilePath.encodeString
textToString :: Text -> Prelude.String
textToString = Text.unpack
ltextToString :: LText -> Prelude.String
ltextToString = LText.unpack