Skip to content

Commit

Permalink
refactor
Browse files Browse the repository at this point in the history
  • Loading branch information
jedimahdi committed Feb 28, 2024
1 parent 77b063b commit 9d52bcc
Show file tree
Hide file tree
Showing 10 changed files with 171 additions and 185 deletions.
1 change: 1 addition & 0 deletions .hlint.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
- "-XGeneralizedNewtypeDeriving"
- "-XLambdaCase"
- "-XOverloadedStrings"
- "-XOverloadedRecordDot"
- "-XRecordWildCards"
- "-XScopedTypeVariables"
- "-XStandaloneDeriving"
Expand Down
2 changes: 1 addition & 1 deletion flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@
packages = p: [ p.flakeit ];
inherit (preCommit) shellHook;
withHoogle = true;
nativeBuildInputs = [ treefmtEval.config.build.wrapper pkgs.ghcid ]
nativeBuildInputs = [ treefmtEval.config.build.wrapper pkgs.ghcid pkgs.just ]
++ (pkgs.lib.attrValues treefmtEval.config.build.programs);
};
});
Expand Down
1 change: 0 additions & 1 deletion flakeit.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ library
FlakeIt.DB
FlakeIt.Nix
FlakeIt.Template
FlakeIt.Types

autogen-modules: Paths_flakeit
other-modules: Paths_flakeit
Expand Down
2 changes: 1 addition & 1 deletion src/FlakeIt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,4 +3,4 @@ module FlakeIt (module FlakeIt) where
import FlakeIt.Cli as FlakeIt
import FlakeIt.DB as FlakeIt
import FlakeIt.Nix as FlakeIt
import FlakeIt.Types as FlakeIt
import FlakeIt.Template as FlakeIt
43 changes: 19 additions & 24 deletions src/FlakeIt/Cli.hs
Original file line number Diff line number Diff line change
@@ -1,55 +1,50 @@
module FlakeIt.Cli where

import Data.List qualified as List
import Data.Text qualified as Text
import Data.Text.IO qualified as TIO
import Data.Version (Version, showVersion)
import FlakeIt.Cli.Parser
import FlakeIt.DB qualified as DB
import FlakeIt.Nix qualified as Nix
import FlakeIt.Template
import FlakeIt.Types
import Options.Applicative
import Options.Applicative (execParser)
import Paths_flakeit qualified as Meta (version)
import System.Exit (exitFailure)
import System.IO (stderr)

flakeit :: Version -> (Command -> IO ()) -> IO ()
flakeit version performCommand = execParser (cliParser version) >>= performCommand

flakeitCli :: IO ()
flakeitCli = flakeit Meta.version runCliCommand

addTemplateGroup :: TemplateUrl -> IO ()
addTemplateGroup url = do
maybeTemplates <- Nix.getTemplateGroup url
case maybeTemplates of
Just ts -> DB.add ts
Nothing -> error "Could not find templates..."
runCliCommand :: Command -> IO ()
runCliCommand = \case
List opts -> runList opts
Add opts -> runAdd opts
Remove opts -> runRemove opts
New opts -> runNew opts
Init opts -> runInit opts

runList :: ListOptions -> IO ()
runList opts = do
db <- DB.getAll
TIO.putStr $ prettyTemplates db

runAdd :: AddOptions -> IO ()
runAdd opts = addTemplateGroup opts.path

runUpdate :: UpdateOptions -> IO ()
runUpdate opts = addTemplateGroup opts.path
runAdd opts = do
maybeSource <- Nix.getTemplateSource opts.url
case maybeSource of
Just source -> DB.add source
Nothing -> do
TIO.hPutStrLn stderr "error: Could not parse the flake"
exitFailure

runRemove :: RemoveOptions -> IO ()
runRemove opts = DB.remove opts.path
runRemove opts = DB.remove opts.url

runNew :: NewOptions -> IO ()
runNew opts = Nix.newTemplate opts.name opts.template
runNew opts = Nix.newTemplate opts.projectName opts.template

runInit :: InitOptions -> IO ()
runInit opts = Nix.initTemplate opts.template

