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.Common

Description

 

Documentation

data Literal Source #

Instances

Instances details
Eq Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Data Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Literal -> c Literal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Literal #

toConstr :: Literal -> Constr #

dataTypeOf :: Literal -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Literal) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal) #

gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r #

gmapQ :: (forall d. Data d => d -> u) -> Literal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Literal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Literal -> m Literal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal #

Ord Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

Show Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

Generic Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

type Rep Literal :: Type -> Type #

Methods

from :: Literal -> Rep Literal x #

to :: Rep Literal x -> Literal #

Binary Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

put :: Literal -> Put #

get :: Get Literal #

putList :: [Literal] -> Put #

Alpha Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

Lift Literal Source # 
Instance details

Defined in Language.Jsonnet.TH

Methods

lift :: Literal -> Q Exp #

liftTyped :: Literal -> Q (TExp Literal) #

Subst a Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep Literal Source # 
Instance details

Defined in Language.Jsonnet.Common

data Prim Source #

Constructors

UnyOp UnyOp 
BinOp BinOp 
Cond 

Instances

Instances details
Eq Prim Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Data Prim Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Prim -> c Prim #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Prim #

toConstr :: Prim -> Constr #

dataTypeOf :: Prim -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Prim) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prim) #

gmapT :: (forall b. Data b => b -> b) -> Prim -> Prim #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prim -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prim -> r #

gmapQ :: (forall d. Data d => d -> u) -> Prim -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Prim -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Prim -> m Prim #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Prim -> m Prim #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Prim -> m Prim #

Show Prim Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

showsPrec :: Int -> Prim -> ShowS #

show :: Prim -> String #

showList :: [Prim] -> ShowS #

Generic Prim Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

type Rep Prim :: Type -> Type #

Methods

from :: Prim -> Rep Prim x #

to :: Rep Prim x -> Prim #

Binary Prim Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

put :: Prim -> Put #

get :: Get Prim #

putList :: [Prim] -> Put #

Alpha Prim Source # 
Instance details

Defined in Language.Jsonnet.Common

Lift Prim Source # 
Instance details

Defined in Language.Jsonnet.TH

Methods

lift :: Prim -> Q Exp #

liftTyped :: Prim -> Q (TExp Prim) #

type Rep Prim Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep Prim = D1 ('MetaData "Prim" "Language.Jsonnet.Common" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) (C1 ('MetaCons "UnyOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnyOp)) :+: (C1 ('MetaCons "BinOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BinOp)) :+: C1 ('MetaCons "Cond" 'PrefixI 'False) (U1 :: Type -> Type)))

data BinOp Source #

Constructors

Add 
Sub 
Mul 
Div 
Mod 
Lt 
Le 
Gt 
Ge 
Eq 
Ne 
And 
Or 
Xor 
ShiftL 
ShiftR 
LAnd 
LOr 
In 
Lookup 

Instances

Instances details
Eq BinOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Data BinOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinOp -> c BinOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinOp #

toConstr :: BinOp -> Constr #

dataTypeOf :: BinOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinOp) #

gmapT :: (forall b. Data b => b -> b) -> BinOp -> BinOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> BinOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BinOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp #

Show BinOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Generic BinOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

type Rep BinOp :: Type -> Type #

Methods

from :: BinOp -> Rep BinOp x #

to :: Rep BinOp x -> BinOp #

Binary BinOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

put :: BinOp -> Put #

get :: Get BinOp #

putList :: [BinOp] -> Put #

Alpha BinOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Lift BinOp Source # 
Instance details

Defined in Language.Jsonnet.TH

Methods

lift :: BinOp -> Q Exp #

liftTyped :: BinOp -> Q (TExp BinOp) #

