module Data.GI.CodeGen.Util
  ( prime
  , parenthesize
  , padTo
  , withComment
  , ucFirst
  , lcFirst
  , modifyQualified
  , tshow
  , terror
  , utf8ReadFile
  , utf8WriteFile
  , splitOn
  ) where
import Data.Monoid ((<>))
import Data.Char (toLower, toUpper)
import qualified Data.ByteString as B
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
padTo :: Int -> Text -> Text
padTo n s = s <> T.replicate (n - T.length s) " "
withComment :: Text -> Text -> Text
withComment a b = padTo 40 a <> "-- " <> b
prime :: Text -> Text
prime = (<> "'")
parenthesize :: Text -> Text
parenthesize s = "(" <> s <> ")"
tshow :: Show a => a -> Text
tshow = T.pack . show
terror :: Text -> a
terror = error . T.unpack
ucFirst :: Text -> Text
ucFirst "" = ""
ucFirst t = T.cons (toUpper $ T.head t) (T.tail t)
lcFirst :: Text -> Text
lcFirst "" = ""
lcFirst t = T.cons (toLower $ T.head t) (T.tail t)
modifyQualified :: (Text -> Text) -> Text -> Text
modifyQualified f = T.intercalate "." . modify . T.splitOn "."
    where modify :: [Text] -> [Text]
          modify [] = []
          modify (a:[]) = f a : []
          modify (a:as) = a : modify as
splitOn :: Eq a => a -> [a] -> [[a]]
splitOn x xs = go xs []
    where go [] acc = [reverse acc]
          go (y : ys) acc = if x == y
                            then reverse acc : go ys []
                            else go ys (y : acc)
utf8ReadFile :: FilePath -> IO T.Text
utf8ReadFile fname = do
  bytes <- B.readFile fname
  case TE.decodeUtf8' bytes of
    Right text -> return text
    Left error -> terror ("Input file " <> tshow fname <>
                          " seems not to be valid UTF-8. Error was:\n" <>
                          tshow error)
utf8WriteFile :: FilePath -> T.Text -> IO ()
utf8WriteFile fname text = B.writeFile fname (TE.encodeUtf8 text)