Augmented sequence deletion

Data.Sequence offers deleteAt :: Int -> Seq a -> Seq a which deletes the element at the given index. Today, I ran into a situation where I wanted to know what was deleted. deleteLookup :: Int -> Seq a -> Maybe (a, Seq a) The closest thing I can find in `containers` is in Data.Map: updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a,Map k a) Unfortunately, that function is ugly and strange. A better one, whose name I can't guess at the moment: flabbergast :: (a -> (b, Maybe a)) -> Int -> Seq a -> Maybe (b, Seq a) where a Nothing result means the index was out of bounds. There's also a potential flabbergastF :: Functor f => (a -> f (Maybe a)) -> Int -> Seq a -> Maybe (f (Seq a)) I'm not sure if flabbergast can be made as fast as deleteLookup, so it's possible we may want both. Any opinions?

deleteLookup :: Int -> Seq a -> Maybe (a, Seq a)
deleteLookup n q = case Seq.splitAt n q of
(ql, qr) -> case Seq.viewl qr of
Seq.EmptyL -> Nothing
(Seq.:<) a qr' -> Just (a, ql <> qr')
If it were written natively, it'd probably use some of the machinery from
splitAt.
On 13:25, Sat, Dec 28, 2019 David Feuer Data.Sequence offers deleteAt :: Int -> Seq a -> Seq a which deletes the element at the given index. Today, I ran into a
situation where I wanted to know what was deleted. deleteLookup :: Int -> Seq a -> Maybe (a, Seq a) The closest thing I can find in `containers` is in Data.Map: updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a
-> (Maybe a,Map k a) Unfortunately, that function is ugly and strange. A better one, whose
name I can't guess at the moment: flabbergast :: (a -> (b, Maybe a)) -> Int -> Seq a -> Maybe (b, Seq a) where a Nothing result means the index was out of bounds. There's also
a potential flabbergastF :: Functor f => (a -> f (Maybe a)) -> Int -> Seq a ->
Maybe (f (Seq a)) I'm not sure if flabbergast can be made as fast as deleteLookup, so
it's possible we may want both. Any opinions?
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Written natively, it would surely borrow the machinery of deleteAt, which
does quite a bit less reshuffling. It's actually a finger-twisted version
of a classical 2-3 tree deletion.
On Sat, Dec 28, 2019, 2:59 PM Zemyla
deleteLookup :: Int -> Seq a -> Maybe (a, Seq a) deleteLookup n q = case Seq.splitAt n q of (ql, qr) -> case Seq.viewl qr of Seq.EmptyL -> Nothing (Seq.:<) a qr' -> Just (a, ql <> qr')
If it were written natively, it'd probably use some of the machinery from splitAt.
On 13:25, Sat, Dec 28, 2019 David Feuer
Data.Sequence offers
deleteAt :: Int -> Seq a -> Seq a
which deletes the element at the given index. Today, I ran into a situation where I wanted to know what was deleted.
deleteLookup :: Int -> Seq a -> Maybe (a, Seq a)
The closest thing I can find in `containers` is in Data.Map:
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a,Map k a)
Unfortunately, that function is ugly and strange. A better one, whose name I can't guess at the moment:
flabbergast :: (a -> (b, Maybe a)) -> Int -> Seq a -> Maybe (b, Seq a)
where a Nothing result means the index was out of bounds. There's also a potential
flabbergastF :: Functor f => (a -> f (Maybe a)) -> Int -> Seq a -> Maybe (f (Seq a))
I'm not sure if flabbergast can be made as fast as deleteLookup, so it's possible we may want both. Any opinions? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

