-- |
--   Module      :  Data.Edison.Seq.RandList
--   Copyright   :  Copyright (c) 1998-1999, 2008 Chris Okasaki
--   License     :  MIT; see COPYRIGHT file for terms and conditions
--
--   Maintainer  :  robdockins AT fastmail DOT fm
--   Stability   :  stable
--   Portability :  GHC, Hugs (MPTC and FD)
--
--   Random-Access Lists.  All operations are as listed in "Data.Edison.Seq"
--   except the following:
--
--   * rhead*, size  @O( log n )@
--
--   * copy, inBounds    @O( log i )@
--
--   * lookup*, update, adjust, drop @O( min( i, log n ) )@
--
--   * subseq            @O( min( i, log n ) + len )@
--
--   /References:/
--
--   * Chris Okasaki. /Purely Functional Data Structures/. 1998.
--     Section 9.3.1.
--
--   * Chris Okasaki. \"Purely Functional Random Access Lists\".  FPCA'95,
--     pages 86-95.

module Data.Edison.Seq.RandList (
    -- * Sequence Type
    Seq, -- instance of Sequence, Functor, Monad, MonadPlus

    -- * Sequence Operations
    empty,singleton,lcons,rcons,append,lview,lhead,ltail,rview,rhead,rtail,
    lheadM,ltailM,rheadM,rtailM,
    null,size,concat,reverse,reverseOnto,fromList,toList,map,concatMap,
    fold,fold',fold1,fold1',foldr,foldr',foldl,foldl',foldr1,foldr1',foldl1,foldl1',
    reducer,reducer',reducel,reducel',reduce1,reduce1',
    copy,inBounds,lookup,lookupM,lookupWithDefault,update,adjust,
    mapWithIndex,foldrWithIndex,foldrWithIndex',foldlWithIndex,foldlWithIndex',
    take,drop,splitAt,subseq,filter,partition,takeWhile,dropWhile,splitWhile,
    zip,zip3,zipWith,zipWith3,unzip,unzip3,unzipWith,unzipWith3,
    strict, strictWith,

    -- * Unit testing
    structuralInvariant,

    -- * Documentation
    moduleName
) where

import Prelude hiding (concat,reverse,map,concatMap,foldr,foldl,foldr1,foldl1,
                       filter,takeWhile,dropWhile,lookup,take,drop,splitAt,
                       zip,zip3,zipWith,zipWith3,unzip,unzip3,null)

import qualified Control.Applicative as App

import Data.Edison.Prelude ( runFail_ )
import qualified Data.Edison.Seq as S( Sequence(..) )
import Data.Edison.Seq.Defaults
import qualified Control.Monad.Fail as Fail
import Control.Monad.Identity
import Data.Monoid
import Data.Semigroup as SG
import Test.QuickCheck

-- signatures for exported functions
moduleName     :: String
empty          :: Seq a
singleton      :: a -> Seq a
lcons          :: a -> Seq a -> Seq a
rcons          :: a -> Seq a -> Seq a
append         :: Seq a -> Seq a -> Seq a
lview          :: (Fail.MonadFail m) => Seq a -> m (a, Seq a)
lhead          :: Seq a -> a
lheadM         :: (Fail.MonadFail m) => Seq a -> m a
ltail          :: Seq a -> Seq a
ltailM         :: (Fail.MonadFail m) => Seq a -> m (Seq a)
rview          :: (Fail.MonadFail m) => Seq a -> m (a, Seq a)
rhead          :: Seq a -> a
rheadM         :: (Fail.MonadFail m) => Seq a -> m a
rtail          :: Seq a -> Seq a
rtailM         :: (Fail.MonadFail m) => Seq a -> m (Seq a)
null           :: Seq a -> Bool
size           :: Seq a -> Int
concat         :: Seq (Seq a) -> Seq a
reverse        :: Seq a -> Seq a
reverseOnto    :: Seq a -> Seq a -> Seq a
fromList       :: [a] -> Seq a
toList         :: Seq a -> [a]
map            :: (a -> b) -> Seq a -> Seq b
concatMap      :: (a -> Seq b) -> Seq a -> Seq b
fold           :: (a -> b -> b) -> b -> Seq a -> b
fold'          :: (a -> b -> b) -> b -> Seq a -> b
fold1          :: (a -> a -> a) -> Seq a -> a
fold1'         :: (a -> a -> a) -> Seq a -> a
foldr          :: (a -> b -> b) -> b -> Seq a -> b
foldl          :: (b -> a -> b) -> b -> Seq a -> b
foldr1         :: (a -> a -> a) -> Seq a -> a
foldl1         :: (a -> a -> a) -> Seq a -> a
reducer        :: (a -> a -> a) -> a -> Seq a -> a
reducel        :: (a -> a -> a) -> a -> Seq a -> a
reduce1        :: (a -> a -> a) -> Seq a -> a
foldr'         :: (a -> b -> b) -> b -> Seq a -> b
foldl'         :: (b -> a -> b) -> b -> Seq a -> b
foldr1'        :: (a -> a -> a) -> Seq a -> a
foldl1'        :: (a -> a -> a) -> Seq a -> a
reducer'       :: (a -> a -> a) -> a -> Seq a -> a
reducel'       :: (a -> a -> a) -> a -> Seq a -> a
reduce1'       :: (a -> a -> a) -> Seq a -> a
copy           :: Int -> a -> Seq a
inBounds       :: Int -> Seq a -> Bool
lookup         :: Int -> Seq a -> a
lookupM        :: (Fail.MonadFail m) => Int -> Seq a -> m a
lookupWithDefault :: a -> Int -> Seq a -> a
update         :: Int -> a -> Seq a -> Seq a
adjust         :: (a -> a) -> Int -> Seq a -> Seq a
mapWithIndex   :: (Int -> a -> b) -> Seq a -> Seq b
foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> b
foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> b
foldrWithIndex' :: (Int -> a -> b -> b) -> b -> Seq a -> b
foldlWithIndex' :: (b -> Int -> a -> b) -> b -> Seq a -> b
take           :: Int -> Seq a -> Seq a
drop           :: Int -> Seq a -> Seq a
splitAt        :: Int -> Seq a -> (Seq a, Seq a)
subseq         :: Int -> Int -> Seq a -> Seq a
filter         :: (a -> Bool) -> Seq a -> Seq a
partition      :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
takeWhile      :: (a -> Bool) -> Seq a -> Seq a
dropWhile      :: (a -> Bool) -> Seq a -> Seq a
splitWhile     :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
zip            :: Seq a -> Seq b -> Seq (a,b)
zip3           :: Seq a -> Seq b -> Seq c -> Seq (a,b,c)
zipWith        :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
zipWith3       :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
unzip          :: Seq (a,b) -> (Seq a, Seq b)
unzip3         :: Seq (a,b,c) -> (Seq a, Seq b, Seq c)
unzipWith      :: (a -> b) -> (a -> c) -> Seq a -> (Seq b, Seq c)
unzipWith3     :: (a -> b) -> (a -> c) -> (a -> d) -> Seq a -> (Seq b, Seq c, Seq d)
strict         :: Seq a -> Seq a
strictWith     :: (a -> b) -> Seq a -> Seq a
moduleName :: String
moduleName = String
"Data.Edison.Seq.RandList"


