Skip to content

Commit

Permalink
Revert "Define oneOf & foldMapA via the Alternative interfaces."
Browse files Browse the repository at this point in the history
This reverts commit 358c54d.
  • Loading branch information
robrix committed Sep 21, 2019
1 parent 358c54d commit f65b114
Showing 1 changed file with 3 additions and 12 deletions.
15 changes: 3 additions & 12 deletions src/Control/Effect/NonDet.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleContexts, GeneralizedNewtypeDeriving, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts #-}
-- | 'Choose' & 'Empty'-based nondeterminism interfaces.
module Control.Effect.NonDet
( -- * NonDet effects
Expand All @@ -9,7 +9,6 @@ module Control.Effect.NonDet
) where

import Control.Carrier
import qualified Control.Effect.Alternative as Alt
import Control.Effect.Choose
import Control.Effect.Empty
import Data.Coerce
Expand All @@ -26,11 +25,11 @@ import Data.Coerce
-- pure (a, b, c)
-- @
oneOf :: (Foldable t, Carrier sig m, Member Choose sig, Member Empty sig) => t a -> m a
oneOf = runViaEffects . Alt.oneOf
oneOf = foldMapA pure

-- | Map a 'Foldable' collection of values into a nondeterministic computation using the supplied action.
foldMapA :: (Foldable t, Carrier sig m, Member Choose sig, Member Empty sig) => (a -> m b) -> t a -> m b
foldMapA f = runViaEffects #. Alt.foldMapA (ViaEffects #. f)
foldMapA f = getChoosing #. foldMap (Choosing #. f)


-- | Compose a function operationally equivalent to 'id' on the left.
Expand All @@ -39,11 +38,3 @@ foldMapA f = runViaEffects #. Alt.foldMapA (ViaEffects #. f)
(#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c)
(#.) _ = coerce
{-# INLINE (#.) #-}


newtype ViaEffects m a = ViaEffects { runViaEffects :: m a }
deriving (Applicative, Functor, Monad)

instance (Carrier sig m, Member Choose sig, Member Empty sig) => Alt.Alternative (ViaEffects m) where
empty = ViaEffects empty
ViaEffects m1 <|> ViaEffects m2 = ViaEffects (m1 <|> m2)

0 comments on commit f65b114

Please sign in to comment.