From c5147d03e9f460f8ac8abfec2f5fe48bb2f9a5ec Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Fri, 5 Aug 2016 13:24:30 +0200 Subject: linting --- events/src/Events/Types/NDT.hs | 12 ++++-------- 1 file changed, 4 insertions(+), 8 deletions(-) diff --git a/events/src/Events/Types/NDT.hs b/events/src/Events/Types/NDT.hs index 848ad39..a417029 100644 --- a/events/src/Events/Types/NDT.hs +++ b/events/src/Events/Types/NDT.hs @@ -1,6 +1,5 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE TupleSections #-} -{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE FlexibleContexts, FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-} @@ -15,6 +14,7 @@ import Data.Monoid import Data.Foldable (foldr) import Data.Maybe import Data.Either +import Data.Bool (bool) import Control.Applicative (Alternative) import qualified Control.Applicative as Alt (Alternative(..)) @@ -41,7 +41,7 @@ instance Functor m => Functor (NDT m) where instance Applicative m => Applicative (NDT m) where pure x = NDTCons . pure $ Just (x, empty) - fs <*> xs = fs >>= (\f -> xs >>= pure . (f $)) + fs <*> xs = fs >>= (\f -> xs >>= pure . f) instance Applicative m => Monad (NDT m) where return = pure @@ -55,7 +55,7 @@ instance Monad m => Monoid (NDT m a) where mappend x y@(NDTBind _ _) = NDTBind x return <> y instance MonadTrans NDT where - lift = NDTCons . fmap Just . fmap (,empty) + lift = NDTCons . fmap (Just . (, empty)) instance Monad m => Alternative (NDT m) where empty = mempty @@ -88,11 +88,7 @@ foldNDT sel (NDTCons mx) = do mx' <- mx case mx' of Nothing -> return mempty - Just (x, mxs) -> do - continue <- sel x - case continue of - False -> return mempty - True -> (pure x <>) <$> foldNDT sel mxs + Just (x, mxs) -> bool (return mempty) ((pure x <>) <$> foldNDT sel mxs) =<< sel x foldNDT sel (NDTBind (NDTCons x) f) = do x' <- x case x' of -- cgit v1.2.3