data Tree a = L a | T a (Tree a) (Tree a)   deriving (Tree a -> Tree a -> Bool
forall a. Eq a => Tree a -> Tree a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tree a -> Tree a -> Bool
$c/= :: forall a. Eq a => Tree a -> Tree a -> Bool
== :: Tree a -> Tree a -> Bool
$c== :: forall a. Eq a => Tree a -> Tree a -> Bool
Eq)
data Seq a = E | C !Int (Tree a) (Seq a)    deriving (Seq a -> Seq a -> Bool
forall a. Eq a => Seq a -> Seq a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Seq a -> Seq a -> Bool
$c/= :: forall a. Eq a => Seq a -> Seq a -> Bool
== :: Seq a -> Seq a -> Bool
$c== :: forall a. Eq a => Seq a -> Seq a -> Bool
Eq)

half :: Int -> Int
half :: Int -> Int
half Int
n = Int
n forall a. Integral a => a -> a -> a
`quot` Int
2  -- use a shift?

empty :: forall a. Seq a
empty = forall a. Seq a
E
singleton :: forall a. a -> Seq a
singleton a
x = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
1 (forall a. a -> Tree a
L a
x) forall a. Seq a
E

lcons :: forall a. a -> Seq a -> Seq a
lcons a
x (C Int
i Tree a
s (C Int
j Tree a
t Seq a
xs'))
    | Int
i forall a. Eq a => a -> a -> Bool
== Int
j = forall a. Int -> Tree a -> Seq a -> Seq a
C (Int
1 forall a. Num a => a -> a -> a
+ Int
i forall a. Num a => a -> a -> a
+ Int
j) (forall a. a -> Tree a -> Tree a -> Tree a
T a
x Tree a
s Tree a
t) Seq a
xs'
lcons a
x Seq a
xs = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
1 (forall a. a -> Tree a
L a
x) Seq a
xs

copy :: forall a. Int -> a -> Seq a
copy Int
n a
x = if Int
n forall a. Ord a => a -> a -> Bool
<= Int
0 then forall a. Seq a
E else Int -> Tree a -> Seq a
buildTrees (Int
1::Int) (forall a. a -> Tree a
L a
x)
  where buildTrees :: Int -> Tree a -> Seq a
buildTrees Int
j Tree a
t
          | Int
j forall a. Ord a => a -> a -> Bool
> Int
n     = forall {a}. Int -> Int -> Tree a -> Seq a -> Seq a
takeTrees Int
n (Int -> Int
half Int
j) (forall {a}. Tree a -> Tree a
child Tree a
t) forall a. Seq a
E
          | Bool
otherwise = Int -> Tree a -> Seq a
buildTrees (Int
1 forall a. Num a => a -> a -> a
+ Int
j forall a. Num a => a -> a -> a
+ Int
j) (forall a. a -> Tree a -> Tree a -> Tree a
T a
x Tree a
t Tree a
t)

        takeTrees :: Int -> Int -> Tree a -> Seq a -> Seq a
takeTrees Int
i Int
j Tree a
t Seq a
xs
          | Int
i forall a. Ord a => a -> a -> Bool
>= Int
j = Int -> Int -> Tree a -> Seq a -> Seq a
takeTrees (Int
i forall a. Num a => a -> a -> a
- Int
j) Int
j Tree a
t (forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
t Seq a
xs)
          | Int
i forall a. Ord a => a -> a -> Bool
> Int
0  = Int -> Int -> Tree a -> Seq a -> Seq a
takeTrees Int
i (Int -> Int
half Int
j) (forall {a}. Tree a -> Tree a
child Tree a
t) Seq a
xs
          | Bool
otherwise = Seq a
xs

        child :: Tree a -> Tree a
child (T a
_ Tree a
_ Tree a
t) = Tree a
t
        child Tree a
_ = forall a. HasCallStack => String -> a
error String
"RandList.copy: bug!"

lview :: forall (m :: * -> *) a. MonadFail m => Seq a -> m (a, Seq a)
lview Seq a
E = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"RandList.lview: empty sequence"
lview (C Int
_ (L a
x) Seq a
xs) = forall (m :: * -> *) a. Monad m => a -> m a
return (a
x, Seq a
xs)
lview (C Int
i (T a
x Tree a
s Tree a
t) Seq a
xs) = forall (m :: * -> *) a. Monad m => a -> m a
return (a
x, forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
s (forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
t Seq a
xs))
  where j :: Int
j = Int -> Int
half Int
i

lhead :: forall a. Seq a -> a
lhead Seq a
E = forall a. HasCallStack => String -> a
error String
"RandList.lhead: empty sequence"
lhead (C Int
_ (L a
x) Seq a
_) = a
x
lhead (C Int
_ (T a
x Tree a
_ Tree a
_) Seq a
_) = a
x

lheadM :: forall (m :: * -> *) a. MonadFail m => Seq a -> m a
lheadM Seq a
E = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"RandList.lheadM: empty sequence"
lheadM (C Int
_ (L a
x) Seq a
_) = forall (m :: * -> *) a. Monad m => a -> m a
return a
x
lheadM (C Int
_ (T a
x Tree a
_ Tree a
_) Seq a
_) = forall (m :: * -> *) a. Monad m => a -> m a
return a
x

ltail :: forall a. Seq a -> Seq a
ltail Seq a
E = forall a. HasCallStack => String -> a
error String
"RandList.ltail: empty sequence"
ltail (C Int
_ (L a
_) Seq a
xs) = Seq a
xs
ltail (C Int
i (T a
_ Tree a
s Tree a
t) Seq a
xs) = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
s (forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
t Seq a
xs)
  where j :: Int
j = Int -> Int
half Int
i

ltailM :: forall (m :: * -> *) a. MonadFail m => Seq a -> m (Seq a)
ltailM Seq a
E = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"RandList.ltailM: empty sequence"
ltailM (C Int
_ (L a
_) Seq a
xs) = forall (m :: * -> *) a. Monad m => a -> m a
return Seq a
xs
ltailM (C Int
i (T a
_ Tree a
s Tree a
t) Seq a
xs) = forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
s (forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
t Seq a
xs))
  where j :: Int
j = Int -> Int
half Int
i

rhead :: forall a. Seq a -> a
rhead Seq a
E = forall a. HasCallStack => String -> a
error String
"RandList.rhead: empty sequence"
rhead (C Int
_ Tree a
t Seq a
E) = forall {a}. Tree a -> a
treeLast Tree a
t
  where treeLast :: Tree a -> a
treeLast (L a
x) = a
x
        treeLast (T a
_ Tree a
_ Tree a
t) = Tree a -> a
treeLast Tree a
t
rhead (C Int
_ Tree a
_ Seq a
xs) = forall a. Seq a -> a
rhead Seq a
xs

rheadM :: forall (m :: * -> *) a. MonadFail m => Seq a -> m a
rheadM Seq a
E = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"RandList.rhead: empty sequence"
rheadM (C Int
_ Tree a
t Seq a
E) = forall (m :: * -> *) a. Monad m => a -> m a
return(forall {a}. Tree a -> a
treeLast Tree a
t)
  where treeLast :: Tree a -> a
treeLast (L a
x) = a
x
        treeLast (T a
_ Tree a
_ Tree a
t) = Tree a -> a
treeLast Tree a
t
rheadM (C Int
_ Tree a
_ Seq a
xs) = forall (m :: * -> *) a. MonadFail m => Seq a -> m a
rheadM Seq a
xs


null :: forall a. Seq a -> Bool
null Seq a
E = Bool
True
null Seq a
_ = Bool
False

size :: forall a. Seq a -> Int
size Seq a
xs = forall a. Seq a -> Int
sz Seq a
xs
  where sz :: Seq a -> Int
sz Seq a
E = (Int
0::Int)
        sz (C Int
j Tree a
_ Seq a
xs) = Int
j forall a. Num a => a -> a -> a
+ Seq a -> Int
sz Seq a
xs

reverseOnto :: forall a. Seq a -> Seq a -> Seq a
reverseOnto Seq a
E Seq a
ys = Seq a
ys
reverseOnto (C Int
_ Tree a
t Seq a
xs) Seq a
ys = forall a. Seq a -> Seq a -> Seq a
reverseOnto Seq a
xs (forall {a}. Tree a -> Seq a -> Seq a
revTree Tree a
t Seq a
ys)
  where revTree :: Tree a -> Seq a -> Seq a
revTree (L a
x) Seq a
ys = forall a. a -> Seq a -> Seq a
lcons a
x Seq a
ys
        revTree (T a
x Tree a
s Tree a
t) Seq a
ys = Tree a -> Seq a -> Seq a
revTree Tree a
t (Tree a -> Seq a -> Seq a
revTree Tree a
s (forall a. a -> Seq a -> Seq a
lcons a
x Seq a
ys))

map :: forall a b. (a -> b) -> Seq a -> Seq b
map a -> b
_ Seq a
E = forall a. Seq a
E
map a -> b
f (C Int
j Tree a
t Seq a
xs) = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j (forall {t} {a}. (t -> a) -> Tree t -> Tree a
mapTree a -> b
f Tree a
t) (forall a b. (a -> b) -> Seq a -> Seq b
map a -> b
f Seq a
xs)
  where mapTree :: (t -> a) -> Tree t -> Tree a
mapTree t -> a
f (L t
x) = forall a. a -> Tree a
L (t -> a
f t
x)
        mapTree t -> a
f (T t
x Tree t
s Tree t
t) = forall a. a -> Tree a -> Tree a -> Tree a
T (t -> a
f t
x) ((t -> a) -> Tree t -> Tree a
mapTree t -> a
f Tree t
s) ((t -> a) -> Tree t -> Tree a
mapTree t -> a
f Tree t
t)

fold :: forall a b. (a -> b -> b) -> b -> Seq a -> b
fold  = forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr
fold' :: forall a b. (a -> b -> b) -> b -> Seq a -> b
fold' a -> b -> b
f = forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> b
f)
fold1 :: forall a. (a -> a -> a) -> Seq a -> a
fold1  = forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
fold1UsingFold
fold1' :: forall a. (a -> a -> a) -> Seq a -> a
fold1' = forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
fold1'UsingFold'

