-----------------------------------------------------------------------------
-- Copyright 2019, Advise-Me project team. This file is distributed under 
-- the terms of the Apache License 2.0. For more information, see the files
-- "LICENSE.txt" and "NOTICE.txt", which are included in the distribution.
-----------------------------------------------------------------------------
-- |
-- Maintainer  :  bastiaan.heeren@ou.nl
-- Stability   :  provisional
-- Portability :  portable (depends on ghc)
--
-----------------------------------------------------------------------------

module Util.String where

import Data.Char
import Data.List
import Text.Printf ( printf, PrintfType )

-- | Trim whitespace from the beginning and end of a string.
trim :: String -> String
trim = dropWhileEnd isSpace . dropWhile isSpace

-- | Split on elements of a list.
split :: Eq a => a -> [a] -> [[a]]
split _ [] = []
split delimiter string =
   let (a,b) = span (/= delimiter) string
   in  a:split delimiter (drop 1 b)

-- | Add characters before, between and after a string.
wrap :: String -> String -> String -> [String] -> String
wrap before between after elems =
   before ++ intercalate between elems ++ after

strToLower :: String -> String
strToLower = map toLower

strToUpper :: String -> String
strToUpper = map toUpper

splitOn :: Eq a => [a] -> [a] -> ([a],[a])
splitOn = flip splitOn' []

splitOn' :: Eq a => [a] -> [a] -> [a] -> ([a],[a])
splitOn' [] zs _ = (reverse zs, [])
splitOn' yss@(y:ys) zs xs | xs `isPrefixOf` yss = (reverse zs, drop (length xs) yss)
                          | otherwise = splitOn' ys (y:zs) xs

breaksOn :: (a -> Bool) -> [a] -> [[a]]
breaksOn _ [] = []
breaksOn p xs | (a,ys) <- break p xs = a : breaksOn p (case ys of
                                                        [] -> []
                                                        _:zs -> zs)

indent :: String -> String
indent = unlines . map ('\t':) . lines

replace :: String -> String -> String -> String
replace _ _ [] = []
replace x y oz@(z:zs) | Just r <- stripPrefix x oz = y ++ replace x y r
                      | otherwise = z : replace x y zs

-- | Make string lowercase and remove non-alphanumerics.
normalize :: String -> String
normalize xs = [ toLower x | x <- xs, isAlphaNum x ]


-- | Format a double n to a percentage with i decimals.
percentage :: Int -> Double -> String
percentage i = printf ("%." ++ show i ++ "f%%") . (* 100)


-- | Generic division.
(//) :: (Real a, Real b) => a -> b -> Double
a // b = realToFrac a / realToFrac b