module Development.Duplo.Git where
import Control.Applicative ((<$>))
import Control.Lens hiding (Action, Level)
import Control.Monad.Except (runExceptT)
import Data.List (intercalate, filter)
import Data.Text (unpack, pack, splitOn)
import Development.Shake
import Development.Shake.FilePath ((</>))
import System.FilePath.Posix (makeRelative)
import qualified Development.Duplo.Component as CM
import qualified Development.Duplo.Types.AppInfo as AI
import qualified Development.Duplo.Types.Config as TC
type Level = String
type Version = String
type Subversion = String
type FileExtension = String
versionLength :: Int
versionLength = 3
commit :: TC.BuildConfig
-> Level
-> Action (Version, Version)
commit config level = do
let utilPath = config ^. TC.utilPath
appInfo <- liftIO CM.readManifest
let version = AI.version appInfo
let cwd = config ^. TC.cwd
let manifest = cwd </> "component.json"
command_ [] "git" ["stash"]
command_ [] "git" ["checkout", "master"]
let newVersion = incrementVersion level version
let appInfo' = updateVersion appInfo newVersion
appInfo'' <- updateFileRegistry config appInfo'
liftIO $ CM.writeManifest appInfo''
command_ [] (utilPath </> "commit.sh") [newVersion]
return (version, newVersion)
incrementVersion :: Version
-> Level
-> Version
incrementVersion level version =
intercalate "." $ incrementSubversion expanded index
where
expanded = unpack <$> splitOn (pack ".") (pack version)
index = case level of
"major" -> 0
"minor" -> 1
"patch" -> 2
incrementSubversion :: [Subversion] -> Int -> [Subversion]
incrementSubversion version index =
resetVer
where
oldPart = version ^. element index
oldPart' = read oldPart :: Int
newPart = oldPart' + 1
newPart' = show newPart :: String
incrVer = version & element index .~ newPart'
resetVer = resetSubversion incrVer (index + 1) versionLength
resetSubversion :: [Subversion] -> Int -> Int -> [Subversion]
resetSubversion version index max
| index <= max = let newVersion = resetSubversion version (index + 1) max
in newVersion & element index .~ "0"
| otherwise = version
updateVersion :: AI.AppInfo -> Version -> AI.AppInfo
updateVersion manifest version = manifest { AI.version = version }
updateFileRegistry :: TC.BuildConfig -> AI.AppInfo -> Action AI.AppInfo
updateFileRegistry config appInfo = do
let cwd = config ^. TC.cwd
let utilPath = config ^. TC.utilPath
let appPath = cwd </> "app"
let assetPath = appPath </> "assets"
let imagePath = assetPath </> "images"
let fontPath = assetPath </> "fonts"
let find path pttrn = command [] (utilPath </> "find.sh") [path, pttrn]
let split = fmap unpack . splitOn "\n" . pack
let makeRelative' = makeRelative cwd
let filterNames = filter ((> 0) . length)
let prepareFileList = filterNames . fmap (makeRelative cwd) . split
Stdout scripts <- find appPath "*.js"
Stdout styles <- find appPath "*.styl"
Stdout markups <- find appPath "*.jade"
Stdout images <- find imagePath "*"
Stdout fonts <- find fontPath "*"
let scripts' = prepareFileList scripts
let styles' = prepareFileList styles
let markups' = prepareFileList markups
let images' = prepareFileList images
let fonts' = prepareFileList fonts
return appInfo { AI.images = images'
, AI.scripts = scripts'
, AI.styles = styles'
, AI.templates = markups'
, AI.fonts = fonts'
}