jsonnet-0.3.1.1: Jsonnet implementaton in pure Haskell
Copyright(c) 2020-2021 Alexandre Moreno
LicenseBSD-3-Clause OR Apache-2.0
MaintainerAlexandre Moreno <alexmorenocano@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Language.Jsonnet.Core

Description

 

Documentation

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

data CField Source #

Constructors

CField 

Instances

Instances details
Show CField Source # 
Instance details

Defined in Language.Jsonnet.Core

Generic CField Source # 
Instance details

Defined in Language.Jsonnet.Core

Associated Types

type Rep CField :: Type -> Type #

Methods

from :: CField -> Rep CField x #

to :: Rep CField x -> CField #

Binary CField Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

put :: CField -> Put #

get :: Get CField #

putList :: [CField] -> Put #

Alpha CField Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep CField Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep CField = D1 ('MetaData "CField" "Language.Jsonnet.Core" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) (C1 ('MetaCons "CField" 'PrefixI 'True) (S1 ('MetaSel ('Just "fieldKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: (S1 ('MetaSel ('Just "fieldVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Core) :*: S1 ('MetaSel ('Just "fieldVis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Visibility))))

data Comp Source #

Constructors

ArrC (Bind (Name Core) (Core, Maybe Core)) 
ObjC (Bind (Name Core) (CField, Maybe Core)) 

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 #

Binary Comp Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

put :: Comp -> Put #

get :: Get Comp #

putList :: [Comp] -> Put #

Alpha Comp Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep Comp Source # 
Instance details

Defined in Language.Jsonnet.Core

type Rep Comp = D1 ('MetaData "Comp" "Language.Jsonnet.Core" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) (C1 ('MetaCons "ArrC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bind (Name Core) (Core, Maybe Core)))) :+: C1 ('MetaCons "ObjC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bind (Name Core) (CField, Maybe Core)))))

data Core where Source #

Constructors

CLoc :: SrcSpan -> Core -> Core 
CLit :: Literal -> Core 
CVar :: Name Core -> Core 
CLam :: Lam -> Core 
CPrim :: Prim -> Core 
CApp :: Core -> Args Core -> Core 
CLet :: Let -> Core 
CObj :: [CField] -> Core 
CArr :: [Core] -> Core 
CComp :: Comp -> Core -> Core 

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 #

Binary Core Source # 
Instance details

Defined in Language.Jsonnet.Core

Methods

put :: Core -> Put #

get :: Get Core #

putList :: [Core] -> Put #

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.3.1.1-HRvoiMrrp7QzMlnzingfy" '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 "CLam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lam)) :+: C1 ('MetaCons "CPrim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Prim))))) :+: ((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 [CField])) :+: (C1 ('MetaCons "CArr" 'PrefixI 'False) (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))))))

Orphan instances

Binary a => Binary (Rec a) Source # 
Instance details

Methods

put :: Rec a -> Put #

get :: Get (Rec a) #

putList :: [Rec a] -> Put #

Binary a => Binary (Embed a) Source # 
Instance details

Methods

put :: Embed a -> Put #

get :: Get (Embed a) #

putList :: [Embed a] -> Put #

Binary a => Binary (Name a) Source # 
Instance details

Methods

put :: Name a -> Put #

get :: Get (Name a) #

putList :: [Name a] -> Put #

(Binary a, Binary b) => Binary (Bind a b) Source # 
Instance details

Methods

put :: Bind a b -> Put #

get :: Get (Bind a b) #

putList :: [Bind a b] -> Put #