foldr :: forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr a -> b -> b
_ b
e Seq a
E = b
e
foldr a -> b -> b
f b
e (C Int
_ Tree a
t Seq a
xs) = Tree a -> b -> b
foldTree Tree a
t (forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr a -> b -> b
f b
e Seq a
xs)
  where foldTree :: Tree a -> b -> b
foldTree (L a
x) b
e = a -> b -> b
f a
x b
e
        foldTree (T a
x Tree a
s Tree a
t) b
e = a -> b -> b
f a
x (Tree a -> b -> b
foldTree Tree a
s (Tree a -> b -> b
foldTree Tree a
t b
e))

foldr' :: forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr' a -> b -> b
_ b
e Seq a
E = b
e
foldr' a -> b -> b
f b
e (C Int
_ Tree a
t Seq a
xs) = Tree a -> b -> b
foldTree Tree a
t forall a b. (a -> b) -> a -> b
$! (forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr' a -> b -> b
f b
e Seq a
xs)
  where foldTree :: Tree a -> b -> b
foldTree (L a
x) b
e = a -> b -> b
f a
x forall a b. (a -> b) -> a -> b
$! b
e
        foldTree (T a
x Tree a
s Tree a
t) b
e = a -> b -> b
f a
x forall a b. (a -> b) -> a -> b
$! (Tree a -> b -> b
foldTree Tree a
s forall a b. (a -> b) -> a -> b
$! (Tree a -> b -> b
foldTree Tree a
t forall a b. (a -> b) -> a -> b
$! b
e))

foldl :: forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl b -> a -> b
_ b
e Seq a
E = b
e
foldl b -> a -> b
f b
e (C Int
_ Tree a
t Seq a
xs) = forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl b -> a -> b
f (b -> Tree a -> b
foldTree b
e Tree a
t) Seq a
xs
  where foldTree :: b -> Tree a -> b
foldTree b
e (L a
x) = b -> a -> b
f b
e a
x
        foldTree b
e (T a
x Tree a
s Tree a
t) = b -> Tree a -> b
foldTree (b -> Tree a -> b
foldTree (b -> a -> b
f b
e a
x) Tree a
s) Tree a
t

foldl' :: forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl' b -> a -> b
_ b
e Seq a
E = b
e
foldl' b -> a -> b
f b
e (C Int
_ Tree a
t Seq a
xs) = (forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl b -> a -> b
f forall a b. (a -> b) -> a -> b
$! (b -> Tree a -> b
foldTree b
e Tree a
t)) Seq a
xs
  where foldTree :: b -> Tree a -> b
foldTree b
e (L a
x) = b
e seq :: forall a b. a -> b -> b
`seq` b -> a -> b
f b
e a
x
        foldTree b
e (T a
x Tree a
s Tree a
t) = b
e seq :: forall a b. a -> b -> b
`seq` (b -> Tree a -> b
foldTree forall a b. (a -> b) -> a -> b
$! (b -> Tree a -> b
foldTree (b -> a -> b
f b
e a
x) Tree a
s)) Tree a
t

reduce1 :: forall a. (a -> a -> a) -> Seq a -> a
reduce1 a -> a -> a
f Seq a
xs = case forall (m :: * -> *) a. MonadFail m => Seq a -> m (a, Seq a)
lview Seq a
xs of
                 Maybe (a, Seq a)
Nothing      -> forall a. HasCallStack => String -> a
error String
"RandList.reduce1: empty seq"
                 Just (a
x, Seq a
xs) -> a -> Seq a -> a
red1 a
x Seq a
xs
  where red1 :: a -> Seq a -> a
red1 a
x Seq a
E = a
x
        red1 a
x (C Int
_ Tree a
t Seq a
xs) = a -> Seq a -> a
red1 (a -> Tree a -> a
redTree a
x Tree a
t) Seq a
xs

        redTree :: a -> Tree a -> a
redTree a
x (L a
y) = a -> a -> a
f a
x a
y
        redTree a
x (T a
y Tree a
s Tree a
t) = a -> Tree a -> a
redTree (a -> Tree a -> a
redTree (a -> a -> a
f a
x a
y) Tree a
s) Tree a
t

reduce1' :: forall a. (a -> a -> a) -> Seq a -> a
reduce1' a -> a -> a
f Seq a
xs = case forall (m :: * -> *) a. MonadFail m => Seq a -> m (a, Seq a)
lview Seq a
xs of
                  Maybe (a, Seq a)
