module Data.GI.CodeGen.Util
( prime
, parenthesize
, padTo
, withComment
, ucFirst
, lcFirst
, modifyQualified
, tshow
, terror
, utf8ReadFile
, utf8WriteFile
, splitOn
, printWarning
) where
import GHC.Stack (HasCallStack)
#if !MIN_VERSION_base(4,13,0)
import Data.Monoid ((<>))
#endif
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
import qualified Data.Text.IO as TIO
import qualified System.Console.ANSI as A
import System.IO (stderr, hFlush)
padTo :: Int -> Text -> Text
padTo :: Int -> Text -> Text
padTo Int
n Text
s = Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
s) Text
" "
withComment :: Text -> Text -> Text
Text
a Text
b = Int -> Text -> Text
padTo Int
40 Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-- " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
b
prime :: Text -> Text
prime :: Text -> Text
prime = (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'")
parenthesize :: Text -> Text
parenthesize :: Text -> Text
parenthesize Text
s = Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
tshow :: Show a => a -> Text
tshow :: a -> Text
tshow = String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
ucFirst :: Text -> Text
ucFirst :: Text -> Text
ucFirst Text
"" = Text
""
ucFirst Text
t = Char -> Text -> Text
T.cons (Char -> Char
toUpper (Char -> Char) -> Char -> Char
forall a b. (a -> b) -> a -> b
$ Text -> Char
T.head Text
t) (Text -> Text
T.tail Text
t)
lcFirst :: Text -> Text
lcFirst :: Text -> Text
lcFirst Text
"" = Text
""
lcFirst Text
t = Char -> Text -> Text
T.cons (Char -> Char
toLower (Char -> Char) -> Char -> Char
forall a b. (a -> b) -> a -> b
$ Text -> Char
T.head Text
t) (Text -> Text
T.tail Text
t)
modifyQualified :: (Text -> Text) -> Text -> Text
modifyQualified :: (Text -> Text) -> Text -> Text
modifyQualified Text -> Text
f = Text -> [Text] -> Text
T.intercalate Text
"." ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
modify ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
"."
where modify :: [Text] -> [Text]
modify :: [Text] -> [Text]
modify [] = []
modify (Text
a:[]) = Text -> Text
f Text
a Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: []
modify (Text
a:[Text]
as) = Text
a Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text] -> [Text]
modify [Text]
as
splitOn :: Eq a => a -> [a] -> [[a]]
splitOn :: a -> [a] -> [[a]]
splitOn a
x [a]
xs = [a] -> [a] -> [[a]]
go [a]
xs []
where go :: [a] -> [a] -> [[a]]
go [] [a]
acc = [[a] -> [a]
forall a. [a] -> [a]
reverse [a]
acc]
go (a
y : [a]
ys) [a]
acc = if a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y
then [a] -> [a]
forall a. [a] -> [a]
reverse [a]
acc [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [a] -> [a] -> [[a]]
go [a]
ys []
else [a] -> [a] -> [[a]]
go [a]
ys (a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
acc)
utf8ReadFile :: FilePath -> IO T.Text
utf8ReadFile :: String -> IO Text
utf8ReadFile String
fname = do
ByteString
bytes <- String -> IO ByteString
B.readFile String
fname
case ByteString -> Either UnicodeException Text
TE.decodeUtf8' ByteString
bytes of
Right Text
text -> Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
text
Left UnicodeException
error -> Text -> IO Text
forall a. HasCallStack => Text -> a
terror (Text
"Input file " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
forall a. Show a => a -> Text
tshow String
fname Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
" seems not to be valid UTF-8. Error was:\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
UnicodeException -> Text
forall a. Show a => a -> Text
tshow UnicodeException
error)
utf8WriteFile :: FilePath -> T.Text -> IO ()
utf8WriteFile :: String -> Text -> IO ()
utf8WriteFile String
fname Text
text = String -> ByteString -> IO ()
B.writeFile String
fname (Text -> ByteString
TE.encodeUtf8 Text
text)
printWarning :: Text -> IO ()
printWarning :: Text -> IO ()
printWarning Text
warning = do
Bool
inColour <- Handle -> IO Bool
A.hSupportsANSIColor Handle
stderr
if Bool -> Bool
not Bool
inColour
then Handle -> Text -> IO ()
TIO.hPutStrLn Handle
stderr Text
warning
else do
Handle -> [SGR] -> IO ()
A.hSetSGR Handle
stderr [ConsoleIntensity -> SGR
A.SetConsoleIntensity ConsoleIntensity
A.BoldIntensity,
ConsoleLayer -> ColorIntensity -> Color -> SGR
A.SetColor ConsoleLayer
A.Foreground ColorIntensity
A.Vivid Color
A.Yellow]
Handle -> Text -> IO ()
TIO.hPutStr Handle
stderr Text
"Warning: "
Handle -> [SGR] -> IO ()
A.hSetSGR Handle
stderr [ConsoleLayer -> ColorIntensity -> Color -> SGR
A.SetColor ConsoleLayer
A.Foreground ColorIntensity
A.Vivid Color
A.White]
Handle -> Text -> IO ()
TIO.hPutStrLn Handle
stderr Text
warning
Handle -> [SGR] -> IO ()
A.hSetSGR Handle
stderr [SGR
A.Reset]
Handle -> IO ()
hFlush Handle
stderr
terror :: HasCallStack => Text -> a
terror :: Text -> a
terror Text
errMsg =
let fmt :: String
fmt = [SGR] -> String
A.setSGRCode [ConsoleIntensity -> SGR
A.SetConsoleIntensity ConsoleIntensity
A.BoldIntensity,
ConsoleLayer -> ColorIntensity -> Color -> SGR
A.SetColor ConsoleLayer
A.Foreground ColorIntensity
A.Vivid Color
A.Red]
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"ERROR: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ [SGR] -> String
A.setSGRCode [ConsoleLayer -> ColorIntensity -> Color -> SGR
A.SetColor ConsoleLayer
A.Foreground ColorIntensity
A.Vivid Color
A.White]
String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
errMsg
String -> String -> String
forall a. [a] -> [a] -> [a]
++ [SGR] -> String
A.setSGRCode [ConsoleIntensity -> SGR
A.SetConsoleIntensity ConsoleIntensity
A.NormalIntensity,
ConsoleLayer -> ColorIntensity -> Color -> SGR
A.SetColor ConsoleLayer
A.Foreground ColorIntensity
A.Vivid Color
A.Blue]
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\nPlease report this at https://github.com/haskell-gi/haskell-gi/issues"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ [SGR] -> String
A.setSGRCode [SGR
A.Reset]
in String -> a
forall a. HasCallStack => String -> a
error String
fmt