jsonnet-0.2.0.0: Jsonnet implementaton in pure Haskell
Safe HaskellNone
LanguageHaskell2010

Language.Jsonnet.Core

Documentation

type Param a = (Name a, Embed (Maybe a)) Source #

data KeyValue a Source #

Constructors

KeyValue a (Hideable a) 

Instances

Instances details
Show a => Show (KeyValue a) Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

showsPrec :: Int -> KeyValue a -> ShowS #

show :: KeyValue a -> String #

showList :: [KeyValue a] -> ShowS #

Generic (KeyValue a) Source # 
Instance details

Defined in Language.Jsonnet.Core

Associated Types

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

Methods

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

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

Alpha a => Alpha (KeyValue a) Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep (KeyValue a) Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep (KeyValue a) = D1 ('MetaData "KeyValue" "Language.Jsonnet.Core" "jsonnet-0.2.0.0-inplace" 'False) (C1 ('MetaCons "KeyValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hideable a))))

newtype Fun Source #

Constructors

Fun (Bind (Rec [Param Core]) Core) 

Instances

Instances details
Show Fun Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

showsPrec :: Int -> Fun -> ShowS #

show :: Fun -> String #

showList :: [Fun] -> ShowS #

Generic Fun Source # 
Instance details

Defined in Language.Jsonnet.Core

Associated Types

type Rep Fun :: Type -> Type #

Methods

from :: Fun -> Rep Fun x #

to :: Rep Fun x -> Fun #

Alpha Fun Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep Fun Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep Fun = D1 ('MetaData "Fun" "Language.Jsonnet.Core" "jsonnet-0.2.0.0-inplace" 'True) (C1 ('MetaCons "Fun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bind (Rec [Param Core]) Core))))

newtype Let Source #

Constructors

Let (Bind (Rec [(Name Core, Embed Core)]) Core) 

Instances

Instances details
Show Let Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

showsPrec :: Int -> Let -> ShowS #

show :: Let -> String #

showList :: [Let] -> ShowS #

Generic Let Source # 
Instance details

Defined in Language.Jsonnet.Core

Associated Types

type Rep Let :: Type -> Type #

Methods

from :: Let -> Rep Let x #

to :: Rep Let x -> Let #

Alpha Let Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep Let Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep Let = D1 ('MetaData "Let" "Language.Jsonnet.Core" "jsonnet-0.2.0.0-inplace" 'True) (C1 ('MetaCons "Let" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bind (Rec [(Name Core, Embed Core)]) Core))))

data Comp Source #

Instances

Instances details
Show Comp Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

showsPrec :: Int -> Comp -> ShowS #

show :: Comp -> String #

showList :: [Comp] -> ShowS #

Generic Comp Source # 
Instance details

Defined in Language.Jsonnet.Core

Associated Types

type Rep Comp :: Type -> Type #

Methods

from :: Comp -> Rep Comp x #

to :: Rep Comp x -> Comp #

Alpha Comp Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep Comp Source # 
Instance details

Defined in Language.Jsonnet.Core

data Core Source #

Instances

Instances details
Show Core Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

showsPrec :: Int -> Core -> ShowS #

show :: Core -> String #

showList :: [Core] -> ShowS #

Generic Core Source # 
Instance details

Defined in Language.Jsonnet.Core

Associated Types

type Rep Core :: Type -> Type #

Methods

from :: Core -> Rep Core x #

to :: Rep Core x -> Core #

Alpha Core Source # 
Instance details

Defined in Language.Jsonnet.Core

IsString (Name Core) Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

fromString :: String -> Name Core #

type Rep Core Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep Core = D1 ('MetaData "Core" "Language.Jsonnet.Core" "jsonnet-0.2.0.0-inplace" 'False) (((C1 ('MetaCons "CLoc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core)) :+: (C1 ('MetaCons "CLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Literal)) :+: C1 ('MetaCons "CVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name Core))))) :+: ((C1 ('MetaCons "CFun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fun)) :+: C1 ('MetaCons "CApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Args Core)))) :+: (C1 ('MetaCons "CLet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Let)) :+: C1 ('MetaCons "CObj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [KeyValue Core]))))) :+: ((C1 ('MetaCons "CArr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Core])) :+: (C1 ('MetaCons "CBinOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BinOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core))) :+: C1 ('MetaCons "CUnyOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnyOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core)))) :+: ((C1 ('MetaCons "CIfElse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core))) :+: C1 ('MetaCons "CErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core))) :+: (C1 ('MetaCons "CLookup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core)) :+: C1 ('MetaCons "CComp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core))))))