Nothing      -> forall a. HasCallStack => String -> a
error String
"RandList.reduce1': empty seq"
                  Just (a
x, Seq a
xs) -> a -> Seq a -> a
red1 a
x Seq a
xs
  where red1 :: a -> Seq a -> a
red1 a
x Seq a
E = a
x
        red1 a
x (C Int
_ Tree a
t Seq a
xs) = (a -> Seq a -> a
red1 forall a b. (a -> b) -> a -> b
$! (a -> Tree a -> a
redTree a
x Tree a
t)) Seq a
xs

        redTree :: a -> Tree a -> a
redTree a
x (L a
y) = a
x seq :: forall a b. a -> b -> b
`seq` a
y seq :: forall a b. a -> b -> b
`seq` a -> a -> a
f a
x a
y
        redTree a
x (T a
y Tree a
s Tree a
t) = a
x seq :: forall a b. a -> b -> b
`seq` a
y seq :: forall a b. a -> b -> b
`seq` (a -> Tree a -> a
redTree forall a b. (a -> b) -> a -> b
$! (a -> Tree a -> a
redTree (a -> a -> a
f a
x a
y) Tree a
s)) Tree a
t


inBounds :: forall a. Int -> Seq a -> Bool
inBounds Int
i Seq a
xs = forall {a}. Seq a -> Int -> Bool
inb Seq a
xs Int
i
  where inb :: Seq a -> Int -> Bool
inb Seq a
E Int
_ = Bool
False
        inb (C Int
j Tree a
_ Seq a
xs) Int
i
          | Int
i forall a. Ord a => a -> a -> Bool
< Int
j     = (Int
i forall a. Ord a => a -> a -> Bool
>= Int
0)
          | Bool
otherwise = Seq a -> Int -> Bool
inb Seq a
xs (Int
i forall a. Num a => a -> a -> a
- Int
j)

lookup :: forall a. Int -> Seq a -> a
lookup Int
i Seq a
xs = forall a. Fail a -> a
runFail_ (forall (m :: * -> *) a. MonadFail m => Int -> Seq a -> m a
lookupM Int
i Seq a
xs)

lookupM :: forall (m :: * -> *) a. MonadFail m => Int -> Seq a -> m a
lookupM Int
i Seq a
xs = forall {a}. Seq a -> Int -> m a
look Seq a
xs Int
i
  where look :: Seq a -> Int -> m a
look Seq a
E Int
_ = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"RandList.lookup bad subscript"
        look (C Int
j Tree a
t Seq a
xs) Int
i
            | Int
i forall a. Ord a => a -> a -> Bool
< Int
j     = forall {a}. Int -> Tree a -> Int -> m a
lookTree Int
j Tree a
t Int
i
            | Bool
otherwise = Seq a -> Int -> m a
look Seq a
xs (Int
i forall a. Num a => a -> a -> a
- Int
j)

        lookTree :: Int -> Tree a -> Int -> m a
lookTree Int
_ (L a
x) Int
i
            | Int
i forall a. Eq a => a -> a -> Bool
== Int
0    = forall (m :: * -> *) a. Monad m => a -> m a
return a
x
            | Bool
otherwise = forall {a}. m a
nothing
        lookTree Int
j (T a
x Tree a
s Tree a
t) Int
i
            | Int
i forall a. Ord a => a -> a -> Bool
> Int
k  = Int -> Tree a -> Int -> m a
lookTree Int
k Tree a
t (Int
i forall a. Num a => a -> a -> a
- Int
1 forall a. Num a => a -> a -> a
- Int
k)
            | Int
i forall a. Eq a => a -> a -> Bool
/= Int
0 = Int -> Tree a -> Int -> m a
lookTree Int
k Tree a
s (Int
i forall a. Num a => a -> a -> a
- Int
1)
            | Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return a
x
          where k :: Int
k = Int -> Int
half Int
j
        nothing :: m a
nothing = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"RandList.lookup: not found"

lookupWithDefault :: forall a. a -> Int -> Seq a -> a
lookupWithDefault a
d Int
i Seq a
xs = Seq a -> Int -> a
look Seq a
xs Int
i
  where look :: Seq a -> Int -> a
look Seq a
E Int
_ = a
d
        look (C Int
j Tree a
t Seq a
xs) Int
i
            | Int
i forall a. Ord a => a -> a -> Bool
< Int
j     = Int -> Tree a -> Int -> a
lookTree Int
j Tree a
t Int
i
            | Bool
otherwise = Seq a -> Int -> a
look Seq a
xs (Int
i forall a. Num a => a -> a -> a
- Int
j)

        lookTree :: Int -> Tree a -> Int -> a
lookTree Int
_ (L a
x) Int
i
            | Int
i forall a. Eq a => a -> a -> Bool
== Int
0    = a
x
            | Bool
otherwise = a
d
        lookTree Int
j (T a
x Tree a
s Tree a
t) Int
i
            | Int
i forall a. Ord a => a -> a -> Bool
> Int
k   = Int -> Tree a -> Int -> a
lookTree Int
k Tree a
t (Int
i forall a. Num a => a -> a -> a
- Int
1 forall a. Num a => a -> a -> a
- Int
k)
            | Int
i forall a. Eq a => a -> a -> Bool
/= Int
0  = Int -> Tree a -> Int -> a
lookTree Int
k Tree a
s (Int
i forall a. Num a => a -> a -> a
- Int
1)
            | Bool
otherwise = a
x
          where k :: Int
k = Int -> Int
half Int
j

update :: forall a. Int -> a -> Seq a -> Seq a
update Int
i a
y Seq a
xs = Int -> Seq a -> Seq a
upd Int
i Seq a
xs
  where upd :: Int -> Seq a -> Seq a
upd Int
_ Seq a
E = forall a. Seq a
E
        upd Int
i (C Int
j Tree a
t Seq a
xs)
            | Int
i forall a. Ord a => a -> a -> Bool
< Int
j     = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j (Int -> Int -> Tree a -> Tree a
updTree Int
i Int
j Tree a
t) Seq a
xs
            | Bool
otherwise = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
t (Int -> Seq a -> Seq a
upd (Int
i forall a. Num a => a -> a -> a
- Int
j) Seq a
xs)

        updTree :: Int -> Int -> Tree a -> Tree a
updTree Int
i Int
_ t :: Tree a
t@(L a
_)
            | Int
i forall a. Eq a => a -> a -> Bool
== Int
0    = forall a. a -> Tree a
L a
y
            | Bool
otherwise = Tree a
t
        updTree Int
i Int
j (T a
x Tree a
s Tree a
t)
            | Int
i forall a. Ord a => a -> a -> Bool
> Int
k   = forall a. a -> Tree a -> Tree a -> Tree a
T a
x Tree a
s (Int -> Int -> Tree a -> Tree a
updTree (Int
i forall a. Num a => a -> a -> a
- Int
1 forall a. Num a => a -> a -> a
- Int
k) Int
k Tree a
t)
            | Int
i forall a. Eq a => a -> a -> Bool
/= Int
0  = forall a. a -> Tree a -> Tree a -> Tree a
T a
x (Int -> Int -> Tree a -> Tree a
updTree (Int
i forall a. Num a => a -> a -> a
- Int
1) Int
k Tree a
s) Tree a
t
            | Bool
otherwise = forall a. a -> Tree a -> Tree a -> Tree a
T a
y Tree a
s Tree a
t
          where k :: Int
k = Int -> Int
half Int
j