runCliCommand :: Command -> IO ()
runCliCommand = \case
List opts -> runList opts
Add opts -> runAdd opts
Update opts -> runUpdate opts
Remove opts -> runRemove opts
New opts -> runNew opts
Init opts -> runInit opts
129 changes: 50 additions & 79 deletions src/FlakeIt/Cli/Parser.hs
Original file line number Diff line number Diff line change
@@ -1,106 +1,92 @@
module FlakeIt.Cli.Parser where

import Data.List qualified as List
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Version (Version, showVersion)
import FlakeIt.DB qualified as DB
import FlakeIt.Nix qualified as Nix
import FlakeIt.Template
import FlakeIt.Types
import Options.Applicative

data Command
= List !ListOptions
| Add !AddOptions
| Remove !RemoveOptions
| Init !InitOptions
| New !NewOptions
deriving (Show)

cliParser :: Version -> ParserInfo Command
cliParser version = info (helper <*> versionP version <*> commandP) $ fullDesc <> progDesc "Flake It Program"

versionP :: Version -> Parser (a -> a)
versionP version =
infoOption (flakeitVersion version) $
long "version"
<> short 'v'
<> help "Show flakeit's version"
<> hidden

flakeitVersion :: Version -> String
flakeitVersion version = "flakeit " <> "v" <> showVersion version
commandP :: Parser Command
commandP =
hsubparser $
mconcat
[ command "add" (info addCommand $ progDesc "Add tempalates with flake url")
, command "list" (info listCommand $ progDesc "List templates")
, command "remove" (info removeCommand $ progDesc "Remove templates with flake url")
, command "init" (info initCommand $ progDesc "Init flake template")
, command "new" (info newCommand $ progDesc "New flake template")
]

templateCompleter :: Completer
templateCompleter = mkCompleter comp
where
comp :: String -> IO [String]
comp s = do
map Text.unpack . concatMap listTemplates <$> DB.getAll
map templateToString . concatMap listTemplates <$> DB.getAll

pathCompleter :: Completer
pathCompleter = mkCompleter comp
urlCompleter :: Completer
urlCompleter = mkCompleter comp
where
comp :: String -> IO [String]
comp s =
filter (\t -> s `List.isPrefixOf` t) . map (Text.unpack . (\l -> l.url)) <$> DB.getAll
filter (\t -> s `List.isPrefixOf` t) . map (urlToString . (\l -> l.url)) <$> DB.getAll

data Command
= List !ListOptions
| Add !AddOptions
| Remove !RemoveOptions
| Update !UpdateOptions
| Init !InitOptions
| New !NewOptions
deriving (Show)
versionP :: Version -> Parser (a -> a)
versionP version =
infoOption flakeitVersion $
long "version"
<> short 'v'
<> help "Show flakeit's version"
<> hidden
where
flakeitVersion :: String
flakeitVersion = "flakeit " <> "v" <> showVersion version

templateP :: Parser Template
templateP = strOption (long "template" <> short 't' <> help "Choose template to use" <> completer templateCompleter)

projectNameP :: Parser String
projectNameP = argument str (metavar "NAME")

urlP :: Parser SourceUrl
urlP = argument str (completer urlCompleter <> metavar "PATH")

