Skip to content

Commit

Permalink
better fix for absolute path fails
Browse files Browse the repository at this point in the history
  • Loading branch information
nkpart committed Mar 27, 2012
1 parent 732ab73 commit fffffb9
Show file tree
Hide file tree
Showing 3 changed files with 22 additions and 4 deletions.
8 changes: 5 additions & 3 deletions Kit/Contents.hs
Expand Up @@ -8,6 +8,7 @@ module Kit.Contents (
import Kit.Spec
import Kit.Util
import Kit.Xcode.XCConfig
import Kit.FilePath

import qualified Data.Traversable as T

Expand All @@ -30,9 +31,10 @@ instance Packageable KitContents where
namedPrefix :: KitContents -> Maybe String
namedPrefix kc = fmap (\s -> "//" ++ (packageFileName kc) ++ "\n" ++ s) $ contentPrefix kc

readKitContents :: (Applicative m, MonadIO m) => FilePath -> KitSpec -> m KitContents
readKitContents kitDir spec =
let find dir tpe = liftIO $ inDirectory kitDir $ do
readKitContents :: (Applicative m, MonadIO m) => AbsolutePath -> KitSpec -> m KitContents
readKitContents absKitDir spec =
let kitDir = filePath absKitDir
find dir tpe = liftIO $ inDirectory kitDir $ do
files <- glob (dir </> "**/*" ++ tpe)
mapM canonicalizePath files
findSrc = find $ specSourceDirectory spec
Expand Down
15 changes: 15 additions & 0 deletions Kit/FilePath.hs
@@ -0,0 +1,15 @@
module Kit.FilePath (
AbsolutePath,
filePath,
absolutePath
) where

import System.Directory (canonicalizePath)

data AbsolutePath = AbsolutePath FilePath deriving (Eq, Show)

filePath :: AbsolutePath -> FilePath
filePath (AbsolutePath fp) = fp

absolutePath :: FilePath -> IO AbsolutePath
absolutePath path = fmap AbsolutePath $ canonicalizePath path
3 changes: 2 additions & 1 deletion Kit/Main.hs
Expand Up @@ -17,6 +17,7 @@ module Kit.Main where
import Data.Function (on)
import Kit.Repository (KitRepository, unpackKit, packagesDirectory, publishLocally)
import Control.Monad.State
import Kit.FilePath

kitMain :: IO ()
kitMain = do
Expand Down Expand Up @@ -74,7 +75,7 @@ module Kit.Main where
dependencyContents repo dep = readKitContents' baseDir (depSpec dep) where
baseDir = dependency ((packagesDirectory repo </>) . packageFileName) (\fp spec -> devKitDir </> fp) dep
readKitContents' base spec = do
absoluteBase <- liftIO $ canonicalizePath base
absoluteBase <- liftIO $ absolutePath base
readKitContents absoluteBase spec

doPackageKit :: Command ()
Expand Down

0 comments on commit fffffb9

Please sign in to comment.