{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Life.Shell
(
lifePath
, repoName
, LifeExistence (..)
, createDirInHome
, relativeToHome
, whatIsLife
, ($|)
) where
import Path (Abs, Dir, File, Path, Rel, mkRelDir, mkRelFile, (</>))
import Path.IO (createDirIfMissing, doesDirExist, doesFileExist, getHomeDir)
import System.Process (callCommand, readProcess, showCommandForUser)
lifePath :: Path Rel File
lifePath = $(mkRelFile ".life")
repoName :: Path Rel Dir
repoName = $(mkRelDir "dotfiles/")
instance (a ~ Text, b ~ ()) => IsString ([a] -> IO b) where
fromString cmd args = do
let cmdStr = showCommandForUser cmd (map toString args)
putStrLn $ "⚙ " ++ cmdStr
callCommand cmdStr
infix 5 $|
($|) :: FilePath -> [Text] -> IO String
cmd $| args = readProcess cmd (map toString args) ""
createDirInHome :: Path Rel Dir -> IO (Path Abs Dir)
createDirInHome dirName = do
newDir <- relativeToHome dirName
newDir <$ createDirIfMissing False newDir
relativeToHome :: MonadIO m => Path Rel t -> m (Path Abs t)
relativeToHome path = do
homeDir <- getHomeDir
pure $ homeDir </> path
data LifeExistence
= NoLife
| OnlyLife (Path Abs File)
| OnlyRepo (Path Abs Dir)
| Both (Path Abs File) (Path Abs Dir)
whatIsLife :: IO LifeExistence
whatIsLife = do
lifeFile <- relativeToHome lifePath
repoDir <- relativeToHome repoName
isFile <- doesFileExist lifeFile
isDir <- doesDirExist repoDir
pure $ case (isFile, isDir) of
(False, False) -> NoLife
(True, False) -> OnlyLife lifeFile
(False, True) -> OnlyRepo repoDir
(True, True) -> Both lifeFile repoDir