type Rep BinOp Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep BinOp = D1 ('MetaData "BinOp" "Language.Jsonnet.Common" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) ((((C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mul" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Div" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Lt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Le" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Gt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eq" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Ne" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Xor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ShiftL" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ShiftR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LAnd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "In" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lookup" 'PrefixI 'False) (U1 :: Type -> Type))))))

data UnyOp Source #

Constructors

Compl 
LNot 
Plus 
Minus 
Err 

Instances

Instances details
Eq UnyOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Data UnyOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnyOp -> c UnyOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnyOp #

toConstr :: UnyOp -> Constr #

dataTypeOf :: UnyOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnyOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnyOp) #

gmapT :: (forall b. Data b => b -> b) -> UnyOp -> UnyOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnyOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnyOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> UnyOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnyOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnyOp -> m UnyOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnyOp -> m UnyOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnyOp -> m UnyOp #

Show UnyOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

showsPrec :: Int -> UnyOp -> ShowS #

show :: UnyOp -> String #

showList :: [UnyOp] -> ShowS #

Generic UnyOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

type Rep UnyOp :: Type -> Type #

Methods

from :: UnyOp -> Rep UnyOp x #

to :: Rep UnyOp x -> UnyOp #

Binary UnyOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

put :: UnyOp -> Put #

get :: Get UnyOp #

putList :: [UnyOp] -> Put #

Alpha UnyOp Source # 
Instance details

Defined in Language.Jsonnet.Common

Lift UnyOp Source # 
Instance details

Defined in Language.Jsonnet.TH

Methods

lift :: UnyOp -> Q Exp #

liftTyped :: UnyOp -> Q (TExp UnyOp) #

type Rep UnyOp Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep UnyOp = D1 ('MetaData "UnyOp" "Language.Jsonnet.Common" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) ((C1 ('MetaCons "Compl" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LNot" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Plus" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Minus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Err" 'PrefixI 'False) (U1 :: Type -> Type))))

data Strictness Source #

Constructors

Strict 
Lazy 

Instances

Instances details
Eq Strictness Source # 
Instance details

Defined in Language.Jsonnet.Common

Data Strictness Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Strictness -> c Strictness #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Strictness #

toConstr :: Strictness -> Constr #

dataTypeOf :: Strictness -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Strictness) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Strictness) #

gmapT :: (forall b. Data b => b -> b) -> Strictness -> Strictness #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Strictness -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Strictness -> r #

gmapQ :: (forall d. Data d => d -> u) -> Strictness -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Strictness -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness #

Read Strictness Source # 
Instance details

Defined in Language.Jsonnet.Common

Show Strictness Source # 
Instance details

Defined in Language.Jsonnet.Common

Generic Strictness Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

type Rep Strictness :: Type -> Type #

Binary Strictness Source # 
Instance details

Defined in Language.Jsonnet.Common

Alpha Strictness Source # 
Instance details

Defined in Language.Jsonnet.Common

Lift Strictness Source # 
Instance details

Defined in Language.Jsonnet.TH

type Rep Strictness Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep Strictness = D1 ('MetaData "Strictness" "Language.Jsonnet.Common" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) (C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lazy" 'PrefixI 'False) (U1 :: Type -> Type))

data Arg a Source #

Constructors

Pos a 
Named String a 

Instances

Instances details
Functor Arg Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

fmap :: (a -> b) -> Arg a -> Arg b #

(<$) :: a -> Arg b -> Arg a #

Foldable Arg Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

fold :: Monoid m => Arg m -> m #

foldMap :: Monoid m => (a -> m) -> Arg a -> m #

foldMap' :: Monoid m => (a -> m) -> Arg a -> m #

foldr :: (a -> b -> b) -> b -> Arg a -> b #

foldr' :: (a -> b -> b) -> b -> Arg a -> b #

foldl :: (b -> a -> b) -> b -> Arg a -> b #

foldl' :: (b -> a -> b) -> b -> Arg a -> b #

foldr1 :: (a -> a -> a) -> Arg a -> a #

foldl1 :: (a -> a -> a) -> Arg a -> a #

toList :: Arg a -> [a] #

null :: Arg a -> Bool #

length :: Arg a -> Int #

elem :: Eq a => a -> Arg a -> Bool #

maximum :: Ord a => Arg a -> a #

minimum :: Ord a => Arg a -> a #

sum :: Num a => Arg a -> a #

product :: Num a => Arg a -> a #

Traversable Arg Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

traverse :: Applicative f => (a -> f b) -> Arg a -> f (Arg b) #

sequenceA :: Applicative f => Arg (f a) -> f (Arg a) #

mapM :: Monad m => (a -> m b) -> Arg a -> m (Arg b) #

sequence :: Monad m => Arg (m a) -> m (Arg a) #

Show1 Arg Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Arg a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Arg a] -> ShowS #

