vgrep-0.2.2.0: A pager for grep

Safe HaskellNone
LanguageHaskell2010

Vgrep.Environment.Config.Sources.File

Contents

Synopsis

Documentation

configFromFile :: MonadIO io => io ConfigMonoid Source #

Reads the configuration from a JSON or YAML file. The file should be located in one of the following places:

  • ~/.vgrep/config.yaml,
  • ~/.vgrep/config.yml,
  • ~/.vgrep/config.json or
  • ~/.vgrep/config.

When none of these files exist, no error is raised. When a file exists, but cannot be parsed, a warning is written to stderr.

Supported formats are JSON and YAML. The example YAML config given in the project directory (config.yaml.example) is equivalent to the default config:

>>> import qualified Vgrep.Environment.Config as C
>>> Right config <- decodeFileEither "config.yaml.example" :: IO (Either ParseException ConfigMonoid)
>>> C.fromConfigMonoid config == C.defaultConfig
True

Example YAML config file for defaultConfig:

colors:
  line-numbers:
    fore-color: blue
  line-numbers-hl:
    fore-color: blue
    style: bold
  normal: {}
  normal-hl:
    style: bold
  file-headers:
    back-color: green
  selected:
    style: standout
tabstop: 8
editor: "vi"

Example JSON file for the same config:

{
  "colors": {
    "line-numbers" : {
      "fore-color": "blue"
    },
    "line-numbers-hl": {
      "fore-color": "blue",
      "style": "bold"
    },
    "normal": {},
    "normal-hl": {
      "style": "bold"
    },
    "file-headers": {
      "back-color": "green"
    },
    "selected": {
      "style": "standout"
    }
  },
  "tabstop": 8,
  "editor": "vi"
}

The JSON/YAML keys correspond to the lenses in Vgrep.Environment.Config, the values for Color and Style can be obtained from the corresponding predefined constants in Graphics.Vty.Attributes.

data Attr Source #

A JSON-parsable data type for Attr.

JSON example:

>>> decodeEither "{\"fore-color\": \"black\", \"style\": \"standout\"}" :: Either String Attr
Right (Attr {foreColor = Just Black, backColor = Nothing, style = Just Standout})

JSON example without quotes: >>> decodeEither "{fore-color: black, style: standout}" :: Either String Attr Right (Attr {foreColor = Just Black, backColor = Nothing, style = Just Standout})

YAML example:

>>> :{
>>> decodeEither
>>> $  "fore-color: \"blue\"\n"
>>> <> "back-color: \"bright-blue\"\n"
>>> <> "style: \"reverse-video\"\n"
>>> :: Either String Attr
>>> :}
Right (Attr {foreColor = Just Blue, backColor = Just BrightBlue, style = Just ReverseVideo})

YAML example without quotes:

>>> :{
>>> decodeEither
>>> $  "fore-color: blue\n"
>>> <> "back-color: bright-blue\n"
>>> <> "style: reverse-video\n"
>>> :: Either String Attr
>>> :}
Right (Attr {foreColor = Just Blue, backColor = Just BrightBlue, style = Just ReverseVideo})

An empty JSON/YAML object yields the default colors:

>>> decodeEither "{}" :: Either String Attr
Right (Attr {foreColor = Nothing, backColor = Nothing, style = Nothing})

Instances

Eq Attr Source # 

Methods

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

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

Show Attr Source # 

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Generic Attr Source # 

Associated Types

type Rep Attr :: * -> * #

Methods

from :: Attr -> Rep Attr x #

to :: Rep Attr x -> Attr #

FromJSON Attr Source # 
type Rep Attr Source # 
type Rep Attr = D1 * (MetaData "Attr" "Vgrep.Environment.Config.Sources.File" "vgrep-0.2.2.0-IScrB41HG5t6kfzIkcOjbm" False) (C1 * (MetaCons "Attr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "foreColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) ((:*:) * (S1 * (MetaSel (Just Symbol "backColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "style") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Style))))))

data Color Source #

A JSON-parsable data type for Color.

>>> decodeEither "[\"black\",\"red\",\"bright-black\"]" :: Either String [Color]
Right [Black,Red,BrightBlack]

Also works without quotes:

>>> decodeEither "[black,red,bright-black]" :: Either String [Color]
Right [Black,Red,BrightBlack]

Fails with error message if the Color cannot be parsed:

>>> let Left err = decodeEither "foo" :: Either String Color
>>> "The key \"foo\" was not found" `isInfixOf` err
True

Instances

Eq Color Source # 

Methods

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

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

Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 

Associated Types

type Rep Color :: * -> * #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

FromJSON Color Source # 
type Rep Color Source # 
type Rep Color = D1 * (MetaData "Color" "Vgrep.Environment.Config.Sources.File" "vgrep-0.2.2.0-IScrB41HG5t6kfzIkcOjbm" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Black" PrefixI False) (U1 *)) (C1 * (MetaCons "Red" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Green" PrefixI False) (U1 *)) (C1 * (MetaCons "Yellow" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Blue" PrefixI False) (U1 *)) (C1 * (MetaCons "Magenta" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Cyan" PrefixI False) (U1 *)) (C1 * (MetaCons "White" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "BrightBlack" PrefixI False) (U1 *)) (C1 * (MetaCons "BrightRed" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "BrightGreen" PrefixI False) (U1 *)) (C1 * (MetaCons "BrightYellow" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "BrightBlue" PrefixI False) (U1 *)) (C1 * (MetaCons "BrightMagenta" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "BrightCyan" PrefixI False) (U1 *)) (C1 * (MetaCons "BrightWhite" PrefixI False) (U1 *))))))

data Style Source #

A JSON-parsable data type for Style.

>>> decodeEither "[\"standout\", \"underline\", \"bold\"]" :: Either String [Style]
Right [Standout,Underline,Bold]

Also works without quotes:

>>> decodeEither "[standout, underline, bold]" :: Either String [Style]
Right [Standout,Underline,Bold]

Fails with error message if the Style cannot be parsed:

>>> let Left err = decodeEither "foo" :: Either String Style
>>> "The key \"foo\" was not found" `isInfixOf` err
True

Instances

Eq Style Source # 

Methods

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

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

Show Style Source # 

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style Source # 

Associated Types

type Rep Style :: * -> * #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

FromJSON Style Source # 
type Rep Style Source # 
type Rep Style = D1 * (MetaData "Style" "Vgrep.Environment.Config.Sources.File" "vgrep-0.2.2.0-IScrB41HG5t6kfzIkcOjbm" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Standout" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Underline" PrefixI False) (U1 *)) (C1 * (MetaCons "ReverseVideo" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Blink" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Dim" PrefixI False) (U1 *)) (C1 * (MetaCons "Bold" PrefixI False) (U1 *)))))

Orphan instances