adjust :: forall a. (a -> a) -> Int -> Seq a -> Seq a
adjust a -> a
f Int
i Seq a
xs = Int -> Seq a -> Seq a
adj Int
i Seq a
xs
  where adj :: Int -> Seq a -> Seq a
adj Int
_ Seq a
E = forall a. Seq a
E
        adj Int
i (C Int
j Tree a
t Seq a
xs)
            | Int
i forall a. Ord a => a -> a -> Bool
< Int
j     = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j (Int -> Int -> Tree a -> Tree a
adjTree Int
i Int
j Tree a
t) Seq a
xs
            | Bool
otherwise = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
t (Int -> Seq a -> Seq a
adj (Int
i forall a. Num a => a -> a -> a
- Int
j) Seq a
xs)

        adjTree :: Int -> Int -> Tree a -> Tree a
adjTree Int
i Int
_ t :: Tree a
t@(L a
x)
            | Int
i forall a. Eq a => a -> a -> Bool
== Int
0    = forall a. a -> Tree a
L (a -> a
f a
x)
            | Bool
otherwise = Tree a
t
        adjTree Int
i Int
j (T a
x Tree a
s Tree a
t)
            | Int
i forall a. Ord a => a -> a -> Bool
> Int
k  = forall a. a -> Tree a -> Tree a -> Tree a
T a
x Tree a
s (Int -> Int -> Tree a -> Tree a
adjTree (Int
i forall a. Num a => a -> a -> a
- Int
1 forall a. Num a => a -> a -> a
- Int
k) Int
k Tree a
t)
            | Int
i forall a. Eq a => a -> a -> Bool
/= Int
0 = forall a. a -> Tree a -> Tree a -> Tree a
T a
x (Int -> Int -> Tree a -> Tree a
adjTree (Int
i forall a. Num a => a -> a -> a
- Int
1) Int
k Tree a
s) Tree a
t
            | Bool
otherwise = forall a. a -> Tree a -> Tree a -> Tree a
T (a -> a
f a
x) Tree a
s Tree a
t
          where k :: Int
k = Int -> Int
half Int
j

drop :: forall a. Int -> Seq a -> Seq a
drop Int
n Seq a
xs = if Int
n forall a. Ord a => a -> a -> Bool
< Int
0 then Seq a
xs else forall a. Int -> Seq a -> Seq a
drp Int
n Seq a
xs
  where drp :: Int -> Seq a -> Seq a
drp Int
_ Seq a
E = forall a. Seq a
E
        drp Int
i (C Int
j Tree a
t Seq a
xs)
            | Int
i forall a. Ord a => a -> a -> Bool
< Int
j     = forall {a}. Int -> Int -> Tree a -> Seq a -> Seq a
drpTree Int
i Int
j Tree a
t Seq a
xs
            | Bool
otherwise = Int -> Seq a -> Seq a
drp (Int
i forall a. Num a => a -> a -> a
- Int
j) Seq a
xs

        drpTree :: Int -> Int -> Tree a -> Seq a -> Seq a
drpTree Int
0 Int
j Tree a
t Seq a
xs = forall a. Int -> Tree a -> Seq a -> Seq a
C Int
j Tree a
t Seq a
xs
        drpTree Int
_ Int
_ (L a
_) Seq a
_ = forall a. HasCallStack => String -> a
error String
"RandList.drop: bug.  Impossible case!"
        drpTree Int
i Int
j (T a
_ Tree a
s Tree a
t) Seq a
xs
            | Int
i forall a. Ord a => a -> a -> Bool
> Int
k     = Int -> Int -> Tree a -> Seq a -> Seq a
drpTree (Int
i forall a. Num a => a -> a -> a
- Int
1 forall a. Num a => a -> a -> a
- Int
k) Int
k Tree a
t Seq a
xs
            | Bool
otherwise = Int -> Int -> Tree a -> Seq a -> Seq a
drpTree (Int
i forall a. Num a => a -> a -> a
- Int
1) Int
k Tree a
s (forall a. Int -> Tree a -> Seq a -> Seq a
C Int
k Tree a
t Seq a
xs)
          where k :: Int
k = Int -> Int
half Int
j

strict :: forall a. Seq a -> Seq a
strict s :: Seq a
s@Seq a
E = Seq a
s
strict s :: Seq a
s@(C Int
_ Tree a
t Seq a
xs) = forall {a}. Tree a -> Tree a
strictTree Tree a
t seq :: forall a b. a -> b -> b
`seq` forall a. Seq a -> Seq a
strict Seq a
xs seq :: forall a b. a -> b -> b
`seq` Seq a
s

strictTree :: Tree t -> Tree t
strictTree :: forall {a}. Tree a -> Tree a
strictTree t :: Tree t
t@(L t
_) = Tree t
t
strictTree t :: Tree t
t@(T t
_ Tree t
l Tree t
r) = forall {a}. Tree a -> Tree a
strictTree Tree t
l seq :: forall a b. a -> b -> b
`seq` forall {a}. Tree a -> Tree a
strictTree Tree t
r seq :: forall a b. a -> b -> b
`seq` Tree t
t

strictWith :: forall a b. (a -> b) -> Seq a -> Seq a
strictWith a -> b
_ s :: Seq a
s@Seq a
E = Seq a
s
strictWith a -> b
f s :: Seq a
s@(C Int
_ Tree a
t Seq a
xs) = forall t a. (t -> a) -> Tree t -> Tree t
strictWithTree a -> b
f Tree a
t seq :: forall a b. a -> b -> b
`seq` forall a b. (a -> b) -> Seq a -> Seq a
strictWith a -> b
f Seq a
xs seq :: forall a b. a -> b -> b
`seq` Seq a
s

strictWithTree :: (t -> a) -> Tree t -> Tree t
strictWithTree :: forall t a. (t -> a) -> Tree t -> Tree t
strictWithTree t -> a
f t :: Tree t
t@(L t
x) = t -> a
f t
x seq :: forall a b. a -> b -> b
`seq` Tree t
t
strictWithTree t -> a
f t :: Tree t
t@(T t
x Tree t
l Tree t
r) = t -> a
f t
x seq :: forall a b. a -> b -> b
`seq` forall t a. (t -> a) -> Tree t -> Tree t
strictWithTree t -> a
f Tree t
l seq :: forall a b. a -> b -> b
`seq` forall t a. (t -> a) -> Tree t -> Tree t
strictWithTree t -> a
f Tree t
r seq :: forall a b. a -> b -> b
`seq` Tree t
t


-- the remaining functions all use defaults

