Skip to content

Commit

Permalink
Simplify script
Browse files Browse the repository at this point in the history
  • Loading branch information
berberman committed Jan 16, 2024
1 parent 7dfb9da commit fb244da
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 57 deletions.
4 changes: 1 addition & 3 deletions .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -24,9 +24,7 @@ jobs:
- name: Build
run: |
export LANG=C.UTF-8
mkdir build
cd build
runghc ../Main.hs -j everything
runghc ./Main.hs -j everything
- uses: "marvinpinto/action-automatic-releases@latest"
with:
Expand Down
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1 +1,2 @@
build
report.html
79 changes: 25 additions & 54 deletions Main.hs
Original file line number Diff line number Diff line change
@@ -1,20 +1,11 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wall #-}

module Main where

import Control.Monad (forM_, void)
import Data.List.Extra (find)
import Data.Maybe (fromJust)
import Control.Monad (forM_)
import Development.Shake
import Development.Shake.Classes
import Development.Shake.FilePath
import GHC.Generics (Generic)
import GHC.Stack (HasCallStack, SrcLoc (srcLocFile), callStack, getCallStack, withFrozenCallStack)
import System.Directory.Extra (canonicalizePath)

extraTableNames :: [String]
extraTableNames =
Expand Down Expand Up @@ -67,14 +58,24 @@ otherTableNames =
tablesVersion :: String
tablesVersion = "1"

outputDir :: FilePath
outputDir = "build"

main :: IO ()
main = shakeArgs shakeOptions {shakeReport = ["report.html"], shakeVersion = tablesVersion} $ do
mainPathRule
forM_ extraTableNames $ tableIMRule "fcitx5-table-extra"
forM_ otherTableNames $ tableIMRule "fcitx5-table-other"
"fcitx5-table-extra" ~> need [name <.> "zip" | name <- extraTableNames]
"fcitx5-table-other" ~> need [takeBaseName name <.> "zip" | name <- otherTableNames]
"everything" ~> need ["fcitx5-table-extra", "fcitx5-table-other"]
main = shakeArgs
shakeOptions
{ shakeReport = ["report.html"],
shakeVersion = tablesVersion,
shakeFiles = outputDir
}
$ do
forM_ extraTableNames $ tableIMRule "fcitx5-table-extra"
forM_ otherTableNames $ tableIMRule "fcitx5-table-other"
"fcitx5-table-extra" ~> need [outputDir </> name <.> "zip" | name <- extraTableNames]
"fcitx5-table-other" ~> need [outputDir </> takeBaseName name <.> "zip" | name <- otherTableNames]
"everything" ~> need ["fcitx5-table-extra", "fcitx5-table-other"]
"clean" ~> do
removeFilesAfter outputDir ["//*"]

--------------------------------------------------------------------------------

Expand All @@ -83,49 +84,19 @@ tableIMRule fp name = do
-- @tableName@ is the name of the table
-- while @name@ is the path to the table relative to fcitx5-table-extra or fcitx5-table-other
let tableName = takeBaseName name
conf = tableName <.> "conf"
dict = tableName <.> "main" <.> "dict"
packaged = tableName <.> "zip"
conf = outputDir </> tableName <.> "conf"
dict = outputDir </> tableName <.> "main" <.> "dict"
packaged = outputDir </> tableName <.> "zip"
conf %> \out -> do
src <- getCanonicalizedRootSrc $ fp </> "tables" </> name <.> "conf" <.> "in"
poDir <- getCanonicalizedRootSrc $ fp </> "po"
let src = fp </> "tables" </> name <.> "conf" <.> "in"
poDir = fp </> "po"
_ <- getDirectoryFiles poDir ["*.po"]
need [src]
cmd_ "msgfmt" "-d" poDir "--desktop" "--template" src "-o" out
dict %> \out -> do
src <- getCanonicalizedRootSrc $ fp </> "tables" </> name <.> "txt"
let src = fp </> "tables" </> name <.> "txt"
need [src]
cmd_ "libime_tabledict" src out
packaged %> \_ -> do
need [dict, conf]
cmd_ "zip" tableName dict conf

--------------------------------------------------------------------------------

data MainPath = MainPath
deriving (Show, Typeable, Eq, Generic, Hashable, Binary, NFData)

type instance RuleResult MainPath = FilePath

getCanonicalizedRootSrc :: FilePath -> Action FilePath
getCanonicalizedRootSrc fp = do
root <- askOracle MainPath
liftIO . canonicalizePath $ root </> fp

mainPathRule :: Rules ()
mainPathRule = void $
addOracleCache $
\MainPath -> takeDirectory <$> liftIO getMainPath

getMainPath :: HasCallStack => IO FilePath
getMainPath =
withFrozenCallStack
$ canonicalizePath
. srcLocFile
. snd
. fromJust
. find ((== "getMainPath") . fst)
. getCallStack
$ callStack

--------------------------------------------------------------------------------
cmd_ (Cwd outputDir) "zip" tableName (takeFileName dict) (takeFileName conf)

0 comments on commit fb244da

Please sign in to comment.