tomland-1.3.3.2: Bidirectional TOML serialization
Copyright(c) 2018-2022 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Toml.Type.TOML

Description

Type of TOML AST. This is intermediate representation of TOML parsed from text.

Synopsis

Documentation

data TOML Source #

Represents TOML configuration value.

For example, if we have the following TOML file:

server.port        = 8080
server.codes       = [ 5, 10, 42 ]
server.description = "This is production server."

[mail]
    host = "smtp.gmail.com"
    send-if-inactive = false

[[user]]
    id = 42

[[user]]
    name = "Foo Bar"

corresponding TOML looks like:

TOML
    { tomlPairs = fromList
        [ ( "server" :| [ "port" ] , Integer 8080)
        , ( "server" :| [ "codes" ] , Array [ Integer 5 , Integer 10 , Integer 42])
        , ( "server" :| [ "description" ] , Text "This is production server.")
        ]
    , tomlTables = fromList
        [ ( "mail"
          , Leaf ( "mail" :| [] )
              ( TOML
                  { tomlPairs = fromList
                      [ ( "host" :| [] , Text "smtp.gmail.com")
                      , ( "send-if-inactive" :| [] , Bool False)
                      ]
                  , tomlTables = fromList []
                  , tomlTableArrays = fromList []
                  }
              )
          )
        ]
    , tomlTableArrays = fromList
        [ ( "user" :| []
          , TOML
              { tomlPairs = fromList [( "id" :| [] , Integer 42)]
              , tomlTables = fromList []
              , tomlTableArrays = fromList []
              } :|
              [ TOML
                  { tomlPairs = fromList [( "name" :| [] , Text "Foo Bar")]
                  , tomlTables = fromList []
                  , tomlTableArrays = fromList []
                  }
              ]
          )
        ]
    }

Since: 0.0.0

Instances

Instances details
Monoid TOML Source #

Since: 0.3

Instance details

Defined in Toml.Type.TOML

Methods

mempty :: TOML #

mappend :: TOML -> TOML -> TOML #

mconcat :: [TOML] -> TOML #

Semigroup TOML Source #

Since: 0.3

Instance details

Defined in Toml.Type.TOML

Methods

(<>) :: TOML -> TOML -> TOML #

sconcat :: NonEmpty TOML -> TOML #

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

Generic TOML Source # 
Instance details

Defined in Toml.Type.TOML

Associated Types

type Rep TOML :: Type -> Type #

Methods

from :: TOML -> Rep TOML x #

to :: Rep TOML x -> TOML #

Show TOML Source # 
Instance details

Defined in Toml.Type.TOML

Methods

showsPrec :: Int -> TOML -> ShowS #

show :: TOML -> String #

showList :: [TOML] -> ShowS #

NFData TOML Source # 
Instance details

Defined in Toml.Type.TOML

Methods

rnf :: TOML -> () #

Eq TOML Source # 
Instance details

Defined in Toml.Type.TOML

Methods

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

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

type Rep TOML Source # 
Instance details

Defined in Toml.Type.TOML

type Rep TOML = D1 ('MetaData "TOML" "Toml.Type.TOML" "tomland-1.3.3.2-JRrBhNpiCh26pzVBpYNNR0" 'False) (C1 ('MetaCons "TOML" 'PrefixI 'True) (S1 ('MetaSel ('Just "tomlPairs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashMap Key AnyValue)) :*: (S1 ('MetaSel ('Just "tomlTables") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PrefixMap TOML)) :*: S1 ('MetaSel ('Just "tomlTableArrays") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashMap Key (NonEmpty TOML))))))

insertKeyVal :: Key -> Value a -> TOML -> TOML Source #

Inserts given key-value into the TOML.

insertKeyAnyVal :: Key -> AnyValue -> TOML -> TOML Source #

Inserts given key-value into the TOML.

insertTable :: Key -> TOML -> TOML -> TOML Source #

Inserts given table into the TOML.

insertTableArrays :: Key -> NonEmpty TOML -> TOML -> TOML Source #

Inserts given array of tables into the TOML.

tomlDiff :: TOML -> TOML -> TOML Source #

Difference of two TOMLs. Returns elements of the first TOML that are not existing in the second one.

Since: 1.3.2.0