rcons :: forall a. a -> Seq a -> Seq a
rcons = forall (s :: * -> *) a. Sequence s => a -> s a -> s a
rconsUsingFoldr
append :: forall a. Seq a -> Seq a -> Seq a
append = forall (s :: * -> *) a. Sequence s => s a -> s a -> s a
appendUsingFoldr
rview :: forall (m :: * -> *) a. MonadFail m => Seq a -> m (a, Seq a)
rview = forall (m :: * -> *) (s :: * -> *) a.
(MonadFail m, Sequence s) =>
s a -> m (a, s a)
rviewDefault
rtail :: forall a. Seq a -> Seq a
rtail = forall (s :: * -> *) a. Sequence s => s a -> s a
rtailUsingLview
rtailM :: forall (m :: * -> *) a. MonadFail m => Seq a -> m (Seq a)
rtailM = forall (m :: * -> *) (s :: * -> *) a.
(MonadFail m, Sequence s) =>
s a -> m (s a)
rtailMUsingLview
concat :: forall a. Seq (Seq a) -> Seq a
concat = forall (s :: * -> *) a. Sequence s => s (s a) -> s a
concatUsingFoldr
reverse :: forall a. Seq a -> Seq a
reverse = forall (s :: * -> *) a. Sequence s => s a -> s a
reverseUsingReverseOnto
fromList :: forall a. [a] -> Seq a
fromList = forall (s :: * -> *) a. Sequence s => [a] -> s a
fromListUsingCons
toList :: forall a. Seq a -> [a]
toList = forall (s :: * -> *) a. Sequence s => s a -> [a]
toListUsingFoldr
concatMap :: forall a b. (a -> Seq b) -> Seq a -> Seq b
concatMap = forall (s :: * -> *) a b. Sequence s => (a -> s b) -> s a -> s b
concatMapUsingFoldr
foldr1 :: forall a. (a -> a -> a) -> Seq a -> a
foldr1  = forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
foldr1UsingLview
foldr1' :: forall a. (a -> a -> a) -> Seq a -> a
foldr1' = forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
foldr1'UsingLview
foldl1 :: forall a. (a -> a -> a) -> Seq a -> a
foldl1  = forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
foldl1UsingFoldl
foldl1' :: forall a. (a -> a -> a) -> Seq a -> a
foldl1' = forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
foldl1'UsingFoldl'
reducer :: forall a. (a -> a -> a) -> a -> Seq a -> a
reducer  = forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> s a -> a
reducerUsingReduce1
reducer' :: forall a. (a -> a -> a) -> a -> Seq a -> a
reducer' = forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> s a -> a
reducer'UsingReduce1'
reducel :: forall a. (a -> a -> a) -> a -> Seq a -> a
reducel  = forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> s a -> a
reducelUsingReduce1
reducel' :: forall a. (a -> a -> a) -> a -> Seq a -> a
reducel' = forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> s a -> a
reducel'UsingReduce1'
mapWithIndex :: forall a b. (Int -> a -> b) -> Seq a -> Seq b
mapWithIndex = forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b) -> s a -> s b
mapWithIndexUsingLists
foldrWithIndex :: forall a b. (Int -> a -> b -> b) -> b -> Seq a -> b
foldrWithIndex  = forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b -> b) -> b -> s a -> b
foldrWithIndexUsingLists
foldrWithIndex' :: forall a b. (Int -> a -> b -> b) -> b -> Seq a -> b
foldrWithIndex' = forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b -> b) -> b -> s a -> b
foldrWithIndex'UsingLists
foldlWithIndex :: forall b a. (b -> Int -> a -> b) -> b -> Seq a -> b
foldlWithIndex  = forall (s :: * -> *) b a.
Sequence s =>
(b -> Int -> a -> b) -> b -> s a -> b
foldlWithIndexUsingLists
foldlWithIndex' :: forall b a. (b -> Int -> a -> b) -> b -> Seq a -> b
foldlWithIndex' = forall (s :: * -> *) b a.
Sequence s =>
(b -> Int -> a -> b) -> b -> s a -> b
foldlWithIndex'UsingLists
take :: forall a. Int -> Seq a -> Seq a
take = forall (s :: * -> *) a. Sequence s => Int -> s a -> s a
takeUsingLists
splitAt :: forall a. Int -> Seq a -> (Seq a, Seq a)
splitAt = forall (s :: * -> *) a. Sequence s => Int -> s a -> (s a, s a)
splitAtDefault
filter :: forall a. (a -> Bool) -> Seq a -> Seq a
filter = forall (s :: * -> *) a. Sequence s => (a -> Bool) -> s a -> s a
filterUsingFoldr
partition :: forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
partition = forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> s a -> (s a, s a)
partitionUsingFoldr
subseq :: forall a. Int -> Int -> Seq a -> Seq a
subseq = forall (s :: * -> *) a. Sequence s => Int -> Int -> s a -> s a
subseqDefault
takeWhile :: forall a. (a -> Bool) -> Seq a -> Seq a
takeWhile = forall (s :: * -> *) a. Sequence s => (a -> Bool) -> s a -> s a
takeWhileUsingLview
dropWhile :: forall a. (a -> Bool) -> Seq a -> Seq a
dropWhile = forall (s :: * -> *) a. Sequence s => (a -> Bool) -> s a -> s a
dropWhileUsingLview
splitWhile :: forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
splitWhile = forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> s a -> (s a, s a)
splitWhileUsingLview

-- for zips, could optimize by calculating which one is shorter and
-- retaining its shape

zip :: forall a b. Seq a -> Seq b -> Seq (a, b)
zip = forall (s :: * -> *) a b. Sequence s => s a -> s b -> s (a, b)
zipUsingLists
zip3 :: forall a b c. Seq a -> Seq b -> Seq c -> Seq (a, b, c)
zip3 = forall (s :: * -> *) a b c.
Sequence s =>
s a -> s b -> s c -> s (a, b, c)
zip3UsingLists
zipWith :: forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
zipWith = forall (s :: * -> *) a b c.
Sequence s =>
(a -> b -> c) -> s a -> s b -> s c
zipWithUsingLists
zipWith3 :: forall a b c d.
(a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
zipWith3 = forall (s :: * -> *) a b c d.
Sequence s =>
(a -> b -> c -> d) -> s a -> s b -> s c -> s d
zipWith3UsingLists
unzip :: forall a b. Seq (a, b) -> (Seq a, Seq b)
unzip = forall (s :: * -> *) a b. Sequence s => s (a, b) -> (s a, s b)
unzipUsingLists
unzip3 :: forall a b c. Seq (a, b, c) -> (Seq a, Seq b, Seq c)
unzip3 = forall (s :: * -> *) a b c.
Sequence s =>
s (a, b, c) -> (s a, s b, s c)
unzip3UsingLists
unzipWith :: forall a b c. (a -> b) -> (a -> c) -> Seq a -> (Seq b, Seq c)
unzipWith = forall (s :: * -> *) a b c.
Sequence s =>
(a -> b) -> (a -> c) -> s a -> (s b, s c)
unzipWithUsingLists
unzipWith3 :: forall a b c d.
(a -> b) -> (a -> c) -> (a -> d) -> Seq a -> (Seq b, Seq c, Seq d)
unzipWith3 = forall (s :: * -> *) a b c d.
Sequence s =>
(a -> b) -> (a -> c) -> (a -> d) -> s a -> (s b, s c, s d)
unzipWith3UsingLists

-- invariants:
--   * list of complete binary trees in non-decreasing
--     order by size
--   * first argument to 'C' is the number
--     of nodes in the tree
structuralInvariant :: Seq t -> Bool
structuralInvariant :: forall a. Seq a -> Bool
structuralInvariant Seq t
E = Bool
True
structuralInvariant (C Int
x Tree t
t Seq t
s) = Int
x forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& forall {t} {a}. Integral t => t -> Tree a -> Bool
checkTree Int
x Tree t
t Bool -> Bool -> Bool
&& forall a. Int -> Seq a -> Bool
checkSeq Int
x Seq t
s

   where checkTree :: t -> Tree a -> Bool
checkTree t
1 (L a
_) = Bool
True
         checkTree t
w (T a
_ Tree a
l Tree a
r) =
             let w' :: t
w' = (t
w forall a. Num a => a -> a -> a
- t
1) forall a. Integral a => a -> a -> a
`div` t
2
             in t
