On 04/12/2013 12:49 PM, o...@okmij.org wrote:
One problem with such monad implementations is efficiency. Let's define
step :: (MonadPlus m) => Int -> m Int
step i = choose [i, i + 1]
-- repeated application of step on 0:
stepN :: (Monad m) => Int -> m (S.Set Int)
st
> One problem with such monad implementations is efficiency. Let's define
>
> step :: (MonadPlus m) => Int -> m Int
> step i = choose [i, i + 1]
>
> -- repeated application of step on 0:
> stepN :: (Monad m) => Int -> m (S.Set Int)
> stepN = runSet . f
> where
> f
One problem with such monad implementations is efficiency. Let's define
step :: (MonadPlus m) => Int -> m Int
step i = choose [i, i + 1]
-- repeated application of step on 0:
stepN :: (Monad m) => Int -> m (S.Set Int)
stepN = runSet . f
where
f 0 = return 0
On Sun, Jan 9, 2011 at 10:11 PM, Lennart Augustsson
wrote:
> That looks like it looses the efficiency of the underlying representation.
>
Yes, I don't think one can retain that cleanly without using restricted
monads to exclude things like
liftM ($42) (mplus (return pred) (return succ))
or
That looks like it looses the efficiency of the underlying representation.
On Sun, Jan 9, 2011 at 6:45 AM, Sebastian Fischer wrote:
> On Sun, Jan 9, 2011 at 6:53 AM, Lennart Augustsson > wrote:
>
>> It so happens that you can make a set data type that is a Monad, but it's
>> not exactly the bes
On Sun, Jan 9, 2011 at 7:45 AM, Sebastian Fischer wrote:
> [...]
> Only conversion to the underlying Set type requires an Ord constraint.
> getSet :: Ord a => Set a -> S.Set a
> getSet a = a >>- S.singleton
this unfortunately also means that duplicated elements only get
filtered out at th
On Sun, Jan 9, 2011 at 6:53 AM, Lennart Augustsson
wrote:
> It so happens that you can make a set data type that is a Monad, but it's
> not exactly the best possible sets.
>
> module SetMonad where
>
> newtype Set a = Set { unSet :: [a] }
>
Here is a version that also does not require restricted
On Sat, Jan 8, 2011 at 4:53 PM, Lennart Augustsson
wrote:
> It so happens that you can make a set data type that is a Monad, but it's
> not exactly the best possible sets.
There's also the infinite search monad, which allows you to search
infinite sets in finite time, provided your queries meet s
It so happens that you can make a set data type that is a Monad, but it's
not exactly the best possible sets.
module SetMonad where
newtype Set a = Set { unSet :: [a] }
singleton :: a -> Set a
singleton x = Set [x]
unions :: [Set a] -> Set a
unions ss = Set $ concatMap unSet ss
member :: (Eq a
Hello Peter,
This is a classic problem with the normal monad type class. You can
achieve this with "restricted monads", but there is a bit of tomfoolery
you have to do to get do-notation support for them.
Here is some relevant reading:
- http://okmij.org/ftp/Haskell/types.html#restricted-da
On 9 January 2011 07:28, Peter Padawitz wrote:
> Hi,
>
> is there any way to instantiate m in Monad m with a set datatype in order to
> implement the usual powerset monad?
>
> My straightforward attempt failed because the bind operator of this instance
> requires the Eq constraint on the argument
11 matches
Mail list logo