vcs-ignore-0.0.1.0: Library for handling files ignored by VCS systems.
Copyright(c) 2020-2021 Vaclav Svejcar
LicenseBSD-3-Clause
Maintainervaclav.svejcar@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Data.VCS.Ignore

Description

vcs-ignore is small Haskell library used to find, check and process files ignored by selected VCS.

Example of Use

Because this library is really simple to use, following example should be enough to understand how to use it for your project.

Listing all files/directories ignored by VCS


module Data.VCS.Test where

import Data.VCS.Ignore ( Git, Repo(..), listRepo )

example :: IO [FilePath]
example = do
  repo <- scanRepo @Git "pathtorepo"
  listRepo repo

Walking files/directories ignored by VCS


module Data.VCS.Test where

import Data.Maybe       ( catMaybes )
import System.Directory ( doesFileExist )
import Data.VCS.Ignore  ( Git, Repo(..), walkRepo )

onlyFiles :: IO [FilePath]
onlyFiles = do
  repo <- scanRepo @Git "pathtorepo"
  catMaybes $ walkRepo repo walkFn
 where
  walkFn path = do
    file <- doesFileExist path
    pure (if file then Just path else Nothing)

Checking if path is ignored by VCS


module Data.VCS.Test where

import Data.VCS.Ignore ( Git, Repo(..) )

checkIgnored :: IO Bool
checkIgnored = do
  repo <- scanRepo @Git "pathtorepo"
  isIgnored repo "somepath/.DS_Store"
Synopsis

Documentation

findRepo Source #

Arguments

:: (MonadIO m, Repo r) 
=> FilePath

path where to start scanning

-> m (Maybe r)

scanned Repo (if found)

Attempts to find (and scan via scanRepo) repository at given path. If given path doesn't contain valid repository, it recursively tries in every parent directory until the root directory (e.g. C: or /) is reached.

listRepo Source #

Arguments

:: (MonadIO m, Repo r) 
=> r

repository to list

-> m [FilePath]

list of non-ignored paths within the repository

Resursively lists all non-ignored paths withing the given repository (both files and directories).

walkRepo Source #

Arguments

:: (MonadIO m, Repo r) 
=> r

repository to walk

-> (FilePath -> m a)

action to perform on every non-excluded filepath

-> m [a]

list of paths transformed by the action function

Similar to listRepo, but allows to perform any action on every non-ignored path within the repository.

Repo type class

class Repo r where Source #

Type class representing instance of VCS repository of selected type. In order to obtain instance, the physical repository needs to be scanned first by the scanRepo method. Then absolute path to the repository root is provided by repoRoot method. To check if any path (relative to the repo root) is ignored or not, use the isIgnored method.

Methods

repoName Source #

Arguments

:: r

VCS repository instance

-> Text

name of the repository

Returns name of the repository (e.g. GIT).

repoRoot Source #

Arguments

:: r

VCS repository instance

-> FilePath

absolute path to the repository

Returns absolute path to the root of the VCS repository.

scanRepo Source #

Arguments

:: (MonadIO m, MonadThrow m) 
=> FilePath

path to the VCS repository root

-> m r

scanned repository (or failure)

Scans repository at given path. If the given path doesn't contain valid repository, RepoError may be thrown.

isIgnored Source #

Arguments

:: MonadIO m 
=> r

VCS repository instance

-> FilePath

path to check, relative to the repository root

-> m Bool

whether the path is ignored or not

Checks whether the given path is ignored. The input path is expected to be relative to the repository root, it might or might not point to existing file or directory.

Instances

Instances details
Repo Git Source # 
Instance details

Defined in Data.VCS.Ignore.Repo.Git

data RepoError Source #

Represents error related to operations over the VCS repository.

Constructors

InvalidRepo FilePath Text

Given FilePath doesn't contain valid VCS repository root.

Instances

Instances details
Eq RepoError Source # 
Instance details

Defined in Data.VCS.Ignore.Repo

Show RepoError Source # 
Instance details

Defined in Data.VCS.Ignore.Repo

Exception RepoError Source # 
Instance details

Defined in Data.VCS.Ignore.Repo

GIT implementation

data Git Source #

Data type representing scanned instance of GIT repository.

Constructors

Git 

Fields

Instances

Instances details
Eq Git Source # 
Instance details

Defined in Data.VCS.Ignore.Repo.Git

Methods

(==) :: Git -> Git -> Bool #

(/=) :: Git -> Git -> Bool #

Show Git Source # 
Instance details

Defined in Data.VCS.Ignore.Repo.Git

Methods

showsPrec :: Int -> Git -> ShowS #

show :: Git -> String #

showList :: [Git] -> ShowS #

Repo Git Source # 
Instance details

Defined in Data.VCS.Ignore.Repo.Git

Common data types

data VCSIgnoreError Source #

Top-level of any exception thrown by this library.

Constructors

forall e.Exception e => VCSIgnoreError e