mirror of
https://github.com/Avi-D-coder/implicit-hie.git
synced 2024-11-25 06:34:41 +03:00
Refactor
This commit is contained in:
parent
a88f56114c
commit
89ace448a3
39
app/Main.hs
39
app/Main.hs
@ -5,6 +5,7 @@ module Main where
|
|||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.Trans.Maybe
|
import Control.Monad.Trans.Maybe
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
import Hie.Cabal.Parser
|
||||||
import Hie.Locate
|
import Hie.Locate
|
||||||
import Hie.Yaml
|
import Hie.Yaml
|
||||||
import System.Directory
|
import System.Directory
|
||||||
@ -16,27 +17,29 @@ import System.IO
|
|||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
pwd <- getCurrentDirectory
|
pwd <- getCurrentDirectory
|
||||||
name <- resolveName pwd
|
ct <- resolveCradleType pwd
|
||||||
cfs <- runMaybeT $ case name of
|
cfs <- runMaybeT $ case ct of
|
||||||
"cabal" -> cabalPkgs pwd
|
CabalCradle -> cabalPkgs pwd
|
||||||
_ -> stackYamlPkgs pwd
|
StackCradle -> stackYamlPkgs pwd
|
||||||
when (null cfs) $
|
when (null cfs) $
|
||||||
die $
|
die $
|
||||||
"Used " <> name
|
"Used "
|
||||||
|
<> cradleTypeName ct
|
||||||
<> "\n No .cabal files found under"
|
<> "\n No .cabal files found under"
|
||||||
<> pwd
|
<> pwd
|
||||||
<> "\n You may need to run stack build."
|
<> "\n You may need to run stack build."
|
||||||
pkgs <- catMaybes <$> mapM (nestedPkg pwd) (concat cfs)
|
pkgs <- catMaybes <$> mapM (nestedPkg pwd) (concat cfs)
|
||||||
putStr <$> hieYaml name $ fmtPkgs name pkgs
|
putStr <$> hieYaml ct $ fmtPkgs ct pkgs
|
||||||
|
|
||||||
resolveName :: FilePath -> IO String
|
resolveCradleType :: FilePath -> IO CradleType
|
||||||
resolveName pwd = do
|
resolveCradleType pwd = do
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
files <- listDirectory pwd
|
files <- listDirectory pwd
|
||||||
when ("--help" `elem` args || "-h" `elem` args) $ do
|
when ("--help" `elem` args || "-h" `elem` args) $ do
|
||||||
progName <- getProgName
|
progName <- getProgName
|
||||||
hPutStrLn stderr $
|
hPutStrLn stderr $
|
||||||
"Usage: " <> progName
|
"Usage: "
|
||||||
|
<> progName
|
||||||
<> " [ --cabal | --stack ]\n\n\
|
<> " [ --cabal | --stack ]\n\n\
|
||||||
\If neither argument is given then "
|
\If neither argument is given then "
|
||||||
<> progName
|
<> progName
|
||||||
@ -44,13 +47,13 @@ resolveName pwd = do
|
|||||||
\looking for dist-newstyle, .stack-work, cabal.project and stack.yaml in that order."
|
\looking for dist-newstyle, .stack-work, cabal.project and stack.yaml in that order."
|
||||||
exitSuccess
|
exitSuccess
|
||||||
let fileNames = map takeFileName files
|
let fileNames = map takeFileName files
|
||||||
name =
|
ct =
|
||||||
if
|
if
|
||||||
| "--cabal" `elem` args -> "cabal"
|
| "--cabal" `elem` args -> CabalCradle
|
||||||
| "--stack" `elem` args -> "stack"
|
| "--stack" `elem` args -> StackCradle
|
||||||
| "dist-newstyle" `elem` fileNames -> "cabal"
|
| "dist-newstyle" `elem` fileNames -> CabalCradle
|
||||||
| ".stack-work" `elem` fileNames -> "stack"
|
| ".stack-work" `elem` fileNames -> StackCradle
|
||||||
| "cabal.project" `elem` fileNames -> "cabal"
|
| "cabal.project" `elem` fileNames -> CabalCradle
|
||||||
| "stack.yaml" `elem` fileNames -> "stack"
|
| "stack.yaml" `elem` fileNames -> StackCradle
|
||||||
| otherwise -> "cabal"
|
| otherwise -> CabalCradle
|
||||||
return name
|
return ct
|
||||||
|
@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
|
||||||
@ -6,6 +7,9 @@ module Hie.Cabal.Parser
|
|||||||
Component (..),
|
Component (..),
|
||||||
CompType (..),
|
CompType (..),
|
||||||
Name,
|
Name,
|
||||||
|
CradleType (..),
|
||||||
|
CradlePer (..),
|
||||||
|
cradleTypeName,
|
||||||
extractPkgs,
|
extractPkgs,
|
||||||
parsePackage',
|
parsePackage',
|
||||||
)
|
)
|
||||||
@ -71,6 +75,17 @@ data Component
|
|||||||
= Comp CompType Name Path
|
= Comp CompType Name Path
|
||||||
deriving (Show, Eq, Ord)
|
deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
|
data CradleType = StackCradle | CabalCradle
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
cradleTypeName :: CradleType -> String
|
||||||
|
cradleTypeName = \case
|
||||||
|
StackCradle -> "stack"
|
||||||
|
CabalCradle -> "cabal"
|
||||||
|
|
||||||
|
data CradlePer = PerSrcDir | PerModule
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
parseQuoted :: Parser Text
|
parseQuoted :: Parser Text
|
||||||
parseQuoted = do
|
parseQuoted = do
|
||||||
q <- char '"' <|> char '\''
|
q <- char '"' <|> char '\''
|
||||||
|
@ -1,3 +1,4 @@
|
|||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
module Hie.Yaml
|
module Hie.Yaml
|
||||||
@ -6,17 +7,18 @@ module Hie.Yaml
|
|||||||
fmtPkgs,
|
fmtPkgs,
|
||||||
cabalComponent,
|
cabalComponent,
|
||||||
stackComponent,
|
stackComponent,
|
||||||
|
component,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Hie.Cabal.Parser
|
import Hie.Cabal.Parser
|
||||||
|
|
||||||
hieYaml :: String -> String -> String
|
hieYaml :: CradleType -> String -> String
|
||||||
hieYaml sOrC pkgs =
|
hieYaml ct pkgs =
|
||||||
"cradle:\n"
|
"cradle:\n"
|
||||||
<> indent'
|
<> indent'
|
||||||
(sOrC <> ":\n" <> indent' pkgs)
|
(cradleTypeName ct <> ":\n" <> indent' pkgs)
|
||||||
|
|
||||||
indent' :: String -> String
|
indent' :: String -> String
|
||||||
indent' =
|
indent' =
|
||||||
@ -28,6 +30,11 @@ indent' =
|
|||||||
)
|
)
|
||||||
. lines
|
. lines
|
||||||
|
|
||||||
|
component :: CradleType -> Name -> Component -> (FilePath, String)
|
||||||
|
component = \case
|
||||||
|
CabalCradle -> cabalComponent
|
||||||
|
StackCradle -> stackComponent
|
||||||
|
|
||||||
cabalComponent :: Name -> Component -> (FilePath, String)
|
cabalComponent :: Name -> Component -> (FilePath, String)
|
||||||
cabalComponent n (Comp Lib "" p) = (T.unpack p, T.unpack $ "lib:" <> n)
|
cabalComponent n (Comp Lib "" p) = (T.unpack p, T.unpack $ "lib:" <> n)
|
||||||
cabalComponent n (Comp Lib cn p) = (T.unpack p, T.unpack $ n <> ":lib:" <> cn)
|
cabalComponent n (Comp Lib cn p) = (T.unpack p, T.unpack $ n <> ":lib:" <> cn)
|
||||||
@ -54,11 +61,10 @@ fmtComponent (p, c) =
|
|||||||
dropLast :: [a] -> [a]
|
dropLast :: [a] -> [a]
|
||||||
dropLast l = take (length l - 1) l
|
dropLast l = take (length l - 1) l
|
||||||
|
|
||||||
fmtPkgs :: String -> [Package] -> String
|
fmtPkgs :: CradleType -> [Package] -> String
|
||||||
fmtPkgs sOrC pkgs = dropLast $ unlines l
|
fmtPkgs ct pkgs = dropLast $ unlines l
|
||||||
where
|
where
|
||||||
comp = if sOrC == "cabal" then cabalComponent else stackComponent
|
f (Package n cs) = map ((<> "\n") . fmtComponent . component ct n) cs
|
||||||
f (Package n cs) = map ((<> "\n") . fmtComponent . comp n) cs
|
|
||||||
l = concatMap f pkgs
|
l = concatMap f pkgs
|
||||||
|
|
||||||
dQuote :: String -> String
|
dQuote :: String -> String
|
||||||
|
Loading…
Reference in New Issue
Block a user