tomland-0.2.1: TOML parser

Safe HaskellNone
LanguageHaskell2010

Toml.PrefixTree

Contents

Synopsis

Documentation

data PrefixTree a Source #

Data structure to represent table tree for toml.

Constructors

Leaf !Key !a 
Branch 

Fields

Instances

Eq a => Eq (PrefixTree a) Source # 

Methods

(==) :: PrefixTree a -> PrefixTree a -> Bool #

(/=) :: PrefixTree a -> PrefixTree a -> Bool #

Show a => Show (PrefixTree a) Source # 

singleT :: Key -> a -> PrefixTree a Source #

Creates a PrefixTree of one key-value element.

insertT :: Key -> a -> PrefixTree a -> PrefixTree a Source #

Inserts key-value element into the given PrefixTree.

lookupT :: Key -> PrefixTree a -> Maybe a Source #

Looks up the value at a key in the PrefixTree.

type PrefixMap a = HashMap Piece (PrefixTree a) Source #

Map of layer names and corresponding PrefixTrees.

single :: Key -> a -> PrefixMap a Source #

Creates a PrefixMap of one key-value element.

insert :: Key -> a -> PrefixMap a -> PrefixMap a Source #

Inserts key-value element into the given PrefixMap.

lookup :: Key -> PrefixMap a -> Maybe a Source #

Looks up the value at a key in the PrefixMap.

fromList :: [(Key, a)] -> PrefixMap a Source #

Constructs PrettyMap structure from the given list of Key and value pairs.

Types

newtype Piece Source #

Represents the key piece of some layer.

Constructors

Piece 

Fields

Instances

newtype Key Source #

Key of value in key = val pair. Represents as non-empty list of key components -- Pieces. Key like

site."google.com"

is represented like

Key (Piece "site" :| [Piece "\"google.com\""])

Constructors

Key 

Fields

Instances

Eq Key Source # 

Methods

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

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

Ord Key Source # 

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key Source #

Split a dot-separated string into Key. Empty string turns into a Key with single element - empty Piece. This instance is not safe for now. Use carefully. If you try to use as a key string like this site."google.com" you will have list of three components instead of desired two.

Methods

fromString :: String -> Key #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Semigroup Key Source # 

Methods

(<>) :: Key -> Key -> Key #

sconcat :: NonEmpty Key -> Key #

stimes :: Integral b => b -> Key -> Key #

Hashable Key Source # 

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

type Rep Key Source # 
type Rep Key = D1 * (MetaData "Key" "Toml.PrefixTree" "tomland-0.2.1-EzDrZoCyBj94qZmajBMeJi" True) (C1 * (MetaCons "Key" PrefixI True) (S1 * (MetaSel (Just Symbol "unKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (NonEmpty Piece))))

pattern (:||) :: Piece -> [Piece] -> Key Source #

type Prefix = Key Source #

Type synonym for Key.

data KeysDiff Source #

Constructors

Equal

Keys are equal

NoPrefix

Keys don't have any common part.

FstIsPref

The first key is the prefix for the second one.

Fields

SndIsPref

The second key is the prefix for the first one.

Fields

Diff

Key have same prefix.

Fields