Skip to content

Commit 94d1638

Browse files
committed
Merge pull request #168 from hvr/pr/minor-cleanups
Minor cleanups
2 parents 4634081 + 5f232df commit 94d1638

File tree

5 files changed

+9
-13
lines changed

5 files changed

+9
-13
lines changed

Data/Graph.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -295,7 +295,7 @@ chop (Node v ts : us)
295295
newtype SetM s a = SetM { runSetM :: STArray s Vertex Bool -> ST s a }
296296

297297
instance Monad (SetM s) where
298-
return x = SetM $ const (return x)
298+
return = pure
299299
{-# INLINE return #-}
300300
SetM v >>= f = SetM $ \s -> do { x <- v s; runSetM (f x) s }
301301
{-# INLINE (>>=) #-}

Data/IntMap/Base.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -216,9 +216,7 @@ module Data.IntMap.Base (
216216
, highestBitMask
217217
) where
218218

219-
#if MIN_VERSION_base(4,8,0)
220-
import Control.Applicative ((<$>))
221-
#else
219+
#if !(MIN_VERSION_base(4,8,0))
222220
import Control.Applicative (Applicative(pure, (<*>)), (<$>))
223221
import Data.Monoid (Monoid(..))
224222
import Data.Traversable (Traversable(traverse))

Data/Map/Base.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -270,9 +270,7 @@ module Data.Map.Base (
270270
, filterLt
271271
) where
272272

273-
#if MIN_VERSION_base(4,8,0)
274-
import Control.Applicative ((<$>))
275-
#else
273+
#if !(MIN_VERSION_base(4,8,0))
276274
import Control.Applicative (Applicative(..), (<$>))
277275
import Data.Monoid (Monoid(..))
278276
import Data.Traversable (Traversable(traverse))

Data/Sequence.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -158,7 +158,7 @@ module Data.Sequence (
158158
import Prelude hiding (
159159
Functor(..),
160160
#if MIN_VERSION_base(4,8,0)
161-
Applicative, foldMap, Monoid,
161+
Applicative, (<$>), foldMap, Monoid,
162162
#endif
163163
null, length, take, drop, splitAt, foldl, foldl1, foldr, foldr1,
164164
scanl, scanl1, scanr, scanr1, replicate, zip, zipWith, zip3, zipWith3,
@@ -267,7 +267,7 @@ instance NFData a => NFData (Seq a) where
267267
rnf (Seq xs) = rnf xs
268268

269269
instance Monad Seq where
270-
return = singleton
270+
return = pure
271271
xs >>= f = foldl' add empty xs
272272
where add ys x = ys >< f x
273273
(>>) = (*>)
@@ -861,12 +861,13 @@ instance Functor (State s) where
861861
instance Monad (State s) where
862862
{-# INLINE return #-}
863863
{-# INLINE (>>=) #-}
864-
return x = State $ \ s -> (s, x)
864+
return = pure
865865
m >>= k = State $ \ s -> case runState m s of
866866
(s', x) -> runState (k x) s'
867867

868868
instance Applicative (State s) where
869-
pure = return
869+
{-# INLINE pure #-}
870+
pure x = State $ \ s -> (s, x)
870871
(<*>) = ap
871872

872873
execState :: State s a -> s -> a

Data/Tree.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,6 @@ module Data.Tree(
3535
) where
3636

3737
#if MIN_VERSION_base(4,8,0)
38-
import Control.Applicative ((<$>))
3938
import Data.Foldable (toList)
4039
#else
4140
import Control.Applicative (Applicative(..), (<$>))
@@ -92,7 +91,7 @@ instance Applicative Tree where
9291
Node (f x) (map (f <$>) txs ++ map (<*> tx) tfs)
9392

9493
instance Monad Tree where
95-
return x = Node x []
94+
return = pure
9695
Node x ts >>= f = Node x' (ts' ++ map (>>= f) ts)
9796
where Node x' ts' = f x
9897

0 commit comments

Comments
 (0)