Skip to content

Commit 1395eb1

Browse files
committed
Move from return to pure
1 parent b1ff1ee commit 1395eb1

File tree

12 files changed

+120
-120
lines changed

12 files changed

+120
-120
lines changed

.ghci

+6-6
Original file line numberDiff line numberDiff line change
@@ -3,11 +3,11 @@
33
:set -isrc -itest
44
:load Extra Generate Test
55
:module Extra
6-
:def docs_ const $ return $ unlines [":!cabal haddock"]
7-
:def docs const $ return $ unlines [":docs_",":!start dist\\doc\\html\\extra\\Extra.html"]
8-
:def generate const $ return $ unlines ["Generate.main"]
9-
:def test const $ return $ unlines ["Test.main"]
10-
:def travis const $ return $ unlines [":!runhaskell -isrc travis.hs"]
6+
:def docs_ const $ pure $ unlines [":!cabal haddock"]
7+
:def docs const $ pure $ unlines [":docs_",":!start dist\\doc\\html\\extra\\Extra.html"]
8+
:def generate const $ pure $ unlines ["Generate.main"]
9+
:def test const $ pure $ unlines ["Test.main"]
10+
:def travis const $ pure $ unlines [":!runhaskell -isrc travis.hs"]
1111

1212
-- if there are errors in generate or reload I want them at the bottom of the screen so I can see them
13-
:def go const $ return $ unlines [":reload",":generate",":reload",":test",":generate",":reload"]
13+
:def go const $ pure $ unlines [":reload",":generate",":reload",":test",":generate",":reload"]

