{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
module Ouroboros.Network.AnchoredSeq
(
AnchoredSeq (Empty, (:>), (:<))
, Anchorable (..)
, anchor
, head
, headAnchor
, last
, toNewestFirst
, toOldestFirst
, fromNewestFirst
, fromOldestFirst
, splitAt
, dropNewest
, takeOldest
, dropWhileNewest
, takeWhileOldest
, length
, null
, contains
, withinBounds
, map
, bimap
, mapPreservingMeasure
, bimapPreservingMeasure
, rollback
, isPrefixOf
, isPrefixOfByMeasure
, lookupByMeasure
, splitAfterMeasure
, splitBeforeMeasure
, join
, anchorNewest
, selectOffsets
, filter
, filterWithStop
, prettyPrint
, filterWithStopSpec
) where
import Prelude hiding (filter, head, last, length, map, null, splitAt)
import Data.Coerce (coerce)
import Data.FingerTree.Strict (Measured (measure), StrictFingerTree)
import qualified Data.FingerTree.Strict as FT
import qualified Data.Foldable as Foldable
import qualified Data.List as L
import Data.Maybe (fromMaybe)
import Data.Proxy (Proxy (..))
import Data.Word (Word64)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks)
data AnchoredSeq v a b = AnchoredSeq {
AnchoredSeq v a b -> a
anchor :: !a
, AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
unanchorSeq :: !(StrictFingerTree (Measure v) (MeasuredWith v a b))
}
deriving (Int -> AnchoredSeq v a b -> ShowS
[AnchoredSeq v a b] -> ShowS
AnchoredSeq v a b -> String
(Int -> AnchoredSeq v a b -> ShowS)
-> (AnchoredSeq v a b -> String)
-> ([AnchoredSeq v a b] -> ShowS)
-> Show (AnchoredSeq v a b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall v a b. (Show a, Show b) => Int -> AnchoredSeq v a b -> ShowS
forall v a b. (Show a, Show b) => [AnchoredSeq v a b] -> ShowS
forall v a b. (Show a, Show b) => AnchoredSeq v a b -> String
showList :: [AnchoredSeq v a b] -> ShowS
$cshowList :: forall v a b. (Show a, Show b) => [AnchoredSeq v a b] -> ShowS
show :: AnchoredSeq v a b -> String
$cshow :: forall v a b. (Show a, Show b) => AnchoredSeq v a b -> String
showsPrec :: Int -> AnchoredSeq v a b -> ShowS
$cshowsPrec :: forall v a b. (Show a, Show b) => Int -> AnchoredSeq v a b -> ShowS
Show, AnchoredSeq v a b -> AnchoredSeq v a b -> Bool
(AnchoredSeq v a b -> AnchoredSeq v a b -> Bool)
-> (AnchoredSeq v a b -> AnchoredSeq v a b -> Bool)
-> Eq (AnchoredSeq v a b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall v a b.
(Eq a, Eq b) =>
AnchoredSeq v a b -> AnchoredSeq v a b -> Bool
/= :: AnchoredSeq v a b -> AnchoredSeq v a b -> Bool
$c/= :: forall v a b.
(Eq a, Eq b) =>
AnchoredSeq v a b -> AnchoredSeq v a b -> Bool
== :: AnchoredSeq v a b -> AnchoredSeq v a b -> Bool
$c== :: forall v a b.
(Eq a, Eq b) =>
AnchoredSeq v a b -> AnchoredSeq v a b -> Bool
Eq, (forall x. AnchoredSeq v a b -> Rep (AnchoredSeq v a b) x)
-> (forall x. Rep (AnchoredSeq v a b) x -> AnchoredSeq v a b)
-> Generic (AnchoredSeq v a b)
forall x. Rep (AnchoredSeq v a b) x -> AnchoredSeq v a b
forall x. AnchoredSeq v a b -> Rep (AnchoredSeq v a b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v a b x. Rep (AnchoredSeq v a b) x -> AnchoredSeq v a b
forall v a b x. AnchoredSeq v a b -> Rep (AnchoredSeq v a b) x
$cto :: forall v a b x. Rep (AnchoredSeq v a b) x -> AnchoredSeq v a b
$cfrom :: forall v a b x. AnchoredSeq v a b -> Rep (AnchoredSeq v a b) x
Generic, Context -> AnchoredSeq v a b -> IO (Maybe ThunkInfo)
Proxy (AnchoredSeq v a b) -> String
(Context -> AnchoredSeq v a b -> IO (Maybe ThunkInfo))
-> (Context -> AnchoredSeq v a b -> IO (Maybe ThunkInfo))
-> (Proxy (AnchoredSeq v a b) -> String)
-> NoThunks (AnchoredSeq v a b)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall v a b.
(NoThunks a, NoThunks b) =>
Context -> AnchoredSeq v a b -> IO (Maybe ThunkInfo)
forall v a b.
(NoThunks a, NoThunks b) =>
Proxy (AnchoredSeq v a b) -> String
showTypeOf :: Proxy (AnchoredSeq v a b) -> String
$cshowTypeOf :: forall v a b.
(NoThunks a, NoThunks b) =>
Proxy (AnchoredSeq v a b) -> String
wNoThunks :: Context -> AnchoredSeq v a b -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall v a b.
(NoThunks a, NoThunks b) =>
Context -> AnchoredSeq v a b -> IO (Maybe ThunkInfo)
noThunks :: Context -> AnchoredSeq v a b -> IO (Maybe ThunkInfo)
$cnoThunks :: forall v a b.
(NoThunks a, NoThunks b) =>
Context -> AnchoredSeq v a b -> IO (Maybe ThunkInfo)
NoThunks)
class (Ord v, Bounded v) => Anchorable v a b | a -> v where
asAnchor :: b -> a
getAnchorMeasure :: Proxy b -> a -> v
getElementMeasure :: forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure :: MeasuredWith v a b -> v
getElementMeasure (MeasuredWith b
x) =
Proxy b -> a -> v
forall v a b. Anchorable v a b => Proxy b -> a -> v
getAnchorMeasure @v @a (Proxy b
forall k (t :: k). Proxy t
Proxy @b) (a -> v) -> a -> v
forall a b. (a -> b) -> a -> b
$ b -> a
forall v a b. Anchorable v a b => b -> a
asAnchor b
x
data Measure v = Measure {
Measure v -> v
measureMin :: !v
, Measure v -> v
measureMax :: !v
, Measure v -> Int
measureSize :: !Int
}
deriving (Int -> Measure v -> ShowS
[Measure v] -> ShowS
Measure v -> String
(Int -> Measure v -> ShowS)
-> (Measure v -> String)
-> ([Measure v] -> ShowS)
-> Show (Measure v)
forall v. Show v => Int -> Measure v -> ShowS
forall v. Show v => [Measure v] -> ShowS
forall v. Show v => Measure v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Measure v] -> ShowS
$cshowList :: forall v. Show v => [Measure v] -> ShowS
show :: Measure v -> String
$cshow :: forall v. Show v => Measure v -> String
showsPrec :: Int -> Measure v -> ShowS
$cshowsPrec :: forall v. Show v => Int -> Measure v -> ShowS
Show)
newtype MeasuredWith v a b = MeasuredWith {
MeasuredWith v a b -> b
unMeasuredWith :: b
}
deriving (Int -> MeasuredWith v a b -> ShowS
[MeasuredWith v a b] -> ShowS
MeasuredWith v a b -> String
(Int -> MeasuredWith v a b -> ShowS)
-> (MeasuredWith v a b -> String)
-> ([MeasuredWith v a b] -> ShowS)
-> Show (MeasuredWith v a b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall v a b. Show b => Int -> MeasuredWith v a b -> ShowS
forall v a b. Show b => [MeasuredWith v a b] -> ShowS
forall v a b. Show b => MeasuredWith v a b -> String
showList :: [MeasuredWith v a b] -> ShowS
$cshowList :: forall v a b. Show b => [MeasuredWith v a b] -> ShowS
show :: MeasuredWith v a b -> String
$cshow :: forall v a b. Show b => MeasuredWith v a b -> String
showsPrec :: Int -> MeasuredWith v a b -> ShowS
$cshowsPrec :: forall v a b. Show b => Int -> MeasuredWith v a b -> ShowS
Show, MeasuredWith v a b -> MeasuredWith v a b -> Bool
(MeasuredWith v a b -> MeasuredWith v a b -> Bool)
-> (MeasuredWith v a b -> MeasuredWith v a b -> Bool)
-> Eq (MeasuredWith v a b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall v a b.
Eq b =>
MeasuredWith v a b -> MeasuredWith v a b -> Bool
/= :: MeasuredWith v a b -> MeasuredWith v a b -> Bool
$c/= :: forall v a b.
Eq b =>
MeasuredWith v a b -> MeasuredWith v a b -> Bool
== :: MeasuredWith v a b -> MeasuredWith v a b -> Bool
$c== :: forall v a b.
Eq b =>
MeasuredWith v a b -> MeasuredWith v a b -> Bool
Eq, (forall x. MeasuredWith v a b -> Rep (MeasuredWith v a b) x)
-> (forall x. Rep (MeasuredWith v a b) x -> MeasuredWith v a b)
-> Generic (MeasuredWith v a b)
forall x. Rep (MeasuredWith v a b) x -> MeasuredWith v a b
forall x. MeasuredWith v a b -> Rep (MeasuredWith v a b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v a b x. Rep (MeasuredWith v a b) x -> MeasuredWith v a b
forall v a b x. MeasuredWith v a b -> Rep (MeasuredWith v a b) x
$cto :: forall v a b x. Rep (MeasuredWith v a b) x -> MeasuredWith v a b
$cfrom :: forall v a b x. MeasuredWith v a b -> Rep (MeasuredWith v a b) x
Generic, Context -> MeasuredWith v a b -> IO (Maybe ThunkInfo)
Proxy (MeasuredWith v a b) -> String
(Context -> MeasuredWith v a b -> IO (Maybe ThunkInfo))
-> (Context -> MeasuredWith v a b -> IO (Maybe ThunkInfo))
-> (Proxy (MeasuredWith v a b) -> String)
-> NoThunks (MeasuredWith v a b)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall v a b.
NoThunks b =>
Context -> MeasuredWith v a b -> IO (Maybe ThunkInfo)
forall v a b. NoThunks b => Proxy (MeasuredWith v a b) -> String
showTypeOf :: Proxy (MeasuredWith v a b) -> String
$cshowTypeOf :: forall v a b. NoThunks b => Proxy (MeasuredWith v a b) -> String
wNoThunks :: Context -> MeasuredWith v a b -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall v a b.
NoThunks b =>
Context -> MeasuredWith v a b -> IO (Maybe ThunkInfo)
noThunks :: Context -> MeasuredWith v a b -> IO (Maybe ThunkInfo)
$cnoThunks :: forall v a b.
NoThunks b =>
Context -> MeasuredWith v a b -> IO (Maybe ThunkInfo)
NoThunks)
instance Anchorable v a b => Measured (Measure v) (MeasuredWith v a b) where
measure :: MeasuredWith v a b -> Measure v
measure MeasuredWith v a b
x = Measure :: forall v. v -> v -> Int -> Measure v
Measure {
measureMin :: v
measureMin = v
m
, measureMax :: v
measureMax = v
m
, measureSize :: Int
measureSize = Int
1
}
where
m :: v
m :: v
m = MeasuredWith v a b -> v
forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure MeasuredWith v a b
x
instance Ord v => Semigroup (Measure v) where
Measure v
v1 <> :: Measure v -> Measure v -> Measure v
<> Measure v
v2 = Measure :: forall v. v -> v -> Int -> Measure v
Measure {
measureMin :: v
measureMin = Measure v -> v
forall v. Measure v -> v
measureMin Measure v
v1 v -> v -> v
forall a. Ord a => a -> a -> a
`min` Measure v -> v
forall v. Measure v -> v
measureMin Measure v
v2
, measureMax :: v
measureMax = Measure v -> v
forall v. Measure v -> v
measureMax Measure v
v1 v -> v -> v
forall a. Ord a => a -> a -> a
`max` Measure v -> v
forall v. Measure v -> v
measureMax Measure v
v2
, measureSize :: Int
measureSize = Measure v -> Int
forall v. Measure v -> Int
measureSize Measure v
v1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Measure v -> Int
forall v. Measure v -> Int
measureSize Measure v
v2
}
instance (Ord v, Bounded v) => Monoid (Measure v) where
mempty :: Measure v
mempty = v -> v -> Int -> Measure v
forall v. v -> v -> Int -> Measure v
Measure v
forall a. Bounded a => a
maxBound v
forall a. Bounded a => a
minBound Int
0
mappend :: Measure v -> Measure v -> Measure v
mappend = Measure v -> Measure v -> Measure v
forall a. Semigroup a => a -> a -> a
(<>)
pattern Empty :: Anchorable v a b => a -> AnchoredSeq v a b
pattern $bEmpty :: a -> AnchoredSeq v a b
$mEmpty :: forall r v a b.
Anchorable v a b =>
AnchoredSeq v a b -> (a -> r) -> (Void# -> r) -> r
Empty a <- (viewRight -> EmptyR a)
where
Empty a
a = a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a. Measured v a => StrictFingerTree v a
FT.empty
data ViewRight v a b
= EmptyR a
| ConsR (AnchoredSeq v a b) b
viewRight :: Anchorable v a b => AnchoredSeq v a b -> ViewRight v a b
viewRight :: AnchoredSeq v a b -> ViewRight v a b
viewRight (AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft) = case StrictFingerTree (Measure v) (MeasuredWith v a b)
-> ViewR (StrictFingerTree (Measure v)) (MeasuredWith v a b)
forall v a.
Measured v a =>
StrictFingerTree v a -> ViewR (StrictFingerTree v) a
FT.viewr StrictFingerTree (Measure v) (MeasuredWith v a b)
ft of
ViewR (StrictFingerTree (Measure v)) (MeasuredWith v a b)
FT.EmptyR -> a -> ViewRight v a b
forall v a b. a -> ViewRight v a b
EmptyR a
a
StrictFingerTree (Measure v) (MeasuredWith v a b)
ft' FT.:> MeasuredWith b
b -> AnchoredSeq v a b -> b -> ViewRight v a b
forall v a b. AnchoredSeq v a b -> b -> ViewRight v a b
ConsR (a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft') b
b
pattern (:>) :: Anchorable v a b => AnchoredSeq v a b -> b -> AnchoredSeq v a b
pattern s' $b:> :: AnchoredSeq v a b -> b -> AnchoredSeq v a b
$m:> :: forall r v a b.
Anchorable v a b =>
AnchoredSeq v a b
-> (AnchoredSeq v a b -> b -> r) -> (Void# -> r) -> r
:> b <- (viewRight -> ConsR s' b)
where
AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft :> b
b = a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a (StrictFingerTree (Measure v) (MeasuredWith v a b)
ft StrictFingerTree (Measure v) (MeasuredWith v a b)
-> MeasuredWith v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a.
Measured v a =>
StrictFingerTree v a -> a -> StrictFingerTree v a
FT.|> b -> MeasuredWith v a b
forall v a b. b -> MeasuredWith v a b
MeasuredWith b
b)
data ViewLeft v a b
= EmptyL a
| ConsL b (AnchoredSeq v a b)
viewLeft ::
forall v a b. Anchorable v a b
=> AnchoredSeq v a b
-> ViewLeft v a b
viewLeft :: AnchoredSeq v a b -> ViewLeft v a b
viewLeft (AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft) = case StrictFingerTree (Measure v) (MeasuredWith v a b)
-> ViewL (StrictFingerTree (Measure v)) (MeasuredWith v a b)
forall v a.
Measured v a =>
StrictFingerTree v a -> ViewL (StrictFingerTree v) a
FT.viewl StrictFingerTree (Measure v) (MeasuredWith v a b)
ft of
ViewL (StrictFingerTree (Measure v)) (MeasuredWith v a b)
FT.EmptyL ->
a -> ViewLeft v a b
forall v a b. a -> ViewLeft v a b
EmptyL a
a
MeasuredWith b
b FT.:< StrictFingerTree (Measure v) (MeasuredWith v a b)
ft' ->
b -> AnchoredSeq v a b -> ViewLeft v a b
forall v a b. b -> AnchoredSeq v a b -> ViewLeft v a b
ConsL b
b (a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq (b -> a
forall v a b. Anchorable v a b => b -> a
asAnchor b
b) StrictFingerTree (Measure v) (MeasuredWith v a b)
ft')
pattern (:<) :: Anchorable v a b => b -> AnchoredSeq v a b -> AnchoredSeq v a b
pattern b $m:< :: forall r v a b.
Anchorable v a b =>
AnchoredSeq v a b
-> (b -> AnchoredSeq v a b -> r) -> (Void# -> r) -> r
:< s' <- (viewLeft -> ConsL b s')
infixl 5 :>, :<
{-# COMPLETE Empty, (:>) #-}
{-# COMPLETE Empty, (:<) #-}
prettyPrint ::
String
-> (a -> String)
-> (b -> String)
-> AnchoredSeq v a b
-> String
prettyPrint :: String
-> (a -> String) -> (b -> String) -> AnchoredSeq v a b -> String
prettyPrint String
nl a -> String
ppA b -> String
ppB (AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft) =
(String -> MeasuredWith v a b -> String)
-> String
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> String
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl'
(\String
s (MeasuredWith b
b) -> String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
nl String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ b -> String
ppB b
b)
(String
"AnchoredSeq (" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
ppA a
a String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"):")
StrictFingerTree (Measure v) (MeasuredWith v a b)
ft
anchorMeasure :: forall v a b. Anchorable v a b => AnchoredSeq v a b -> v
anchorMeasure :: AnchoredSeq v a b -> v
anchorMeasure = Proxy b -> a -> v
forall v a b. Anchorable v a b => Proxy b -> a -> v
getAnchorMeasure (Proxy b
forall k (t :: k). Proxy t
Proxy @b) (a -> v) -> (AnchoredSeq v a b -> a) -> AnchoredSeq v a b -> v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredSeq v a b -> a
forall v a b. AnchoredSeq v a b -> a
anchor
head :: Anchorable v a b => AnchoredSeq v a b -> Either a b
head :: AnchoredSeq v a b -> Either a b
head (AnchoredSeq v a b
_ :> b
b) = b -> Either a b
forall a b. b -> Either a b
Right b
b
head (Empty a
a) = a -> Either a b
forall a b. a -> Either a b
Left a
a
headAnchor :: forall v a b. Anchorable v a b => AnchoredSeq v a b -> a
headAnchor :: AnchoredSeq v a b -> a
headAnchor = (a -> a) -> (b -> a) -> Either a b -> a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> a
forall a. a -> a
id b -> a
forall v a b. Anchorable v a b => b -> a
asAnchor (Either a b -> a)
-> (AnchoredSeq v a b -> Either a b) -> AnchoredSeq v a b -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredSeq v a b -> Either a b
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Either a b
head
last :: Anchorable v a b => AnchoredSeq v a b -> Either a b
last :: AnchoredSeq v a b -> Either a b
last (b
b :< AnchoredSeq v a b
_) = b -> Either a b
forall a b. b -> Either a b
Right b
b
last (Empty a
a) = a -> Either a b
forall a b. a -> Either a b
Left a
a
toNewestFirst :: AnchoredSeq v a b -> [b]
toNewestFirst :: AnchoredSeq v a b -> [b]
toNewestFirst = [MeasuredWith v a b] -> [b]
coerce ([MeasuredWith v a b] -> [b])
-> (AnchoredSeq v a b -> [MeasuredWith v a b])
-> AnchoredSeq v a b
-> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([MeasuredWith v a b]
-> MeasuredWith v a b -> [MeasuredWith v a b])
-> [MeasuredWith v a b]
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> [MeasuredWith v a b]
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl' ((MeasuredWith v a b
-> [MeasuredWith v a b] -> [MeasuredWith v a b])
-> [MeasuredWith v a b]
-> MeasuredWith v a b
-> [MeasuredWith v a b]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (:)) [] (StrictFingerTree (Measure v) (MeasuredWith v a b)
-> [MeasuredWith v a b])
-> (AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b))
-> AnchoredSeq v a b
-> [MeasuredWith v a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a b.
AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
unanchorSeq
toOldestFirst :: AnchoredSeq v a b -> [b]
toOldestFirst :: AnchoredSeq v a b -> [b]
toOldestFirst = [MeasuredWith v a b] -> [b]
coerce ([MeasuredWith v a b] -> [b])
-> (AnchoredSeq v a b -> [MeasuredWith v a b])
-> AnchoredSeq v a b
-> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictFingerTree (Measure v) (MeasuredWith v a b)
-> [MeasuredWith v a b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList (StrictFingerTree (Measure v) (MeasuredWith v a b)
-> [MeasuredWith v a b])
-> (AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b))
-> AnchoredSeq v a b
-> [MeasuredWith v a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a b.
AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
unanchorSeq
fromNewestFirst :: Anchorable v a b => a -> [b] -> AnchoredSeq v a b
fromNewestFirst :: a -> [b] -> AnchoredSeq v a b
fromNewestFirst a
a = (b -> AnchoredSeq v a b -> AnchoredSeq v a b)
-> AnchoredSeq v a b -> [b] -> AnchoredSeq v a b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((AnchoredSeq v a b -> b -> AnchoredSeq v a b)
-> b -> AnchoredSeq v a b -> AnchoredSeq v a b
forall a b c. (a -> b -> c) -> b -> a -> c
flip AnchoredSeq v a b -> b -> AnchoredSeq v a b
forall v a b.
Anchorable v a b =>
AnchoredSeq v a b -> b -> AnchoredSeq v a b
(:>)) (a -> AnchoredSeq v a b
forall v a b. Anchorable v a b => a -> AnchoredSeq v a b
Empty a
a)
fromOldestFirst :: Anchorable v a b => a -> [b] -> AnchoredSeq v a b
fromOldestFirst :: a -> [b] -> AnchoredSeq v a b
fromOldestFirst a
a = a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a (StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b)
-> ([b] -> StrictFingerTree (Measure v) (MeasuredWith v a b))
-> [b]
-> AnchoredSeq v a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [MeasuredWith v a b]
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a. Measured v a => [a] -> StrictFingerTree v a
FT.fromList ([MeasuredWith v a b]
-> StrictFingerTree (Measure v) (MeasuredWith v a b))
-> ([b] -> [MeasuredWith v a b])
-> [b]
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [b] -> [MeasuredWith v a b]
coerce
splitAt ::
Anchorable v a b
=> Int
-> AnchoredSeq v a b
-> (AnchoredSeq v a b, AnchoredSeq v a b)
splitAt :: Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
splitAt Int
i (AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft) = case (Measure v -> Bool)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> (StrictFingerTree (Measure v) (MeasuredWith v a b),
StrictFingerTree (Measure v) (MeasuredWith v a b))
forall v a.
Measured v a =>
(v -> Bool)
-> StrictFingerTree v a
-> (StrictFingerTree v a, StrictFingerTree v a)
FT.split (\Measure v
v -> Measure v -> Int
forall v. Measure v -> Int
measureSize Measure v
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
i) StrictFingerTree (Measure v) (MeasuredWith v a b)
ft of
(StrictFingerTree (Measure v) (MeasuredWith v a b)
before, StrictFingerTree (Measure v) (MeasuredWith v a b)
after) ->
let before' :: AnchoredSeq v a b
before' = a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
before
in (AnchoredSeq v a b
before', a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq (AnchoredSeq v a b -> a
forall v a b. Anchorable v a b => AnchoredSeq v a b -> a
headAnchor AnchoredSeq v a b
before') StrictFingerTree (Measure v) (MeasuredWith v a b)
after)
dropNewest :: Anchorable v a b => Int -> AnchoredSeq v a b -> AnchoredSeq v a b
dropNewest :: Int -> AnchoredSeq v a b -> AnchoredSeq v a b
dropNewest Int
n s :: AnchoredSeq v a b
s@(AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft)
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
= AnchoredSeq v a b
s
| Bool
otherwise
= a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a (StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall a b. (a -> b) -> a -> b
$ (Measure v -> Bool)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a.
Measured v a =>
(v -> Bool) -> StrictFingerTree v a -> StrictFingerTree v a
FT.takeUntil (\Measure v
v -> Measure v -> Int
forall v. Measure v -> Int
measureSize Measure v
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
remainingLength) StrictFingerTree (Measure v) (MeasuredWith v a b)
ft
where
remainingLength :: Int
remainingLength = AnchoredSeq v a b -> Int
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Int
length AnchoredSeq v a b
s Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n
takeOldest :: Anchorable v a b => Int -> AnchoredSeq v a b -> AnchoredSeq v a b
takeOldest :: Int -> AnchoredSeq v a b -> AnchoredSeq v a b
takeOldest Int
n s :: AnchoredSeq v a b
s@(AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft)
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredSeq v a b -> Int
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Int
length AnchoredSeq v a b
s
= AnchoredSeq v a b
s
| Bool
otherwise
= a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a (StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall a b. (a -> b) -> a -> b
$ (Measure v -> Bool)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a.
Measured v a =>
(v -> Bool) -> StrictFingerTree v a -> StrictFingerTree v a
FT.takeUntil (\Measure v
v -> Measure v -> Int
forall v. Measure v -> Int
measureSize Measure v
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n) StrictFingerTree (Measure v) (MeasuredWith v a b)
ft
dropWhileNewest ::
Anchorable v a b
=> (b -> Bool)
-> AnchoredSeq v a b
-> AnchoredSeq v a b
dropWhileNewest :: (b -> Bool) -> AnchoredSeq v a b -> AnchoredSeq v a b
dropWhileNewest b -> Bool
_ (Empty a
a) = a -> AnchoredSeq v a b
forall v a b. Anchorable v a b => a -> AnchoredSeq v a b
Empty a
a
dropWhileNewest b -> Bool
p s :: AnchoredSeq v a b
s@(AnchoredSeq v a b
s' :> b
b)
| b -> Bool
p b
b = (b -> Bool) -> AnchoredSeq v a b -> AnchoredSeq v a b
forall v a b.
Anchorable v a b =>
(b -> Bool) -> AnchoredSeq v a b -> AnchoredSeq v a b
dropWhileNewest b -> Bool
p AnchoredSeq v a b
s'
| Bool
otherwise = AnchoredSeq v a b
s
takeWhileOldest ::
Anchorable v a b
=> (b -> Bool)
-> AnchoredSeq v a b
-> AnchoredSeq v a b
takeWhileOldest :: (b -> Bool) -> AnchoredSeq v a b -> AnchoredSeq v a b
takeWhileOldest b -> Bool
p = \(AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft) -> a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a (StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a v a.
(Anchorable v a b, Anchorable v a b) =>
StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
go StrictFingerTree (Measure v) (MeasuredWith v a b)
ft)
where
go :: StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
go StrictFingerTree (Measure v) (MeasuredWith v a b)
ft = case StrictFingerTree (Measure v) (MeasuredWith v a b)
-> ViewL (StrictFingerTree (Measure v)) (MeasuredWith v a b)
forall v a.
Measured v a =>
StrictFingerTree v a -> ViewL (StrictFingerTree v) a
FT.viewl StrictFingerTree (Measure v) (MeasuredWith v a b)
ft of
ViewL (StrictFingerTree (Measure v)) (MeasuredWith v a b)
FT.EmptyL
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a. Measured v a => StrictFingerTree v a
FT.empty
MeasuredWith b
b FT.:< StrictFingerTree (Measure v) (MeasuredWith v a b)
ft'
| b -> Bool
p b
b
-> b -> MeasuredWith v a b
forall v a b. b -> MeasuredWith v a b
MeasuredWith b
b MeasuredWith v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a.
Measured v a =>
a -> StrictFingerTree v a -> StrictFingerTree v a
FT.<| StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
go StrictFingerTree (Measure v) (MeasuredWith v a b)
ft'
| Bool
otherwise
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a. Measured v a => StrictFingerTree v a
FT.empty
length :: Anchorable v a b => AnchoredSeq v a b -> Int
length :: AnchoredSeq v a b -> Int
length = Measure v -> Int
forall v. Measure v -> Int
measureSize (Measure v -> Int)
-> (AnchoredSeq v a b -> Measure v) -> AnchoredSeq v a b -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictFingerTree (Measure v) (MeasuredWith v a b) -> Measure v
forall v a. Measured v a => a -> v
FT.measure (StrictFingerTree (Measure v) (MeasuredWith v a b) -> Measure v)
-> (AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b))
-> AnchoredSeq v a b
-> Measure v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a b.
AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
unanchorSeq
null :: AnchoredSeq v a b -> Bool
null :: AnchoredSeq v a b -> Bool
null = StrictFingerTree (Measure v) (MeasuredWith v a b) -> Bool
forall v a. StrictFingerTree v a -> Bool
FT.null (StrictFingerTree (Measure v) (MeasuredWith v a b) -> Bool)
-> (AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b))
-> AnchoredSeq v a b
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a b.
AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
unanchorSeq
rollback ::
Anchorable v a b
=> v
-> (Either a b -> Bool)
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b)
rollback :: v
-> (Either a b -> Bool)
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b)
rollback v
k Either a b -> Bool
p AnchoredSeq v a b
s
| AnchoredSeq v a b -> v
forall v a b. Anchorable v a b => AnchoredSeq v a b -> v
anchorMeasure AnchoredSeq v a b
s v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
k, Either a b -> Bool
p (a -> Either a b
forall a b. a -> Either a b
Left (AnchoredSeq v a b -> a
forall v a b. AnchoredSeq v a b -> a
anchor AnchoredSeq v a b
s))
= AnchoredSeq v a b -> Maybe (AnchoredSeq v a b)
forall a. a -> Maybe a
Just (a -> AnchoredSeq v a b
forall v a b. Anchorable v a b => a -> AnchoredSeq v a b
Empty (AnchoredSeq v a b -> a
forall v a b. AnchoredSeq v a b -> a
anchor AnchoredSeq v a b
s))
| Bool
otherwise
= (AnchoredSeq v a b, AnchoredSeq v a b) -> AnchoredSeq v a b
forall a b. (a, b) -> a
fst ((AnchoredSeq v a b, AnchoredSeq v a b) -> AnchoredSeq v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
-> Maybe (AnchoredSeq v a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v
-> (Either a b -> Bool)
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
forall v a b.
Anchorable v a b =>
v
-> (Either a b -> Bool)
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
splitAfterMeasure v
k Either a b -> Bool
p AnchoredSeq v a b
s
lookupByMeasureFT ::
Anchorable v a b
=> v
-> AnchoredSeq v a b
-> FT.SearchResult (Measure v) (MeasuredWith v a b)
lookupByMeasureFT :: v
-> AnchoredSeq v a b
-> SearchResult (Measure v) (MeasuredWith v a b)
lookupByMeasureFT v
k (AnchoredSeq a
_ StrictFingerTree (Measure v) (MeasuredWith v a b)
ft) =
(Measure v -> Measure v -> Bool)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> SearchResult (Measure v) (MeasuredWith v a b)
forall v a.
Measured v a =>
(v -> v -> Bool) -> StrictFingerTree v a -> SearchResult v a
FT.search (\Measure v
ml Measure v
mr -> Measure v -> v
forall v. Measure v -> v
measureMax Measure v
ml v -> v -> Bool
forall a. Ord a => a -> a -> Bool
>= v
k Bool -> Bool -> Bool
&& Measure v -> v
forall v. Measure v -> v
measureMin Measure v
mr v -> v -> Bool
forall a. Ord a => a -> a -> Bool
> v
k) StrictFingerTree (Measure v) (MeasuredWith v a b)
ft
lookupByMeasure ::
Anchorable v a b
=> v
-> AnchoredSeq v a b
-> [b]
lookupByMeasure :: v -> AnchoredSeq v a b -> [b]
lookupByMeasure v
k AnchoredSeq v a b
s = case v
-> AnchoredSeq v a b
-> SearchResult (Measure v) (MeasuredWith v a b)
forall v a b.
Anchorable v a b =>
v
-> AnchoredSeq v a b
-> SearchResult (Measure v) (MeasuredWith v a b)
lookupByMeasureFT v
k AnchoredSeq v a b
s of
FT.Position StrictFingerTree (Measure v) (MeasuredWith v a b)
before MeasuredWith v a b
b StrictFingerTree (Measure v) (MeasuredWith v a b)
_after
| MeasuredWith v a b -> v
forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure MeasuredWith v a b
b v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
k
-> StrictFingerTree (Measure v) (MeasuredWith v a b) -> [b] -> [b]
forall a a.
Anchorable v a a =>
StrictFingerTree (Measure v) (MeasuredWith v a a) -> [a] -> [a]
elementsBefore StrictFingerTree (Measure v) (MeasuredWith v a b)
before [MeasuredWith v a b -> b
forall v a b. MeasuredWith v a b -> b
unMeasuredWith MeasuredWith v a b
b]
SearchResult (Measure v) (MeasuredWith v a b)
_ -> []
where
elementsBefore :: StrictFingerTree (Measure v) (MeasuredWith v a a) -> [a] -> [a]
elementsBefore StrictFingerTree (Measure v) (MeasuredWith v a a)
before [a]
acc = case StrictFingerTree (Measure v) (MeasuredWith v a a)
-> ViewR (StrictFingerTree (Measure v)) (MeasuredWith v a a)
forall v a.
Measured v a =>
StrictFingerTree v a -> ViewR (StrictFingerTree v) a
FT.viewr StrictFingerTree (Measure v) (MeasuredWith v a a)
before of
StrictFingerTree (Measure v) (MeasuredWith v a a)
before' FT.:> MeasuredWith v a a
b
| MeasuredWith v a a -> v
forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure MeasuredWith v a a
b v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
k
-> StrictFingerTree (Measure v) (MeasuredWith v a a) -> [a] -> [a]
elementsBefore StrictFingerTree (Measure v) (MeasuredWith v a a)
before' (MeasuredWith v a a -> a
forall v a b. MeasuredWith v a b -> b
unMeasuredWith MeasuredWith v a a
ba -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
acc)
ViewR (StrictFingerTree (Measure v)) (MeasuredWith v a a)
_ -> [a]
acc
contains :: Anchorable v a b => v -> (b -> Bool) -> AnchoredSeq v a b -> Bool
contains :: v -> (b -> Bool) -> AnchoredSeq v a b -> Bool
contains v
k b -> Bool
p AnchoredSeq v a b
s = (b -> Bool) -> [b] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any b -> Bool
p ([b] -> Bool) -> [b] -> Bool
forall a b. (a -> b) -> a -> b
$ v -> AnchoredSeq v a b -> [b]
forall v a b. Anchorable v a b => v -> AnchoredSeq v a b -> [b]
lookupByMeasure v
k AnchoredSeq v a b
s
withinBounds ::
Anchorable v a b
=> v
-> (Either a b -> Bool)
-> AnchoredSeq v a b
-> Bool
withinBounds :: v -> (Either a b -> Bool) -> AnchoredSeq v a b -> Bool
withinBounds v
k Either a b -> Bool
p AnchoredSeq v a b
s =
(v
k v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredSeq v a b -> v
forall v a b. Anchorable v a b => AnchoredSeq v a b -> v
anchorMeasure AnchoredSeq v a b
s Bool -> Bool -> Bool
&& Either a b -> Bool
p (a -> Either a b
forall a b. a -> Either a b
Left (AnchoredSeq v a b -> a
forall v a b. AnchoredSeq v a b -> a
anchor AnchoredSeq v a b
s)))
Bool -> Bool -> Bool
|| v -> (b -> Bool) -> AnchoredSeq v a b -> Bool
forall v a b.
Anchorable v a b =>
v -> (b -> Bool) -> AnchoredSeq v a b -> Bool
contains v
k (Either a b -> Bool
p (Either a b -> Bool) -> (b -> Either a b) -> b -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Either a b
forall a b. b -> Either a b
Right) AnchoredSeq v a b
s
map ::
Anchorable v2 a b2
=> (b1 -> b2)
-> AnchoredSeq v1 a b1
-> AnchoredSeq v2 a b2
map :: (b1 -> b2) -> AnchoredSeq v1 a b1 -> AnchoredSeq v2 a b2
map = (a -> a)
-> (b1 -> b2) -> AnchoredSeq v1 a b1 -> AnchoredSeq v2 a b2
forall v2 a2 b2 a1 b1 v1.
Anchorable v2 a2 b2 =>
(a1 -> a2)
-> (b1 -> b2) -> AnchoredSeq v1 a1 b1 -> AnchoredSeq v2 a2 b2
bimap a -> a
forall a. a -> a
id
bimap ::
Anchorable v2 a2 b2
=> (a1 -> a2)
-> (b1 -> b2)
-> AnchoredSeq v1 a1 b1
-> AnchoredSeq v2 a2 b2
bimap :: (a1 -> a2)
-> (b1 -> b2) -> AnchoredSeq v1 a1 b1 -> AnchoredSeq v2 a2 b2
bimap a1 -> a2
f b1 -> b2
g AnchoredSeq v1 a1 b1
s =
a2 -> [b2] -> AnchoredSeq v2 a2 b2
forall v a b. Anchorable v a b => a -> [b] -> AnchoredSeq v a b
fromOldestFirst (a1 -> a2
f (AnchoredSeq v1 a1 b1 -> a1
forall v a b. AnchoredSeq v a b -> a
anchor AnchoredSeq v1 a1 b1
s)) (b1 -> b2
g (b1 -> b2) -> [b1] -> [b2]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AnchoredSeq v1 a1 b1 -> [b1]
forall v a b. AnchoredSeq v a b -> [b]
toOldestFirst AnchoredSeq v1 a1 b1
s)
mapPreservingMeasure ::
(b1 -> b2)
-> AnchoredSeq v a b1
-> AnchoredSeq v a b2
mapPreservingMeasure :: (b1 -> b2) -> AnchoredSeq v a b1 -> AnchoredSeq v a b2
mapPreservingMeasure = (a -> a) -> (b1 -> b2) -> AnchoredSeq v a b1 -> AnchoredSeq v a b2
forall a1 a2 b1 b2 v.
(a1 -> a2)
-> (b1 -> b2) -> AnchoredSeq v a1 b1 -> AnchoredSeq v a2 b2
bimapPreservingMeasure a -> a
forall a. a -> a
id
bimapPreservingMeasure ::
(a1 -> a2)
-> (b1 -> b2)
-> AnchoredSeq v a1 b1
-> AnchoredSeq v a2 b2
bimapPreservingMeasure :: (a1 -> a2)
-> (b1 -> b2) -> AnchoredSeq v a1 b1 -> AnchoredSeq v a2 b2
bimapPreservingMeasure a1 -> a2
f b1 -> b2
g (AnchoredSeq a1
a StrictFingerTree (Measure v) (MeasuredWith v a1 b1)
ft) =
a2
-> StrictFingerTree (Measure v) (MeasuredWith v a2 b2)
-> AnchoredSeq v a2 b2
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq (a1 -> a2
f a1
a) ((MeasuredWith v a1 b1 -> MeasuredWith v a2 b2)
-> StrictFingerTree (Measure v) (MeasuredWith v a1 b1)
-> StrictFingerTree (Measure v) (MeasuredWith v a2 b2)
forall a b v.
(a -> b) -> StrictFingerTree v a -> StrictFingerTree v b
FT.unsafeFmap ((b1 -> b2) -> MeasuredWith v a1 b1 -> MeasuredWith v a2 b2
coerce b1 -> b2
g) StrictFingerTree (Measure v) (MeasuredWith v a1 b1)
ft)
anchorNewest ::
forall v a b. Anchorable v a b
=> Word64
-> AnchoredSeq v a b
-> AnchoredSeq v a b
anchorNewest :: Word64 -> AnchoredSeq v a b -> AnchoredSeq v a b
anchorNewest Word64
n AnchoredSeq v a b
c
| Int
toDrop Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
= AnchoredSeq v a b
c
| Int
toDrop Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
5
= Int -> AnchoredSeq v a b -> AnchoredSeq v a b
linearDrop Int
toDrop AnchoredSeq v a b
c
| Bool
otherwise
= (AnchoredSeq v a b, AnchoredSeq v a b) -> AnchoredSeq v a b
forall a b. (a, b) -> b
snd ((AnchoredSeq v a b, AnchoredSeq v a b) -> AnchoredSeq v a b)
-> (AnchoredSeq v a b, AnchoredSeq v a b) -> AnchoredSeq v a b
forall a b. (a -> b) -> a -> b
$ Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
forall v a b.
Anchorable v a b =>
Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
splitAt Int
toDrop AnchoredSeq v a b
c
where
len, toDrop :: Int
len :: Int
len = AnchoredSeq v a b -> Int
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Int
length AnchoredSeq v a b
c
toDrop :: Int
toDrop = Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
n
linearDrop :: Int -> AnchoredSeq v a b -> AnchoredSeq v a b
linearDrop :: Int -> AnchoredSeq v a b -> AnchoredSeq v a b
linearDrop !Int
_ (Empty a
a) = a -> AnchoredSeq v a b
forall v a b. Anchorable v a b => a -> AnchoredSeq v a b
Empty a
a
linearDrop !Int
0 AnchoredSeq v a b
c' = AnchoredSeq v a b
c'
linearDrop !Int
m (b
_ :< AnchoredSeq v a b
c') = Int -> AnchoredSeq v a b -> AnchoredSeq v a b
linearDrop (Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) AnchoredSeq v a b
c'
isPrefixOf ::
forall v a b. (Eq a, Eq b)
=> AnchoredSeq v a b
-> AnchoredSeq v a b
-> Bool
AnchoredSeq v a b
s1 isPrefixOf :: AnchoredSeq v a b -> AnchoredSeq v a b -> Bool
`isPrefixOf` AnchoredSeq v a b
s2 =
AnchoredSeq v a b -> a
forall v a b. AnchoredSeq v a b -> a
anchor AnchoredSeq v a b
s1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredSeq v a b -> a
forall v a b. AnchoredSeq v a b -> a
anchor AnchoredSeq v a b
s2
Bool -> Bool -> Bool
&& AnchoredSeq v a b -> [b]
toElements AnchoredSeq v a b
s1 [b] -> [b] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`L.isPrefixOf` AnchoredSeq v a b -> [b]
toElements AnchoredSeq v a b
s2
where
toElements :: AnchoredSeq v a b -> [b]
toElements :: AnchoredSeq v a b -> [b]
toElements = (MeasuredWith v a b -> b) -> [MeasuredWith v a b] -> [b]
forall a b. (a -> b) -> [a] -> [b]
L.map MeasuredWith v a b -> b
forall v a b. MeasuredWith v a b -> b
unMeasuredWith ([MeasuredWith v a b] -> [b])
-> (AnchoredSeq v a b -> [MeasuredWith v a b])
-> AnchoredSeq v a b
-> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictFingerTree (Measure v) (MeasuredWith v a b)
-> [MeasuredWith v a b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList (StrictFingerTree (Measure v) (MeasuredWith v a b)
-> [MeasuredWith v a b])
-> (AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b))
-> AnchoredSeq v a b
-> [MeasuredWith v a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a b.
AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
unanchorSeq
isPrefixOfByMeasure ::
forall v a b. Anchorable v a b
=> AnchoredSeq v a b
-> AnchoredSeq v a b
-> Bool
AnchoredSeq v a b
s1 isPrefixOfByMeasure :: AnchoredSeq v a b -> AnchoredSeq v a b -> Bool
`isPrefixOfByMeasure` AnchoredSeq v a b
s2 =
AnchoredSeq v a b -> v
forall v a b. Anchorable v a b => AnchoredSeq v a b -> v
anchorMeasure AnchoredSeq v a b
s1 v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredSeq v a b -> v
forall v a b. Anchorable v a b => AnchoredSeq v a b -> v
anchorMeasure AnchoredSeq v a b
s2
Bool -> Bool -> Bool
&& AnchoredSeq v a b -> [v]
toMeasures AnchoredSeq v a b
s1 [v] -> [v] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`L.isPrefixOf` AnchoredSeq v a b -> [v]
toMeasures AnchoredSeq v a b
s2
where
toMeasures :: AnchoredSeq v a b -> [v]
toMeasures :: AnchoredSeq v a b -> [v]
toMeasures = (MeasuredWith v a b -> v) -> [MeasuredWith v a b] -> [v]
forall a b. (a -> b) -> [a] -> [b]
L.map MeasuredWith v a b -> v
forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure ([MeasuredWith v a b] -> [v])
-> (AnchoredSeq v a b -> [MeasuredWith v a b])
-> AnchoredSeq v a b
-> [v]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictFingerTree (Measure v) (MeasuredWith v a b)
-> [MeasuredWith v a b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList (StrictFingerTree (Measure v) (MeasuredWith v a b)
-> [MeasuredWith v a b])
-> (AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b))
-> AnchoredSeq v a b
-> [MeasuredWith v a b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a b.
AnchoredSeq v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
unanchorSeq
splitAfterMeasure ::
Anchorable v a b
=> v
-> (Either a b -> Bool)
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
splitAfterMeasure :: v
-> (Either a b -> Bool)
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
splitAfterMeasure v
k Either a b -> Bool
p s :: AnchoredSeq v a b
s@(AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft)
| AnchoredSeq v a b -> v
forall v a b. Anchorable v a b => AnchoredSeq v a b -> v
anchorMeasure AnchoredSeq v a b
s v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
k, Either a b -> Bool
p (a -> Either a b
forall a b. a -> Either a b
Left a
a)
= (AnchoredSeq v a b, AnchoredSeq v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
forall a. a -> Maybe a
Just (a -> AnchoredSeq v a b
forall v a b. Anchorable v a b => a -> AnchoredSeq v a b
Empty a
a, AnchoredSeq v a b
s)
| (StrictFingerTree (Measure v) (MeasuredWith v a b)
l, StrictFingerTree (Measure v) (MeasuredWith v a b)
r) <- (Measure v -> Bool)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> (StrictFingerTree (Measure v) (MeasuredWith v a b),
StrictFingerTree (Measure v) (MeasuredWith v a b))
forall v a.
Measured v a =>
(v -> Bool)
-> StrictFingerTree v a
-> (StrictFingerTree v a, StrictFingerTree v a)
FT.split (\Measure v
v -> Measure v -> v
forall v. Measure v -> v
measureMax Measure v
v v -> v -> Bool
forall a. Ord a => a -> a -> Bool
> v
k) StrictFingerTree (Measure v) (MeasuredWith v a b)
ft
= StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
go StrictFingerTree (Measure v) (MeasuredWith v a b)
l StrictFingerTree (Measure v) (MeasuredWith v a b)
r
| Bool
otherwise
= Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
forall a. Maybe a
Nothing
where
go :: StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
go StrictFingerTree (Measure v) (MeasuredWith v a b)
l StrictFingerTree (Measure v) (MeasuredWith v a b)
r = case StrictFingerTree (Measure v) (MeasuredWith v a b)
-> ViewR (StrictFingerTree (Measure v)) (MeasuredWith v a b)
forall v a.
Measured v a =>
StrictFingerTree v a -> ViewR (StrictFingerTree v) a
FT.viewr StrictFingerTree (Measure v) (MeasuredWith v a b)
l of
StrictFingerTree (Measure v) (MeasuredWith v a b)
l' FT.:> m :: MeasuredWith v a b
m@(MeasuredWith b
b)
| MeasuredWith v a b -> v
forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure MeasuredWith v a b
m v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
k, Either a b -> Bool
p (b -> Either a b
forall a b. b -> Either a b
Right b
b)
, let al :: AnchoredSeq v a b
al = a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
l
-> (AnchoredSeq v a b, AnchoredSeq v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
forall a. a -> Maybe a
Just (AnchoredSeq v a b
al, a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq (AnchoredSeq v a b -> a
forall v a b. Anchorable v a b => AnchoredSeq v a b -> a
headAnchor AnchoredSeq v a b
al) StrictFingerTree (Measure v) (MeasuredWith v a b)
r)
| MeasuredWith v a b -> v
forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure MeasuredWith v a b
m v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
k
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
go StrictFingerTree (Measure v) (MeasuredWith v a b)
l' (MeasuredWith v a b
m MeasuredWith v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a.
Measured v a =>
a -> StrictFingerTree v a -> StrictFingerTree v a
FT.<| StrictFingerTree (Measure v) (MeasuredWith v a b)
r)
ViewR (StrictFingerTree (Measure v)) (MeasuredWith v a b)
_ -> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
forall a. Maybe a
Nothing
splitBeforeMeasure ::
Anchorable v a b
=> v
-> (b -> Bool)
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
splitBeforeMeasure :: v
-> (b -> Bool)
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
splitBeforeMeasure v
k b -> Bool
p (AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
ft)
| (StrictFingerTree (Measure v) (MeasuredWith v a b)
l, StrictFingerTree (Measure v) (MeasuredWith v a b)
r) <- (Measure v -> Bool)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> (StrictFingerTree (Measure v) (MeasuredWith v a b),
StrictFingerTree (Measure v) (MeasuredWith v a b))
forall v a.
Measured v a =>
(v -> Bool)
-> StrictFingerTree v a
-> (StrictFingerTree v a, StrictFingerTree v a)
FT.split (\Measure v
v -> Measure v -> v
forall v. Measure v -> v
measureMax Measure v
v v -> v -> Bool
forall a. Ord a => a -> a -> Bool
>= v
k) StrictFingerTree (Measure v) (MeasuredWith v a b)
ft
= StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
go StrictFingerTree (Measure v) (MeasuredWith v a b)
l StrictFingerTree (Measure v) (MeasuredWith v a b)
r
| Bool
otherwise
= Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
forall a. Maybe a
Nothing
where
go :: StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
go StrictFingerTree (Measure v) (MeasuredWith v a b)
l StrictFingerTree (Measure v) (MeasuredWith v a b)
r = case StrictFingerTree (Measure v) (MeasuredWith v a b)
-> ViewL (StrictFingerTree (Measure v)) (MeasuredWith v a b)
forall v a.
Measured v a =>
StrictFingerTree v a -> ViewL (StrictFingerTree v) a
FT.viewl StrictFingerTree (Measure v) (MeasuredWith v a b)
r of
m :: MeasuredWith v a b
m@(MeasuredWith b
b) FT.:< StrictFingerTree (Measure v) (MeasuredWith v a b)
r'
| MeasuredWith v a b -> v
forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure MeasuredWith v a b
m v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
k, b -> Bool
p b
b
, let al :: AnchoredSeq v a b
al = a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a StrictFingerTree (Measure v) (MeasuredWith v a b)
l
-> (AnchoredSeq v a b, AnchoredSeq v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
forall a. a -> Maybe a
Just (AnchoredSeq v a b
al, a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq (AnchoredSeq v a b -> a
forall v a b. Anchorable v a b => AnchoredSeq v a b -> a
headAnchor AnchoredSeq v a b
al) StrictFingerTree (Measure v) (MeasuredWith v a b)
r)
| MeasuredWith v a b -> v
forall v a b. Anchorable v a b => MeasuredWith v a b -> v
getElementMeasure MeasuredWith v a b
m v -> v -> Bool
forall a. Eq a => a -> a -> Bool
== v
k
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
go (StrictFingerTree (Measure v) (MeasuredWith v a b)
l StrictFingerTree (Measure v) (MeasuredWith v a b)
-> MeasuredWith v a b
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a.
Measured v a =>
StrictFingerTree v a -> a -> StrictFingerTree v a
FT.|> MeasuredWith v a b
m) StrictFingerTree (Measure v) (MeasuredWith v a b)
r'
ViewL (StrictFingerTree (Measure v)) (MeasuredWith v a b)
_ -> Maybe (AnchoredSeq v a b, AnchoredSeq v a b)
forall a. Maybe a
Nothing
join ::
forall v a b. Anchorable v a b
=> (Either a b -> a -> Bool)
-> AnchoredSeq v a b
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b)
join :: (Either a b -> a -> Bool)
-> AnchoredSeq v a b
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b)
join Either a b -> a -> Bool
f s1 :: AnchoredSeq v a b
s1@(AnchoredSeq a
a1 StrictFingerTree (Measure v) (MeasuredWith v a b)
ft1) (AnchoredSeq a
a2 StrictFingerTree (Measure v) (MeasuredWith v a b)
ft2)
| Either a b -> a -> Bool
f (AnchoredSeq v a b -> Either a b
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Either a b
head AnchoredSeq v a b
s1) a
a2
= AnchoredSeq v a b -> Maybe (AnchoredSeq v a b)
forall a. a -> Maybe a
Just (AnchoredSeq v a b -> Maybe (AnchoredSeq v a b))
-> AnchoredSeq v a b -> Maybe (AnchoredSeq v a b)
forall a b. (a -> b) -> a -> b
$ a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
forall v a b.
a
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> AnchoredSeq v a b
AnchoredSeq a
a1 (StrictFingerTree (Measure v) (MeasuredWith v a b)
ft1 StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
-> StrictFingerTree (Measure v) (MeasuredWith v a b)
forall v a.
Measured v a =>
StrictFingerTree v a
-> StrictFingerTree v a -> StrictFingerTree v a
FT.>< StrictFingerTree (Measure v) (MeasuredWith v a b)
ft2)
| Bool
otherwise
= Maybe (AnchoredSeq v a b)
forall a. Maybe a
Nothing
selectOffsets ::
forall v a b. Anchorable v a b
=> [Int]
-> AnchoredSeq v a b
-> [Either a b]
selectOffsets :: [Int] -> AnchoredSeq v a b -> [Either a b]
selectOffsets [Int]
offsets = [Int] -> AnchoredSeq v a b -> [Either a b]
go [Int]
relativeOffsets
where
relativeOffsets :: [Int]
relativeOffsets = (Int -> Int -> Int) -> [Int] -> [Int] -> [Int]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) [Int]
offsets (Int
0Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
offsets)
go :: [Int] -> AnchoredSeq v a b -> [Either a b]
go :: [Int] -> AnchoredSeq v a b -> [Either a b]
go [] AnchoredSeq v a b
_
= []
go (Int
off:[Int]
offs) AnchoredSeq v a b
s
| let i :: Int
i = AnchoredSeq v a b -> Int
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Int
length AnchoredSeq v a b
s Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
off
, Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
, (AnchoredSeq v a b
s', AnchoredSeq v a b
_) <- Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
forall v a b.
Anchorable v a b =>
Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
splitAt Int
i AnchoredSeq v a b
s
= AnchoredSeq v a b -> Either a b
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Either a b
head AnchoredSeq v a b
s' Either a b -> [Either a b] -> [Either a b]
forall a. a -> [a] -> [a]
: [Int] -> AnchoredSeq v a b -> [Either a b]
go [Int]
offs AnchoredSeq v a b
s'
| Bool
otherwise
= []
filter ::
forall v a b. Anchorable v a b
=> (b -> Bool)
-> AnchoredSeq v a b
-> [AnchoredSeq v a b]
filter :: (b -> Bool) -> AnchoredSeq v a b -> [AnchoredSeq v a b]
filter b -> Bool
p = (b -> Bool)
-> (b -> Bool) -> AnchoredSeq v a b -> [AnchoredSeq v a b]
forall v a b.
Anchorable v a b =>
(b -> Bool)
-> (b -> Bool) -> AnchoredSeq v a b -> [AnchoredSeq v a b]
filterWithStop b -> Bool
p (Bool -> b -> Bool
forall a b. a -> b -> a
const Bool
False)
filterWithStop ::
forall v a b. Anchorable v a b
=> (b -> Bool)
-> (b -> Bool)
-> AnchoredSeq v a b
-> [AnchoredSeq v a b]
filterWithStop :: (b -> Bool)
-> (b -> Bool) -> AnchoredSeq v a b -> [AnchoredSeq v a b]
filterWithStop b -> Bool
p b -> Bool
stop AnchoredSeq v a b
c =
AnchoredSeq v a b -> FilterRange -> AnchoredSeq v a b
forall v a b.
Anchorable v a b =>
AnchoredSeq v a b -> FilterRange -> AnchoredSeq v a b
applyFilterRange AnchoredSeq v a b
c (FilterRange -> AnchoredSeq v a b)
-> [FilterRange] -> [AnchoredSeq v a b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Int, b)] -> [FilterRange]
startRange ([Int] -> [b] -> [(Int, b)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] (AnchoredSeq v a b -> [b]
forall v a b. AnchoredSeq v a b -> [b]
toOldestFirst AnchoredSeq v a b
c))
where
startRange :: [(Int, b)] -> [FilterRange]
startRange :: [(Int, b)] -> [FilterRange]
startRange [] = []
startRange ((Int
i, b
b):[(Int, b)]
bs)
| b -> Bool
stop b
b
= [Int -> Int -> FilterRange
FilterRange Int
i (AnchoredSeq v a b -> Int
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Int
length AnchoredSeq v a b
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)]
| b -> Bool
p b
b
= Int -> Int -> [(Int, b)] -> [FilterRange]
extendRange Int
i Int
i [(Int, b)]
bs
| Bool
otherwise
= [(Int, b)] -> [FilterRange]
startRange [(Int, b)]
bs
extendRange :: Int -> Int -> [(Int, b)] -> [FilterRange]
extendRange :: Int -> Int -> [(Int, b)] -> [FilterRange]
extendRange !Int
start !Int
end [] = [Int -> Int -> FilterRange
FilterRange Int
start Int
end]
extendRange !Int
start !Int
end ((Int
i, b
b):[(Int, b)]
bs)
| b -> Bool
stop b
b
= [Int -> Int -> FilterRange
FilterRange Int
start (AnchoredSeq v a b -> Int
forall v a b. Anchorable v a b => AnchoredSeq v a b -> Int
length AnchoredSeq v a b
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)]
| b -> Bool
p b
b
= Int -> Int -> [(Int, b)] -> [FilterRange]
extendRange Int
start Int
i [(Int, b)]
bs
| Bool
otherwise
= Int -> Int -> FilterRange
FilterRange Int
start Int
end FilterRange -> [FilterRange] -> [FilterRange]
forall a. a -> [a] -> [a]
: [(Int, b)] -> [FilterRange]
startRange [(Int, b)]
bs
data FilterRange = FilterRange !Int !Int
deriving (Int -> FilterRange -> ShowS
[FilterRange] -> ShowS
FilterRange -> String
(Int -> FilterRange -> ShowS)
-> (FilterRange -> String)
-> ([FilterRange] -> ShowS)
-> Show FilterRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilterRange] -> ShowS
$cshowList :: [FilterRange] -> ShowS
show :: FilterRange -> String
$cshow :: FilterRange -> String
showsPrec :: Int -> FilterRange -> ShowS
$cshowsPrec :: Int -> FilterRange -> ShowS
Show)
applyFilterRange ::
forall v a b. Anchorable v a b
=> AnchoredSeq v a b
-> FilterRange
-> AnchoredSeq v a b
applyFilterRange :: AnchoredSeq v a b -> FilterRange -> AnchoredSeq v a b
applyFilterRange AnchoredSeq v a b
c (FilterRange Int
start Int
stop) = AnchoredSeq v a b
inRange
where
(AnchoredSeq v a b
_before, AnchoredSeq v a b
fromStart) = Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
forall v a b.
Anchorable v a b =>
Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
splitAt Int
start AnchoredSeq v a b
c
(AnchoredSeq v a b
inRange, AnchoredSeq v a b
_after) = Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
forall v a b.
Anchorable v a b =>
Int -> AnchoredSeq v a b -> (AnchoredSeq v a b, AnchoredSeq v a b)
splitAt (Int
stop Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) AnchoredSeq v a b
fromStart
filterWithStopSpec ::
forall v a b. Anchorable v a b
=> (b -> Bool)
-> (b -> Bool)
-> AnchoredSeq v a b
-> [AnchoredSeq v a b]
filterWithStopSpec :: (b -> Bool)
-> (b -> Bool) -> AnchoredSeq v a b -> [AnchoredSeq v a b]
filterWithStopSpec b -> Bool
p b -> Bool
stop = [AnchoredSeq v a b] -> AnchoredSeq v a b -> [AnchoredSeq v a b]
goNext []
where
goNext :: [AnchoredSeq v a b]
-> AnchoredSeq v a b
-> [AnchoredSeq v a b]
goNext :: [AnchoredSeq v a b] -> AnchoredSeq v a b -> [AnchoredSeq v a b]
goNext [AnchoredSeq v a b]
cs AnchoredSeq v a b
af = [AnchoredSeq v a b]
-> AnchoredSeq v a b -> AnchoredSeq v a b -> [AnchoredSeq v a b]
go [AnchoredSeq v a b]
cs (a -> AnchoredSeq v a b
forall v a b. Anchorable v a b => a -> AnchoredSeq v a b
Empty (AnchoredSeq v a b -> a
forall v a b. AnchoredSeq v a b -> a
anchor AnchoredSeq v a b
af)) AnchoredSeq v a b
af
go :: [AnchoredSeq v a b]
-> AnchoredSeq v a b
-> AnchoredSeq v a b
-> [AnchoredSeq v a b]
go :: [AnchoredSeq v a b]
-> AnchoredSeq v a b -> AnchoredSeq v a b -> [AnchoredSeq v a b]
go [AnchoredSeq v a b]
cs AnchoredSeq v a b
c' af :: AnchoredSeq v a b
af@(b
b :< AnchoredSeq v a b
c) | b -> Bool
stop b
b = [AnchoredSeq v a b] -> [AnchoredSeq v a b]
forall a. [a] -> [a]
reverse (AnchoredSeq v a b -> [AnchoredSeq v a b] -> [AnchoredSeq v a b]
addToAcc (AnchoredSeq v a b -> AnchoredSeq v a b -> AnchoredSeq v a b
join' AnchoredSeq v a b
c' AnchoredSeq v a b
af) [AnchoredSeq v a b]
cs)
| b -> Bool
p b
b = [AnchoredSeq v a b]
-> AnchoredSeq v a b -> AnchoredSeq v a b -> [AnchoredSeq v a b]
go [AnchoredSeq v a b]
cs (AnchoredSeq v a b
c' AnchoredSeq v a b -> b -> AnchoredSeq v a b
forall v a b.
Anchorable v a b =>
AnchoredSeq v a b -> b -> AnchoredSeq v a b
:> b
b) AnchoredSeq v a b
c
go [AnchoredSeq v a b]
cs AnchoredSeq v a b
c' (b
_ :< AnchoredSeq v a b
c) = [AnchoredSeq v a b] -> AnchoredSeq v a b -> [AnchoredSeq v a b]
goNext (AnchoredSeq v a b -> [AnchoredSeq v a b] -> [AnchoredSeq v a b]
addToAcc AnchoredSeq v a b
c' [AnchoredSeq v a b]
cs) AnchoredSeq v a b
c
go [AnchoredSeq v a b]
cs AnchoredSeq v a b
c' (Empty a
_) = [AnchoredSeq v a b] -> [AnchoredSeq v a b]
forall a. [a] -> [a]
reverse (AnchoredSeq v a b -> [AnchoredSeq v a b] -> [AnchoredSeq v a b]
addToAcc AnchoredSeq v a b
c' [AnchoredSeq v a b]
cs)
addToAcc :: AnchoredSeq v a b
-> [AnchoredSeq v a b]
-> [AnchoredSeq v a b]
addToAcc :: AnchoredSeq v a b -> [AnchoredSeq v a b] -> [AnchoredSeq v a b]
addToAcc (Empty a
_) [AnchoredSeq v a b]
acc = [AnchoredSeq v a b]
acc
addToAcc AnchoredSeq v a b
c' [AnchoredSeq v a b]
acc = AnchoredSeq v a b
c'AnchoredSeq v a b -> [AnchoredSeq v a b] -> [AnchoredSeq v a b]
forall a. a -> [a] -> [a]
:[AnchoredSeq v a b]
acc
join' :: AnchoredSeq v a b
-> AnchoredSeq v a b
-> AnchoredSeq v a b
join' :: AnchoredSeq v a b -> AnchoredSeq v a b -> AnchoredSeq v a b
join' AnchoredSeq v a b
a AnchoredSeq v a b
b =
AnchoredSeq v a b -> Maybe (AnchoredSeq v a b) -> AnchoredSeq v a b
forall a. a -> Maybe a -> a
fromMaybe (String -> AnchoredSeq v a b
forall a. HasCallStack => String -> a
error String
"could not join sequences") (Maybe (AnchoredSeq v a b) -> AnchoredSeq v a b)
-> Maybe (AnchoredSeq v a b) -> AnchoredSeq v a b
forall a b. (a -> b) -> a -> b
$
(Either a b -> a -> Bool)
-> AnchoredSeq v a b
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b)
forall v a b.
Anchorable v a b =>
(Either a b -> a -> Bool)
-> AnchoredSeq v a b
-> AnchoredSeq v a b
-> Maybe (AnchoredSeq v a b)
join (\Either a b
_ a
_ -> Bool
True) AnchoredSeq v a b
a AnchoredSeq v a b
b