Skip to content

Commit

Permalink
Added arel to repo monolith
Browse files Browse the repository at this point in the history
  • Loading branch information
fosskers committed Apr 20, 2016
1 parent 325e03c commit a3e36ce
Show file tree
Hide file tree
Showing 7 changed files with 833 additions and 0 deletions.
14 changes: 14 additions & 0 deletions arel/Arel/Util.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
module Arel.Util where

import Data.Text (unpack)
import Prelude hiding (FilePath)
import Shelly

---

eitherToMaybe :: Either a b -> Maybe b
eitherToMaybe (Left _) = Nothing
eitherToMaybe (Right b) = Just b

fptos :: FilePath -> String
fptos = unpack . toTextIgnore
41 changes: 41 additions & 0 deletions arel/Arel/Versions.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
{-# LANGUAGE OverloadedStrings #-}

module Arel.Versions
( Version(..)
, version ) where

import Data.Char (digitToInt)
import Data.Text (Text, pack)
import Text.Parsec
import Text.Parsec.Text

import Arel.Util

---

data Version = Version { unitsOf :: [Unit]
, revisionOf :: Maybe Int } -- The number after `-`.
deriving (Eq,Show,Read,Ord)

data Unit = IUnit Int | SUnit Text deriving (Eq,Show,Read,Ord)

version :: Text -> Maybe Version
version = eitherToMaybe . parse versionNumber ""

versionNumber :: Parser Version
versionNumber = Version <$> units <*> optionMaybe revision

units :: Parser [Unit]
units = concat <$> (many1 (iunit <|> sunit) `sepBy` oneOf ".:_+")

iunit :: Parser Unit
iunit = IUnit . asInt <$> many1 digit

sunit :: Parser Unit
sunit = SUnit . pack <$> many1 letter

revision :: Parser Int
revision = char '-' *> pure asInt <*> many1 digit

asInt :: String -> Int
asInt = foldl (\acc i -> acc * 10 + digitToInt i) 0
674 changes: 674 additions & 0 deletions arel/LICENSE

Large diffs are not rendered by default.

2 changes: 2 additions & 0 deletions arel/Setup.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
import Distribution.Simple
main = defaultMain
31 changes: 31 additions & 0 deletions arel/arel.cabal
Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
-- Initial arel.cabal generated by cabal init. For further documentation,
-- see http://haskell.org/cabal/users-guide/

name: arel
version: 1.0.1
-- synopsis:
-- description:
license: GPL-3
license-file: LICENSE
author: Colin Woodbury
maintainer: [email protected]
-- copyright:
category: System
build-type: Simple
-- extra-source-files:
cabal-version: >=1.10

executable arel
main-is: arel.hs

other-modules: Arel.Util
, Arel.Versions

-- other-extensions:
build-depends: base >=4.8 && <4.9
, parsec >= 3.1.9
, regex-pcre-builtin
, shelly
, text >= 1.2.1.1
-- hs-source-dirs:
default-language: Haskell2010
70 changes: 70 additions & 0 deletions arel/arel.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,70 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}

-- arel - Helps create aura releases.

import Data.List (sortBy)
import qualified Data.Text as T
import Prelude hiding (FilePath)
import Shelly
import Text.Regex.PCRE ((=~))

import Arel.Util
import Arel.Versions

---

projectDir :: FilePath
projectDir = "/home/colin/code/haskell/aura/aura/"

aurDir :: FilePath
aurDir = "/home/colin/code/aur/aura/"

main :: IO ()
main = shelly $ errExit False $ do
cd projectDir
removeOldFiles
makeNewPkgFile
alterPKGBUILD
makeSrcInfo
copyOver
echo "Done."

removeOldFiles :: Sh ()
removeOldFiles = (filter isPkgFile <$> ls projectDir) >>= mapM_ rm

isPkgFile :: FilePath -> Bool
isPkgFile (toTextIgnore -> f) = T.isPrefixOf "./aura-" f

makeNewPkgFile :: Sh ()
makeNewPkgFile = do
run_ "cabal" ["configure"]
run_ "cabal" ["sdist"]
cd "dist/"
pkgs <- ls "."
let latest = last . sortPkgFiles . filter isPkgFile $ pkgs
cp latest projectDir
cd projectDir

sortPkgFiles :: [FilePath] -> [FilePath]
sortPkgFiles [] = []
sortPkgFiles fs = sortBy verNums fs
where verNums a b = compare (ver a) (ver b)

ver :: FilePath -> Maybe Version
ver (fptos -> f) = case f =~ patt :: (String,String,String) of
(_,m,_) -> version $ T.pack m
where patt = "[0-9.]+[0-9]" :: String

alterPKGBUILD :: Sh ()
alterPKGBUILD = do
md5 <- run "makepkg" ["-g"]
pb <- T.lines <$> readfile "PKGBUILD"
let news = map (\l -> if T.isPrefixOf "md5sums=" l then md5 else l) pb
writefile "PKGBUILD" $ T.unlines news

makeSrcInfo :: Sh ()
makeSrcInfo = run_ "mksrcinfo" []

copyOver :: Sh ()
copyOver = cp "PKGBUILD" aurDir >> cp ".SRCINFO" aurDir
1 change: 1 addition & 0 deletions stack.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ resolver: lts-5.13
packages:
- aura/
- aur/
- arel/

extra-deps:
- aur-5.0.1
Expand Down

0 comments on commit a3e36ce

Please sign in to comment.