Generate.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ main = do
2525
words $ replace "," " " $ drop1 $ dropWhile (/= '(') $
2626
unlines $ filter (\x -> not $ any (`isPrefixOf` trim x) ["--","#"]) $ lines src
2727
let tests = mapMaybe (stripPrefix "-- > ") $ lines src
28-
return (mod, funcs, tests)
28+
pure (mod, funcs, tests)
2929
writeFileBinaryChanged "src/Extra.hs" $ unlines $
3030
["-- GENERATED CODE - DO NOT MODIFY"
3131
,"-- See Generate.hs for details of how to generate"
@@ -62,7 +62,7 @@ rejoin [] = []
6262
writeFileBinaryChanged :: FilePath -> String -> IO ()
6363
writeFileBinaryChanged file x = do
6464
evaluate $ length x -- ensure we don't write out files with _|_ in them
65-
old <- ifM (doesFileExist file) (Just <$> readFileBinary' file) (return Nothing)
65+
old <- ifM (doesFileExist file) (Just <$> readFileBinary' file) (pure Nothing)
6666
when (Just x /= old) $
6767
writeFileBinary file x
6868

src/Control/Concurrent/Extra.hs

+13-13
Original file line numberDiff line numberDiff line change
@@ -46,23 +46,23 @@ withNumCapabilities _ act = act
4646
-- If the function raises an exception, the same exception will be reraised each time.
4747
--
4848
-- > let x ||| y = do t1 <- onceFork x; t2 <- onceFork y; t1; t2
49-
-- > \(x :: IO Int) -> void (once x) == return ()
49+
-- > \(x :: IO Int) -> void (once x) == pure ()
5050
-- > \(x :: IO Int) -> join (once x) == x
5151
-- > \(x :: IO Int) -> (do y <- once x; y; y) == x
5252
-- > \(x :: IO Int) -> (do y <- once x; y ||| y) == x
5353
once :: IO a -> IO (IO a)
5454
once act = do
5555
var <- newVar OncePending
56-
let run = either throwIO return
57-
return $ mask $ \unmask -> join $ modifyVar var $ \v -> case v of
58-
OnceDone x -> return (v, unmask $ run x)
59-
OnceRunning x -> return (v, unmask $ run =<< waitBarrier x)
56+
let run = either throwIO pure
57+
pure $ mask $ \unmask -> join $ modifyVar var $ \v -> case v of
58+
OnceDone x -> pure (v, unmask $ run x)
59+
OnceRunning x -> pure (v, unmask $ run =<< waitBarrier x)
6060
OncePending -> do
6161
b <- newBarrier
62-
return $ (OnceRunning b,) $ do
62+
pure $ (OnceRunning b,) $ do
6363
res <- try_ $ unmask act
6464
signalBarrier b res
65-
modifyVar_ var $ \_ -> return $ OnceDone res
65+
modifyVar_ var $ \_ -> pure $ OnceDone res
6666
run res
6767

6868
data Once a = OncePending | OnceRunning (Barrier a) | OnceDone a
@@ -76,7 +76,7 @@ onceFork :: IO a -> IO (IO a)
7676
onceFork act = do
7777
bar <- newBarrier
7878
forkFinally act $ signalBarrier bar
79-
return $ eitherM throwIO return $ waitBarrier bar
79+
pure $ eitherM throwIO pure $ waitBarrier bar
8080

8181

8282
---------------------------------------------------------------------
@@ -115,7 +115,7 @@ withLockTry :: Lock -> IO a -> IO (Maybe a)
115115
withLockTry (Lock m) act = bracket
116116
(tryTakeMVar m)
117117
(\v -> when (isJust v) $ putMVar m ())
118-
(\v -> if isJust v then fmap Just act else return Nothing)
118+
(\v -> if isJust v then fmap Just act else pure Nothing)
119119

120120

121121
---------------------------------------------------------------------
@@ -150,7 +150,7 @@ readVar (Var x) = readMVar x
150150

151151
-- | Write a value to become the new value of 'Var'.
152152
writeVar :: Var a -> a -> IO ()
153-
writeVar v x = modifyVar_ v $ const $ return x
153+
writeVar v x = modifyVar_ v $ const $ pure x
154154

155155
-- | Modify a 'Var' producing a new value and a return result.
156156
modifyVar :: Var a -> (a -> IO (a, b)) -> IO b
@@ -195,7 +195,7 @@ newBarrier = fmap Barrier $ newVar . Left =<< newEmptyMVar
195195
signalBarrier :: Partial => Barrier a -> a -> IO ()
196196
signalBarrier (Barrier var) v = mask_ $ -- use mask so never in an inconsistent state
197197
join $ modifyVar var $ \x -> case x of
198-
Left bar -> return (Right v, putMVar bar ())
198+
Left bar -> pure (Right v, putMVar bar ())
199199
Right res -> error "Control.Concurrent.Extra.signalBarrier, attempt to signal a barrier that has already been signaled"
200200

201201

@@ -204,12 +204,12 @@ waitBarrier :: Barrier a -> IO a
204204
waitBarrier (Barrier var) = do
205205
x <- readVar var
206206
case x of
207-
Right res -> return res
207+
Right res -> pure res
208208
Left bar -> do
209209
readMVar bar
210210
x <- readVar var
211211
case x of
212-
Right res -> return res
212+
Right res -> pure res
213213
Left bar -> error "Control.Concurrent.Extra, internal invariant violated in Barrier"
214214

215215

src/Control/Exception/Extra.hs

+10-10
Original file line numberDiff line numberDiff line change
@@ -35,16 +35,16 @@ import Prelude
3535

3636
-- | Fully evaluate an input String. If the String contains embedded exceptions it will produce @\<Exception\>@.
3737
--
38-
-- > stringException "test" == return "test"
39-
-- > stringException ("test" ++ undefined) == return "test<Exception>"
40-
-- > stringException ("test" ++ undefined ++ "hello") == return "test<Exception>"
41-
-- > stringException ['t','e','s','t',undefined] == return "test<Exception>"
38+
-- > stringException "test" == pure "test"
39+
-- > stringException ("test" ++ undefined) == pure "test<Exception>"
40+
-- > stringException ("test" ++ undefined ++ "hello") == pure "test<Exception>"
41+
-- > stringException ['t','e','s','t',undefined] == pure "test<Exception>"
4242
stringException :: String -> IO String
4343
stringException x = do
4444
r <- try_ $ evaluate $ list [] (\x xs -> x `seq` x:xs) x
4545
case r of
46-
Left e -> return "<Exception>"
47-
Right [] -> return []
46+
Left e -> pure "<Exception>"
47+
Right [] -> pure []
4848
Right (x:xs) -> (x:) <$> stringException xs
4949

5050

@@ -66,15 +66,15 @@ errorWithoutStackTrace = error
6666
-- | Ignore any exceptions thrown by the action.
6767
--
6868
-- > ignore (print 1) == print 1
69-
-- > ignore (fail "die") == return ()
69+
-- > ignore (fail "die") == pure ()
7070
ignore :: IO () -> IO ()
7171
ignore = void . try_
7272

7373

7474
-- | An 'IO' action that when evaluated calls 'error', in the 'IO' monad.
7575
-- Note that while 'fail' in 'IO' raises an 'IOException', this function raises an 'ErrorCall' exception with a call stack.
7676
--
77-
-- > catch (errorIO "Hello") (\(ErrorCall x) -> return x) == return "Hello"
77+
-- > catch (errorIO "Hello") (\(ErrorCall x) -> pure x) == pure "Hello"
7878
-- > seq (errorIO "foo") (print 1) == print 1
7979
errorIO :: Partial => String -> IO a
8080
errorIO x = withFrozenCallStack $ evaluate $ error x
@@ -103,7 +103,7 @@ retryBool p i x = do
103103
res <- tryBool p x
104104
case res of
105105
Left _ -> retryBool p (i-1) x
106-
Right v -> return v
106+
Right v -> pure v
107107

108108

109109
-- | A version of 'catch' without the 'Exception' context, restricted to 'SomeException',
@@ -135,7 +135,7 @@ tryJust_ = tryJust
135135
-- As an example:
136136
--
137137
-- @
138-
-- readFileExists x == catchBool isDoesNotExistError (readFile \"myfile\") (const $ return \"\")
138+
-- readFileExists x == catchBool isDoesNotExistError (readFile \"myfile\") (const $ pure \"\")
139139
-- @
140140
catchBool :: Exception e => (e -> Bool) -> IO a -> (e -> IO a) -> IO a
141141
catchBool f a b = catchJust (bool f) a b

src/Control/Monad/Extra.hs

+21-21
Original file line numberDiff line numberDiff line change
@@ -30,22 +30,22 @@ import Prelude
3030

3131
-- | Perform some operation on 'Just', given the field inside the 'Just'.
3232
--
33-
-- > whenJust Nothing print == return ()
33+
-- > whenJust Nothing print == pure ()
3434
-- > whenJust (Just 1) print == print 1
3535
whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m ()
3636
whenJust mg f = maybe (pure ()) f mg
3737

3838
-- | Like 'whenJust', but where the test can be monadic.
3939
whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
4040
-- Can't reuse whenMaybe on GHC 7.8 or lower because Monad does not imply Applicative
41-
whenJustM mg f = maybeM (return ()) f mg
41+
whenJustM mg f = maybeM (pure ()) f mg
4242

4343

4444
-- | Like 'when', but return either 'Nothing' if the predicate was 'False',
4545
-- of 'Just' with the result of the computation.
4646
--
4747
-- > whenMaybe True (print 1) == fmap Just (print 1)
48-
-- > whenMaybe False (print 1) == return Nothing
48+
-- > whenMaybe False (print 1) == pure Nothing
4949
whenMaybe :: Applicative m => Bool -> m a -> m (Maybe a)
5050
whenMaybe b x = if b then Just <$> x else pure Nothing
5151

@@ -54,7 +54,7 @@ whenMaybeM :: Monad m => m Bool -> m a -> m (Maybe a)
5454
-- Can't reuse whenMaybe on GHC 7.8 or lower because Monad does not imply Applicative
5555
whenMaybeM mb x = do
5656
b <- mb
57-
if b then liftM Just x else return Nothing
57+
if b then liftM Just x else pure Nothing
5858

5959

6060
-- | The identity function which requires the inner argument to be @()@. Useful for functions
@@ -89,7 +89,7 @@ fold1M f xs = error "fold1M: empty list"
8989

9090
-- | Like 'fold1M' but discards the result.
9191
fold1M_ :: (Partial, Monad m) => (a -> a -> m a) -> [a] -> m ()
92-
fold1M_ f xs = fold1M f xs >> return ()
92+
fold1M_ f xs = fold1M f xs >> pure ()
9393

9494

9595
-- Data.List for Monad
@@ -99,18 +99,18 @@ fold1M_ f xs = fold1M f xs >> return ()
9999
-- > partitionM (Just . even) [1,2,3] == Just ([2], [1,3])
100100
-- > partitionM (const Nothing) [1,2,3] == Nothing
101101
partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a])
102-
partitionM f [] = return ([], [])
102+
partitionM f [] = pure ([], [])
103103
partitionM f (x:xs) = do
104104
res <- f x
105105
(as,bs) <- partitionM f xs
106-
return ([x | res]++as, [x | not res]++bs)
106+
pure ([x | res]++as, [x | not res]++bs)
107107

108108

109109
-- | A version of 'concatMap' that works with a monadic predicate.
110110
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
111111
{-# INLINE concatMapM #-}
112-
concatMapM op = foldr f (return [])
113-
where f x xs = do x <- op x; if null x then xs else do xs <- xs; return $ x++xs
112+
concatMapM op = foldr f (pure [])
113+
where f x xs = do x <- op x; if null x then xs else do xs <- xs; pure $ x++xs
114114

115115
-- | Like 'concatMapM', but has its arguments flipped, so can be used
116116
-- instead of the common @fmap concat $ forM@ pattern.
@@ -124,8 +124,8 @@ mconcatMapM f = liftM mconcat . mapM f
124124
-- | A version of 'mapMaybe' that works with a monadic predicate.
125125
mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]
126126
{-# INLINE mapMaybeM #-}
127-
mapMaybeM op = foldr f (return [])
128-
where f x xs = do x <- op x; case x of Nothing -> xs; Just x -> do xs <- xs; return $ x:xs
127+
mapMaybeM op = foldr f (pure [])
128+
where f x xs = do x <- op x; case x of Nothing -> xs; Just x -> do xs <- xs; pure $ x:xs
129129

130130
-- Looping
131131

@@ -145,7 +145,7 @@ loopM act x = do
145145
res <- act x
146146
case res of
147147
Left x -> loopM act x
148-
Right v -> return v
148+
Right v -> pure v
149149

150150
-- | Keep running an operation until it becomes 'False'. As an example:
151151
--
@@ -164,11 +164,11 @@ whileM act = do
164164

165165
-- | Like 'when', but where the test can be monadic.
166166
whenM :: Monad m => m Bool -> m () -> m ()
167-
whenM b t = ifM b t (return ())
167+
whenM b t = ifM b t (pure ())
168168

169169
-- | Like 'unless', but where the test can be monadic.
170170
unlessM :: Monad m => m Bool -> m () -> m ()
171-
unlessM b f = ifM b (return ()) f
171+
unlessM b f = ifM b (pure ()) f
172172

173173
-- | Like @if@, but where the test can be monadic.
174174
ifM :: Monad m => m Bool -> m a -> m a -> m a
@@ -186,7 +186,7 @@ notM = fmap not
186186
-- > Just False ||^ Just True == Just True
187187
-- > Just False ||^ Just False == Just False
188188
(||^) :: Monad m => m Bool -> m Bool -> m Bool
189-
(||^) a b = ifM a (return True) b
189+
(||^) a b = ifM a (pure True) b
190190

191191
-- | The lazy '&&' operator lifted to a monad. If the first
192192
-- argument evaluates to 'False' the second argument will not
@@ -196,23 +196,23 @@ notM = fmap not
196196
-- > Just True &&^ Just True == Just True
197197
-- > Just True &&^ Just False == Just False
198198
(&&^) :: Monad m => m Bool -> m Bool -> m Bool
199-
(&&^) a b = ifM a b (return False)
199+
(&&^) a b = ifM a b (pure False)
200200

201201
-- | A version of 'any' lifted to a monad. Retains the short-circuiting behaviour.
202202
--
203203
-- > anyM Just [False,True ,undefined] == Just True
204204
-- > anyM Just [False,False,undefined] == undefined
205205
-- > \(f :: Int -> Maybe Bool) xs -> anyM f xs == orM (map f xs)
206206
anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
207-
anyM p = foldr ((||^) . p) (return False)
207+
anyM p = foldr ((||^) . p) (pure False)
208208

209209
-- | A version of 'all' lifted to a monad. Retains the short-circuiting behaviour.
210210
--
211211
-- > allM Just [True,False,undefined] == Just False
212212
-- > allM Just [True,True ,undefined] == undefined
213213
-- > \(f :: Int -> Maybe Bool) xs -> anyM f xs == orM (map f xs)
214214
allM :: Monad m => (a -> m Bool) -> [a] -> m Bool
215-
allM p = foldr ((&&^) . p) (return True)
215+
allM p = foldr ((&&^) . p) (pure True)
216216

217217
-- | A version of 'or' lifted to a monad. Retains the short-circuiting behaviour.
218218
--
@@ -238,9 +238,9 @@ andM = allM id
238238
-- > findM (Just . isUpper) "test" == Just Nothing
239239
-- > findM (Just . const True) ["x",undefined] == Just (Just "x")
240240
findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)
241-
findM p = foldr (\x -> ifM (p x) (return $ Just x)) (return Nothing)
241+
findM p = foldr (\x -> ifM (p x) (pure $ Just x)) (pure Nothing)
242242

243243
-- | Like 'findM', but also allows you to compute some additional information in the predicate.
244244
firstJustM :: Monad m => (a -> m (Maybe b)) -> [a] -> m (Maybe b)
245-
firstJustM p [] = return Nothing
246-
firstJustM p (x:xs) = maybeM (firstJustM p xs) (return . Just) (p x)
245+
firstJustM p [] = pure Nothing
246+
firstJustM p (x:xs) = maybeM (firstJustM p xs) (pure . Just) (p x)

src/System/Directory/Extra.hs

+7-7
Original file line numberDiff line numberDiff line change
@@ -52,12 +52,12 @@ withCurrentDirectory dir act =
5252
--
5353
-- > withTempDir $ \dir -> do writeFile (dir </> "test.txt") ""; (== [dir </> "test.txt"]) <$> listContents dir
5454
-- > let touch = mapM_ $ \x -> createDirectoryIfMissing True (takeDirectory x) >> writeFile x ""
55-
-- > let listTest op as bs = withTempDir $ \dir -> do touch $ map (dir </>) as; res <- op dir; return $ map (drop (length dir + 1)) res == bs
55+
-- > let listTest op as bs = withTempDir $ \dir -> do touch $ map (dir </>) as; res <- op dir; pure $ map (drop (length dir + 1)) res == bs
5656
-- > listTest listContents ["bar.txt","foo/baz.txt","zoo"] ["bar.txt","foo","zoo"]
5757
listContents :: FilePath -> IO [FilePath]
5858
listContents dir = do
5959
xs <- getDirectoryContents dir
60-
return $ sort [dir </> x | x <- xs, not $ all (== '.') x]
60+
pure $ sort [dir </> x | x <- xs, not $ all (== '.') x]
6161

6262

6363
-- | Like 'listContents', but only returns the directories in a directory, not the files.
@@ -81,21 +81,21 @@ listFiles dir = filterM doesFileExist =<< listContents dir
8181
--
8282
-- > listTest listFilesRecursive ["bar.txt","zoo","foo" </> "baz.txt"] ["bar.txt","zoo","foo" </> "baz.txt"]
8383
listFilesRecursive :: FilePath -> IO [FilePath]
84-
listFilesRecursive = listFilesInside (const $ return True)
84+
listFilesRecursive = listFilesInside (const $ pure True)
8585

8686

8787
-- | Like 'listFilesRecursive', but with a predicate to decide where to recurse into.
8888
-- Typically directories starting with @.@ would be ignored. The initial argument directory
8989
-- will have the test applied to it.
9090
--
91-
-- > listTest (listFilesInside $ return . not . isPrefixOf "." . takeFileName)
91+
-- > listTest (listFilesInside $ pure . not . isPrefixOf "." . takeFileName)
9292
-- > ["bar.txt","foo" </> "baz.txt",".foo" </> "baz2.txt", "zoo"] ["bar.txt","zoo","foo" </> "baz.txt"]
93-
-- > listTest (listFilesInside $ const $ return False) ["bar.txt"] []
93+
-- > listTest (listFilesInside $ const $ pure False) ["bar.txt"] []
9494
listFilesInside :: (FilePath -> IO Bool) -> FilePath -> IO [FilePath]
95-
listFilesInside test dir = ifM (notM $ test $ dropTrailingPathSeparator dir) (return []) $ do
95+
listFilesInside test dir = ifM (notM $ test $ dropTrailingPathSeparator dir) (pure []) $ do
9696
(dirs,files) <- partitionM doesDirectoryExist =<< listContents dir
9797
rest <- concatMapM (listFilesInside test) dirs
98-
return $ files ++ rest
98+
pure $ files ++ rest
9999

100100

101101
-- | Create a directory with permissions so that only the current user can view it.

0 commit comments

Comments
 (0)