{-# LANGUAGE NoImplicitPrelude, BangPatterns #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Rhythmicity.MarkerSeqs where
import GHC.Num
import GHC.Real
import GHC.Base
import GHC.Word
import Data.List hiding (foldr)
import Data.Ord (Down(..))
import GHC.Show
import Data.Bits
import Numeric (showIntAtBase,showInt)
import Data.Foldable (Foldable)
import GHC.Int
import Data.Char (isDigit)
import Data.Maybe (mapMaybe, catMaybes)
import Rhythmicity.BasicF
import Text.Read
import GHC.Enum (fromEnum)
import GHC.Arr (listArray,unsafeAt)
import Data.Tuple (fst,snd)
showBin :: Int -> [Char]
showBin :: Int -> [Char]
showBin Int
x = Char
'0'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
'b'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Int -> (Int -> Char) -> Int -> [Char] -> [Char]
forall a. Integral a => a -> (Int -> Char) -> a -> [Char] -> [Char]
showIntAtBase Int
2 ([Char] -> Char
forall a. HasCallStack => [a] -> a
head ([Char] -> Char) -> (Int -> [Char]) -> Int -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> [Char] -> [Char]) -> [Char] -> Int -> [Char]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> [Char] -> [Char]
forall a. Integral a => a -> [Char] -> [Char]
showInt [Char]
"") Int
x [Char]
""
{-# INLINE showBin #-}
unionCount :: (Bits a) => a -> a -> Integer
unionCount :: forall a. Bits a => a -> a -> Integer
unionCount a
x = Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> (a -> Int) -> a -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a. Bits a => a -> Int
popCount (a -> Int) -> (a -> a) -> a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> a
forall a. Bits a => a -> a -> a
(.&.) a
x
{-# INLINE unionCount #-}
countWeightsQs :: (Foldable t) => [t a -> Int] -> [t a] -> [[Int]]
countWeightsQs :: forall (t :: * -> *) a.
Foldable t =>
[t a -> Int] -> [t a] -> [[Int]]
countWeightsQs [t a -> Int]
fs [t a]
xs = ((t a -> Int) -> [Int]) -> [t a -> Int] -> [[Int]]
forall a b. (a -> b) -> [a] -> [b]
map (((t a -> Int) -> [t a] -> [Int]) -> [t a] -> (t a -> Int) -> [Int]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (t a -> Int) -> [t a] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [t a]
xs) [t a -> Int]
fs
data Sort2 a = S2 {
forall a. Sort2 a -> Int8
id :: Int8,
forall a. Sort2 a -> a
val :: a
}
instance Eq a => Eq (Sort2 a) where
S2 Int8
_ a
x == :: Sort2 a -> Sort2 a -> Bool
== S2 Int8
_ a
y = a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y
instance Ord a => Ord (Sort2 a) where
compare :: Sort2 a -> Sort2 a -> Ordering
compare (S2 Int8
_ a
x) (S2 Int8
_ a
y) = a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare a
y a
x
S2 Int8
_ a
x > :: Sort2 a -> Sort2 a -> Bool
> S2 Int8
_ a
y = a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
y
S2 Int8
_ a
x < :: Sort2 a -> Sort2 a -> Bool
< S2 Int8
_ a
y = a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
y
S2 Int8
_ a
x >= :: Sort2 a -> Sort2 a -> Bool
>= S2 Int8
_ a
y = a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
y
S2 Int8
_ a
x <= :: Sort2 a -> Sort2 a -> Bool
<= S2 Int8
_ a
y = a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
y
instance Functor Sort2 where
fmap :: forall a b. (a -> b) -> Sort2 a -> Sort2 b
fmap a -> b
f (S2 Int8
k a
x) = Int8 -> b -> Sort2 b
forall a. Int8 -> a -> Sort2 a
S2 Int8
k (b -> Sort2 b) -> (a -> b) -> a -> Sort2 b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f (a -> Sort2 b) -> a -> Sort2 b
forall a b. (a -> b) -> a -> b
$ a
x
instance Show a => Show (Sort2 a) where
show :: Sort2 a -> [Char]
show (S2 Int8
k a
x) = Int8 -> [Char]
forall a. Show a => a -> [Char]
show Int8
k [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Char
'~'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:a -> [Char]
forall a. Show a => a -> [Char]
show a
x
data ASort3 a = As3 {
forall a. ASort3 a -> Int8
id3 :: Int8,
forall a. ASort3 a -> Int8
orD :: Int8,
forall a. ASort3 a -> a
val3 :: a
}
instance Eq a => Eq (ASort3 a) where
As3 Int8
_ Int8
_ a
x == :: ASort3 a -> ASort3 a -> Bool
== As3 Int8
_ Int8
_ a
y = a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y
instance Show a => Show (ASort3 a) where
show :: ASort3 a -> [Char]
show (As3 Int8
n Int8
k a
x) = Int8 -> [Char]
forall a. Show a => a -> [Char]
show Int8
n [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Char
'&'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Int8 -> [Char]
forall a. Show a => a -> [Char]
show Int8
k [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Char
'~'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:a -> [Char]
forall a. Show a => a -> [Char]
show a
x
splitF :: Int -> [a] -> [[a]]
splitF :: forall a. Int -> [a] -> [[a]]
splitF Int
n [a]
ys = let (Int
q,Int
r) = [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
ys Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
n in Int -> [[a]] -> [[a]]
forall a. Int -> [a] -> [a]
take (if Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int
q Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
q) ([[a]] -> [[a]]) -> ([a] -> [[a]]) -> [a] -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a] -> ([a], [a])) -> [a] -> [[a]]
forall {t} {a}. (t -> (a, t)) -> t -> [a]
g (Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
n) ([a] -> [[a]]) -> [a] -> [[a]]
forall a b. (a -> b) -> a -> b
$ [a]
ys
where {-# INLINE g #-}
g :: (t -> (a, t)) -> t -> [a]
g t -> (a, t)
f t
b0 = (forall b. (a -> b -> b) -> b -> b) -> [a]
forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build (\a -> b -> b
c b
n ->
let go :: t -> b
go t
b = case t -> (a, t)
f t
b of
(a
a, t
new_b) -> a
a a -> b -> b
`c` t -> b
go t
new_b in t -> b
go t
b0)
getHashes2
:: Ord a => Int8
-> [Int8]
-> [a]
-> [[Integer]]
getHashes2 :: forall a. Ord a => Int8 -> [Int8] -> [a] -> [[Integer]]
getHashes2 Int8
selmarkNum [Int8]
ks [a]
xs = ([a] -> [Integer]) -> [[a]] -> [[Integer]]
forall a b. (a -> b) -> [a] -> [b]
map (([Int8] -> Integer) -> [[Int8]] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map [Int8] -> Integer
toNum ([[Int8]] -> [Integer]) -> ([a] -> [[Int8]]) -> [a] -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Int8] -> Bool) -> [[Int8]] -> [[Int8]]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> ([Int8] -> Bool) -> [Int8] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int8] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([[Int8]] -> [[Int8]]) -> ([a] -> [[Int8]]) -> [a] -> [[Int8]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([ASort3 a] -> [Int8]) -> [[ASort3 a]] -> [[Int8]]
forall a b. (a -> b) -> [a] -> [b]
map ([Int8] -> [ASort3 a] -> [Int8]
forall a. Eq a => [Int8] -> [ASort3 a] -> [Int8]
idList [Int8]
ks) ([[ASort3 a]] -> [[Int8]])
-> ([a] -> [[ASort3 a]]) -> [a] -> [[Int8]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Int8] -> [Sort2 a] -> [[ASort3 a]]
forall {a}. Eq a => [Int8] -> [Sort2 a] -> [[ASort3 a]]
g [Int8
selmarkNumInt8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
-Int8
1,Int8
selmarkNumInt8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
-Int8
2..] ([Sort2 a] -> [[ASort3 a]])
-> ([a] -> [Sort2 a]) -> [a] -> [[ASort3 a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sort2 a -> Sort2 a) -> [Sort2 a] -> [Sort2 a]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Sort2 a -> Sort2 a
forall a. a -> a
GHC.Base.id ([Sort2 a] -> [Sort2 a]) -> ([a] -> [Sort2 a]) -> [a] -> [Sort2 a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Int8 -> a -> Sort2 a) -> [Int8] -> [a] -> [Sort2 a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int8 -> a -> Sort2 a
forall a. Int8 -> a -> Sort2 a
S2 [Int8
selmarkNumInt8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
-Int8
1,Int8
selmarkNumInt8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
-Int8
2..]) ([[a]] -> [[Integer]]) -> ([a] -> [[a]]) -> [a] -> [[Integer]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [a] -> [[a]]
forall a. Int -> [a] -> [[a]]
splitF (Int8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
selmarkNum) ([a] -> [[Integer]]) -> [a] -> [[Integer]]
forall a b. (a -> b) -> a -> b
$ [a]
xs
where g :: [Int8] -> [Sort2 a] -> [[ASort3 a]]
g (Int8
q:[Int8]
qs) xs :: [Sort2 a]
xs@(Sort2 a
x:[Sort2 a]
ys) = let ([Sort2 a]
js,[Sort2 a]
rs) = (Sort2 a -> Bool) -> [Sort2 a] -> ([Sort2 a], [Sort2 a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Sort2 a -> Sort2 a -> Bool
forall a. Eq a => a -> a -> Bool
== Sort2 a
x) [Sort2 a]
ys in (Sort2 a -> ASort3 a) -> [Sort2 a] -> [ASort3 a]
forall a b. (a -> b) -> [a] -> [b]
map (\(S2 Int8
k a
y) -> Int8 -> Int8 -> a -> ASort3 a
forall a. Int8 -> Int8 -> a -> ASort3 a
As3 Int8
k Int8
q a
y) (Sort2 a
xSort2 a -> [Sort2 a] -> [Sort2 a]
forall a. a -> [a] -> [a]
:[Sort2 a]
js) [ASort3 a] -> [[ASort3 a]] -> [[ASort3 a]]
forall a. a -> [a] -> [a]
: [Int8] -> [Sort2 a] -> [[ASort3 a]]
g [Int8]
qs [Sort2 a]
rs
g [Int8]
_ [Sort2 a]
_ = []
countHashesPrioritized :: [[b]] -> [[Integer]]
countHashesPrioritized tss :: [[b]]
tss@([b]
ts:[b]
vs:[[b]]
xss) = (b -> b -> Integer) -> [b] -> [b] -> [Integer]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith b -> b -> Integer
forall a. Bits a => a -> a -> Integer
unionCount [b]
ts [b]
vs [Integer] -> [[Integer]] -> [[Integer]]
forall a. a -> [a] -> [a]
: [[b]] -> [[Integer]]
countHashesPrioritized ([b]
vs[b] -> [[b]] -> [[b]]
forall a. a -> [a] -> [a]
:[[b]]
xss)
countHashesPrioritized [[b]]
_ = []
count1Hashes
:: Ord a => Int8
-> [Int8]
-> [a]
-> Integer
count1Hashes :: forall a. Ord a => Int8 -> [Int8] -> [a] -> Integer
count1Hashes Int8
groupLength [Int8]
ks = [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Integer] -> Integer) -> ([a] -> [Integer]) -> [a] -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Integer] -> Integer) -> [[Integer]] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map [Integer] -> Integer
createNewHash ([[Integer]] -> [Integer])
-> ([a] -> [[Integer]]) -> [a] -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Integer]] -> [[Integer]]
forall {b}. Bits b => [[b]] -> [[Integer]]
countHashesPrioritized ([[Integer]] -> [[Integer]])
-> ([a] -> [[Integer]]) -> [a] -> [[Integer]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> [Int8] -> [a] -> [[Integer]]
forall a. Ord a => Int8 -> [Int8] -> [a] -> [[Integer]]
getHashes2 Int8
groupLength [Int8]
ws
where !ws :: [Int8]
ws = (Int8 -> Down Int8) -> [Int8] -> [Int8]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Int8 -> Down Int8
forall a. a -> Down a
Down ([Int8] -> [Int8]) -> ([Int8] -> [Int8]) -> [Int8] -> [Int8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int8 -> Bool) -> [Int8] -> [Int8]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int8 -> Int8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int8
0) ([Int8] -> [Int8]) -> [Int8] -> [Int8]
forall a b. (a -> b) -> a -> b
$ [Int8]
ks
{-# INLINE count1Hashes #-}
data HashCorrections = H [Int8] Int8 deriving (HashCorrections -> HashCorrections -> Bool
(HashCorrections -> HashCorrections -> Bool)
-> (HashCorrections -> HashCorrections -> Bool)
-> Eq HashCorrections
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HashCorrections -> HashCorrections -> Bool
== :: HashCorrections -> HashCorrections -> Bool
$c/= :: HashCorrections -> HashCorrections -> Bool
/= :: HashCorrections -> HashCorrections -> Bool
Eq, Int -> HashCorrections -> [Char] -> [Char]
[HashCorrections] -> [Char] -> [Char]
HashCorrections -> [Char]
(Int -> HashCorrections -> [Char] -> [Char])
-> (HashCorrections -> [Char])
-> ([HashCorrections] -> [Char] -> [Char])
-> Show HashCorrections
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> HashCorrections -> [Char] -> [Char]
showsPrec :: Int -> HashCorrections -> [Char] -> [Char]
$cshow :: HashCorrections -> [Char]
show :: HashCorrections -> [Char]
$cshowList :: [HashCorrections] -> [Char] -> [Char]
showList :: [HashCorrections] -> [Char] -> [Char]
Show)
hashCorrections2F :: HashCorrections -> (Int8 -> [Integer] -> Integer)
hashCorrections2F :: HashCorrections -> Int8 -> [Integer] -> Integer
hashCorrections2F (H [Int8]
_ Int8
k)
| Int8
k Int8 -> Int8 -> Bool
forall a. Ord a => a -> a -> Bool
> Int8
0 = Int8 -> [Integer] -> Integer
hashPosLF2
| Int8
k Int8 -> Int8 -> Bool
forall a. Eq a => a -> a -> Bool
== Int8
0 = Int8 -> [Integer] -> Integer
hashBalancingLF2
| Bool
otherwise = Int8 -> [Integer] -> Integer
hashBasicLF2
{-# INLINE hashCorrections2F #-}
hashList :: HashCorrections -> [Int8]
hashList :: HashCorrections -> [Int8]
hashList (H [Int8]
_ Int8
1) = [Int8
24,Int8
23..]
hashList (H [Int8]
_ Int8
2) = [Int8
1..Int8
21] [Int8] -> [Int8] -> [Int8]
forall a. Monoid a => a -> a -> a
`mappend` [Int8] -> [Int8]
forall a. HasCallStack => [a] -> [a]
cycle [Int8
0]
hashList (H [Int8]
xs Int8
_) = [Int8]
xs [Int8] -> [Int8] -> [Int8]
forall a. Monoid a => a -> a -> a
`mappend` [Int8] -> [Int8]
forall a. HasCallStack => [a] -> [a]
cycle [Int8
0]
{-# INLINE hashList #-}
readHashCorrections :: String -> HashCorrections
readHashCorrections :: [Char] -> HashCorrections
readHashCorrections [Char]
xs = if [Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Char]
ys Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 then let ([Char]
ts,[Char]
us) = Int -> [Char] -> ([Char], [Char])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
1 [Char]
ys in [Int8] -> Int8 -> HashCorrections
H ((Char -> Int8) -> [Char] -> [Int8]
forall a b. (a -> b) -> [a] -> [b]
map (\Char
x -> [Char] -> Int8
forall a. Read a => [Char] -> a
read [Char
x]::Int8) [Char]
us) (if Bool
sgn then (-([Char] -> Int8
forall a. Read a => [Char] -> a
read [Char]
ts::Int8)) else ([Char] -> Int8
forall a. Read a => [Char] -> a
read [Char]
ts::Int8)) else [Int8] -> Int8 -> HashCorrections
H [Int8
0,Int8
0..] Int8
0
where ys :: [Char]
ys = (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Char
x -> Char -> Bool
isDigit Char
x) [Char]
xs
sgn :: Bool
sgn = (Char -> Bool) -> [Char] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-') [Char]
xs
grouppingR :: String -> (Int8, [Int8])
grouppingR :: [Char] -> (Int8, [Int8])
grouppingR [Char]
xs = if [Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Char]
ys Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 then let ([Char]
ts,[Char]
us) = Int -> [Char] -> ([Char], [Char])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
1 [Char]
ys in ([Char] -> Int8
forall a. Read a => [Char] -> a
read [Char]
ts::Int8, (Char -> Int8) -> [Char] -> [Int8]
forall a b. (a -> b) -> [a] -> [b]
map (\Char
x -> [Char] -> Int8
forall a. Read a => [Char] -> a
read [Char
x]::Int8) [Char]
us) else (Int8
4,[Int8
3,Int8
2])
where ys :: [Char]
ys = Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
take Int
8 ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Char
x -> Char -> Bool
isDigit Char
x) ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
xs
countHashesG
:: Ord a => HashCorrections
-> Int8
-> [Int8]
-> [a]
-> [Integer]
countHashesG :: forall a.
Ord a =>
HashCorrections -> Int8 -> [Int8] -> [a] -> [Integer]
countHashesG HashCorrections
hc Int8
groupLength [Int8]
ks =
(Int8 -> [Integer] -> Integer)
-> [Int8] -> [[Integer]] -> [Integer]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ((Int8 -> [Integer] -> Integer) -> Int8 -> [Integer] -> Integer
createHashG Int8 -> [Integer] -> Integer
f) [Int8]
positions ([[Integer]] -> [Integer])
-> ([a] -> [[Integer]]) -> [a] -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Integer]] -> [[Integer]]
forall {b}. Bits b => [[b]] -> [[Integer]]
countHashesPrioritized ([[Integer]] -> [[Integer]])
-> ([a] -> [[Integer]]) -> [a] -> [[Integer]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> [Int8] -> [a] -> [[Integer]]
forall a. Ord a => Int8 -> [Int8] -> [a] -> [[Integer]]
getHashes2 Int8
groupLength [Int8]
ws
where f :: Int8 -> [Integer] -> Integer
f = HashCorrections -> Int8 -> [Integer] -> Integer
hashCorrections2F HashCorrections
hc
positions :: [Int8]
positions = HashCorrections -> [Int8]
hashList HashCorrections
hc
!ws :: [Int8]
ws = (Int8 -> Down Int8) -> [Int8] -> [Int8]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Int8 -> Down Int8
forall a. a -> Down a
Down ([Int8] -> [Int8]) -> ([Int8] -> [Int8]) -> [Int8] -> [Int8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int8 -> Bool) -> [Int8] -> [Int8]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int8 -> Int8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int8
0) ([Int8] -> [Int8]) -> [Int8] -> [Int8]
forall a b. (a -> b) -> a -> b
$ [Int8]
ks
{-# INLINE countHashesG #-}
countHashes2G
:: Ord a => Int
-> HashCorrections
-> Int8
-> [Int8]
-> [a]
-> [Integer]
countHashes2G :: forall a.
Ord a =>
Int -> HashCorrections -> Int8 -> [Int8] -> [a] -> [Integer]
countHashes2G Int
k HashCorrections
hc Int8
groupLength [Int8]
ks =
(Int8 -> [Integer] -> Integer)
-> [Int8] -> [[Integer]] -> [Integer]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Int -> HashCorrections -> Int8 -> [Integer] -> Integer
createHash2G Int
k HashCorrections
hc) [Int8]
positions ([[Integer]] -> [Integer])
-> ([a] -> [[Integer]]) -> [a] -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Integer]] -> [[Integer]]
forall {b}. Bits b => [[b]] -> [[Integer]]
countHashesPrioritized ([[Integer]] -> [[Integer]])
-> ([a] -> [[Integer]]) -> [a] -> [[Integer]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> [Int8] -> [a] -> [[Integer]]
forall a. Ord a => Int8 -> [Int8] -> [a] -> [[Integer]]
getHashes2 Int8
groupLength [Int8]
ws
where positions :: [Int8]
positions = HashCorrections -> [Int8]
hashList HashCorrections
hc
!ws :: [Int8]
ws = (Int8 -> Down Int8) -> [Int8] -> [Int8]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Int8 -> Down Int8
forall a. a -> Down a
Down ([Int8] -> [Int8]) -> ([Int8] -> [Int8]) -> [Int8] -> [Int8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int8 -> Bool) -> [Int8] -> [Int8]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int8 -> Int8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int8
0) ([Int8] -> [Int8]) -> [Int8] -> [Int8]
forall a b. (a -> b) -> a -> b
$ [Int8]
ks
{-# INLINE countHashes2G #-}
createNewHash :: [Integer] -> Integer
createNewHash :: [Integer] -> Integer
createNewHash (Integer
x1:Integer
x2:Integer
x3:Integer
x4:Integer
x5:Integer
x6:Integer
x7:[Integer]
_) = [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x1 Int
120, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x2 Int
100, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x3 Int
80, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x4 Int
60, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x5 Int
40, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x6 Int
20, Integer
x7]
createNewHash (Integer
x1:Integer
x2:Integer
x3:Integer
x4:Integer
x5:Integer
x6:[Integer]
_) = [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x1 Int
120, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x2 Int
100, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x3 Int
80, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x4 Int
60, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x5 Int
40, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x6 Int
20]
createNewHash (Integer
x1:Integer
x2:Integer
x3:Integer
x4:Integer
x5:[Integer]
_) = [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x1 Int
120, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x2 Int
100, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x3 Int
80, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x4 Int
60, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x5 Int
40]
createNewHash (Integer
x1:Integer
x2:Integer
x3:Integer
x4:[Integer]
_) = [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x1 Int
120, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x2 Int
100, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x3 Int
80, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x4 Int
60]
createNewHash (Integer
x1:Integer
x2:Integer
x3:[Integer]
_) = [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x1 Int
120, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x2 Int
100, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x3 Int
80]
createNewHash (Integer
x1:Integer
x2:[Integer]
_) = [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x1 Int
120, Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x2 Int
100]
createNewHash (Integer
x1:[Integer]
_) = Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
x1 Int
120
createNewHash [Integer]
_ = Integer
0
createHashG :: (Int8 -> [Integer] -> Integer) -> Int8 -> [Integer] -> Integer
createHashG :: (Int8 -> [Integer] -> Integer) -> Int8 -> [Integer] -> Integer
createHashG Int8 -> [Integer] -> Integer
f Int8
pos = Int8 -> [Integer] -> Integer
f Int8
pos ([Integer] -> Integer)
-> ([Integer] -> [Integer]) -> [Integer] -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Integer -> Integer) -> [Int] -> [Integer] -> [Integer]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Int
n Integer
x -> Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shift Integer
x (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
20)) [Int
6,Int
5..Int
0]
{-# INLINE createHashG #-}
createHash2G :: Int -> HashCorrections -> Int8 -> [Integer] -> Integer
createHash2G :: Int -> HashCorrections -> Int8 -> [Integer] -> Integer
createHash2G Int
k hc :: HashCorrections
hc@(H [Int8]
_ Int8
0) Int8
pos = (Int -> Int8 -> [Integer] -> Integer
hashBalancingLF2G Int
k) Int8
pos ([Integer] -> Integer)
-> ([Integer] -> [Integer]) -> [Integer] -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Integer -> Integer) -> [Int] -> [Integer] -> [Integer]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Int
n Integer
x -> Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shift Integer
x (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
k)) [Int
6,Int
5..Int
0]
createHash2G Int
k (H [Int8]
_ Int8
m) Int8
pos = (if Int8
m Int8 -> Int8 -> Bool
forall a. Ord a => a -> a -> Bool
> Int8
0 then Int8 -> [Integer] -> Integer
hashPosLF2 else Int8 -> [Integer] -> Integer
hashBasicLF2) Int8
pos ([Integer] -> Integer)
-> ([Integer] -> [Integer]) -> [Integer] -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Integer -> Integer) -> [Int] -> [Integer] -> [Integer]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Int
n Integer
x -> Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shift Integer
x (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
k)) [Int
6,Int
5..Int
0]
{-# INLINE createHash2G #-}
createNHash :: [Int8] -> [Integer] -> Integer
createNHash :: [Int8] -> [Integer] -> Integer
createNHash [Int8]
_ = [Integer] -> Integer
createNewHash ([Integer] -> Integer)
-> ([Integer] -> [Integer]) -> [Integer] -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Integer] -> [Integer]
forall a. Int -> [a] -> [a]
take Int
7
{-# INLINE createNHash #-}
idList :: Eq a => [Int8] -> [ASort3 a] -> [Int8]
idList :: forall a. Eq a => [Int8] -> [ASort3 a] -> [Int8]
idList [Int8]
orDs [ASort3 a]
ys = (ASort3 a -> Int8) -> [ASort3 a] -> [Int8]
forall a b. (a -> b) -> [a] -> [b]
map (\(As3 Int8
k Int8
_ a
_) -> Int8
k) ([ASort3 a] -> [Int8])
-> ([ASort3 a] -> [ASort3 a]) -> [ASort3 a] -> [Int8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ASort3 a -> Bool) -> [ASort3 a] -> [ASort3 a]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(As3 Int8
_ Int8
n a
_) -> Int8
n Int8 -> [Int8] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int8]
orDs) ([ASort3 a] -> [Int8]) -> [ASort3 a] -> [Int8]
forall a b. (a -> b) -> a -> b
$ [ASort3 a]
ys
toNum :: [Int8] -> Integer
toNum :: [Int8] -> Integer
toNum [Int8]
xs = (Integer -> Int -> Integer) -> Integer -> [Int] -> Integer
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
setBit Integer
0 ([Int] -> Integer) -> ([Int8] -> [Int]) -> [Int8] -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int8 -> Int) -> [Int8] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Int8 -> Int
forall a. Enum a => a -> Int
fromEnum ([Int8] -> Integer) -> [Int8] -> Integer
forall a b. (a -> b) -> a -> b
$ [Int8]
xs
toNum2 :: [Int8] -> Integer
toNum2 :: [Int8] -> Integer
toNum2 [Int8]
xs = ([Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Integer] -> Integer)
-> ([Int8] -> [Integer]) -> [Int8] -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int8 -> Integer) -> [Int8] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Integer
1 (Int -> Integer) -> (Int8 -> Int) -> Int8 -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> Int
forall a. Enum a => a -> Int
fromEnum) ([Int8] -> Integer) -> [Int8] -> Integer
forall a b. (a -> b) -> a -> b
$ [Int8]
xs)::Integer
showZerosFor2Period
:: (Ord a) => [[a]]
-> Int
-> (b -> String)
-> [[[b]]]
-> (String, [Integer])
showZerosFor2Period :: forall a b.
Ord a =>
[[a]] -> Int -> (b -> [Char]) -> [[[b]]] -> ([Char], [Integer])
showZerosFor2Period [[a]]
structData Int
syllN b -> [Char]
f [[[b]]]
sylls = ([Char]
breaks, [Integer]
rs)
where rs :: [Integer]
rs = [[Integer]] -> [Integer]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Integer]] -> [Integer])
-> ([[a]] -> [[Integer]]) -> [[a]] -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Integer]] -> [[Integer]]
forall {b}. Bits b => [[b]] -> [[Integer]]
countHashesPrioritized ([[Integer]] -> [[Integer]])
-> ([[a]] -> [[Integer]]) -> [[a]] -> [[Integer]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> [Int8] -> [a] -> [[Integer]]
forall a. Ord a => Int8 -> [Int8] -> [a] -> [[Integer]]
getHashes2 Int8
2 [Int8
1] ([a] -> [[Integer]]) -> ([[a]] -> [a]) -> [[a]] -> [[Integer]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [Integer]) -> [[a]] -> [Integer]
forall a b. (a -> b) -> a -> b
$ [[a]]
structData
indeces :: [Int]
indeces = (Integer -> Bool) -> [Integer] -> [Int]
forall a. (a -> Bool) -> [a] -> [Int]
findIndices (Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0) [Integer]
rs
resSylls :: Array Int [Char]
resSylls = (Int, Int) -> [[Char]] -> Array Int [Char]
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) ([[Char]] -> Array Int [Char])
-> ([[[b]]] -> [[Char]]) -> [[[b]]] -> Array Int [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([b] -> [Char]) -> [[b]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ((b -> [Char]) -> [b] -> [Char]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap b -> [Char]
f) ([[b]] -> [[Char]]) -> ([[[b]]] -> [[b]]) -> [[[b]]] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[b]]] -> [[b]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[[b]]] -> Array Int [Char]) -> [[[b]]] -> Array Int [Char]
forall a b. (a -> b) -> a -> b
$ [[[b]]]
sylls
addlist :: [[Int]]
addlist
| Int
syllN Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [Int
0,Int
1,Int
2] [Int] -> [[Int]] -> [[Int]]
forall a. a -> [a] -> [a]
: ((Int -> [Int] -> [[Int]]
forall a. Int -> [a] -> [[a]]
splitF Int
2 ([Int] -> [[Int]]) -> ([Int] -> [Int]) -> [Int] -> [[Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take (Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
6) ([Int] -> [[Int]]) -> [Int] -> [[Int]]
forall a b. (a -> b) -> a -> b
$ [Int
3,Int
4..]) [[Int]] -> [[Int]] -> [[Int]]
forall a. Monoid a => a -> a -> a
`mappend` [[Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3, Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2, Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]])
| Bool
otherwise = [Int
0,Int
1,Int
2] [Int] -> [[Int]] -> [[Int]]
forall a. a -> [a] -> [a]
: (Int -> [Int] -> [[Int]]
forall a. Int -> [a] -> [[a]]
splitF Int
2 ([Int] -> [[Int]]) -> ([Int] -> [Int]) -> [Int] -> [[Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take (Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3) ([Int] -> [[Int]]) -> [Int] -> [[Int]]
forall a b. (a -> b) -> a -> b
$ [Int
3,Int
4..])
arrinds :: Array Int [Int]
arrinds = (Int, Int) -> [[Int]] -> Array Int [Int]
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
syllN Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
2) [[Int]]
addlist
neededinds :: [[Int]]
neededinds = (Int -> [Int]) -> [Int] -> [[Int]]
forall a b. (a -> b) -> [a] -> [b]
map (Array Int [Int] -> Int -> [Int]
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Int]
arrinds) [Int]
indeces
neededsylls :: [[[Char]]]
neededsylls = ([Int] -> [[Char]]) -> [[Int]] -> [[[Char]]]
forall a b. (a -> b) -> [a] -> [b]
map ((Int -> [Char]) -> [Int] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (Array Int [Char] -> Int -> [Char]
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Char]
resSylls)) [[Int]]
neededinds
breaks :: [Char]
breaks = [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char]
" ... " ([[Char]] -> [Char])
-> ([[[Char]]] -> [[Char]]) -> [[[Char]]] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Char]] -> [Char]) -> [[[Char]]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [[Char]] -> [Char]
unwords ([[[Char]]] -> [Char]) -> [[[Char]]] -> [Char]
forall a b. (a -> b) -> a -> b
$ [[[Char]]]
neededsylls
showZerosFor2PeriodMusic
:: [(String, Word8)]
-> (String, [Integer])
showZerosFor2PeriodMusic :: [([Char], Word8)] -> ([Char], [Integer])
showZerosFor2PeriodMusic [([Char], Word8)]
qqs = ([Char]
breaks, [Integer]
rs)
where rs :: [Integer]
rs = [[Integer]] -> [Integer]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Integer]] -> [Integer])
-> ([([Char], Word8)] -> [[Integer]])
-> [([Char], Word8)]
-> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Integer]] -> [[Integer]]
forall {b}. Bits b => [[b]] -> [[Integer]]
countHashesPrioritized ([[Integer]] -> [[Integer]])
-> ([([Char], Word8)] -> [[Integer]])
-> [([Char], Word8)]
-> [[Integer]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> [Int8] -> [Word8] -> [[Integer]]
forall a. Ord a => Int8 -> [Int8] -> [a] -> [[Integer]]
getHashes2 Int8
2 [Int8
1] ([Word8] -> [[Integer]])
-> ([([Char], Word8)] -> [Word8])
-> [([Char], Word8)]
-> [[Integer]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([Char], Word8) -> Word8) -> [([Char], Word8)] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map ([Char], Word8) -> Word8
forall a b. (a, b) -> b
snd ([([Char], Word8)] -> [Integer]) -> [([Char], Word8)] -> [Integer]
forall a b. (a -> b) -> a -> b
$ [([Char], Word8)]
qqs
syllN :: Int
syllN = [([Char], Word8)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [([Char], Word8)]
qqs
indeces :: [Int]
indeces = (Integer -> Bool) -> [Integer] -> [Int]
forall a. (a -> Bool) -> [a] -> [Int]
findIndices (Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0) [Integer]
rs
resSylls :: Array Int [Char]
resSylls = (Int, Int) -> [[Char]] -> Array Int [Char]
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) ([[Char]] -> Array Int [Char])
-> ([([Char], Word8)] -> [[Char]])
-> [([Char], Word8)]
-> Array Int [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([Char], Word8) -> [Char]) -> [([Char], Word8)] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char], Word8) -> [Char]
forall a b. (a, b) -> a
fst ([([Char], Word8)] -> Array Int [Char])
-> [([Char], Word8)] -> Array Int [Char]
forall a b. (a -> b) -> a -> b
$ [([Char], Word8)]
qqs
addlist :: [[Int]]
addlist
| Int
syllN Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` Int
2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [Int
0,Int
1,Int
2] [Int] -> [[Int]] -> [[Int]]
forall a. a -> [a] -> [a]
: ((Int -> [Int] -> [[Int]]
forall a. Int -> [a] -> [[a]]
splitF Int
2 ([Int] -> [[Int]]) -> ([Int] -> [Int]) -> [Int] -> [[Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take (Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
6) ([Int] -> [[Int]]) -> [Int] -> [[Int]]
forall a b. (a -> b) -> a -> b
$ [Int
3,Int
4..]) [[Int]] -> [[Int]] -> [[Int]]
forall a. Monoid a => a -> a -> a
`mappend` [[Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3, Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2, Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]])
| Bool
otherwise = [Int
0,Int
1,Int
2] [Int] -> [[Int]] -> [[Int]]
forall a. a -> [a] -> [a]
: (Int -> [Int] -> [[Int]]
forall a. Int -> [a] -> [[a]]
splitF Int
2 ([Int] -> [[Int]]) -> ([Int] -> [Int]) -> [Int] -> [[Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take (Int
syllN Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3) ([Int] -> [[Int]]) -> [Int] -> [[Int]]
forall a b. (a -> b) -> a -> b
$ [Int
3,Int
4..])
arrinds :: Array Int [Int]
arrinds = (Int, Int) -> [[Int]] -> Array Int [Int]
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
syllN Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
2) [[Int]]
addlist
neededinds :: [[Int]]
neededinds = (Int -> [Int]) -> [Int] -> [[Int]]
forall a b. (a -> b) -> [a] -> [b]
map (Array Int [Int] -> Int -> [Int]
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Int]
arrinds) [Int]
indeces
neededsylls :: [[[Char]]]
neededsylls = ([Int] -> [[Char]]) -> [[Int]] -> [[[Char]]]
forall a b. (a -> b) -> [a] -> [b]
map ((Int -> [Char]) -> [Int] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (Array Int [Char] -> Int -> [Char]
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Char]
resSylls)) [[Int]]
neededinds
breaks :: [Char]
breaks = [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate [Char]
" ... " ([[Char]] -> [Char])
-> ([[[Char]]] -> [[Char]]) -> [[[Char]]] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Char]] -> [Char]) -> [[[Char]]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [[Char]] -> [Char]
unwords ([[[Char]]] -> [Char]) -> [[[Char]]] -> [Char]
forall a b. (a -> b) -> a -> b
$ [[[Char]]]
neededsylls