module Text.Hyphenation.Hyphenator
( Hyphenator(..)
, hyphenate
) where
import Text.Hyphenation.Pattern
import Text.Hyphenation.Exception
data Hyphenator = Hyphenator
{ Hyphenator -> Char -> Char
hyphenatorChars :: Char -> Char
, Hyphenator -> Patterns
hyphenatorPatterns :: Patterns
, Hyphenator -> Exceptions
hyphenatorExceptions :: Exceptions
, Hyphenator -> Int
hyphenatorLeftMin :: {-# UNPACK #-} !Int
, Hyphenator -> Int
hyphenatorRightMin :: {-# UNPACK #-} !Int
}
hyphenationScore :: Hyphenator -> String -> [Int]
hyphenationScore :: Hyphenator -> String -> [Int]
hyphenationScore (Hyphenator Char -> Char
nf Patterns
ps Exceptions
es Int
l Int
r) String
s
| Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n = Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
0
| Bool
otherwise = case String -> Exceptions -> Maybe [Int]
lookupException String
ls Exceptions
es of
Just [Int]
pts -> [Int] -> [Int]
forall a. Num a => [a] -> [a]
trim [Int]
pts
Maybe [Int]
Nothing -> [Int] -> [Int]
forall a. Num a => [a] -> [a]
trim (String -> Patterns -> [Int]
lookupPattern String
ls Patterns
ps)
where
trim :: [a] -> [a]
trim [a]
result = Int -> a -> [a]
forall a. Int -> a -> [a]
replicate Int
l a
0 [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
r Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
l [a]
result)
n :: Int
n = String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s
ls :: String
ls = (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
nf String
s
hyphenate :: Hyphenator -> String -> [String]
hyphenate :: Hyphenator -> String -> [String]
hyphenate Hyphenator
h String
s0 = String -> String -> [Int] -> [String]
forall a a. Integral a => [a] -> [a] -> [a] -> [[a]]
go [] String
s0 ([Int] -> [String]) -> [Int] -> [String]
forall a b. (a -> b) -> a -> b
$ [Int] -> [Int]
forall a. [a] -> [a]
tail ([Int] -> [Int]) -> [Int] -> [Int]
forall a b. (a -> b) -> a -> b
$ Hyphenator -> String -> [Int]
hyphenationScore Hyphenator
h String
s0 where
go :: [a] -> [a] -> [a] -> [[a]]
go [a]
acc (a
w:[a]
ws) (a
p:[a]
ps)
| a -> Bool
forall a. Integral a => a -> Bool
odd a
p = [a] -> [a]
forall a. [a] -> [a]
reverse (a
wa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
acc) [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [a] -> [a] -> [a] -> [[a]]
go [] [a]
ws [a]
ps
| Bool
otherwise = [a] -> [a] -> [a] -> [[a]]
go (a
wa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
acc) [a]
ws [a]
ps
go [a]
acc [a]
ws [a]
_ = [[a] -> [a]
forall a. [a] -> [a]
reverse [a]
acc [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
ws]