tomland-1.1.0.0: Bidirectional TOML serialization

Safe HaskellNone
LanguageHaskell2010

Toml.PrefixTree

Contents

Description

Implementation of prefix tree for TOML AST.

Synopsis

Core types

newtype Piece Source #

Represents the key piece of some layer.

Constructors

Piece 

Fields

Instances
Eq Piece Source # 
Instance details

Defined in Toml.PrefixTree

Methods

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

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

Ord Piece Source # 
Instance details

Defined in Toml.PrefixTree

Methods

compare :: Piece -> Piece -> Ordering #

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

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

(>) :: Piece -> Piece -> Bool #

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

max :: Piece -> Piece -> Piece #

min :: Piece -> Piece -> Piece #

Show Piece Source # 
Instance details

Defined in Toml.PrefixTree

Methods

showsPrec :: Int -> Piece -> ShowS #

show :: Piece -> String #

showList :: [Piece] -> ShowS #

IsString Piece Source # 
Instance details

Defined in Toml.PrefixTree

Methods

fromString :: String -> Piece #

Generic Piece Source # 
Instance details

Defined in Toml.PrefixTree

Associated Types

type Rep Piece :: Type -> Type #

Methods

from :: Piece -> Rep Piece x #

to :: Rep Piece x -> Piece #

NFData Piece Source # 
Instance details

Defined in Toml.PrefixTree

Methods

rnf :: Piece -> () #

Hashable Piece Source # 
Instance details

Defined in Toml.PrefixTree

Methods

hashWithSalt :: Int -> Piece -> Int

hash :: Piece -> Int

type Rep Piece Source # 
Instance details

Defined in Toml.PrefixTree

type Rep Piece = D1 (MetaData "Piece" "Toml.PrefixTree" "tomland-1.1.0.0-inplace" True) (C1 (MetaCons "Piece" PrefixI True) (S1 (MetaSel (Just "unPiece") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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 # 
Instance details

Defined in Toml.PrefixTree

Methods

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

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

Ord Key Source # 
Instance details

Defined in Toml.PrefixTree

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 # 
Instance details

Defined in Toml.PrefixTree

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.

Instance details

Defined in Toml.PrefixTree

Methods

fromString :: String -> Key #

Generic Key Source # 
Instance details

Defined in Toml.PrefixTree

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Semigroup Key Source # 
Instance details

Defined in Toml.PrefixTree

Methods

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

sconcat :: NonEmpty Key -> Key #

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

NFData Key Source # 
Instance details

Defined in Toml.PrefixTree

Methods

rnf :: Key -> () #

Hashable Key Source # 
Instance details

Defined in Toml.PrefixTree

Methods

hashWithSalt :: Int -> Key -> Int

hash :: Key -> Int

type Rep Key Source # 
Instance details

Defined in Toml.PrefixTree

type Rep Key = D1 (MetaData "Key" "Toml.PrefixTree" "tomland-1.1.0.0-inplace" True) (C1 (MetaCons "Key" PrefixI True) (S1 (MetaSel (Just "unKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty Piece))))

type Prefix = Key Source #

Type synonym for Key.

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

Bidirectional pattern synonym for constructing and deconstructing Keys.

Key difference

data KeysDiff Source #

Data structure to compare keys.

Constructors

Equal

Keys are equal

NoPrefix

Keys don't have any common part.

FstIsPref

The first key is the prefix of the second one.

Fields

  • !Key

    Rest of the second key.

SndIsPref

The second key is the prefix of the first one.

Fields

  • !Key

    Rest of the first key.

Diff

Key have a common prefix.

Fields

  • !Key

    Common prefix.

  • !Key

    Rest of the first key.

  • !Key

    Rest of the second key.

Instances
Eq KeysDiff Source # 
Instance details

Defined in Toml.PrefixTree

Show KeysDiff Source # 
Instance details

Defined in Toml.PrefixTree

keysDiff :: Key -> Key -> KeysDiff Source #

Compares two keys

Non-empty prefix tree

data PrefixTree a Source #

Data structure to represent table tree for toml.

Constructors

Leaf

End of a key.

Fields

  • !Key

    End piece of the key.

  • !a

    Value at the end.

Branch

Values along pieces of a key.

Fields

  • !Prefix

    Greatest common key prefix.

  • !(Maybe a)

    Possible value at that point.

  • !(PrefixMap a)

    Values at suffixes of the prefix.

Instances
Eq a => Eq (PrefixTree a) Source # 
Instance details

Defined in Toml.PrefixTree

Methods

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

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

Show a => Show (PrefixTree a) Source # 
Instance details

Defined in Toml.PrefixTree

Generic (PrefixTree a) Source # 
Instance details

Defined in Toml.PrefixTree

Associated Types

type Rep (PrefixTree a) :: Type -> Type #

Methods

from :: PrefixTree a -> Rep (PrefixTree a) x #

to :: Rep (PrefixTree a) x -> PrefixTree a #

Semigroup (PrefixTree a) Source # 
Instance details

Defined in Toml.PrefixTree

NFData a => NFData (PrefixTree a) Source # 
Instance details

Defined in Toml.PrefixTree

Methods

rnf :: PrefixTree a -> () #

type Rep (PrefixTree a) Source # 
Instance details

Defined in Toml.PrefixTree

(<|) :: Piece -> Key -> Key Source #

Prepends Piece to the beginning of the Key.

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.

toListT :: PrefixTree a -> [(Key, a)] Source #

Converts PrefixTree to the list of pairs.

Prefix map that stores roots of 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 PrefixMap structure from the given list of Key and value pairs.

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

Converts PrefixMap to the list of pairs.