Skip to content

Commit

Permalink
Remove unnecessary return definitions (#1095)
Browse files Browse the repository at this point in the history
The default return=pure works and we are long past the
Functor-Applicative-Monad Proposal.
  • Loading branch information
meooow25 authored Jan 19, 2025
1 parent 9f31352 commit 25036a9
Show file tree
Hide file tree
Showing 4 changed files with 0 additions and 7 deletions.
3 changes: 0 additions & 3 deletions containers/src/Data/Graph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -587,8 +587,6 @@ newtype SetM s a = SetM { runSetM :: STArray s Vertex Bool -> ST s a }
#endif

instance Monad (SetM s) where
return = pure
{-# INLINE return #-}
SetM v >>= f = SetM $ \s -> do { x <- v s; runSetM (f x) s }
{-# INLINE (>>=) #-}

Expand Down Expand Up @@ -621,7 +619,6 @@ include v = SetM $ \ m -> writeArray m v True
newtype SetM s a = SetM { runSetM :: IntSet -> (a, IntSet) }

instance Monad (SetM s) where
return x = SetM $ \s -> (x, s)
SetM v >>= f = SetM $ \s -> case v s of (x, s') -> runSetM (f x) s'

instance Functor (SetM s) where
Expand Down
1 change: 0 additions & 1 deletion containers/src/Data/Sequence/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -521,7 +521,6 @@ instance NFData1 Seq where
liftRnf rnfx (Seq xs) = liftRnf (liftRnf rnfx) xs

instance Monad Seq where
return = pure
xs >>= f = foldl' add empty xs
where add ys x = ys >< f x
(>>) = (*>)
Expand Down
1 change: 0 additions & 1 deletion containers/src/Data/Tree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -171,7 +171,6 @@ instance Applicative Tree where
Node y (tys ++ map (*> ty) txs)

instance Monad Tree where
return = pure
Node x ts >>= f = case f x of
Node x' ts' -> Node x' (ts' ++ map (>>= f) ts)

Expand Down
2 changes: 0 additions & 2 deletions containers/src/Utils/Containers/Internal/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,9 +16,7 @@ instance Functor (State s) where
fmap = liftA

instance Monad (State s) where
{-# INLINE return #-}
{-# INLINE (>>=) #-}
return = pure
m >>= k = State $ \ s -> case runState m s of
(s', x) -> runState (k x) s'

Expand Down

0 comments on commit 25036a9

Please sign in to comment.