This sounds like 'unconsAt', if 'uncons' isn't already too obtuse.
On December 28, 2019 8:06:21 PM UTC, David Feuer
Written natively, it would surely borrow the machinery of deleteAt, which does quite a bit less reshuffling. It's actually a finger-twisted version of a classical 2-3 tree deletion.
On Sat, Dec 28, 2019, 2:59 PM Zemyla
wrote: deleteLookup :: Int -> Seq a -> Maybe (a, Seq a) deleteLookup n q = case Seq.splitAt n q of (ql, qr) -> case Seq.viewl qr of Seq.EmptyL -> Nothing (Seq.:<) a qr' -> Just (a, ql <> qr')
If it were written natively, it'd probably use some of the machinery from splitAt.
On 13:25, Sat, Dec 28, 2019 David Feuer
Data.Sequence offers
deleteAt :: Int -> Seq a -> Seq a
which deletes the element at the given index. Today, I ran into a situation where I wanted to know what was deleted.
deleteLookup :: Int -> Seq a -> Maybe (a, Seq a)
The closest thing I can find in `containers` is in Data.Map:
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a,Map k a)
Unfortunately, that function is ugly and strange. A better one, whose name I can't guess at the moment:
flabbergast :: (a -> (b, Maybe a)) -> Int -> Seq a -> Maybe (b, Seq a)
where a Nothing result means the index was out of bounds. There's also a potential
flabbergastF :: Functor f => (a -> f (Maybe a)) -> Int -> Seq a -> Maybe (f (Seq a))
I'm not sure if flabbergast can be made as fast as deleteLookup, so it's possible we may want both. Any opinions? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-- Sent from my Android device with K-9 Mail. Please excuse my brevity.

I'd advocate a Swiss army knife like atM :: Applicative m => Int -> (Maybe a -> m (Maybe a)) -> Seq a -> m (Seq a) Then you can get your deleteLookup function by a suitable instance of the effect m. Nothing stands for "index does not point to any element", "Just a" means the index points to value a. On 2019-12-28 20:24, David Feuer wrote:
Data.Sequence offers
deleteAt :: Int -> Seq a -> Seq a
which deletes the element at the given index. Today, I ran into a situation where I wanted to know what was deleted.
deleteLookup :: Int -> Seq a -> Maybe (a, Seq a)
The closest thing I can find in `containers` is in Data.Map:
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a,Map k a)
Unfortunately, that function is ugly and strange. A better one, whose name I can't guess at the moment:
flabbergast :: (a -> (b, Maybe a)) -> Int -> Seq a -> Maybe (b, Seq a)
where a Nothing result means the index was out of bounds. There's also a potential
flabbergastF :: Functor f => (a -> f (Maybe a)) -> Int -> Seq a -> Maybe (f (Seq a))
I'm not sure if flabbergast can be made as fast as deleteLookup, so it's possible we may want both. Any opinions? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

That approach works great for maps and sets, but not so well for sequences.
If a sequence has ten elements, then you can't really insert a twentieth
one.
On Sat, Dec 28, 2019, 7:25 PM Andreas Abel
I'd advocate a Swiss army knife like
atM :: Applicative m => Int -> (Maybe a -> m (Maybe a)) -> Seq a -> m (Seq a)
Then you can get your deleteLookup function by a suitable instance of the effect m.
Nothing stands for "index does not point to any element", "Just a" means the index points to value a.
On 2019-12-28 20:24, David Feuer wrote:
Data.Sequence offers
deleteAt :: Int -> Seq a -> Seq a
which deletes the element at the given index. Today, I ran into a situation where I wanted to know what was deleted.
deleteLookup :: Int -> Seq a -> Maybe (a, Seq a)
The closest thing I can find in `containers` is in Data.Map:
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a,Map k a)
Unfortunately, that function is ugly and strange. A better one, whose name I can't guess at the moment:
flabbergast :: (a -> (b, Maybe a)) -> Int -> Seq a -> Maybe (b, Seq a)
where a Nothing result means the index was out of bounds. There's also a potential
flabbergastF :: Functor f => (a -> f (Maybe a)) -> Int -> Seq a -> Maybe (f (Seq a))
I'm not sure if flabbergast can be made as fast as deleteLookup, so it's possible we may want both. Any opinions? _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (4)
-
Andreas Abel
-
David Feuer
-
Keith
-
Zemyla