Many functions can be generalised

David Feuer david.feuer at gmail.com
Sat Dec 3 19:32:44 UTC 2016


You can also sift monomorphic containers using my class, which should
probably be called MonoSiftable.

data IntList = Cons !Int IntList | Nil

instance Siftable Int IntList where
  sift _ Nil = Nil
  sift p (Cons x xs)
    | p x = Cons x (sift p xs)
    | otherwise = sift p xs

On Dec 3, 2016 2:17 PM, "David Menendez" <dave at zednenem.com> wrote:

> On Sat, Dec 3, 2016 at 12:50 AM, David Feuer <david.feuer at gmail.com>
> wrote:
>
>> On Dec 2, 2016 6:14 PM, "David Menendez" <dave at zednenem.com> wrote:
>>
>> A while back, I found myself deriving this class:
>>
>>     class Functor f => Siftable f where
>>         siftWith :: (a -> Maybe b) -> f a -> f b
>>         sift :: (a -> Bool) -> f a -> f a
>>         sift f = siftWith (\a -> if f a then Just a else Nothing)
>>
>>
>> I would expect several classes, corresponding to different methods of
>> Witherable:
>>
>> class Siftable a m | m -> a where
>>   sift :: (a -> Bool) -> m -> m
>>   default sift :: SiftWithable f => (a -> Bool) -> f a -> f a
>>   sift p = siftWith (\x -> x <$ guard (p x))
>>
>> class Functor f => SiftWithable f where
>>   siftWith :: (a -> Maybe b) -> f a -> f b
>>
>> class Siftable a m => SiftableA a m where
>>   siftA :: Applicative g => (a -> g Bool) -> m -> g m
>>   default siftA :: (SiftWithAAble f, Applicative g) => (a -> g Bool) -> f
>> a -> g (f a)
>>   siftA p = siftWithA (\x -> (x <$) . guard <$> p x)
>>
>> class (Traversable f, SiftWithAble f) => SiftWithAAble f where
>>   siftWithA :: Applicative g => (a -> g (Maybe b)) -> f a -> g (f a)
>>
>
> Yes, sift is more general than siftWith (which I should have called
> siftMap, in hindsight). But, so far as I know, the only things you can
> define sift for but not siftWith are sets and set-like things.
>
> At the time, I had also rejected sift by itself because I couldn’t think
> of any laws, but now that I look at it again, I guess they would be:
>
>     sift (const True) = id
>     sift (\x -> p x && q x) = sift q . sift p
>
> I think those would make sift a monoid homomorphism.
>
> These still allow some weird instances, like sift _ = id, or something
> like this:
>
>     newtype Weird a = Map a Bool
>
>     instance Ord a => Siftable a (Weird a) where
>         sift p (Weird m) = Weird (Map.union (Map.updateMin (const False)
> yes) no)
>             where
>             (yes, no) = Map.partitionWithKey (const . p) m
>
> I imagine it isn’t worth making the laws tighter to forbid this.
>
> --
> Dave Menendez <dave at zednenem.com>
> <http://www.eyrie.org/~zednenem/>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20161203/f7bea577/attachment.html>


More information about the Libraries mailing list