w' forall a. Ord a => a -> a -> Bool
> t
0 Bool -> Bool -> Bool
&& t -> Tree a -> Bool
checkTree t
w' Tree a
l Bool -> Bool -> Bool
&& t -> Tree a -> Bool
checkTree t
w' Tree a
r
         checkTree t
_ Tree a
_ = Bool
False

         checkSeq :: Int -> Seq a -> Bool
checkSeq Int
_ Seq a
E = Bool
True
         checkSeq Int
x (C Int
y Tree a
t Seq a
s) =
             Int
x forall a. Ord a => a -> a -> Bool
<= Int
y Bool -> Bool -> Bool
&& forall {t} {a}. Integral t => t -> Tree a -> Bool
checkTree Int
y Tree a
t Bool -> Bool -> Bool
&& Int -> Seq a -> Bool
checkSeq Int
y Seq a
s


-- instances

instance S.Sequence Seq where
  {lcons :: forall a. a -> Seq a -> Seq a
lcons = forall a. a -> Seq a -> Seq a
lcons; rcons :: forall a. a -> Seq a -> Seq a
rcons = forall a. a -> Seq a -> Seq a
rcons;
   lview :: forall (m :: * -> *) a. MonadFail m => Seq a -> m (a, Seq a)
lview = forall (m :: * -> *) a. MonadFail m => Seq a -> m (a, Seq a)
lview; lhead :: forall a. Seq a -> a
lhead = forall a. Seq a -> a
lhead; ltail :: forall a. Seq a -> Seq a
ltail = forall a. Seq a -> Seq a
ltail;
   lheadM :: forall (m :: * -> *) a. MonadFail m => Seq a -> m a
lheadM = forall (m :: * -> *) a. MonadFail m => Seq a -> m a
lheadM; ltailM :: forall (m :: * -> *) a. MonadFail m => Seq a -> m (Seq a)
ltailM = forall (m :: * -> *) a. MonadFail m => Seq a -> m (Seq a)
ltailM; rheadM :: forall (m :: * -> *) a. MonadFail m => Seq a -> m a
rheadM = forall (m :: * -> *) a. MonadFail m => Seq a -> m a
rheadM; rtailM :: forall (m :: * -> *) a. MonadFail m => Seq a -> m (Seq a)
rtailM = forall (m :: * -> *) a. MonadFail m => Seq a -> m (Seq a)
rtailM;
   rview :: forall (m :: * -> *) a. MonadFail m => Seq a -> m (a, Seq a)
rview = forall (m :: * -> *) a. MonadFail m => Seq a -> m (a, Seq a)
rview; rhead :: forall a. Seq a -> a
rhead = forall a. Seq a -> a
rhead; rtail :: forall a. Seq a -> Seq a
rtail = forall a. Seq a -> Seq a
rtail; null :: forall a. Seq a -> Bool
null = forall a. Seq a -> Bool
null;
   size :: forall a. Seq a -> Int
size = forall a. Seq a -> Int
size; concat :: forall a. Seq (Seq a) -> Seq a
concat = forall a. Seq (Seq a) -> Seq a
concat; reverse :: forall a. Seq a -> Seq a
reverse = forall a. Seq a -> Seq a
reverse;
   reverseOnto :: forall a. Seq a -> Seq a -> Seq a
reverseOnto = forall a. Seq a -> Seq a -> Seq a
reverseOnto; fromList :: forall a. [a] -> Seq a
fromList = forall a. [a] -> Seq a
fromList; toList :: forall a. Seq a -> [a]
toList = forall a. Seq a -> [a]
toList;
   fold :: forall a b. (a -> b -> b) -> b -> Seq a -> b
fold = forall a b. (a -> b -> b) -> b -> Seq a -> b
fold; fold' :: forall a b. (a -> b -> b) -> b -> Seq a -> b
fold' = forall a b. (a -> b -> b) -> b -> Seq a -> b
fold'; fold1 :: forall a. (a -> a -> a) -> Seq a -> a
fold1 = forall a. (a -> a -> a) -> Seq a -> a
fold1; fold1' :: forall a. (a -> a -> a) -> Seq a -> a
fold1' = forall a. (a -> a -> a) -> Seq a -> a
fold1';
   foldr :: forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr = forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr; foldr' :: forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr' = forall a b. (a -> b -> b) -> b -> Seq a -> b
foldr'; foldl :: forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl = forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl; foldl' :: forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl' = forall b a. (b -> a -> b) -> b -> Seq a -> b
foldl';
   foldr1 :: forall a. (a -> a -> a) -> Seq a -> a
foldr1 = forall a. (a -> a -> a) -> Seq a -> a
foldr1; foldr1' :: forall a. (a -> a -> a) -> Seq a -> a
foldr1' = forall a. (a -> a -> a) -> Seq a -> a
foldr1'; foldl1 :: forall a. (a -> a -> a) -> Seq a -> a
foldl1 = forall a. (a -> a -> a) -> Seq a -> a
foldl1; foldl1' :: forall a. (a -> a -> a) -> Seq a -> a
foldl1' = forall a. (a -> a -> a) -> Seq a -> a
foldl1';
   reducer :: forall a. (a -> a -> a) -> a -> Seq a -> a
reducer = forall a. (a -> a -> a) -> a -> Seq a -> a
reducer; reducer' :: forall a. (a -> a -> a) -> a -> Seq a -> a
reducer' = forall a. (a -> a -> a) -> a -> Seq a -> a
reducer'; reducel :: forall a. (a -> a -> a) -> a -> Seq a -> a
reducel = forall a. (a -> a -> a) -> a -> Seq a -> a
reducel;
   reducel' :: forall a. (a -> a -> a) -> a -> Seq a -> a
reducel' = forall a. (a -> a -> a) -> a -> Seq a -> a
reducel'; reduce1 :: forall a. (a -> a -> a) -> Seq a -> a
reduce1 = forall a. (a -> a -> a) -> Seq a -> a
reduce1; reduce1' :: forall a. (a -> a -> a) -> Seq a -> a
reduce1' = forall a. (a -> a -> a) -> Seq a -> a
reduce1';
   copy :: forall a. Int -> a -> Seq a
copy = forall a. Int -> a -> Seq a
copy; inBounds :: forall a. Int -> Seq a -> Bool
inBounds = forall a. Int -> Seq a -> Bool
inBounds; lookup :: forall a. Int -> Seq a -> a
lookup = forall a. Int -> Seq a -> a
lookup;
   lookupM :: forall (m :: * -> *) a. MonadFail m => Int -> Seq a -> m a
lookupM = forall (m :: * -> *) a. MonadFail m => Int -> Seq a -> m a
lookupM; lookupWithDefault :: forall a. a -> Int -> Seq a -> a
lookupWithDefault = forall a. a -> Int -> Seq a -> a
lookupWithDefault;
   update :: forall a. Int -> a -> Seq a -> Seq a
update = forall a. Int -> a -> Seq a -> Seq a
update; adjust :: forall a. (a -> a) -> Int -> Seq a -> Seq a
adjust = forall a. (a -> a) -> Int -> Seq a -> Seq a
adjust; mapWithIndex :: forall a b. (Int -> a -> b) -> Seq a -> Seq b
mapWithIndex = forall a b. (Int -> a -> b) -> Seq a -> Seq b
mapWithIndex;
   foldrWithIndex :: forall a b. (Int -> a -> b -> b) -> b -> Seq a -> b
foldrWithIndex = forall a b. (Int -> a -> b -> b) -> b -> Seq a -> b
foldrWithIndex; foldrWithIndex' :: forall a b. (Int -> a -> b -> b) -> b -> Seq a -> b
foldrWithIndex' = forall a b. (Int -> a -> b -> b) -> b -> Seq a -> b
foldrWithIndex';
   foldlWithIndex :: forall b a. (b -> Int -> a -> b) -> b -> Seq a -> b
foldlWithIndex = forall b a. (b -> Int -> a -> b) -> b -> Seq a -> b
foldlWithIndex; foldlWithIndex' :: forall b a. (b -> Int -> a -> b) -> b -> Seq a -> b
foldlWithIndex' = forall b a. (b -> Int -> a -> b) -> b -> Seq a -> b
foldlWithIndex';
   take :: forall a. Int -> Seq a -> Seq a
take = forall a. Int -> Seq a -> Seq a
take; drop :: forall a. Int -> Seq a -> Seq a
drop = forall a. Int -> Seq a -> Seq a
drop; splitAt :: forall a. Int -> Seq a -> (Seq a, Seq a)
splitAt = forall a. Int -> Seq a -> (Seq a, Seq a)
splitAt; subseq :: forall a. Int -> Int -> Seq a -> Seq a
subseq = forall a. Int -> Int -> Seq a -> Seq a
subseq;
   filter :: forall a. (a -> Bool) -> Seq a -> Seq a
filter = forall a. (a -> Bool) -> Seq a -> Seq a
filter; partition :: forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
partition = forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
partition; takeWhile :: forall a. (a -> Bool) -> Seq a -> Seq a
takeWhile = forall a. (a -> Bool) -> Seq a -> Seq a
takeWhile;
   dropWhile :: forall a. (a -> Bool) -> Seq a -> Seq a
dropWhile = forall a. (a -> Bool) -> Seq a -> Seq a
dropWhile; splitWhile :: forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
splitWhile = forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
splitWhile; zip :: forall a b. Seq a -> Seq b -> Seq (a, b)
zip = forall a b. Seq a -> Seq b -> Seq (a, b)
zip;
   zip3 :: forall a b c. Seq a -> Seq b -> Seq c -> Seq (a, b, c)
zip3 = forall a b c. Seq a -> Seq b -> Seq c -> Seq (a, b, c)
zip3; zipWith :: forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
zipWith = forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
zipWith; zipWith3 :: forall a b c d.
(a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
zipWith3 = forall a b c d.
(a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
zipWith3; unzip :: forall a b. Seq (a, b) -> (Seq a, Seq b)
unzip = forall a b. Seq (a, b) -> (Seq a, Seq b)
unzip;
   unzip3 :: forall a b c. Seq (a, b, c) -> (Seq a, Seq b, Seq c)
unzip3 = forall a b c. Seq (a, b, c) -> (Seq a, Seq b, Seq c)
unzip3; unzipWith :: forall a b c. (a -> b) -> (a -> c) -> Seq a -> (Seq b, Seq c)
unzipWith = forall a b c. (a -> b) -> (a -> c) -> Seq a -> (Seq b, Seq c)
unzipWith; unzipWith3 :: forall a b c d.
(a -> b) -> (a -> c) -> (a -> d) -> Seq a -> (Seq b, Seq c, Seq d)
unzipWith3 = forall a b c d.
(a -> b) -> (a -> c) -> (a -> d) -> Seq a -> (Seq b, Seq c, Seq d)
unzipWith3;
   strict :: forall a. Seq a -> Seq a
strict = forall a. Seq a -> Seq a
strict; strictWith :: forall a b. (a -> b) -> Seq a -> Seq a
strictWith = forall a b. (a -> b) -> Seq a -> Seq a
strictWith;
   structuralInvariant :: forall a. Seq a -> Bool
structuralInvariant = forall a. Seq a -> Bool
structuralInvariant; instanceName :: forall a. Seq a -> String
instanceName Seq a
_ = String
moduleName}

instance Functor Seq where
  fmap :: forall a b. (a -> b) -> Seq a -> Seq b
fmap = forall a b. (a -> b) -> Seq a -> Seq b
map

instance App.Alternative Seq where
  empty :: forall a. Seq a
empty = forall a. Seq a
empty
  <|> :: forall a. Seq a -> Seq a -> Seq a
(<|>) = forall a. Seq a -> Seq a -> Seq a
append

instance App.Applicative Seq where
  pure :: forall a. a -> Seq a
pure = forall (m :: * -> *) a. Monad m => a -> m a
return
  Seq (a -> b)
x <*> :: forall a b. Seq (a -> b) -> Seq a -> Seq b
<*> Seq a
y = do
     a -> b
x' <- Seq (a -> b)
x
     a
y' <- Seq a
y
     forall (m :: * -> *) a. Monad m => a -> m a
return (a -> b
x' a
y')

instance Monad Seq where
  return :: forall a. a -> Seq a
return = forall a. a -> Seq a
singleton
  Seq a
xs >>= :: forall a b. Seq a -> (a -> Seq b) -> Seq b
>>= a -> Seq b
k = forall a b. (a -> Seq b) -> Seq a -> Seq b
concatMap a -> Seq b
k Seq a
xs

instance MonadPlus Seq where
  mplus :: forall a. Seq a -> Seq a -> Seq a
mplus = forall a. Seq a -> Seq a -> Seq a
append
  mzero :: forall a. Seq a
mzero = forall a. Seq a
empty

instance Ord a => Ord (Seq a) where
  compare :: Seq a -> Seq a -> Ordering
compare = forall a (s :: * -> *).
(Ord a, Sequence s) =>
s a -> s a -> Ordering
defaultCompare

instance Show a => Show (Seq a) where
  showsPrec :: Int -> Seq a -> ShowS
showsPrec = forall a (s :: * -> *). (Show a, Sequence s) => Int -> s a -> ShowS
showsPrecUsingToList

instance Read a => Read (Seq a) where
  readsPrec :: Int -> ReadS (Seq a)
readsPrec = forall a (s :: * -> *). (Read a, Sequence s) => Int -> ReadS (s a)
readsPrecUsingFromList

instance Arbitrary a => Arbitrary (Seq a) where
  arbitrary :: Gen (Seq a)
arbitrary = do [a]
xs <- forall a. Arbitrary a => Gen a
arbitrary
                 forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. [a] -> Seq a
fromList [a]
xs)

instance CoArbitrary a => CoArbitrary (Seq a) where
  coarbitrary :: forall b. Seq a -> Gen b -> Gen b
coarbitrary Seq a
xs = forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (forall a. Seq a -> [a]
toList Seq a
xs)

instance Semigroup (Seq a) where
  <> :: Seq a -> Seq a -> Seq a
(<>) = forall a. Seq a -> Seq a -> Seq a
append
instance Monoid (Seq a) where
  mempty :: Seq a
mempty  = forall a. Seq a
empty
  mappend :: Seq a -> Seq a -> Seq a
mappend = forall a. Semigroup a => a -> a -> a
(SG.<>)