Skip to content

Commit

Permalink
canonical-AMP-warning avoidance
Browse files Browse the repository at this point in the history
  • Loading branch information
hvr committed Nov 22, 2015
1 parent 784db6a commit c943003
Show file tree
Hide file tree
Showing 6 changed files with 8 additions and 6 deletions.
4 changes: 2 additions & 2 deletions src/Control/Comonad/Cofree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,7 @@ instance ComonadTrans Cofree where
{-# INLINE lower #-}

instance Alternative f => Monad (Cofree f) where
return x = x :< empty
return = pure
{-# INLINE return #-}
(a :< m) >>= k = case k a of
b :< n -> b :< (n <|> fmap (>>= k) m)
Expand Down Expand Up @@ -188,7 +188,7 @@ instance ComonadApply f => ComonadApply (Cofree f) where
{-# INLINE (@>) #-}

instance Alternative f => Applicative (Cofree f) where
pure = return
pure x = x :< empty
{-# INLINE pure #-}
(<*>) = ap
{-# INLINE (<*>) #-}
Expand Down
2 changes: 2 additions & 0 deletions src/Control/Comonad/Trans/Cofree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -168,8 +168,10 @@ instance Ord (w (CofreeF f a (CofreeT f w a))) => Ord (CofreeT f w a) where
compare (CofreeT a) (CofreeT b) = compare a b

instance (Alternative f, Monad w) => Monad (CofreeT f w) where
#if __GLASGOW_HASKELL__ < 710
return = CofreeT . return . (:< empty)
{-# INLINE return #-}
#endif
CofreeT cx >>= f = CofreeT $ do
a :< m <- cx
b :< n <- runCofreeT $ f a
Expand Down
2 changes: 1 addition & 1 deletion src/Control/Monad/Free.hs
Original file line number Diff line number Diff line change
Expand Up @@ -187,7 +187,7 @@ instance Functor f => Bind (Free f) where
Free m >>- f = Free ((>>- f) <$> m)

instance Functor f => Monad (Free f) where
return = Pure
return = pure
{-# INLINE return #-}
Pure a >>= f = f a
Free m >>= f = Free ((>>= f) <$> m)
Expand Down
2 changes: 1 addition & 1 deletion src/Control/Monad/Free/Church.hs
Original file line number Diff line number Diff line change
Expand Up @@ -110,7 +110,7 @@ instance Bind (F f) where
(>>-) = (>>=)

instance Monad (F f) where
return a = F (\kp _ -> kp a)
return = pure
F m >>= f = F (\kp kf -> m (\a -> runF (f a) kp kf) kf)

instance MonadFix (F f) where
Expand Down
2 changes: 1 addition & 1 deletion src/Control/Monad/Trans/Free.hs
Original file line number Diff line number Diff line change
Expand Up @@ -224,7 +224,7 @@ instance (Functor f, Monad m) => Bind (FreeT f m) where

instance (Functor f, Monad m) => Monad (FreeT f m) where
fail e = FreeT (fail e)
return a = FreeT (return (Pure a))
return = pure
{-# INLINE return #-}
FreeT m >>= f = FreeT $ m >>= \v -> case v of
Pure a -> runFreeT (f a)
Expand Down
2 changes: 1 addition & 1 deletion src/Control/Monad/Trans/Iter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -172,7 +172,7 @@ instance Monad m => Applicative (IterT m) where
{-# INLINE (<*>) #-}

instance Monad m => Monad (IterT m) where
return = IterT . return . Left
return = pure
{-# INLINE return #-}
IterT m >>= k = IterT $ m >>= either (runIterT . k) (return . Right . (>>= k))
{-# INLINE (>>=) #-}
Expand Down

0 comments on commit c943003

Please sign in to comment.