module Data.Edison.Seq.SizedSeq (
Sized,
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,foldlWithIndex,foldrWithIndex',foldlWithIndex',
take,drop,splitAt,subseq,filter,partition,takeWhile,dropWhile,splitWhile,
zip,zip3,zipWith,zipWith3,unzip,unzip3,unzipWith,unzipWith3,
strict, strictWith,
structuralInvariant,
moduleName,instanceName,
fromSeq,toSeq
) where
import Prelude hiding (concat,reverse,map,concatMap,foldr,foldl,foldr1,foldl1,foldl',
filter,takeWhile,dropWhile,lookup,take,drop,splitAt,
zip,zip3,zipWith,zipWith3,unzip,unzip3,null)
import qualified Control.Applicative as App
import qualified Data.Edison.Seq as S
import qualified Data.Edison.Seq.ListSeq as L
import Data.Edison.Seq.Defaults
import Data.Monoid
import Data.Semigroup as SG
import Control.Monad
import qualified Control.Monad.Fail as Fail
import Test.QuickCheck
moduleName :: String
instanceName :: S.Sequence s => Sized s a -> String
empty :: S.Sequence s => Sized s a
singleton :: S.Sequence s => a -> Sized s a
lcons :: S.Sequence s => a -> Sized s a -> Sized s a
rcons :: S.Sequence s => a -> Sized s a -> Sized s a
append :: S.Sequence s => Sized s a -> Sized s a -> Sized s a
lview :: (S.Sequence s, Fail.MonadFail m) => Sized s a -> m (a, Sized s a)
lhead :: S.Sequence s => Sized s a -> a
lheadM :: (S.Sequence s, Fail.MonadFail m) => Sized s a -> m a
ltail :: S.Sequence s => Sized s a -> Sized s a
ltailM :: (S.Sequence s, Fail.MonadFail m) => Sized s a -> m (Sized s a)
rview :: (S.Sequence s, Fail.MonadFail m) => Sized s a -> m (a, Sized s a)
rhead :: S.Sequence s => Sized s a -> a
rheadM :: (S.Sequence s, Fail.MonadFail m) => Sized s a -> m a
rtail :: S.Sequence s => Sized s a -> Sized s a
rtailM :: (S.Sequence s, Fail.MonadFail m) => Sized s a -> m (Sized s a)
null :: S.Sequence s => Sized s a -> Bool
size :: S.Sequence s => Sized s a -> Int
concat :: S.Sequence s => Sized s (Sized s a) -> Sized s a
reverse :: S.Sequence s => Sized s a -> Sized s a
reverseOnto :: S.Sequence s => Sized s a -> Sized s a -> Sized s a
fromList :: S.Sequence s => [a] -> Sized s a
toList :: S.Sequence s => Sized s a -> [a]
map :: S.Sequence s => (a -> b) -> Sized s a -> Sized s b
concatMap :: S.Sequence s => (a -> Sized s b) -> Sized s a -> Sized s b
fold :: S.Sequence s => (a -> b -> b) -> b -> Sized s a -> b
fold' :: S.Sequence s => (a -> b -> b) -> b -> Sized s a -> b
fold1 :: S.Sequence s => (a -> a -> a) -> Sized s a -> a
fold1' :: S.Sequence s => (a -> a -> a) -> Sized s a -> a
foldr :: S.Sequence s => (a -> b -> b) -> b -> Sized s a -> b
foldl :: S.Sequence s => (b -> a -> b) -> b -> Sized s a -> b
foldr1 :: S.Sequence s => (a -> a -> a) -> Sized s a -> a
foldl1 :: S.Sequence s => (a -> a -> a) -> Sized s a -> a
reducer :: S.Sequence s => (a -> a -> a) -> a -> Sized s a -> a
reducel :: S.Sequence s => (a -> a -> a) -> a -> Sized s a -> a
reduce1 :: S.Sequence s => (a -> a -> a) -> Sized s a -> a
foldr' :: S.Sequence s => (a -> b -> b) -> b -> Sized s a -> b
foldl' :: S.Sequence s => (b -> a -> b) -> b -> Sized s a -> b
foldr1' :: S.Sequence s => (a -> a -> a) -> Sized s a -> a
foldl1' :: S.Sequence s => (a -> a -> a) -> Sized s a -> a
reducer' :: S.Sequence s => (a -> a -> a) -> a -> Sized s a -> a
reducel' :: S.Sequence s => (a -> a -> a) -> a -> Sized s a -> a
reduce1' :: S.Sequence s => (a -> a -> a) -> Sized s a -> a
copy :: S.Sequence s => Int -> a -> Sized s a
inBounds :: S.Sequence s => Int -> Sized s a -> Bool
lookup :: S.Sequence s => Int -> Sized s a -> a
lookupM :: (S.Sequence s, Fail.MonadFail m) => Int -> Sized s a -> m a
lookupWithDefault :: S.Sequence s => a -> Int -> Sized s a -> a
update :: S.Sequence s => Int -> a -> Sized s a -> Sized s a
adjust :: S.Sequence s => (a -> a) -> Int -> Sized s a -> Sized s a
mapWithIndex :: S.Sequence s => (Int -> a -> b) -> Sized s a -> Sized s b
foldrWithIndex :: S.Sequence s => (Int -> a -> b -> b) -> b -> Sized s a -> b
foldlWithIndex :: S.Sequence s => (b -> Int -> a -> b) -> b -> Sized s a -> b
foldrWithIndex' :: S.Sequence s => (Int -> a -> b -> b) -> b -> Sized s a -> b
foldlWithIndex' :: S.Sequence s => (b -> Int -> a -> b) -> b -> Sized s a -> b
take :: S.Sequence s => Int -> Sized s a -> Sized s a
drop :: S.Sequence s => Int -> Sized s a -> Sized s a
splitAt :: S.Sequence s => Int -> Sized s a -> (Sized s a, Sized s a)
subseq :: S.Sequence s => Int -> Int -> Sized s a -> Sized s a
filter :: S.Sequence s => (a -> Bool) -> Sized s a -> Sized s a
partition :: S.Sequence s => (a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
takeWhile :: S.Sequence s => (a -> Bool) -> Sized s a -> Sized s a
dropWhile :: S.Sequence s => (a -> Bool) -> Sized s a -> Sized s a
splitWhile :: S.Sequence s => (a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
zip :: S.Sequence s => Sized s a -> Sized s b -> Sized s (a,b)
zip3 :: S.Sequence s => Sized s a -> Sized s b -> Sized s c -> Sized s (a,b,c)
zipWith :: S.Sequence s => (a -> b -> c) -> Sized s a -> Sized s b -> Sized s c
zipWith3 :: S.Sequence s => (a -> b -> c -> d) -> Sized s a -> Sized s b -> Sized s c -> Sized s d
unzip :: S.Sequence s => Sized s (a,b) -> (Sized s a, Sized s b)
unzip3 :: S.Sequence s => Sized s (a,b,c) -> (Sized s a, Sized s b, Sized s c)
unzipWith :: S.Sequence s => (a -> b) -> (a -> c) -> Sized s a -> (Sized s b, Sized s c)
unzipWith3 :: S.Sequence s => (a -> b) -> (a -> c) -> (a -> d) -> Sized s a -> (Sized s b, Sized s c, Sized s d)
strict :: S.Sequence s => Sized s a -> Sized s a
strictWith :: S.Sequence s => (a -> b) -> Sized s a -> Sized s a
structuralInvariant :: S.Sequence s => Sized s a -> Bool
fromSeq :: S.Sequence s => s a -> Sized s a
toSeq :: S.Sequence s => Sized s a -> s a
moduleName :: String
moduleName = String
"Data.Edison.Seq.SizedSeq"
instanceName :: forall (s :: * -> *) a. Sequence s => Sized s a -> String
instanceName (N Int
_ s a
s) = String
"SizedSeq(" String -> String -> String
forall a. [a] -> [a] -> [a]
++ s a -> String
forall a. s a -> String
forall (s :: * -> *) a. Sequence s => s a -> String
S.instanceName s a
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
data Sized s a = N !Int (s a)
fromSeq :: forall (s :: * -> *) a. Sequence s => s a -> Sized s a
fromSeq s a
xs = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (s a -> Int
forall a. s a -> Int
forall (s :: * -> *) a. Sequence s => s a -> Int
S.size s a
xs) s a
xs
toSeq :: forall (s :: * -> *) a. Sequence s => Sized s a -> s a
toSeq (N Int
_ s a
xs) = s a
xs
empty :: forall (s :: * -> *) a. Sequence s => Sized s a
empty = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
0 s a
forall (s :: * -> *) a. Sequence s => s a
S.empty
singleton :: forall (s :: * -> *) a. Sequence s => a -> Sized s a
singleton a
x = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
1 (a -> s a
forall (s :: * -> *) a. Sequence s => a -> s a
S.singleton a
x)
lcons :: forall (s :: * -> *) a. Sequence s => a -> Sized s a -> Sized s a
lcons a
x (N Int
n s a
xs) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (a -> s a -> s a
forall a. a -> s a -> s a
forall (s :: * -> *) a. Sequence s => a -> s a -> s a
S.lcons a
x s a
xs)
rcons :: forall (s :: * -> *) a. Sequence s => a -> Sized s a -> Sized s a
rcons a
x (N Int
n s a
xs) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (a -> s a -> s a
forall a. a -> s a -> s a
forall (s :: * -> *) a. Sequence s => a -> s a -> s a
S.rcons a
x s a
xs)
append :: forall (s :: * -> *) a.
Sequence s =>
Sized s a -> Sized s a -> Sized s a
append (N Int
m s a
xs) (N Int
n s a
ys) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (s a -> s a -> s a
forall (s :: * -> *) a. Sequence s => s a -> s a -> s a
S.append s a
xs s a
ys)
lview :: forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m (a, Sized s a)
lview (N Int
n s a
xs) = case s a -> Maybe (a, s a)
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
s a -> m (a, s a)
forall (m :: * -> *) a. MonadFail m => s a -> m (a, s a)
S.lview s a
xs of
Maybe (a, s a)
Nothing -> String -> m (a, Sized s a)
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"SizedSeq.lview: empty sequence"
Just (a
x,s a
xs) -> (a, Sized s a) -> m (a, Sized s a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x, Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) s a
xs)
lhead :: forall (s :: * -> *) a. Sequence s => Sized s a -> a
lhead (N Int
_ s a
xs) = s a -> a
forall a. s a -> a
forall (s :: * -> *) a. Sequence s => s a -> a
S.lhead s a
xs
lheadM :: forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m a
lheadM (N Int
_ s a
xs) = s a -> m a
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
s a -> m a
forall (m :: * -> *) a. MonadFail m => s a -> m a
S.lheadM s a
xs
ltail :: forall (s :: * -> *) a. Sequence s => Sized s a -> Sized s a
ltail (N Int
0 s a
_) = String -> Sized s a
forall a. HasCallStack => String -> a
error String
"SizedSeq.ltail: empty sequence"
ltail (N Int
n s a
xs) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (s a -> s a
forall a. s a -> s a
forall (s :: * -> *) a. Sequence s => s a -> s a
S.ltail s a
xs)
ltailM :: forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m (Sized s a)
ltailM (N Int
0 s a
_) = String -> m (Sized s a)
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"SizedSeq.ltailM: empty sequence"
ltailM (N Int
n s a
xs) = Sized s a -> m (Sized s a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (s a -> s a
forall a. s a -> s a
forall (s :: * -> *) a. Sequence s => s a -> s a
S.ltail s a
xs))
rview :: forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m (a, Sized s a)
rview (N Int
n s a
xs) = case s a -> Maybe (a, s a)
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
s a -> m (a, s a)
forall (m :: * -> *) a. MonadFail m => s a -> m (a, s a)
S.rview s a
xs of
Maybe (a, s a)
Nothing -> String -> m (a, Sized s a)
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"SizedSeq.rview: empty sequence"
Just (a
x,s a
xs) -> (a, Sized s a) -> m (a, Sized s a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x, Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) s a
xs)
rhead :: forall (s :: * -> *) a. Sequence s => Sized s a -> a
rhead (N Int
_ s a
xs) = s a -> a
forall a. s a -> a
forall (s :: * -> *) a. Sequence s => s a -> a
S.rhead s a
xs
rheadM :: forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m a
rheadM (N Int
_ s a
xs) = s a -> m a
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
s a -> m a
forall (m :: * -> *) a. MonadFail m => s a -> m a
S.rheadM s a
xs
rtail :: forall (s :: * -> *) a. Sequence s => Sized s a -> Sized s a
rtail (N Int
0 s a
_) = String -> Sized s a
forall a. HasCallStack => String -> a
error String
"SizedSeq.rtail: empty sequence"
rtail (N Int
n s a
xs) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (s a -> s a
forall a. s a -> s a
forall (s :: * -> *) a. Sequence s => s a -> s a
S.rtail s a
xs)
rtailM :: forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m (Sized s a)
rtailM (N Int
0 s a
_) = String -> m (Sized s a)
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"SizedSeq.rtailM: empty sequence"
rtailM (N Int
n s a
xs) = Sized s a -> m (Sized s a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (s a -> s a
forall a. s a -> s a
forall (s :: * -> *) a. Sequence s => s a -> s a
S.rtail s a
xs))
null :: forall (s :: * -> *) a. Sequence s => Sized s a -> Bool
null (N Int
n s a
_) = Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
size :: forall (s :: * -> *) a. Sequence s => Sized s a -> Int
size (N Int
n s a
_) = Int
n
concat :: forall (s :: * -> *) a.
Sequence s =>
Sized s (Sized s a) -> Sized s a
concat (N Int
_ s (Sized s a)
xss) = s a -> Sized s a
forall (s :: * -> *) a. Sequence s => s a -> Sized s a
fromSeq (s (s a) -> s a
forall a. s (s a) -> s a
forall (s :: * -> *) a. Sequence s => s (s a) -> s a
S.concat ((Sized s a -> s a) -> s (Sized s a) -> s (s a)
forall (s :: * -> *) a b. Sequence s => (a -> b) -> s a -> s b
S.map Sized s a -> s a
forall (s :: * -> *) a. Sequence s => Sized s a -> s a
toSeq s (Sized s a)
xss))
reverse :: forall (s :: * -> *) a. Sequence s => Sized s a -> Sized s a
reverse (N Int
n s a
xs) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n (s a -> s a
forall a. s a -> s a
forall (s :: * -> *) a. Sequence s => s a -> s a
S.reverse s a
xs)
reverseOnto :: forall (s :: * -> *) a.
Sequence s =>
Sized s a -> Sized s a -> Sized s a
reverseOnto (N Int
m s a
xs) (N Int
n s a
ys) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (s a -> s a -> s a
forall a. s a -> s a -> s a
forall (s :: * -> *) a. Sequence s => s a -> s a -> s a
S.reverseOnto s a
xs s a
ys)
fromList :: forall (s :: * -> *) a. Sequence s => [a] -> Sized s a
fromList = s a -> Sized s a
forall (s :: * -> *) a. Sequence s => s a -> Sized s a
fromSeq (s a -> Sized s a) -> ([a] -> s a) -> [a] -> Sized s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> s a
forall a. [a] -> s a
forall (s :: * -> *) a. Sequence s => [a] -> s a
S.fromList
toList :: forall (s :: * -> *) a. Sequence s => Sized s a -> [a]
toList (N Int
_ s a
xs) = s a -> [a]
forall a. s a -> [a]
forall (s :: * -> *) a. Sequence s => s a -> [a]
S.toList s a
xs
map :: forall (s :: * -> *) a b.
Sequence s =>
(a -> b) -> Sized s a -> Sized s b
map a -> b
f (N Int
n s a
xs) = Int -> s b -> Sized s b
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n ((a -> b) -> s a -> s b
forall (s :: * -> *) a b. Sequence s => (a -> b) -> s a -> s b
S.map a -> b
f s a
xs)
concatMap :: forall (s :: * -> *) a b.
Sequence s =>
(a -> Sized s b) -> Sized s a -> Sized s b
concatMap = (a -> Sized s b) -> Sized s a -> Sized s b
forall (s :: * -> *) a b. Sequence s => (a -> s b) -> s a -> s b
concatMapUsingFoldr
fold :: forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> Sized s a -> b
fold a -> b -> b
f b
e (N Int
_ s a
xs) = (a -> b -> b) -> b -> s a -> b
forall a b. (a -> b -> b) -> b -> s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> s a -> b
S.fold a -> b -> b
f b
e s a
xs
fold' :: forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> Sized s a -> b
fold' a -> b -> b
f b
e (N Int
_ s a
xs) = (a -> b -> b) -> b -> s a -> b
forall a b. (a -> b -> b) -> b -> s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> s a -> b
S.fold' a -> b -> b
f b
e s a
xs
fold1 :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
fold1 a -> a -> a
f (N Int
_ s a
xs) = (a -> a -> a) -> s a -> a
forall a. (a -> a -> a) -> s a -> a
forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
S.fold1 a -> a -> a
f s a
xs
fold1' :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
fold1' a -> a -> a
f (N Int
_ s a
xs) = (a -> a -> a) -> s a -> a
forall a. (a -> a -> a) -> s a -> a
forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
S.fold1' a -> a -> a
f s a
xs
foldr :: forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> Sized s a -> b
foldr a -> b -> b
f b
e (N Int
_ s a
xs) = (a -> b -> b) -> b -> s a -> b
forall a b. (a -> b -> b) -> b -> s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> s a -> b
S.foldr a -> b -> b
f b
e s a
xs
foldr' :: forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> Sized s a -> b
foldr' a -> b -> b
f b
e (N Int
_ s a
xs) = (a -> b -> b) -> b -> s a -> b
forall a b. (a -> b -> b) -> b -> s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> s a -> b
S.foldr' a -> b -> b
f b
e s a
xs
foldl :: forall (s :: * -> *) b a.
Sequence s =>
(b -> a -> b) -> b -> Sized s a -> b
foldl b -> a -> b
f b
e (N Int
_ s a
xs) = (b -> a -> b) -> b -> s a -> b
forall b a. (b -> a -> b) -> b -> s a -> b
forall (s :: * -> *) b a.
Sequence s =>
(b -> a -> b) -> b -> s a -> b
S.foldl b -> a -> b
f b
e s a
xs
foldl' :: forall (s :: * -> *) b a.
Sequence s =>
(b -> a -> b) -> b -> Sized s a -> b
foldl' b -> a -> b
f b
e (N Int
_ s a
xs) = (b -> a -> b) -> b -> s a -> b
forall b a. (b -> a -> b) -> b -> s a -> b
forall (s :: * -> *) b a.
Sequence s =>
(b -> a -> b) -> b -> s a -> b
S.foldl' b -> a -> b
f b
e s a
xs
foldr1 :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
foldr1 a -> a -> a
f (N Int
_ s a
xs) = (a -> a -> a) -> s a -> a
forall a. (a -> a -> a) -> s a -> a
forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
S.foldr1 a -> a -> a
f s a
xs
foldr1' :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
foldr1' a -> a -> a
f (N Int
_ s a
xs) = (a -> a -> a) -> s a -> a
forall a. (a -> a -> a) -> s a -> a
forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
S.foldr1' a -> a -> a
f s a
xs
foldl1 :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
foldl1 a -> a -> a
f (N Int
_ s a
xs) = (a -> a -> a) -> s a -> a
forall a. (a -> a -> a) -> s a -> a
forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
S.foldl1 a -> a -> a
f s a
xs
foldl1' :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
foldl1' a -> a -> a
f (N Int
_ s a
xs) = (a -> a -> a) -> s a -> a
forall a. (a -> a -> a) -> s a -> a
forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
S.foldl1' a -> a -> a
f s a
xs
reducer :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> Sized s a -> a
reducer a -> a -> a
f a
e (N Int
_ s a
xs) = (a -> a -> a) -> a -> s a -> a
forall a. (a -> a -> a) -> a -> s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> s a -> a
S.reducer a -> a -> a
f a
e s a
xs
reducer' :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> Sized s a -> a
reducer' a -> a -> a
f a
e (N Int
_ s a
xs) = (a -> a -> a) -> a -> s a -> a
forall a. (a -> a -> a) -> a -> s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> s a -> a
S.reducer' a -> a -> a
f a
e s a
xs
reducel :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> Sized s a -> a
reducel a -> a -> a
f a
e (N Int
_ s a
xs) = (a -> a -> a) -> a -> s a -> a
forall a. (a -> a -> a) -> a -> s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> s a -> a
S.reducel a -> a -> a
f a
e s a
xs
reducel' :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> Sized s a -> a
reducel' a -> a -> a
f a
e (N Int
_ s a
xs) = (a -> a -> a) -> a -> s a -> a
forall a. (a -> a -> a) -> a -> s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> s a -> a
S.reducel' a -> a -> a
f a
e s a
xs
reduce1 :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
reduce1 a -> a -> a
f (N Int
_ s a
xs) = (a -> a -> a) -> s a -> a
forall a. (a -> a -> a) -> s a -> a
forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
S.reduce1 a -> a -> a
f s a
xs
reduce1' :: forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
reduce1' a -> a -> a
f (N Int
_ s a
xs) = (a -> a -> a) -> s a -> a
forall a. (a -> a -> a) -> s a -> a
forall (s :: * -> *) a. Sequence s => (a -> a -> a) -> s a -> a
S.reduce1' a -> a -> a
f s a
xs
copy :: forall (s :: * -> *) a. Sequence s => Int -> a -> Sized s a
copy Int
n a
x
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty
| Bool
otherwise = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n (Int -> a -> s a
forall a. Int -> a -> s a
forall (s :: * -> *) a. Sequence s => Int -> a -> s a
S.copy Int
n a
x)
inBounds :: forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> Bool
inBounds Int
i (N Int
n s a
_) = (Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0) Bool -> Bool -> Bool
&& (Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n)
lookup :: forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> a
lookup Int
i (N Int
_ s a
xs) = Int -> s a -> a
forall a. Int -> s a -> a
forall (s :: * -> *) a. Sequence s => Int -> s a -> a
S.lookup Int
i s a
xs
lookupM :: forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Int -> Sized s a -> m a
lookupM Int
i (N Int
_ s a
xs) = Int -> s a -> m a
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Int -> s a -> m a
forall (m :: * -> *) a. MonadFail m => Int -> s a -> m a
S.lookupM Int
i s a
xs
lookupWithDefault :: forall (s :: * -> *) a. Sequence s => a -> Int -> Sized s a -> a
lookupWithDefault a
d Int
i (N Int
_ s a
xs) = a -> Int -> s a -> a
forall a. a -> Int -> s a -> a
forall (s :: * -> *) a. Sequence s => a -> Int -> s a -> a
S.lookupWithDefault a
d Int
i s a
xs
update :: forall (s :: * -> *) a.
Sequence s =>
Int -> a -> Sized s a -> Sized s a
update Int
i a
x (N Int
n s a
xs) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n (Int -> a -> s a -> s a
forall a. Int -> a -> s a -> s a
forall (s :: * -> *) a. Sequence s => Int -> a -> s a -> s a
S.update Int
i a
x s a
xs)
adjust :: forall (s :: * -> *) a.
Sequence s =>
(a -> a) -> Int -> Sized s a -> Sized s a
adjust a -> a
f Int
i (N Int
n s a
xs) = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n ((a -> a) -> Int -> s a -> s a
forall a. (a -> a) -> Int -> s a -> s a
forall (s :: * -> *) a. Sequence s => (a -> a) -> Int -> s a -> s a
S.adjust a -> a
f Int
i s a
xs)
mapWithIndex :: forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b) -> Sized s a -> Sized s b
mapWithIndex Int -> a -> b
f (N Int
n s a
xs) = Int -> s b -> Sized s b
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n ((Int -> a -> b) -> s a -> s b
forall a b. (Int -> a -> b) -> s a -> s b
forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b) -> s a -> s b
S.mapWithIndex Int -> a -> b
f s a
xs)
foldrWithIndex :: forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b -> b) -> b -> Sized s a -> b
foldrWithIndex Int -> a -> b -> b
f b
e (N Int
_ s a
xs) = (Int -> a -> b -> b) -> b -> s a -> b
forall a b. (Int -> a -> b -> b) -> b -> s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b -> b) -> b -> s a -> b
S.foldrWithIndex Int -> a -> b -> b
f b
e s a
xs
foldrWithIndex' :: forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b -> b) -> b -> Sized s a -> b
foldrWithIndex' Int -> a -> b -> b
f b
e (N Int
_ s a
xs) = (Int -> a -> b -> b) -> b -> s a -> b
forall a b. (Int -> a -> b -> b) -> b -> s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b -> b) -> b -> s a -> b
S.foldrWithIndex' Int -> a -> b -> b
f b
e s a
xs
foldlWithIndex :: forall (s :: * -> *) b a.
Sequence s =>
(b -> Int -> a -> b) -> b -> Sized s a -> b
foldlWithIndex b -> Int -> a -> b
f b
e (N Int
_ s a
xs) = (b -> Int -> a -> b) -> b -> s a -> b
forall b a. (b -> Int -> a -> b) -> b -> s a -> b
forall (s :: * -> *) b a.
Sequence s =>
(b -> Int -> a -> b) -> b -> s a -> b
S.foldlWithIndex b -> Int -> a -> b
f b
e s a
xs
foldlWithIndex' :: forall (s :: * -> *) b a.
Sequence s =>
(b -> Int -> a -> b) -> b -> Sized s a -> b
foldlWithIndex' b -> Int -> a -> b
f b
e (N Int
_ s a
xs) = (b -> Int -> a -> b) -> b -> s a -> b
forall b a. (b -> Int -> a -> b) -> b -> s a -> b
forall (s :: * -> *) b a.
Sequence s =>
(b -> Int -> a -> b) -> b -> s a -> b
S.foldlWithIndex' b -> Int -> a -> b
f b
e s a
xs
take :: forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> Sized s a
take Int
i original :: Sized s a
original@(N Int
n s a
xs)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n = Sized s a
original
| Bool
otherwise = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
i (Int -> s a -> s a
forall a. Int -> s a -> s a
forall (s :: * -> *) a. Sequence s => Int -> s a -> s a
S.take Int
i s a
xs)
drop :: forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> Sized s a
drop Int
i original :: Sized s a
original@(N Int
n s a
xs)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Sized s a
original
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n = Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty
| Bool
otherwise = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) (Int -> s a -> s a
forall a. Int -> s a -> s a
forall (s :: * -> *) a. Sequence s => Int -> s a -> s a
S.drop Int
i s a
xs)
splitAt :: forall (s :: * -> *) a.
Sequence s =>
Int -> Sized s a -> (Sized s a, Sized s a)
splitAt Int
i original :: Sized s a
original@(N Int
n s a
xs)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = (Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty, Sized s a
original)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n = (Sized s a
original, Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty)
| Bool
otherwise = let (s a
ys,s a
zs) = Int -> s a -> (s a, s a)
forall a. Int -> s a -> (s a, s a)
forall (s :: * -> *) a. Sequence s => Int -> s a -> (s a, s a)
S.splitAt Int
i s a
xs
in (Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
i s a
ys, Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) s a
zs)
subseq :: forall (s :: * -> *) a.
Sequence s =>
Int -> Int -> Sized s a -> Sized s a
subseq Int
i Int
len original :: Sized s a
original@(N Int
n s a
xs)
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Int -> Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> Sized s a
take Int
len Sized s a
original
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n Bool -> Bool -> Bool
|| Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty
| Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) (Int -> s a -> s a
forall a. Int -> s a -> s a
forall (s :: * -> *) a. Sequence s => Int -> s a -> s a
S.drop Int
i s a
xs)
| Bool
otherwise = Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
len (Int -> Int -> s a -> s a
forall a. Int -> Int -> s a -> s a
forall (s :: * -> *) a. Sequence s => Int -> Int -> s a -> s a
S.subseq Int
i Int
len s a
xs)
filter :: forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> Sized s a
filter a -> Bool
p = s a -> Sized s a
forall (s :: * -> *) a. Sequence s => s a -> Sized s a
fromSeq (s a -> Sized s a) -> (Sized s a -> s a) -> Sized s a -> Sized s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> s a -> s a
forall a. (a -> Bool) -> s a -> s a
forall (s :: * -> *) a. Sequence s => (a -> Bool) -> s a -> s a
S.filter a -> Bool
p (s a -> s a) -> (Sized s a -> s a) -> Sized s a -> s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sized s a -> s a
forall (s :: * -> *) a. Sequence s => Sized s a -> s a
toSeq
partition :: forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
partition a -> Bool
p (N Int
n s a
xs) = (Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
m s a
ys, Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
m) s a
zs)
where (s a
ys,s a
zs) = (a -> Bool) -> s a -> (s a, s a)
forall a. (a -> Bool) -> s a -> (s a, s a)
forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> s a -> (s a, s a)
S.partition a -> Bool
p s a
xs
m :: Int
m = s a -> Int
forall a. s a -> Int
forall (s :: * -> *) a. Sequence s => s a -> Int
S.size s a
ys
takeWhile :: forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> Sized s a
takeWhile a -> Bool
p = s a -> Sized s a
forall (s :: * -> *) a. Sequence s => s a -> Sized s a
fromSeq (s a -> Sized s a) -> (Sized s a -> s a) -> Sized s a -> Sized s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> s a -> s a
forall a. (a -> Bool) -> s a -> s a
forall (s :: * -> *) a. Sequence s => (a -> Bool) -> s a -> s a
S.takeWhile a -> Bool
p (s a -> s a) -> (Sized s a -> s a) -> Sized s a -> s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sized s a -> s a
forall (s :: * -> *) a. Sequence s => Sized s a -> s a
toSeq
dropWhile :: forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> Sized s a
dropWhile a -> Bool
p = s a -> Sized s a
forall (s :: * -> *) a. Sequence s => s a -> Sized s a
fromSeq (s a -> Sized s a) -> (Sized s a -> s a) -> Sized s a -> Sized s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> s a -> s a
forall a. (a -> Bool) -> s a -> s a
forall (s :: * -> *) a. Sequence s => (a -> Bool) -> s a -> s a
S.dropWhile a -> Bool
p (s a -> s a) -> (Sized s a -> s a) -> Sized s a -> s a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sized s a -> s a
forall (s :: * -> *) a. Sequence s => Sized s a -> s a
toSeq
splitWhile :: forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
splitWhile a -> Bool
p (N Int
n s a
xs) = (Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
m s a
ys, Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
m) s a
zs)
where (s a
ys,s a
zs) = (a -> Bool) -> s a -> (s a, s a)
forall a. (a -> Bool) -> s a -> (s a, s a)
forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> s a -> (s a, s a)
S.splitWhile a -> Bool
p s a
xs
m :: Int
m = s a -> Int
forall a. s a -> Int
forall (s :: * -> *) a. Sequence s => s a -> Int
S.size s a
ys
zip :: forall (s :: * -> *) a b.
Sequence s =>
Sized s a -> Sized s b -> Sized s (a, b)
zip (N Int
m s a
xs) (N Int
n s b
ys) = Int -> s (a, b) -> Sized s (a, b)
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
m Int
n) (s a -> s b -> s (a, b)
forall a b. s a -> s b -> s (a, b)
forall (s :: * -> *) a b. Sequence s => s a -> s b -> s (a, b)
S.zip s a
xs s b
ys)
zip3 :: forall (s :: * -> *) a b c.
Sequence s =>
Sized s a -> Sized s b -> Sized s c -> Sized s (a, b, c)
zip3 (N Int
l s a
xs) (N Int
m s b
ys) (N Int
n s c
zs) = Int -> s (a, b, c) -> Sized s (a, b, c)
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
l (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
m Int
n)) (s a -> s b -> s c -> s (a, b, c)
forall a b c. s a -> s b -> s c -> s (a, b, c)
forall (s :: * -> *) a b c.
Sequence s =>
s a -> s b -> s c -> s (a, b, c)
S.zip3 s a
xs s b
ys s c
zs)
zipWith :: forall (s :: * -> *) a b c.
Sequence s =>
(a -> b -> c) -> Sized s a -> Sized s b -> Sized s c
zipWith a -> b -> c
f (N Int
m s a
xs) (N Int
n s b
ys) = Int -> s c -> Sized s c
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
m Int
n) ((a -> b -> c) -> s a -> s b -> s c
forall a b c. (a -> b -> c) -> s a -> s b -> s c
forall (s :: * -> *) a b c.
Sequence s =>
(a -> b -> c) -> s a -> s b -> s c
S.zipWith a -> b -> c
f s a
xs s b
ys)
zipWith3 :: forall (s :: * -> *) a b c d.
Sequence s =>
(a -> b -> c -> d)
-> Sized s a -> Sized s b -> Sized s c -> Sized s d
zipWith3 a -> b -> c -> d
f (N Int
l s a
xs) (N Int
m s b
ys) (N Int
n s c
zs) = Int -> s d -> Sized s d
forall (s :: * -> *) a. Int -> s a -> Sized s a
N (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
l (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
m Int
n)) ((a -> b -> c -> d) -> s a -> s b -> s c -> s d
forall a b c d. (a -> b -> c -> d) -> s a -> s b -> s c -> s d
forall (s :: * -> *) a b c d.
Sequence s =>
(a -> b -> c -> d) -> s a -> s b -> s c -> s d
S.zipWith3 a -> b -> c -> d
f s a
xs s b
ys s c
zs)
unzip :: forall (s :: * -> *) a b.
Sequence s =>
Sized s (a, b) -> (Sized s a, Sized s b)
unzip (N Int
n s (a, b)
xys) = (Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s a
xs, Int -> s b -> Sized s b
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s b
ys)
where (s a
xs,s b
ys) = s (a, b) -> (s a, s b)
forall a b. s (a, b) -> (s a, s b)
forall (s :: * -> *) a b. Sequence s => s (a, b) -> (s a, s b)
S.unzip s (a, b)
xys
unzip3 :: forall (s :: * -> *) a b c.
Sequence s =>
Sized s (a, b, c) -> (Sized s a, Sized s b, Sized s c)
unzip3 (N Int
n s (a, b, c)
xyzs) = (Int -> s a -> Sized s a
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s a
xs, Int -> s b -> Sized s b
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s b
ys, Int -> s c -> Sized s c
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s c
zs)
where (s a
xs,s b
ys,s c
zs) = s (a, b, c) -> (s a, s b, s c)
forall a b c. s (a, b, c) -> (s a, s b, s c)
forall (s :: * -> *) a b c.
Sequence s =>
s (a, b, c) -> (s a, s b, s c)
S.unzip3 s (a, b, c)
xyzs
unzipWith :: forall (s :: * -> *) a b c.
Sequence s =>
(a -> b) -> (a -> c) -> Sized s a -> (Sized s b, Sized s c)
unzipWith a -> b
f a -> c
g (N Int
n s a
xys) = (Int -> s b -> Sized s b
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s b
xs, Int -> s c -> Sized s c
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s c
ys)
where (s b
xs,s c
ys) = (a -> b) -> (a -> c) -> s a -> (s b, s c)
forall a b c. (a -> b) -> (a -> c) -> s a -> (s b, s c)
forall (s :: * -> *) a b c.
Sequence s =>
(a -> b) -> (a -> c) -> s a -> (s b, s c)
S.unzipWith a -> b
f a -> c
g s a
xys
unzipWith3 :: forall (s :: * -> *) a b c d.
Sequence s =>
(a -> b)
-> (a -> c)
-> (a -> d)
-> Sized s a
-> (Sized s b, Sized s c, Sized s d)
unzipWith3 a -> b
f a -> c
g a -> d
h (N Int
n s a
xyzs) = (Int -> s b -> Sized s b
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s b
xs, Int -> s c -> Sized s c
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s c
ys, Int -> s d -> Sized s d
forall (s :: * -> *) a. Int -> s a -> Sized s a
N Int
n s d
zs)
where (s b
xs,s c
ys,s d
zs) = (a -> b) -> (a -> c) -> (a -> d) -> s a -> (s b, s c, s d)
forall a b c d.
(a -> b) -> (a -> c) -> (a -> d) -> s a -> (s b, s c, s d)
forall (s :: * -> *) a b c d.
Sequence s =>
(a -> b) -> (a -> c) -> (a -> d) -> s a -> (s b, s c, s d)
S.unzipWith3 a -> b
f a -> c
g a -> d
h s a
xyzs
strict :: forall (s :: * -> *) a. Sequence s => Sized s a -> Sized s a
strict s :: Sized s a
s@(N Int
_ s a
s') = s a -> s a
forall a. s a -> s a
forall (s :: * -> *) a. Sequence s => s a -> s a
S.strict s a
s' s a -> Sized s a -> Sized s a
forall a b. a -> b -> b
`seq` Sized s a
s
strictWith :: forall (s :: * -> *) a b.
Sequence s =>
(a -> b) -> Sized s a -> Sized s a
strictWith a -> b
f s :: Sized s a
s@(N Int
_ s a
s') = (a -> b) -> s a -> s a
forall a b. (a -> b) -> s a -> s a
forall (s :: * -> *) a b. Sequence s => (a -> b) -> s a -> s a
S.strictWith a -> b
f s a
s' s a -> Sized s a -> Sized s a
forall a b. a -> b -> b
`seq` Sized s a
s
structuralInvariant :: forall (s :: * -> *) a. Sequence s => Sized s a -> Bool
structuralInvariant (N Int
i s a
s) = Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== s a -> Int
forall a. s a -> Int
forall (s :: * -> *) a. Sequence s => s a -> Int
S.size s a
s
instance S.Sequence s => S.Sequence (Sized s) where
{lcons :: forall a. a -> Sized s a -> Sized s a
lcons = a -> Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => a -> Sized s a -> Sized s a
lcons; rcons :: forall a. a -> Sized s a -> Sized s a
rcons = a -> Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => a -> Sized s a -> Sized s a
rcons;
lview :: forall (m :: * -> *) a.
MonadFail m =>
Sized s a -> m (a, Sized s a)
lview = Sized s a -> m (a, Sized s a)
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m (a, Sized s a)
lview; lhead :: forall a. Sized s a -> a
lhead = Sized s a -> a
forall (s :: * -> *) a. Sequence s => Sized s a -> a
lhead; ltail :: forall a. Sized s a -> Sized s a
ltail = Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a -> Sized s a
ltail;
lheadM :: forall (m :: * -> *) a. MonadFail m => Sized s a -> m a
lheadM = Sized s a -> m a
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m a
lheadM; ltailM :: forall (m :: * -> *) a. MonadFail m => Sized s a -> m (Sized s a)
ltailM = Sized s a -> m (Sized s a)
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m (Sized s a)
ltailM; rheadM :: forall (m :: * -> *) a. MonadFail m => Sized s a -> m a
rheadM = Sized s a -> m a
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m a
rheadM; rtailM :: forall (m :: * -> *) a. MonadFail m => Sized s a -> m (Sized s a)
rtailM = Sized s a -> m (Sized s a)
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m (Sized s a)
rtailM;
rview :: forall (m :: * -> *) a.
MonadFail m =>
Sized s a -> m (a, Sized s a)
rview = Sized s a -> m (a, Sized s a)
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Sized s a -> m (a, Sized s a)
rview; rhead :: forall a. Sized s a -> a
rhead = Sized s a -> a
forall (s :: * -> *) a. Sequence s => Sized s a -> a
rhead; rtail :: forall a. Sized s a -> Sized s a
rtail = Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a -> Sized s a
rtail; null :: forall a. Sized s a -> Bool
null = Sized s a -> Bool
forall (s :: * -> *) a. Sequence s => Sized s a -> Bool
null;
size :: forall a. Sized s a -> Int
size = Sized s a -> Int
forall (s :: * -> *) a. Sequence s => Sized s a -> Int
size; concat :: forall a. Sized s (Sized s a) -> Sized s a
concat = Sized s (Sized s a) -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
Sized s (Sized s a) -> Sized s a
concat; reverse :: forall a. Sized s a -> Sized s a
reverse = Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a -> Sized s a
reverse;
reverseOnto :: forall a. Sized s a -> Sized s a -> Sized s a
reverseOnto = Sized s a -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
Sized s a -> Sized s a -> Sized s a
reverseOnto; fromList :: forall a. [a] -> Sized s a
fromList = [a] -> Sized s a
forall (s :: * -> *) a. Sequence s => [a] -> Sized s a
fromList; toList :: forall a. Sized s a -> [a]
toList = Sized s a -> [a]
forall (s :: * -> *) a. Sequence s => Sized s a -> [a]
toList;
fold :: forall a b. (a -> b -> b) -> b -> Sized s a -> b
fold = (a -> b -> b) -> b -> Sized s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> Sized s a -> b
fold; fold' :: forall a b. (a -> b -> b) -> b -> Sized s a -> b
fold' = (a -> b -> b) -> b -> Sized s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> Sized s a -> b
fold'; fold1 :: forall a. (a -> a -> a) -> Sized s a -> a
fold1 = (a -> a -> a) -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
fold1; fold1' :: forall a. (a -> a -> a) -> Sized s a -> a
fold1' = (a -> a -> a) -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
fold1';
foldr :: forall a b. (a -> b -> b) -> b -> Sized s a -> b
foldr = (a -> b -> b) -> b -> Sized s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> Sized s a -> b
foldr; foldr' :: forall a b. (a -> b -> b) -> b -> Sized s a -> b
foldr' = (a -> b -> b) -> b -> Sized s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b -> b) -> b -> Sized s a -> b
foldr'; foldl :: forall b a. (b -> a -> b) -> b -> Sized s a -> b
foldl = (b -> a -> b) -> b -> Sized s a -> b
forall (s :: * -> *) b a.
Sequence s =>
(b -> a -> b) -> b -> Sized s a -> b
foldl; foldl' :: forall b a. (b -> a -> b) -> b -> Sized s a -> b
foldl' = (b -> a -> b) -> b -> Sized s a -> b
forall (s :: * -> *) b a.
Sequence s =>
(b -> a -> b) -> b -> Sized s a -> b
foldl';
foldr1 :: forall a. (a -> a -> a) -> Sized s a -> a
foldr1 = (a -> a -> a) -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
foldr1; foldr1' :: forall a. (a -> a -> a) -> Sized s a -> a
foldr1' = (a -> a -> a) -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
foldr1'; foldl1 :: forall a. (a -> a -> a) -> Sized s a -> a
foldl1 = (a -> a -> a) -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
foldl1; foldl1' :: forall a. (a -> a -> a) -> Sized s a -> a
foldl1' = (a -> a -> a) -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
foldl1';
reducer :: forall a. (a -> a -> a) -> a -> Sized s a -> a
reducer = (a -> a -> a) -> a -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> Sized s a -> a
reducer; reducer' :: forall a. (a -> a -> a) -> a -> Sized s a -> a
reducer' = (a -> a -> a) -> a -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> Sized s a -> a
reducer'; reducel :: forall a. (a -> a -> a) -> a -> Sized s a -> a
reducel = (a -> a -> a) -> a -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> Sized s a -> a
reducel;
reducel' :: forall a. (a -> a -> a) -> a -> Sized s a -> a
reducel' = (a -> a -> a) -> a -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> a -> Sized s a -> a
reducel'; reduce1 :: forall a. (a -> a -> a) -> Sized s a -> a
reduce1 = (a -> a -> a) -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
reduce1; reduce1' :: forall a. (a -> a -> a) -> Sized s a -> a
reduce1' = (a -> a -> a) -> Sized s a -> a
forall (s :: * -> *) a.
Sequence s =>
(a -> a -> a) -> Sized s a -> a
reduce1';
copy :: forall a. Int -> a -> Sized s a
copy = Int -> a -> Sized s a
forall (s :: * -> *) a. Sequence s => Int -> a -> Sized s a
copy; inBounds :: forall a. Int -> Sized s a -> Bool
inBounds = Int -> Sized s a -> Bool
forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> Bool
inBounds; lookup :: forall a. Int -> Sized s a -> a
lookup = Int -> Sized s a -> a
forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> a
lookup;
lookupM :: forall (m :: * -> *) a. MonadFail m => Int -> Sized s a -> m a
lookupM = Int -> Sized s a -> m a
forall (s :: * -> *) (m :: * -> *) a.
(Sequence s, MonadFail m) =>
Int -> Sized s a -> m a
lookupM; lookupWithDefault :: forall a. a -> Int -> Sized s a -> a
lookupWithDefault = a -> Int -> Sized s a -> a
forall (s :: * -> *) a. Sequence s => a -> Int -> Sized s a -> a
lookupWithDefault;
update :: forall a. Int -> a -> Sized s a -> Sized s a
update = Int -> a -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
Int -> a -> Sized s a -> Sized s a
update; adjust :: forall a. (a -> a) -> Int -> Sized s a -> Sized s a
adjust = (a -> a) -> Int -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
(a -> a) -> Int -> Sized s a -> Sized s a
adjust; mapWithIndex :: forall a b. (Int -> a -> b) -> Sized s a -> Sized s b
mapWithIndex = (Int -> a -> b) -> Sized s a -> Sized s b
forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b) -> Sized s a -> Sized s b
mapWithIndex;
foldrWithIndex :: forall a b. (Int -> a -> b -> b) -> b -> Sized s a -> b
foldrWithIndex = (Int -> a -> b -> b) -> b -> Sized s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b -> b) -> b -> Sized s a -> b
foldrWithIndex; foldrWithIndex' :: forall a b. (Int -> a -> b -> b) -> b -> Sized s a -> b
foldrWithIndex' = (Int -> a -> b -> b) -> b -> Sized s a -> b
forall (s :: * -> *) a b.
Sequence s =>
(Int -> a -> b -> b) -> b -> Sized s a -> b
foldrWithIndex';
foldlWithIndex :: forall b a. (b -> Int -> a -> b) -> b -> Sized s a -> b
foldlWithIndex = (b -> Int -> a -> b) -> b -> Sized s a -> b
forall (s :: * -> *) b a.
Sequence s =>
(b -> Int -> a -> b) -> b -> Sized s a -> b
foldlWithIndex; foldlWithIndex' :: forall b a. (b -> Int -> a -> b) -> b -> Sized s a -> b
foldlWithIndex' = (b -> Int -> a -> b) -> b -> Sized s a -> b
forall (s :: * -> *) b a.
Sequence s =>
(b -> Int -> a -> b) -> b -> Sized s a -> b
foldlWithIndex';
take :: forall a. Int -> Sized s a -> Sized s a
take = Int -> Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> Sized s a
take; drop :: forall a. Int -> Sized s a -> Sized s a
drop = Int -> Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => Int -> Sized s a -> Sized s a
drop; splitAt :: forall a. Int -> Sized s a -> (Sized s a, Sized s a)
splitAt = Int -> Sized s a -> (Sized s a, Sized s a)
forall (s :: * -> *) a.
Sequence s =>
Int -> Sized s a -> (Sized s a, Sized s a)
splitAt; subseq :: forall a. Int -> Int -> Sized s a -> Sized s a
subseq = Int -> Int -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
Int -> Int -> Sized s a -> Sized s a
subseq;
filter :: forall a. (a -> Bool) -> Sized s a -> Sized s a
filter = (a -> Bool) -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> Sized s a
filter; partition :: forall a. (a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
partition = (a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
partition; takeWhile :: forall a. (a -> Bool) -> Sized s a -> Sized s a
takeWhile = (a -> Bool) -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> Sized s a
takeWhile;
dropWhile :: forall a. (a -> Bool) -> Sized s a -> Sized s a
dropWhile = (a -> Bool) -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> Sized s a
dropWhile; splitWhile :: forall a. (a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
splitWhile = (a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
forall (s :: * -> *) a.
Sequence s =>
(a -> Bool) -> Sized s a -> (Sized s a, Sized s a)
splitWhile; zip :: forall a b. Sized s a -> Sized s b -> Sized s (a, b)
zip = Sized s a -> Sized s b -> Sized s (a, b)
forall (s :: * -> *) a b.
Sequence s =>
Sized s a -> Sized s b -> Sized s (a, b)
zip;
zip3 :: forall a b c.
Sized s a -> Sized s b -> Sized s c -> Sized s (a, b, c)
zip3 = Sized s a -> Sized s b -> Sized s c -> Sized s (a, b, c)
forall (s :: * -> *) a b c.
Sequence s =>
Sized s a -> Sized s b -> Sized s c -> Sized s (a, b, c)
zip3; zipWith :: forall a b c. (a -> b -> c) -> Sized s a -> Sized s b -> Sized s c
zipWith = (a -> b -> c) -> Sized s a -> Sized s b -> Sized s c
forall (s :: * -> *) a b c.
Sequence s =>
(a -> b -> c) -> Sized s a -> Sized s b -> Sized s c
zipWith; zipWith3 :: forall a b c d.
(a -> b -> c -> d)
-> Sized s a -> Sized s b -> Sized s c -> Sized s d
zipWith3 = (a -> b -> c -> d)
-> Sized s a -> Sized s b -> Sized s c -> Sized s d
forall (s :: * -> *) a b c d.
Sequence s =>
(a -> b -> c -> d)
-> Sized s a -> Sized s b -> Sized s c -> Sized s d
zipWith3; unzip :: forall a b. Sized s (a, b) -> (Sized s a, Sized s b)
unzip = Sized s (a, b) -> (Sized s a, Sized s b)
forall (s :: * -> *) a b.
Sequence s =>
Sized s (a, b) -> (Sized s a, Sized s b)
unzip;
unzip3 :: forall a b c.
Sized s (a, b, c) -> (Sized s a, Sized s b, Sized s c)
unzip3 = Sized s (a, b, c) -> (Sized s a, Sized s b, Sized s c)
forall (s :: * -> *) a b c.
Sequence s =>
Sized s (a, b, c) -> (Sized s a, Sized s b, Sized s c)
unzip3; unzipWith :: forall a b c.
(a -> b) -> (a -> c) -> Sized s a -> (Sized s b, Sized s c)
unzipWith = (a -> b) -> (a -> c) -> Sized s a -> (Sized s b, Sized s c)
forall (s :: * -> *) a b c.
Sequence s =>
(a -> b) -> (a -> c) -> Sized s a -> (Sized s b, Sized s c)
unzipWith; unzipWith3 :: forall a b c d.
(a -> b)
-> (a -> c)
-> (a -> d)
-> Sized s a
-> (Sized s b, Sized s c, Sized s d)
unzipWith3 = (a -> b)
-> (a -> c)
-> (a -> d)
-> Sized s a
-> (Sized s b, Sized s c, Sized s d)
forall (s :: * -> *) a b c d.
Sequence s =>
(a -> b)
-> (a -> c)
-> (a -> d)
-> Sized s a
-> (Sized s b, Sized s c, Sized s d)
unzipWith3;
strict :: forall a. Sized s a -> Sized s a
strict = Sized s a -> Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a -> Sized s a
strict; strictWith :: forall a b. (a -> b) -> Sized s a -> Sized s a
strictWith = (a -> b) -> Sized s a -> Sized s a
forall (s :: * -> *) a b.
Sequence s =>
(a -> b) -> Sized s a -> Sized s a
strictWith;
structuralInvariant :: forall a. Sized s a -> Bool
structuralInvariant = Sized s a -> Bool
forall (s :: * -> *) a. Sequence s => Sized s a -> Bool
structuralInvariant; instanceName :: forall a. Sized s a -> String
instanceName = Sized s a -> String
forall (s :: * -> *) a. Sequence s => Sized s a -> String
instanceName}
instance S.Sequence s => Functor (Sized s) where
fmap :: forall a b. (a -> b) -> Sized s a -> Sized s b
fmap = (a -> b) -> Sized s a -> Sized s b
forall (s :: * -> *) a b.
Sequence s =>
(a -> b) -> Sized s a -> Sized s b
map
instance S.Sequence s => App.Alternative (Sized s) where
empty :: forall a. Sized s a
empty = Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty
<|> :: forall a. Sized s a -> Sized s a -> Sized s a
(<|>) = Sized s a -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
Sized s a -> Sized s a -> Sized s a
append
instance S.Sequence s => App.Applicative (Sized s) where
pure :: forall a. a -> Sized s a
pure = a -> Sized s a
forall a. a -> Sized s a
forall (m :: * -> *) a. Monad m => a -> m a
return
Sized s (a -> b)
x <*> :: forall a b. Sized s (a -> b) -> Sized s a -> Sized s b
<*> Sized s a
y = do
a -> b
x' <- Sized s (a -> b)
x
a
y' <- Sized s a
y
b -> Sized s b
forall a. a -> Sized s a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> b
x' a
y')
instance S.Sequence s => Monad (Sized s) where
return :: forall a. a -> Sized s a
return = a -> Sized s a
forall (s :: * -> *) a. Sequence s => a -> Sized s a
singleton
Sized s a
xs >>= :: forall a b. Sized s a -> (a -> Sized s b) -> Sized s b
>>= a -> Sized s b
k = (a -> Sized s b) -> Sized s a -> Sized s b
forall (s :: * -> *) a b.
Sequence s =>
(a -> Sized s b) -> Sized s a -> Sized s b
concatMap a -> Sized s b
k Sized s a
xs
instance S.Sequence s => MonadPlus (Sized s) where
mplus :: forall a. Sized s a -> Sized s a -> Sized s a
mplus = Sized s a -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
Sized s a -> Sized s a -> Sized s a
append
mzero :: forall a. Sized s a
mzero = Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty
instance Eq (s a) => Eq (Sized s a) where
(N Int
m s a
xs) == :: Sized s a -> Sized s a -> Bool
== (N Int
n s a
ys) = (Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
n) Bool -> Bool -> Bool
&& (s a
xs s a -> s a -> Bool
forall a. Eq a => a -> a -> Bool
== s a
ys)
instance (S.Sequence s, Ord a, Eq (s a)) => Ord (Sized s a) where
compare :: Sized s a -> Sized s a -> Ordering
compare = Sized s a -> Sized s a -> Ordering
forall a (s :: * -> *).
(Ord a, Sequence s) =>
s a -> s a -> Ordering
defaultCompare
instance (S.Sequence s, Show (s a)) => Show (Sized s a) where
showsPrec :: Int -> Sized s a -> String -> String
showsPrec Int
i Sized s a
xs String
rest
| Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [String] -> String
forall a. [[a]] -> [a]
L.concat [ String
moduleName,String
".fromSeq ",Int -> s a -> String -> String
forall a. Show a => Int -> a -> String -> String
showsPrec Int
10 (Sized s a -> s a
forall (s :: * -> *) a. Sequence s => Sized s a -> s a
toSeq Sized s a
xs) String
rest]
| Bool
otherwise = [String] -> String
forall a. [[a]] -> [a]
L.concat [String
"(",String
moduleName,String
".fromSeq ",Int -> s a -> String -> String
forall a. Show a => Int -> a -> String -> String
showsPrec Int
10 (Sized s a -> s a
forall (s :: * -> *) a. Sequence s => Sized s a -> s a
toSeq Sized s a
xs) (Char
')'Char -> String -> String
forall a. a -> [a] -> [a]
:String
rest)]
instance (S.Sequence s, Read (s a)) => Read (Sized s a) where
readsPrec :: Int -> ReadS (Sized s a)
readsPrec Int
_ String
xs = ReadS (Sized s a) -> ReadS (Sized s a)
forall a. ReadS a -> ReadS a
maybeParens ReadS (Sized s a)
forall {s :: * -> *} {a}.
(Read (s a), Sequence s) =>
String -> [(Sized s a, String)]
p String
xs
where p :: String -> [(Sized s a, String)]
p String
xs = String -> String -> [String]
forall (m :: * -> *). MonadPlus m => String -> String -> m String
tokenMatch (String
moduleNameString -> String -> String
forall a. [a] -> [a] -> [a]
++String
".fromSeq") String
xs
[String] -> (String -> [(s a, String)]) -> [(s a, String)]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> String -> [(s a, String)]
forall a. Read a => Int -> ReadS a
readsPrec Int
10
[(s a, String)]
-> ((s a, String) -> [(Sized s a, String)])
-> [(Sized s a, String)]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \(s a
l,String
rest) -> (Sized s a, String) -> [(Sized s a, String)]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (s a -> Sized s a
forall (s :: * -> *) a. Sequence s => s a -> Sized s a
fromSeq s a
l, String
rest)
instance (S.Sequence s, Arbitrary (s a)) => Arbitrary (Sized s a) where
arbitrary :: Gen (Sized s a)
arbitrary = do s a
xs <- Gen (s a)
forall a. Arbitrary a => Gen a
arbitrary
Sized s a -> Gen (Sized s a)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (s a -> Sized s a
forall (s :: * -> *) a. Sequence s => s a -> Sized s a
fromSeq s a
xs)
instance (S.Sequence s, CoArbitrary (s a)) => CoArbitrary (Sized s a) where
coarbitrary :: forall b. Sized s a -> Gen b -> Gen b
coarbitrary Sized s a
xs = s a -> Gen b -> Gen b
forall b. s a -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (Sized s a -> s a
forall (s :: * -> *) a. Sequence s => Sized s a -> s a
toSeq Sized s a
xs)
instance S.Sequence s => Semigroup (Sized s a) where
<> :: Sized s a -> Sized s a -> Sized s a
(<>) = Sized s a -> Sized s a -> Sized s a
forall (s :: * -> *) a.
Sequence s =>
Sized s a -> Sized s a -> Sized s a
append
instance S.Sequence s => Monoid (Sized s a) where
mempty :: Sized s a
mempty = Sized s a
forall (s :: * -> *) a. Sequence s => Sized s a
empty
mappend :: Sized s a -> Sized s a -> Sized s a
mappend = Sized s a -> Sized s a -> Sized s a
forall a. Semigroup a => a -> a -> a
(SG.<>)