module Ros.Internal.PathUtil where
import Data.Char (toUpper)
import Data.List (tails)
import System.Directory (doesFileExist)
import System.FilePath
import Paths_roshask
cap :: String -> String
cap [] = []
cap (x:xs) = toUpper x : xs
isPkg :: FilePath -> IO Bool
isPkg = doesFileExist . (</> "manifest.xml")
isStack :: FilePath -> IO Bool
isStack = doesFileExist . (</> "stack.xml")
pathToPkgName :: FilePath -> String
pathToPkgName p | hasExtension p = cap . last . init . splitPath $ p
| otherwise = cap . last . splitPath $ p
stackName :: FilePath -> IO (Maybe String)
stackName = go . tails . reverse . splitPath
where go :: [[FilePath]] -> IO (Maybe String)
go [] = return Nothing
go [[]] = return Nothing
go (d:ds) = do b <- isStack . joinPath . reverse $ d
if b then return (Just (head d)) else go ds
codeGenDir :: FilePath -> IO FilePath
codeGenDir f = do s <- stackName f
r <- getDataDir
let base = case s of
Nothing -> r
Just s' -> r </> s'
return $ base </> pkg </> "Ros" </> pkg
where pkg = pathToPkgName f