super-user-spark-0.4.0.1: Configure your dotfile deployment with a DSL.

Safe HaskellNone
LanguageHaskell2010

SuperUserSpark.Compiler.Types

Documentation

data CompileAssignment Source #

Instances
Eq CompileAssignment Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Show CompileAssignment Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Generic CompileAssignment Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Associated Types

type Rep CompileAssignment :: * -> * #

Validity CompileAssignment Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep CompileAssignment Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep CompileAssignment = D1 (MetaData "CompileAssignment" "SuperUserSpark.Compiler.Types" "super-user-spark-0.4.0.1-P7s2QbrTII5c6XXsq6MCt" False) (C1 (MetaCons "CompileAssignment" PrefixI True) (S1 (MetaSel (Just "compileCardReference") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StrongCardFileReference) :*: (S1 (MetaSel (Just "compileOutput") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Path Abs File))) :*: S1 (MetaSel (Just "compileSettings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CompileSettings))))

data StrongCardFileReference Source #

Instances
Eq StrongCardFileReference Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Show StrongCardFileReference Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Generic StrongCardFileReference Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Associated Types

type Rep StrongCardFileReference :: * -> * #

Validity StrongCardFileReference Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep StrongCardFileReference Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep StrongCardFileReference = D1 (MetaData "StrongCardFileReference" "SuperUserSpark.Compiler.Types" "super-user-spark-0.4.0.1-P7s2QbrTII5c6XXsq6MCt" False) (C1 (MetaCons "StrongCardFileReference" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Path Abs File)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CardNameReference))))

data StrongCardReference Source #

data Deployment a Source #

Instances
Functor Deployment Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Methods

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

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

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

Defined in SuperUserSpark.Compiler.Types

Methods

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

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

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

Defined in SuperUserSpark.Compiler.Types

Generic (Deployment a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Associated Types

type Rep (Deployment a) :: * -> * #

Methods

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

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

ToJSON a => ToJSON (Deployment a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

FromJSON a => FromJSON (Deployment a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Validity a => Validity (Deployment a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep (Deployment a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep (Deployment a) = D1 (MetaData "Deployment" "SuperUserSpark.Compiler.Types" "super-user-spark-0.4.0.1-P7s2QbrTII5c6XXsq6MCt" False) (C1 (MetaCons "Deployment" PrefixI True) (S1 (MetaSel (Just "deploymentDirections") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DeploymentDirections a)) :*: S1 (MetaSel (Just "deploymentKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DeploymentKind)))

data DeploymentDirections a Source #

Constructors

Directions 
Instances
Functor DeploymentDirections Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

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

Defined in SuperUserSpark.Compiler.Types

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

Defined in SuperUserSpark.Compiler.Types

Generic (DeploymentDirections a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Associated Types

type Rep (DeploymentDirections a) :: * -> * #

ToJSON a => ToJSON (DeploymentDirections a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

FromJSON a => FromJSON (DeploymentDirections a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Validity a => Validity (DeploymentDirections a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep (DeploymentDirections a) Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep (DeploymentDirections a) = D1 (MetaData "DeploymentDirections" "SuperUserSpark.Compiler.Types" "super-user-spark-0.4.0.1-P7s2QbrTII5c6XXsq6MCt" False) (C1 (MetaCons "Directions" PrefixI True) (S1 (MetaSel (Just "directionSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a]) :*: S1 (MetaSel (Just "directionDestination") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data PrefixPart Source #

Constructors

Literal String 
Alts [String] 
Instances
Eq PrefixPart Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Show PrefixPart Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Generic PrefixPart Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Associated Types

type Rep PrefixPart :: * -> * #

Validity PrefixPart Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep PrefixPart Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep PrefixPart = D1 (MetaData "PrefixPart" "SuperUserSpark.Compiler.Types" "super-user-spark-0.4.0.1-P7s2QbrTII5c6XXsq6MCt" False) (C1 (MetaCons "Literal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "Alts" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))

data CompilerState Source #

Instances
Eq CompilerState Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Show CompilerState Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Generic CompilerState Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Associated Types

type Rep CompilerState :: * -> * #

Validity CompilerState Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep CompilerState Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep CompilerState = D1 (MetaData "CompilerState" "SuperUserSpark.Compiler.Types" "super-user-spark-0.4.0.1-P7s2QbrTII5c6XXsq6MCt" False) (C1 (MetaCons "CompilerState" PrefixI True) (S1 (MetaSel (Just "stateDeploymentKindLocalOverride") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe DeploymentKind)) :*: (S1 (MetaSel (Just "stateInto") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Directory) :*: S1 (MetaSel (Just "stateOutofPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CompilerPrefix))))

data CompileError Source #

Instances
Eq CompileError Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Show CompileError Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Generic CompileError Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

Associated Types

type Rep CompileError :: * -> * #

Validity CompileError Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep CompileError Source # 
Instance details

Defined in SuperUserSpark.Compiler.Types

type Rep CompileError = D1 (MetaData "CompileError" "SuperUserSpark.Compiler.Types" "super-user-spark-0.4.0.1-P7s2QbrTII5c6XXsq6MCt" False) (C1 (MetaCons "CompileParseError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParseError)) :+: (C1 (MetaCons "PreCompileErrors" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PreCompileError])) :+: C1 (MetaCons "DuringCompilationError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))