module System.Console.Haskeline.Backend.WCWidth(
                            gsWidth,
                            splitAtWidth,
                            takeWidth,
                            ) where

-- Certain characters are "wide", i.e. take up two spaces in the terminal.
-- This module wraps the necessary foreign routines, and also provides some convenience
-- functions for width-breaking code.

import System.Console.Haskeline.LineState

import Data.List (foldl')
import Foreign.C.Types

foreign import ccall unsafe haskeline_mk_wcwidth :: CInt -> CInt

wcwidth :: Char -> Int
wcwidth :: Char -> Int
wcwidth Char
c = case CInt -> CInt
haskeline_mk_wcwidth forall a b. (a -> b) -> a -> b
$ forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum Char
c of
                -1 -> Int
0 -- Control characters have zero width.  (Used by the
                        -- "\SOH...\STX" hack in LineState.stringToGraphemes.)
                CInt
w -> forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
w

gWidth :: Grapheme -> Int
gWidth :: Grapheme -> Int
gWidth Grapheme
g = Char -> Int
wcwidth (Grapheme -> Char
baseChar Grapheme
g)

gsWidth :: [Grapheme] -> Int
gsWidth :: [Grapheme] -> Int
gsWidth = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall a. Num a => a -> a -> a
(+) Int
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Grapheme -> Int
gWidth

-- | Split off the maximal list which is no more than the given width.
-- returns the width of that list.
splitAtWidth :: Int -> [Grapheme] -> ([Grapheme],[Grapheme],Int)
splitAtWidth :: Int -> [Grapheme] -> ([Grapheme], [Grapheme], Int)
splitAtWidth Int
n [Grapheme]
xs = case Int -> [Grapheme] -> ([Grapheme], [Grapheme], Int)
splitAtWidth' Int
n [Grapheme]
xs of
                        ([Grapheme]
this,[Grapheme]
rest,Int
remaining) -> ([Grapheme]
this,[Grapheme]
rest,Int
nforall a. Num a => a -> a -> a
-Int
remaining)

-- Returns the amount of unused space in the line.
splitAtWidth' :: Int -> [Grapheme] -> ([Grapheme],[Grapheme],Int)
splitAtWidth' :: Int -> [Grapheme] -> ([Grapheme], [Grapheme], Int)
splitAtWidth' Int
w [] = ([],[],Int
w)
splitAtWidth' Int
w (Grapheme
g:[Grapheme]
gs)
    | Int
gw forall a. Ord a => a -> a -> Bool
> Int
w = ([],Grapheme
gforall a. a -> [a] -> [a]
:[Grapheme]
gs,Int
w)
    | Bool
otherwise = (Grapheme
gforall a. a -> [a] -> [a]
:[Grapheme]
gs',[Grapheme]
gs'',Int
r)
  where
    gw :: Int
gw = Grapheme -> Int
gWidth Grapheme
g
    ([Grapheme]
gs',[Grapheme]
gs'',Int
r) = Int -> [Grapheme] -> ([Grapheme], [Grapheme], Int)
splitAtWidth' (Int
wforall a. Num a => a -> a -> a
-Int
gw) [Grapheme]
gs

-- Returns the longest prefix less than or equal to the given width
-- plus the width of that list.
takeWidth :: Int -> [Grapheme] -> ([Grapheme],Int)
takeWidth :: Int -> [Grapheme] -> ([Grapheme], Int)
takeWidth Int
n [Grapheme]
gs = case Int -> [Grapheme] -> ([Grapheme], [Grapheme], Int)
splitAtWidth Int
n [Grapheme]
gs of
                    ([Grapheme]
gs',[Grapheme]
_,Int
len) -> ([Grapheme]
gs',Int
len)