data NewOptions = NewOptions
{ template :: !Text
, name :: !Text
{ template :: !Template
, projectName :: !String
}
deriving (Show)

newOpts :: Parser NewOptions
newOpts =
NewOptions
<$> strOption (long "template" <> short 't' <> help "Choose template to use" <> completer templateCompleter)
<*> argument str (completer pathCompleter <> metavar "NAME")

newCommand :: Parser Command
newCommand =
New
<$> ( NewOptions
<$> strOption (long "template" <> short 't' <> help "Choose template to use" <> completer templateCompleter)
<*> argument str (completer pathCompleter <> metavar "NAME")
)
newCommand = New <$> (NewOptions <$> templateP <*> projectNameP)

data InitOptions = InitOptions
{ template :: !Text
{ template :: !Template
}
deriving (Show)

initCommand :: Parser Command
initCommand =
Init . InitOptions
<$> strOption (long "template" <> short 't' <> help "Choose template to use" <> completer templateCompleter)

data UpdateOptions = UpdateOptions
{ path :: Text
}
deriving (Show)

updateOpts :: Parser UpdateOptions
updateOpts =
UpdateOptions
<$> argument str (completer pathCompleter <> metavar "PATH")

updateCommand :: Parser Command
updateCommand =
Update . UpdateOptions
<$> argument str (completer pathCompleter <> metavar "PATH")
initCommand = Init . InitOptions <$> templateP

data RemoveOptions = RemoveOptions
{ path :: Text
{ url :: SourceUrl
}
deriving (Show)

removeCommand :: Parser Command
removeCommand =
Remove . RemoveOptions
<$> argument str (completer pathCompleter <> metavar "PATH")
removeCommand = Remove . RemoveOptions <$> urlP

data ListOptions = ListOptions
{}
Expand All @@ -110,24 +96,9 @@ listCommand :: Parser Command
listCommand = pure (List ListOptions)

data AddOptions = AddOptions
{ path :: Text
{ url :: SourceUrl
}
deriving (Show)

addCommand :: Parser Command
addCommand = Add . AddOptions <$> argument str (metavar "PATH")

commandP :: Parser Command
commandP =
hsubparser $
mconcat
[ command "add" (info addCommand $ progDesc "Add a flake tempalate url")
, command "list" (info listCommand $ progDesc "List templates")
, command "remove" (info removeCommand $ progDesc "Remove flake template url")
, command "update" (info updateCommand $ progDesc "Update flake template url")
, command "init" (info initCommand $ progDesc "Init flake template")
, command "new" (info newCommand $ progDesc "New flake template")
]

flakeitP :: ParserInfo Command
flakeitP = info (helper <*> commandP) (progDesc "Flake It Program")
addCommand = Add . AddOptions <$> urlP
51 changes: 28 additions & 23 deletions src/FlakeIt/DB.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Control.Monad (when)
import Data.Binary
import Data.List qualified as List
import FlakeIt.Nix qualified as Nix
import FlakeIt.Types
import FlakeIt.Template
import System.Directory (
XdgDirectory (XdgData),
createDirectoryIfMissing,
Expand All @@ -21,34 +21,39 @@ import System.FilePath ((</>))

clear :: IO ()
clear = do
dbPath <- getDBPath
dbPath <- defaultDBPath
doesExist <- doesFileExist dbPath
when doesExist $ removeFile dbPath

add :: TemplateGroup -> IO ()
add tg = do
dbPath <- getDBPath
dbExist <- doesFileExist dbPath
prevDb <- if dbExist then decodeFile @[TemplateGroup] dbPath else pure []
let newDb = tg : filter (\t -> t.url /= tg.url) prevDb
encodeFile dbPath newDb
add :: Source -> IO ()
add source = do
dbDirectory <- defaultDBDirectory
createDirectoryIfMissing True dbDirectory
dbPath <- defaultDBPath
prevDb <- readDB dbPath
let newDb = source : filter (\s -> s.url /= source.url) prevDb
writeDB dbPath newDb

remove :: TemplateUrl -> IO ()
remove :: SourceUrl -> IO ()
remove url = do
dbPath <- getDBPath
dbExist <- doesFileExist dbPath
prevDb <- if dbExist then decodeFile @[TemplateGroup] dbPath else pure []
dbPath <- defaultDBPath
prevDb <- readDB dbPath
let newDb = filter (\t -> t.url /= url) prevDb
encodeFile dbPath newDb
writeDB dbPath newDb

getAll :: IO [Source]
getAll = defaultDBPath >>= readDB

getAll :: IO [TemplateGroup]
getAll = do
dbPath <- getDBPath
readDB :: FilePath -> IO [Source]
readDB dbPath = do
dbExist <- doesFileExist dbPath
if dbExist then decodeFile @[TemplateGroup] dbPath else pure []
if dbExist then decodeFile @[Source] dbPath else pure []

writeDB :: FilePath -> [Source] -> IO ()
writeDB = encodeFile

defaultDBDirectory :: IO FilePath
defaultDBDirectory = getXdgDirectory XdgData "flakeit"

getDBPath :: IO FilePath
getDBPath = do
dataPath <- getXdgDirectory XdgData "flakeit"
createDirectoryIfMissing True dataPath
pure $ dataPath </> "db"
defaultDBPath :: IO FilePath
defaultDBPath = fmap (</> "db") defaultDBDirectory
Loading

0 comments on commit 9d52bcc

Please sign in to comment.