Data a => Lift (Arg a :: Type) Source # 
Instance details

Defined in Language.Jsonnet.TH

Methods

lift :: Arg a -> Q Exp #

liftTyped :: Arg a -> Q (TExp (Arg a)) #

Eq a => Eq (Arg a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Data a => Data (Arg a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Arg a -> c (Arg a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Arg a) #

toConstr :: Arg a -> Constr #

dataTypeOf :: Arg a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Arg a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Arg a)) #

gmapT :: (forall b. Data b => b -> b) -> Arg a -> Arg a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arg a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arg a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Arg a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Arg a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arg a -> m (Arg a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a -> m (Arg a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a -> m (Arg a) #

Read a => Read (Arg a) Source # 
Instance details

Defined in Language.Jsonnet.Common

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

Defined in Language.Jsonnet.Common

Methods

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

show :: Arg a -> String #

showList :: [Arg a] -> ShowS #

Generic (Arg a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

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

Methods

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

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

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

Defined in Language.Jsonnet.Common

Methods

put :: Arg a -> Put #

get :: Get (Arg a) #

putList :: [Arg a] -> Put #

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

Defined in Language.Jsonnet.Common

Methods

aeq' :: AlphaCtx -> Arg a -> Arg a -> Bool #

fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> Arg a -> f (Arg a) #

close :: AlphaCtx -> NamePatFind -> Arg a -> Arg a #

open :: AlphaCtx -> NthPatFind -> Arg a -> Arg a #

isPat :: Arg a -> DisjointSet AnyName #

isTerm :: Arg a -> All #

isEmbed :: Arg a -> Bool #

nthPatFind :: Arg a -> NthPatFind #

namePatFind :: Arg a -> NamePatFind #

swaps' :: AlphaCtx -> Perm AnyName -> Arg a -> Arg a #

lfreshen' :: LFresh m => AlphaCtx -> Arg a -> (Arg a -> Perm AnyName -> m b) -> m b #

freshen' :: Fresh m => AlphaCtx -> Arg a -> m (Arg a, Perm AnyName) #

acompare' :: AlphaCtx -> Arg a -> Arg a -> Ordering #

Generic1 Arg Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

type Rep1 Arg :: k -> Type #

Methods

from1 :: forall (a :: k). Arg a -> Rep1 Arg a #

to1 :: forall (a :: k). Rep1 Arg a -> Arg a #

type Rep (Arg a) Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep1 Arg Source # 
Instance details

Defined in Language.Jsonnet.Common

data Args a Source #

Constructors

Args 

Fields

Instances

Instances details
Functor Args Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

fmap :: (a -> b) -> Args a -> Args b #

(<$) :: a -> Args b -> Args a #

Foldable Args Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

fold :: Monoid m => Args m -> m #

foldMap :: Monoid m => (a -> m) -> Args a -> m #

foldMap' :: Monoid m => (a -> m) -> Args a -> m #

foldr :: (a -> b -> b) -> b -> Args a -> b #

foldr' :: (a -> b -> b) -> b -> Args a -> b #

foldl :: (b -> a -> b) -> b -> Args a -> b #

foldl' :: (b -> a -> b) -> b -> Args a -> b #

foldr1 :: (a -> a -> a) -> Args a -> a #

foldl1 :: (a -> a -> a) -> Args a -> a #

toList :: Args a -> [a] #

null :: Args a -> Bool #

length :: Args a -> Int #

elem :: Eq a => a -> Args a -> Bool #

maximum :: Ord a => Args a -> a #

minimum :: Ord a => Args a -> a #

sum :: Num a => Args a -> a #

product :: Num a => Args a -> a #

Traversable Args Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

traverse :: Applicative f => (a -> f b) -> Args a -> f (Args b) #

sequenceA :: Applicative f => Args (f a) -> f (Args a) #

mapM :: Monad m => (a -> m b) -> Args a -> m (Args b) #

sequence :: Monad m => Args (m a) -> m (Args a) #

Show1 Args Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Args a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Args a] -> ShowS #

Data a => Lift (Args a :: Type) Source # 
Instance details

Defined in Language.Jsonnet.TH

Methods

lift :: Args a -> Q Exp #

liftTyped :: Args a -> Q (TExp (Args a)) #

Eq a => Eq (Args a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Data a => Data (Args a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Args a -> c (Args a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Args a) #

toConstr :: Args a -> Constr #

dataTypeOf :: Args a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Args a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Args a)) #

gmapT :: (forall b. Data b => b -> b) -> Args a -> Args a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Args a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Args a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Args a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Args a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Args a -> m (Args a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Args a -> m (Args a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Args a -> m (Args a) #

Read a => Read (Args a) Source # 
Instance details

Defined in Language.Jsonnet.Common

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

Defined in Language.Jsonnet.Common

Methods

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

show :: Args a -> String #

showList :: [Args a] -> ShowS #

Generic (Args a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

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

Methods

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

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

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

Defined in Language.Jsonnet.Common

Methods

put :: Args a -> Put #

get :: Get (Args a) #

putList :: [Args a] -> Put #

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

Defined in Language.Jsonnet.Common

Methods

aeq' :: AlphaCtx -> Args a -> Args a -> Bool #

fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> Args a -> f (Args a) #

close :: AlphaCtx -> NamePatFind -> Args a -> Args a #

open :: AlphaCtx -> NthPatFind -> Args a -> Args a #

isPat :: Args a -> DisjointSet AnyName #

isTerm :: Args a -> All #

isEmbed :: Args a -> Bool #

nthPatFind :: Args a -> NthPatFind #

namePatFind :: Args a -> NamePatFind #

swaps' :: AlphaCtx -> Perm AnyName -> Args a -> Args a #

lfreshen' :: LFresh m => AlphaCtx -> Args a -> (Args a -> Perm AnyName -> m b) -> m b #

freshen' :: Fresh m => AlphaCtx -> Args a -> m (Args a, Perm AnyName) #

acompare' :: AlphaCtx -> Args a -> Args a -> Ordering #

type Rep (Args a) Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep (Args a) = D1 ('MetaData "Args" "Language.Jsonnet.Common" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) (C1 ('MetaCons "Args" 'PrefixI 'True) (S1 ('MetaSel ('Just "args") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Arg a]) :*: S1 ('MetaSel ('Just "strictness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Strictness)))

data Assert a Source #

Constructors

Assert 

Fields

Instances

Instances details
Functor Assert Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

fmap :: (a -> b) -> Assert a -> Assert b #

(<$) :: a -> Assert b -> Assert a #

Foldable Assert Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

fold :: Monoid m => Assert m -> m #

foldMap :: Monoid m => (a -> m) -> Assert a -> m #

foldMap' :: Monoid m => (a -> m) -> Assert a -> m #

foldr :: (a -> b -> b) -> b -> Assert a -> b #

foldr' :: (a -> b -> b) -> b -> Assert a -> b #

foldl :: (b -> a -> b) -> b -> Assert a -> b #

foldl' :: (b -> a -> b) -> b -> Assert a -> b #

foldr1 :: (a -> a -> a) -> Assert a -> a #

foldl1 :: (a -> a -> a) -> Assert a -> a #

toList :: Assert a -> [a] #

null :: Assert a -> Bool #

length :: Assert a -> Int #

elem :: Eq a => a -> Assert a -> Bool #

maximum :: Ord a => Assert a -> a #

minimum :: Ord a => Assert a -> a #

sum :: Num a => Assert a -> a #

product :: Num a => Assert a -> a #

Traversable Assert Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

traverse :: Applicative f => (a -> f b) -> Assert a -> f (Assert b) #

sequenceA :: Applicative f => Assert (f a) -> f (Assert a) #

mapM :: Monad m => (a -> m b) -> Assert a -> m (Assert b) #

sequence :: Monad m => Assert (m a) -> m (Assert a) #

Show1 Assert Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Assert a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Assert a] -> ShowS #

Data a => Lift (Assert a :: Type) Source # 
Instance details

Defined in Language.Jsonnet.TH

Methods

lift :: Assert a -> Q Exp #

liftTyped :: Assert a -> Q (TExp (Assert a)) #

Eq a => Eq (Assert a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Data a => Data (Assert a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Assert a -> c (Assert a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Assert a) #

toConstr :: Assert a -> Constr #

dataTypeOf :: Assert a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Assert a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Assert a)) #

gmapT :: (forall b. Data b => b -> b) -> Assert a -> Assert a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Assert a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Assert a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Assert a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Assert a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Assert a -> m (Assert a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Assert a -> m (Assert a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Assert a -> m (Assert a) #

Read a => Read (Assert a) Source # 
Instance details

Defined in Language.Jsonnet.Common

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

Defined in Language.Jsonnet.Common

Methods

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

show :: Assert a -> String #

showList :: [Assert a] -> ShowS #

Generic (Assert a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

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

Methods

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

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

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

Defined in Language.Jsonnet.Common

type Rep (Assert a) Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep (Assert a) = D1 ('MetaData "Assert" "Language.Jsonnet.Common" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) (C1 ('MetaCons "Assert" 'PrefixI 'True) (S1 ('MetaSel ('Just "cond") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "msg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a)) :*: S1 ('MetaSel ('Just "expr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))

data CompSpec a Source #

Constructors

CompSpec 

Fields

Instances

Instances details
Functor CompSpec Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

fmap :: (a -> b) -> CompSpec a -> CompSpec b #

(<$) :: a -> CompSpec b -> CompSpec a #

Foldable CompSpec Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

fold :: Monoid m => CompSpec m -> m #

foldMap :: Monoid m => (a -> m) -> CompSpec a -> m #

foldMap' :: Monoid m => (a -> m) -> CompSpec a -> m #

foldr :: (a -> b -> b) -> b -> CompSpec a -> b #

foldr' :: (a -> b -> b) -> b -> CompSpec a -> b #

foldl :: (b -> a -> b) -> b -> CompSpec a -> b #

foldl' :: (b -> a -> b) -> b -> CompSpec a -> b #

foldr1 :: (a -> a -> a) -> CompSpec a -> a #

foldl1 :: (a -> a -> a) -> CompSpec a -> a #

toList :: CompSpec a -> [a] #

null :: CompSpec a -> Bool #

length :: CompSpec a -> Int #

elem :: Eq a => a -> CompSpec a -> Bool #

maximum :: Ord a => CompSpec a -> a #

minimum :: Ord a => CompSpec a -> a #

sum :: Num a => CompSpec a -> a #

product :: Num a => CompSpec a -> a #

Traversable CompSpec Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

traverse :: Applicative f => (a -> f b) -> CompSpec a -> f (CompSpec b) #

sequenceA :: Applicative f => CompSpec (f a) -> f (CompSpec a) #

mapM :: Monad m => (a -> m b) -> CompSpec a -> m (CompSpec b) #

sequence :: Monad m => CompSpec (m a) -> m (CompSpec a) #

Show1 CompSpec Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> CompSpec a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [CompSpec a] -> ShowS #

Data a => Lift (CompSpec a :: Type) Source # 
Instance details

Defined in Language.Jsonnet.TH

Methods

lift :: CompSpec a -> Q Exp #

liftTyped :: CompSpec a -> Q (TExp (CompSpec a)) #

Eq a => Eq (CompSpec a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Data a => Data (CompSpec a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompSpec a -> c (CompSpec a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CompSpec a) #

toConstr :: CompSpec a -> Constr #

dataTypeOf :: CompSpec a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CompSpec a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CompSpec a)) #

gmapT :: (forall b. Data b => b -> b) -> CompSpec a -> CompSpec a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompSpec a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompSpec a -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompSpec a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompSpec a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompSpec a -> m (CompSpec a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompSpec a -> m (CompSpec a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompSpec a -> m (CompSpec a) #

Read a => Read (CompSpec a) Source # 
Instance details

Defined in Language.Jsonnet.Common

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

Defined in Language.Jsonnet.Common

Methods

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

show :: CompSpec a -> String #

showList :: [CompSpec a] -> ShowS #

Generic (CompSpec a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

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

Methods

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

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

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

Defined in Language.Jsonnet.Common

type Rep (CompSpec a) Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep (CompSpec a) = D1 ('MetaData "CompSpec" "Language.Jsonnet.Common" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) (C1 ('MetaCons "CompSpec" 'PrefixI 'True) (S1 ('MetaSel ('Just "var") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "forspec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "ifspec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a)))))

data StackFrame a Source #

Constructors

StackFrame 

Fields

Instances

Instances details
Eq (StackFrame a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Show (StackFrame a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Pretty (StackFrame a) Source # 
Instance details

Defined in Language.Jsonnet.Pretty

Methods

pretty :: StackFrame a -> Doc #

prettyList :: [StackFrame a] -> Doc #

newtype Backtrace a Source #

Constructors

Backtrace [StackFrame a] 

Instances

Instances details
Eq (Backtrace a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

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

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

Show (Backtrace a) Source # 
Instance details

Defined in Language.Jsonnet.Common

Pretty (Backtrace a) Source # 
Instance details

Defined in Language.Jsonnet.Pretty

Methods

pretty :: Backtrace a -> Doc #

prettyList :: [Backtrace a] -> Doc #

data Visibility Source #

Constructors

Visible 
Hidden 
Forced 

Instances

Instances details
Eq Visibility Source # 
Instance details

Defined in Language.Jsonnet.Common

Data Visibility Source # 
Instance details

Defined in Language.Jsonnet.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Visibility -> c Visibility #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Visibility #

toConstr :: Visibility -> Constr #

dataTypeOf :: Visibility -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Visibility) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Visibility) #

gmapT :: (forall b. Data b => b -> b) -> Visibility -> Visibility #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Visibility -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Visibility -> r #

gmapQ :: (forall d. Data d => d -> u) -> Visibility -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Visibility -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Visibility -> m Visibility #

Read Visibility Source # 
Instance details

Defined in Language.Jsonnet.Common

Show Visibility Source # 
Instance details

Defined in Language.Jsonnet.Common

Generic Visibility Source # 
Instance details

Defined in Language.Jsonnet.Common

Associated Types

type Rep Visibility :: Type -> Type #

Binary Visibility Source # 
Instance details

Defined in Language.Jsonnet.Common

Alpha Visibility Source # 
Instance details

Defined in Language.Jsonnet.Common

Lift Visibility Source # 
Instance details

Defined in Language.Jsonnet.TH

type Rep Visibility Source # 
Instance details

Defined in Language.Jsonnet.Common

type Rep Visibility = D1 ('MetaData "Visibility" "Language.Jsonnet.Common" "jsonnet-0.3.1.1-HRvoiMrrp7QzMlnzingfy" 'False) (C1 ('MetaCons "Visible" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Hidden" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Forced" 'PrefixI 'False) (U1 :: Type -> Type)))

class HasVisibility a where Source #

Methods

visible :: a -> Bool Source #

forced :: a -> Bool Source #

hidden :: a -> Bool Source #

Instances

Instances details
HasVisibility VField Source # 
Instance details

Defined in Language.Jsonnet.Value