1
1
mirror of https://github.com/sol/hpack.git synced 2024-10-04 03:38:00 +03:00

Initial commit

This commit is contained in:
Simon Hengel 2014-11-19 22:56:44 +08:00
commit 4f99f1bca4
9 changed files with 153 additions and 0 deletions

1
.ghci Normal file
View File

@ -0,0 +1 @@
:set -isrc -itest

1
.gitignore vendored Normal file
View File

@ -0,0 +1 @@
/dist/

7
.package.yaml Normal file
View File

@ -0,0 +1,7 @@
dependencies:
- base
- base-compat
- interpolate
- directory
- filepath
- yaml

4
.travis.yml Normal file
View File

@ -0,0 +1,4 @@
language: haskell
script:
- cabal configure --enable-tests --ghc-options=-Werror && cabal build && cabal test

3
README.md Normal file
View File

@ -0,0 +1,3 @@
Nothing here!
`cabalize` is not yet even self-hosting!
Move along!

19
cabalize.cabal Normal file
View File

@ -0,0 +1,19 @@
name: cabalize
version: 0.0.0
build-type: Simple
cabal-version: >= 1.10
library
hs-source-dirs: src
exposed-modules:
Cabalize
Config
Util
build-depends:
base
, base-compat
, directory
, filepath
, interpolate
, yaml
default-language: Haskell2010

84
src/Cabalize.hs Normal file
View File

@ -0,0 +1,84 @@
{-# LANGUAGE QuasiQuotes, RecordWildCards #-}
module Cabalize where
import Control.Applicative
import Data.Maybe
import Data.Char
import Data.List
import Data.String.Interpolate
import System.Directory
import System.FilePath
import System.Exit.Compat
import Util
import Config (Config)
import qualified Config
type Dependency = String
data Package = Package {
packageName :: String
, packageVersion :: [Int]
, packageLibrary :: Library
} deriving (Eq, Show)
data Library = Library {
libraryExposedModules :: [String]
, libraryDependencies :: [Dependency]
} deriving (Eq, Show)
cabalize :: IO (String, FilePath)
cabalize = do
mConf <- Config.readConfig configFile
case mConf of
Just conf -> do
package <- mkPackage conf
return (packageName package ++ ".cabal", renderPackage package)
Nothing -> die [i|could not parse #{configFile}|]
where
configFile :: FilePath
configFile = ".package.yaml"
renderPackage :: Package -> String
renderPackage Package{..} = stripEmptyLines [i|
name: #{packageName}
version: #{renderVersion packageVersion}
build-type: Simple
cabal-version: >= 1.10
#{renderLibrary packageLibrary}
|]
renderVersion :: [Int] -> String
renderVersion = intercalate "." . map show
renderLibrary :: Library -> String
renderLibrary Library{..} = dropWhile isSpace [i|
library
hs-source-dirs: src
exposed-modules:
#{intercalate "\n" . map (" " ++) $ libraryExposedModules}
build-depends:
#{intercalate "\n , " $ sort libraryDependencies}
default-language: Haskell2010
|]
mkPackage :: Config -> IO Package
mkPackage Config.Config{..} = do
name <- takeBaseName <$> getCurrentDirectory
library <- mkLibrary dependencies
let package = Package {
packageName = name
, packageVersion = [0,0,0]
, packageLibrary = library
}
return package
mkLibrary :: [Dependency] -> IO Library
mkLibrary dependencies = Library <$> getModules "src" <*> pure dependencies
getModules :: FilePath -> IO [String]
getModules src = toModules <$> getFilesRecursive src
where
toModules :: [FilePath] -> [String]
toModules = catMaybes . map (fmap reverse . stripPrefix (reverse ".hs") . reverse)

14
src/Config.hs Normal file
View File

@ -0,0 +1,14 @@
{-# LANGUAGE DeriveGeneric #-}
module Config where
import Data.Yaml
import GHC.Generics
data Config = Config {
dependencies :: [String]
} deriving (Eq, Show, Generic)
instance FromJSON Config
readConfig :: FilePath -> IO (Maybe Config)
readConfig = decodeFile

20
src/Util.hs Normal file
View File

@ -0,0 +1,20 @@
module Util where
import Control.Applicative
import Control.Monad
import Data.List
import System.Directory
import System.FilePath
stripEmptyLines :: String -> String
stripEmptyLines = unlines . reverse . dropWhile null . reverse . dropWhile null . lines
getFilesRecursive :: FilePath -> IO [FilePath]
getFilesRecursive baseDir = sort <$> go []
where
go :: FilePath -> IO [FilePath]
go dir = do
c <- map (dir </>) . filter (`notElem` [".", ".."]) <$> getDirectoryContents (baseDir </> dir)
dirs <- filterM (doesDirectoryExist . (baseDir </>)) c >>= mapM go
files <- filterM (doesFileExist . (baseDir </>)) c
return (files ++ concat dirs)