{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeFamilies #-}
module WEditor.LineWrap (
  BreakWords,
  LineBreak,
  WordSplitter(..),
  breakExact,
  breakWords,
  lazyHyphen,
  lineBreakEnd,
  lineBreakHyphen,
  lineBreakSimple,
  noHyphen,
) where
import Control.Applicative ((<|>))
import Control.Monad (when)
import WEditor.Base
data LineBreak = ParagraphEnd | SimpleBreak | HyphenatedWord deriving (Eq,Ord)
lineBreakEnd :: LineBreak
lineBreakEnd = ParagraphEnd
lineBreakSimple :: LineBreak
lineBreakSimple = SimpleBreak
lineBreakHyphen :: LineBreak
lineBreakHyphen = HyphenatedWord
data NoSplit c = NoSplit deriving (Show)
breakExact :: BreakWords c
breakExact = breakWords NoSplit
instance WordSplitter (NoSplit c) c
class WordSplitter a c | a -> c where
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  splitWord :: a
            -> Int         
            -> Int         
            -> [c]         
            -> Maybe [Int] 
  splitWord _ _ _ _ = Nothing
  
  isWordChar :: a -> c -> Bool
  isWordChar _ _ = False
  
  isWhitespace :: a -> c -> Bool
  isWhitespace _ _ = False
  
  appendHyphen :: a -> [c] -> [c]
  appendHyphen _ = id
data BreakWords c = forall a. (Show a, WordSplitter a c) => BreakWords Int a
breakWords :: (Show a, WordSplitter a c) => a -> BreakWords c
breakWords = BreakWords 0
data NoHyphen c = NoHyphen deriving (Show)
noHyphen :: WordChar c => NoHyphen c
noHyphen = NoHyphen
data LazyHyphen c = LazyHyphen deriving (Show)
lazyHyphen :: (WordChar c, HyphenChar c) => LazyHyphen c
lazyHyphen = LazyHyphen
instance Show LineBreak where
  show ParagraphEnd   = "lineBreakEnd"
  show SimpleBreak    = "lineBreakSimple"
  show HyphenatedWord = "lineBreakHyphen"
instance Show (BreakWords c) where
  show (BreakWords w s) =
    "breakWords { width: " ++ show w ++
               ", split: " ++ show s ++ " }"
instance WordChar c => WordSplitter (NoHyphen c) c where
  splitWord _ k w _ = if k < w then Just [] else Nothing
  isWordChar _ = defaultIsWordChar
  isWhitespace _ = defaultIsWhitespace
instance (WordChar c, HyphenChar c) => WordSplitter (LazyHyphen c) c where
  splitWord _ k w cs
    | w < 4 || k > w          = Nothing
    | k >= length cs || k < 3 = Just []
    | otherwise = Just $ (k-1):(replicate count size) where
        size = w-1
        remainder = length cs-(k-1)
        
        
        count = (remainder-2) `div` size
  isWordChar _ = defaultIsWordChar
  isWhitespace _ = defaultIsWhitespace
  appendHyphen _ = (++[defaultHyphen])
instance FixedFontParser (BreakWords c) c where
  type BreakType (BreakWords c) = LineBreak
  setLineWidth (BreakWords _ s) w = BreakWords w s
  breakLines (BreakWords w s) = breakAllLines w s
  splitLine _ k (VisibleLine b cs) =
    (VisibleLine lineBreakEnd (take k cs),
     VisibleLine b            (drop k cs))
  emptyLine _ = VisibleLine lineBreakEnd []
  renderLine (BreakWords w _) (VisibleLine ParagraphEnd cs)
    | w < 1 = cs
    | otherwise = take w cs
  renderLine (BreakWords _ s) (VisibleLine SimpleBreak cs) =
    reverse $ dropWhile (isWhitespace s) $ reverse cs
  renderLine (BreakWords _ s) (VisibleLine HyphenatedWord cs) = appendHyphen s cs
  tweakCursor (BreakWords w _) (VisibleLine ParagraphEnd _)
    | w < 1 = id
    | otherwise = min w
  tweakCursor (BreakWords _ s) (VisibleLine SimpleBreak cs) = max 0 . min (total-post) where
    post = length $ takeWhile (isWhitespace s) $ reverse cs
    total = length cs
  tweakCursor _ (VisibleLine HyphenatedWord cs) = id
breakAllLines :: WordSplitter a c => Int -> a -> [c] -> [VisibleLine c LineBreak]
breakAllLines _ _ [] = [VisibleLine lineBreakEnd []]
breakAllLines w s cs
  | w < 1 = [VisibleLine lineBreakEnd cs]
  | otherwise = breakOrEmpty cs where
      breakOrEmpty cs = let (Just ls) = handleSplit (reverse $ take w cs) (drop w cs) in ls
      handleSplit line rest =
        tryWord line rest <|>
        trySpaces line rest <|>
        lineDefault line rest
      lineDefault []  _ = Just []
      lineDefault ls [] = Just [VisibleLine lineBreakEnd (reverse ls)]
      lineDefault ls rs = Just $ VisibleLine lineBreakSimple (reverse ls):(breakOrEmpty rs)
      tryWord ls@(l:_) rs@(r:_) | isWordChar s l && isWordChar s r = newLines where
        newLines = do
          breaks <- splitWord s (length wordFront) w word
          
          when (null breaks && length wordFront == w) Nothing
          return $ case breaks of
                        []     -> VisibleLine lineBreakSimple (reverse ls2):(breakOrEmpty (word ++ rs2))
                        (b:bs) -> VisibleLine lineBreakHyphen (reverse ls2 ++ take b word):(hyphenate (drop b word) bs)
        ls2 = dropWhile (isWordChar s) ls
        rs2 = dropWhile (isWordChar s) rs
        wordFront = reverse $ takeWhile (isWordChar s) ls
        wordBack = takeWhile (isWordChar s) rs
        word = wordFront ++ wordBack
        hyphenate word bs | null word || null bs = breakOrEmpty (word ++ rs2)
        hyphenate word (b:bs) = (VisibleLine lineBreakHyphen (take b word)):(hyphenate (drop b word) bs)
      tryWord _ _ = Nothing
      trySpaces ls rs@(r:_) | isWhitespace s r = newLines where
        ls' = reverse ls ++ takeWhile (isWhitespace s) rs
        rs' = dropWhile (isWhitespace s) rs
        newLines
          | null rs'  = Just [VisibleLine lineBreakEnd ls']
          | otherwise = Just $ (VisibleLine lineBreakSimple ls'):(breakOrEmpty rs')
      trySpaces _ _ = Nothing