
1. Is there a more general version of `null`? (e.g. for a Monad, Functor, Applicative, Traversable or the like.) The closest I can come up with is, in decreasing clunkiness: zero :: (MonadPlus m, Eq (m a)) => m a -> Bool zero = m == mzero zero :: (Alternative f, Eq (f a)) => f a -> Bool zero = m == empty zero :: (Monoid m, Eq m) => m -> Bool zero = m == mempty Though requiring Eq seems ugly and unnecessary, in theory. 2. In that vein, is there an existing function for "a value or a default if it's zero"? E.g.: orElse :: (Monoid m) => m -> m -> m a `orElse` b = if zero a then b else a Thank you, Alvaro http://alva.ro

Hi Alvaro, 1. null . toList :: Foldable t => t a -> Bool 2. mappend, mplus, <|> are supposed to drop arguments that are mempty, mzero, empty respectively. There's no requirement to prefer the first argument, but that's what the MonadPlus Maybe instance does at least. -- Adam

On Wed, Jan 29, 2014 at 4:25 AM, Alvaro J. Genial
1. Is there a more general version of `null`? (e.g. for a Monad, Functor, Applicative, Traversable or the like.) The closest I can come up with is, in decreasing clunkiness:
zero :: (MonadPlus m, Eq (m a)) => m a -> Bool zero = m == mzero
zero :: (Alternative f, Eq (f a)) => f a -> Bool zero = m == empty
zero :: (Monoid m, Eq m) => m -> Bool zero = m == mempty
Though requiring Eq seems ugly and unnecessary, in theory.
You can try out onull[1], which will work on any MonoFoldable. That allows it to work with classical Foldable instances (like a list or Maybe), but also monomorphic containers like ByteString or Text. [1] http://hackage.haskell.org/package/mono-traversable-0.2.0.0/docs/Data-MonoTr...
2. In that vein, is there an existing function for "a value or a default if it's zero"? E.g.:
orElse :: (Monoid m) => m -> m -> m a `orElse` b = if zero a then b else a
Thank you,
Alvaro http://alva.ro
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Alvaro,
Not long ago I faced the same question, and ended up developing a very
simplistic library IsNull:
https://github.com/jcristovao/IsNull
To be honest, its a very stripped down version of Mono-traversable
referenced by Michael, which I highly recomend, but in my case
specialized to provide some extra functions, namely nested null:
isNullN (Just "abc") == False
isNullN (Just "" ) == True
isNullN (Nothing ) == True
Now, a small note regarding:
zero :: (Monoid m, Eq m) => m -> Bool
zero = m == mempty
This is dangerous. For example:
-- | Monoid under multiplication.
newtype Product a = Product { getProduct :: a }
deriving (Eq, Ord, Read, Show, Bounded)
instance Num a => Monoid (Product a) where
mempty = Product 1
Product x `mappend` Product y = Product (x * y)
This leads to:
zero (Product 1) = True.
Is this what you wanted?
I had this in my library at first, and ended up removing it, because
it might not always be what is expected.
Cheers,
Joao
2014/1/29 Nikita Danilenko
Hi Alvaro,
as for your second question
2. In that vein, is there an existing function for "a value or a default if it's zero"? E.g.:
orElse :: (Monoid m) => m -> m -> m a `orElse` b = if zero a then b else a
There is the function orElse from the syb package [1] that works on (Maybe a) values. It can be considered a particular instance of the above with mempty = Nothing.
Alternatively, the function fromMaybe from Data.Maybe [2] provides a similar functionality, but with the heterogeneous type
fromMaybe :: a -> Maybe a -> a
Essentially, in both cases the zero predicate is specialised to a pattern matching for Nothing, which doesn't require an Eq instance. Also, there is no need for a mappend function, which may be more convenient.
Best regards,
Nikita
[1] http://hackage.haskell.org/package/syb-0.4.1/docs/Data-Generics-Aliases.html...
[2] http://hackage.haskell.org/package/base-4.6.0.1/docs/Data-Maybe.html#v:fromM...
On 29/01/14 07:46, Michael Snoyman wrote:
On Wed, Jan 29, 2014 at 4:25 AM, Alvaro J. Genial
wrote: 1. Is there a more general version of `null`? (e.g. for a Monad, Functor, Applicative, Traversable or the like.) The closest I can come up with is, in decreasing clunkiness:
zero :: (MonadPlus m, Eq (m a)) => m a -> Bool zero = m == mzero
zero :: (Alternative f, Eq (f a)) => f a -> Bool zero = m == empty
zero :: (Monoid m, Eq m) => m -> Bool zero = m == mempty
Though requiring Eq seems ugly and unnecessary, in theory.
You can try out onull[1], which will work on any MonoFoldable. That allows it to work with classical Foldable instances (like a list or Maybe), but also monomorphic containers like ByteString or Text.
[1] http://hackage.haskell.org/package/mono-traversable-0.2.0.0/docs/Data-MonoTr...
2. In that vein, is there an existing function for "a value or a default if it's zero"? E.g.:
orElse :: (Monoid m) => m -> m -> m a `orElse` b = if zero a then b else a
Thank you,
Alvaro http://alva.ro
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Dipl.-Math. Nikita Danilenko Research group: Computer Aided Program Development Kiel University Olshausenstr. 40, D-24098 Kiel Phone: +49 431 880 7275 URL: https://www.informatik.uni-kiel.de/index.php?id=nikita
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hey João,
On Wed, Jan 29, 2014 at 5:13 AM, João Cristóvão
This leads to:
zero (Product 1) = True.
Is this what you wanted?
Indeed, it seems not. I'll have to think about this further. Thank you, Alvaro http://alva.ro

On Tue, 28 Jan 2014 21:25:31 -0500, "Alvaro J. Genial"
1. Is there a more general version of `null`? (e.g. for a Monad, Functor, Applicative, Traversable or the like.) The closest I can come up with is, in decreasing clunkiness:
Lens can do this via the “hasn't” function for any Fold. You can get some free generalization out of it via “hasn't each”, which works for every instance of Each (includes most Foldable containers along with ByteString, Text, and similar).
2. In that vein, is there an existing function for "a value or a default if it's zero"? E.g.:
This abstraction looks a lot like what you'd want out of Alternative, though admittedly that one is specialized to (* -> *).

On 01/28/14 21:25, Alvaro J. Genial wrote:
1. Is there a more general version of `null`? (e.g. for a Monad, Functor, Applicative, Traversable or the like.)
There is the MonoidNull class from my monoid-subclasses library. It comes with plenty of standard instances. http://hackage.haskell.org/package/monoid-subclasses-0.3.5/docs/Data-Monoid-...

On Sat, Feb 1, 2014 at 12:08 PM, Mario Blažević
On 01/28/14 21:25, Alvaro J. Genial wrote:
1. Is there a more general version of `null`? (e.g. for a Monad, Functor, Applicative, Traversable or the like.)
There is the MonoidNull class from my monoid-subclasses library. It comes with plenty of standard instances.
This is very nice as it seems to mesh with my current thinking; I may end up using it in Neat [1] shortly. Thank you, Alvaro http://alva.ro [1] https://github.com/ajg/neat
participants (7)
-
adam vogt
-
Alvaro J. Genial
-
João Cristóvão
-
Mario Blažević
-
Michael Snoyman
-
Nikita Danilenko
-
Niklas Haas