{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.Nixpkgs.Fetch
( Source(..)
, Hash(..)
, DerivationSource(..), fromDerivationSource, urlDerivationSource
, fetch
, fetchWith
) where
import Control.Applicative
import Control.DeepSeq
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe
import Data.Aeson
import qualified Data.ByteString.Lazy.Char8 as BS
import qualified Data.List as L
import Data.Maybe
import GHC.Generics ( Generic )
import Language.Nix.PrettyPrinting as PP
import System.Directory
import System.Environment
import System.Exit
import System.IO
import System.Process
data Source = Source
{ sourceUrl :: String
, sourceRevision :: String
, sourceHash :: Hash
, sourceCabalDir :: String
} deriving (Show, Eq, Ord, Generic)
instance NFData Source
data Hash = Certain String | Guess String | UnknownHash
deriving (Show, Eq, Ord, Generic)
instance NFData Hash
isUnknown :: Hash -> Bool
isUnknown UnknownHash = True
isUnknown _ = False
hashToList :: Hash -> [String]
hashToList (Certain s) = [s]
hashToList _ = []
data DerivationSource = DerivationSource
{ derivKind :: String
, derivUrl :: String
, derivRevision :: String
, derivHash :: String
, derivSubmodule :: Maybe Bool
}
deriving (Show, Eq, Ord, Generic)
instance NFData DerivationSource
instance FromJSON DerivationSource where
parseJSON (Object o) = DerivationSource (error "undefined DerivationSource.kind")
<$> o .: "url"
<*> o .: "rev"
<*> o .: "sha256"
<*> o .: "fetchSubmodules"
parseJSON _ = error "invalid DerivationSource"
instance PP.Pretty DerivationSource where
pPrint DerivationSource {..} =
let isHackagePackage = "mirror://hackage/" `L.isPrefixOf` derivUrl
fetched = derivKind /= ""
in if isHackagePackage then attr "sha256" $ string derivHash
else if not fetched then attr "src" $ text derivUrl
else vcat
[ text "src" <+> equals <+> text ("fetch" ++ derivKind) <+> lbrace
, nest 2 $ vcat
[ attr "url" $ string derivUrl
, attr "sha256" $ string derivHash
, if derivRevision /= "" then attr "rev" (string derivRevision) else PP.empty
, boolattr "fetchSubmodules" (isJust derivSubmodule) (fromJust derivSubmodule)
]
, rbrace PP.<> semi
]
urlDerivationSource :: String -> String -> DerivationSource
urlDerivationSource url hash = DerivationSource "url" url "" hash Nothing
fromDerivationSource :: DerivationSource -> Source
fromDerivationSource DerivationSource{..} = Source derivUrl derivRevision (Certain derivHash) "."
fetch :: forall a.
Bool
-> (String -> MaybeT IO a)
-> Source
-> IO (Maybe (DerivationSource, a))
fetch optSubModules f = runMaybeT . fetchers where
fetchers :: Source -> MaybeT IO (DerivationSource, a)
fetchers source = msum . (fetchLocal source :) $ map (\fetcher -> fetchWith fetcher source >>= process)
[ (False, "url", [])
, (True, "git", ["--fetch-submodules" | optSubModules ])
, (True, "hg", [])
, (True, "svn", [])
, (True, "bzr", [])
]
stripSlashSuffix :: String -> String
stripSlashSuffix = reverse . dropWhile (== '/') . reverse
fetchLocal :: Source -> MaybeT IO (DerivationSource, a)
fetchLocal src = do
let path = stripSlashSuffix $ stripPrefix "file://" $ sourceUrl src
existsFile <- liftIO $ doesFileExist path
existsDir <- liftIO $ doesDirectoryExist path
guard $ existsDir || existsFile
let path' | '/' `elem` path = path
| otherwise = "./" ++ path
process (localDerivationSource path', path') <|> localArchive path'
localArchive :: FilePath -> MaybeT IO (DerivationSource, a)
localArchive path = do
absolutePath <- liftIO $ canonicalizePath path
unpacked <- snd <$> fetchWith (False, "url", ["--unpack"]) (Source ("file://" ++ absolutePath) "" UnknownHash ".")
process (localDerivationSource absolutePath, unpacked)
process :: (DerivationSource, FilePath) -> MaybeT IO (DerivationSource, a)
process (derivSource, file) = (,) derivSource <$> f file
localDerivationSource p = DerivationSource "" p "" "" Nothing
fetchWith :: (Bool, String, [String]) -> Source -> MaybeT IO (DerivationSource, FilePath)
fetchWith (supportsRev, kind, addArgs) source = do
unless ((sourceRevision source /= "") || isUnknown (sourceHash source) || not supportsRev) $
liftIO (hPutStrLn stderr "** need a revision for VCS when the hash is given. skipping.") >> mzero
MaybeT $ liftIO $ do
envs <- getEnvironment
(Nothing, Just stdoutH, _, processH) <- createProcess (proc script args)
{ env = Just $ ("PRINT_PATH", "1") : envs
, std_in = Inherit
, std_err = Inherit
, std_out = CreatePipe
}
exitCode <- waitForProcess processH
case exitCode of
ExitFailure _ -> return Nothing
ExitSuccess -> do
buf <- BS.hGetContents stdoutH
let (l:ls) = reverse (BS.lines buf)
buf' = BS.unlines (reverse ls)
case length ls of
0 -> return Nothing
1 -> return (Just (DerivationSource { derivKind = kind
, derivUrl = sourceUrl source
, derivRevision = ""
, derivHash = BS.unpack (head ls)
, derivSubmodule = Nothing
}
, sourceUrl source))
_ -> case eitherDecode buf' of
Left err -> error ("invalid JSON: " ++ err ++ " in " ++ show buf')
Right ds -> return (Just (ds { derivKind = kind }, BS.unpack l))
where
script :: String
script = "nix-prefetch-" ++ kind
args :: [String]
args = addArgs ++ sourceUrl source : [ sourceRevision source | supportsRev ] ++ hashToList (sourceHash source)
stripPrefix :: Eq a => [a] -> [a] -> [a]
stripPrefix prefix as
| prefix' == prefix = stripped
| otherwise = as
where
(prefix', stripped) = splitAt (length prefix) as