Skip to content

Commit

Permalink
Merge pull request #80 from howsiwei/misc
Browse files Browse the repository at this point in the history
Miscellaneous changes
  • Loading branch information
snoyberg committed Dec 4, 2017
2 parents cb9fb1a + 790bbee commit 085e658
Show file tree
Hide file tree
Showing 3 changed files with 88 additions and 18 deletions.
97 changes: 80 additions & 17 deletions BasicPrelude.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}

-- | BasicPrelude mostly re-exports
-- several key libraries in their entirety.
Expand Down Expand Up @@ -28,13 +29,19 @@ module BasicPrelude
, elem
, maximum
, minimum
, traverse_
, sequenceA_
, for_
, maximumBy
, minimumBy
, Traversable
(
traverse
, sequenceA
, mapM
, sequence
)
, for

-- * Enhanced exports
-- ** Simpler name for a typeclassed operation
Expand Down Expand Up @@ -70,9 +77,9 @@ module BasicPrelude
, encodeUtf8
, decodeUtf8
-- ** Text operations (IO)
, Text.getLine
, LText.getContents
, LText.interact
, getLine
, getContents
, interact

-- * Miscellaneous prelude re-exports
-- ** Math
Expand All @@ -93,9 +100,9 @@ module BasicPrelude
, Prelude.lex
, readMay
-- ** IO operations
, Prelude.putChar
, Prelude.getChar
, Prelude.readLn
, getChar
, putChar
, readLn
) where

import CorePrelude
Expand All @@ -121,10 +128,11 @@ import Data.List hiding
, foldl'
, foldl1
, foldr
, foldr'
, foldr1
, maximum
, minimum
, maximumBy
, minimumBy
)

-- Import *all of the things* from Control.Monad,
Expand All @@ -137,8 +145,8 @@ import Control.Monad hiding
)


import Data.Foldable (Foldable(..), elem, maximum, minimum)
import Data.Traversable (Traversable(..))
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
Expand All @@ -148,6 +156,22 @@ import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
import Data.Text.Encoding.Error (lenientDecode)
import qualified Safe

#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 = fmap
map :: (Functor f) => (a -> b) -> f a -> f b
map = fmap
Expand Down Expand Up @@ -200,23 +224,31 @@ read = Prelude.read . Text.unpack
-- | The readIO function is similar to read
-- except that it signals parse failure to the IO monad
-- instead of terminating the program.
readIO :: Read a => Text -> IO a
readIO = Prelude.readIO . Text.unpack
--
-- @since 0.7.0
readIO :: (MonadIO m, Read a) => Text -> m a
readIO = liftIO . Prelude.readIO . Text.unpack


-- | Read a file and return the contents of the file as Text.
-- The entire file is read strictly.
readFile :: FilePath -> IO Text
readFile = Text.readFile
--
-- @since 0.7.0
readFile :: MonadIO m => FilePath -> m Text
readFile = liftIO . Text.readFile

-- | Write Text to a file.
-- The file is truncated to zero length before writing begins.
writeFile :: FilePath -> Text -> IO ()
writeFile = Text.writeFile
--
-- @since 0.7.0
writeFile :: MonadIO m => FilePath -> Text -> m ()
writeFile p = liftIO . Text.writeFile p

-- | Write Text to the end of a file.
appendFile :: FilePath -> Text -> IO ()
appendFile = Text.appendFile
--
-- @since 0.7.0
appendFile :: MonadIO m => FilePath -> Text -> m ()
appendFile p = liftIO . Text.appendFile p

textToString :: Text -> Prelude.String
textToString = Text.unpack
Expand Down Expand Up @@ -250,5 +282,36 @@ fpToString = id
decodeUtf8 :: ByteString -> Text
decodeUtf8 = decodeUtf8With lenientDecode

-- |
-- @since 0.7.0
getLine :: MonadIO m => m Text
getLine = liftIO Text.getLine

-- |
-- @since 0.7.0
getContents :: MonadIO m => m LText
getContents = liftIO LText.getContents

-- |
-- @since 0.7.0
interact :: MonadIO m => (LText -> LText) -> m ()
interact = liftIO . LText.interact

readMay :: Read a => Text -> Maybe a
readMay = Safe.readMay . Text.unpack

-- |
-- @since 0.7.0
getChar :: MonadIO m => m Char
getChar = liftIO Prelude.getChar

-- |
-- @since 0.7.0
putChar :: MonadIO m => Char -> m ()
putChar = liftIO . Prelude.putChar

-- | The 'readLn' function combines 'getLine' and 'readIO'.
--
-- @since 0.7.0
readLn :: (MonadIO m, Read a) => m a
readLn = liftIO Prelude.readLn
7 changes: 7 additions & 0 deletions ChangeLog.md
@@ -1,3 +1,10 @@
## 0.7.0

* Export applicative version of Foldable and Traversable functions [#72](https://github.com/snoyberg/basic-prelude/issues/72)
* Generalize all IO functions to MonadIO [#75](https://github.com/snoyberg/basic-prelude/issues/75)
* Use `foldl1` for `maximumBy` and `minimumBy` [#74](https://github.com/snoyberg/basic-prelude/issues/74)
* Remove nonexistent `foldr'` from `Data.List` hiding list

## 0.6.1.1

* Add `HasCallStack` for `terror`
Expand Down
2 changes: 1 addition & 1 deletion basic-prelude.cabal
@@ -1,5 +1,5 @@
name: basic-prelude
version: 0.6.1.1
version: 0.7.0
synopsis: An enhanced core prelude; a common foundation for alternate preludes.
description:
The premise of @basic-prelude@ is that there are a lot of very commonly desired features missing from the standard @Prelude@, such as commonly used operators (@\<$\>@ and @>=>@, for instance) and imports for common datatypes (e.g., @ByteString@ and @Vector@). At the same time, there are lots of other components which are more debatable, such as providing polymorphic versions of common functions.
Expand Down

0 comments on commit 085e658

Please sign in to comment.