From 9628bb69c286ebb309bff680196b546e57efaa62 Mon Sep 17 00:00:00 2001 From: Ross Paterson <ross@soi.city.ac.uk> Date: Sat, 2 Feb 2019 00:45:16 +0000 Subject: [PATCH] backward compatability for MonadFix ListT instance --- Control/Monad/Trans/List.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Control/Monad/Trans/List.hs b/Control/Monad/Trans/List.hs index 3cde4ce..919898e 100644 --- a/Control/Monad/Trans/List.hs +++ b/Control/Monad/Trans/List.hs @@ -145,8 +145,8 @@ instance (Monad m) => MonadPlus (ListT m) where instance (MonadFix m) => MonadFix (ListT m) where mfix f = ListT $ mfix (runListT . f . head) >>= \ xs -> case xs of - [] -> pure [] - x:_ -> (x:) <$> (runListT . mfix) ((mapListT . fmap) tail . f) + [] -> return [] + x:_ -> liftM (x:) (runListT (mfix (mapListT (fmap tail) . f))) {-# INLINE mfix #-} instance MonadTrans ListT where -- GitLab