eventuo11y-dsl-0.2.0.0: DSL for defining eventuo11y fields and selectors
CopyrightCopyright 2022 Shea Levy.
LicenseApache-2.0
Maintainershea@shealevy.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Observe.Event.DSL

Description

DSL for generating Event fields and selectors.

Typical entrypoint is SelectorSpec.

See Example.hs for an idiomatic example.

See Observe.Event.DSL.Compile to compile this into the relevant types.

Synopsis

The core AST

data SelectorSpec Source #

A specification for an Event selector type

Constructors

SelectorSpec 

Fields

data SelectorConstructorSpec Source #

A specification for a single constructor for a selector

End users probably want to use RecordField to create SelectorConstructorSpecs.

Constructors

SelectorConstructorSpec 

Fields

Instances

Instances details
a ~ ExplodedName => RecordField a FieldSpec SelectorConstructorSpec Source #

e.g. "foo" ≔ FieldSpec ...

Instance details

Defined in Observe.Event.DSL

a ~ ExplodedName => RecordField a SelectorField SelectorConstructorSpec Source #

e.g. "foo" ≔ NoFields

Instance details

Defined in Observe.Event.DSL

a ~ ExplodedName => RecordField a Name SelectorConstructorSpec Source #

e.g. "foo" ≔ ''Int

Instance details

Defined in Observe.Event.DSL

(a ~ ExplodedName, m ~ AnyQuote) => RecordField a (m Type) SelectorConstructorSpec Source #

e.g. "foo" ≔ [t|Maybe Int|]

Instance details

Defined in Observe.Event.DSL

data SelectorField Source #

Ways to specify the field for a selector.

Constructors

Specified !FieldSpec

The field is itself specified with the DSL.

The field type will be generated alongside the selector type.

End users probably want to use the RecordField ExplodedName FieldSpec SelectorConstructorSpec instance for Specified SelectorFields.

SimpleType !AnyType

The field type is simply a preexisting type, typically not eventuo11y-aware.

End users probably want to use the RecordField ExplodedName Name SelectorConstructorSpec or RecordField ExplodedName AnyType SelectorConstructorSpec instances for SimpleType SelectorFields

Inject !Name

This selector is a natural injection from a different selector type.

This is typically used to call library code with its own selector types.

NoFields

Events selected by this selector have no fields.

This may be useful purely to add timing to some event, or to create an event that is parent and/or proximate to other events.

Instances

Instances details
a ~ ExplodedName => RecordField a SelectorField SelectorConstructorSpec Source #

e.g. "foo" ≔ NoFields

Instance details

Defined in Observe.Event.DSL

data FieldSpec Source #

A specification for an Event field type.

Constructors

FieldSpec 

Fields

Instances

Instances details
a ~ ExplodedName => RecordField a FieldSpec SelectorConstructorSpec Source #

e.g. "foo" ≔ FieldSpec ...

Instance details

Defined in Observe.Event.DSL

data FieldConstructorSpec Source #

A specification for a single constructor for a field

End users probably want to use RecordField to create FieldConstructorSpecs.

Constructors

FieldConstructorSpec 

Fields

Instances

Instances details
a ~ ExplodedName => RecordField a Name FieldConstructorSpec Source #

e.g. "foo" ≔ ''Int

Instance details

Defined in Observe.Event.DSL

(a ~ ExplodedName, m ~ AnyQuote) => RecordField a (NonEmpty (m Type)) FieldConstructorSpec Source #

e.g. "foo" ≔ [t|Int] :| [ [t|Bool], [t|Char] ]

Instance details

Defined in Observe.Event.DSL

a ~ ExplodedName => RecordField a [Name] FieldConstructorSpec Source #

e.g. "foo" ≔ [''Int, ''Char]

Instance details

Defined in Observe.Event.DSL

Methods

(≔) :: a -> [Name] -> FieldConstructorSpec Source #

(a ~ ExplodedName, m ~ AnyQuote) => RecordField a (m Type) FieldConstructorSpec Source #

e.g. "foo" ≔ [t|Maybe Int]

Instance details

Defined in Observe.Event.DSL

Methods

(≔) :: a -> m Type -> FieldConstructorSpec Source #

Syntax

class RecordField k v a where Source #

A type class for common syntax for types that are key-value-like.

For example, the appropriate RecordField instances allow for [ "bytes", "asked" ] ≔ ''ByteCount and [ "bytes", "actual" ] ≔ [t|Maybe ByteCount|] to both construct FieldConstructorSpecs, the former creating a constructor BytesAsked taking a ByteCount and the latter a constructor BytesActual taking a Maybe ByteCount.

Methods

(≔) :: k -> v -> a infixr 4 Source #

Instances

Instances details
a ~ ExplodedName => RecordField a FieldSpec SelectorConstructorSpec Source #

e.g. "foo" ≔ FieldSpec ...

Instance details

Defined in Observe.Event.DSL

a ~ ExplodedName => RecordField a SelectorField SelectorConstructorSpec Source #

e.g. "foo" ≔ NoFields

Instance details

Defined in Observe.Event.DSL

a ~ ExplodedName => RecordField a Name FieldConstructorSpec Source #

e.g. "foo" ≔ ''Int

Instance details

Defined in Observe.Event.DSL

a ~ ExplodedName => RecordField a Name SelectorConstructorSpec Source #

e.g. "foo" ≔ ''Int

Instance details

Defined in Observe.Event.DSL

(a ~ ExplodedName, m ~ AnyQuote) => RecordField a (NonEmpty (m Type)) FieldConstructorSpec Source #

e.g. "foo" ≔ [t|Int] :| [ [t|Bool], [t|Char] ]

Instance details

Defined in Observe.Event.DSL

a ~ ExplodedName => RecordField a [Name] FieldConstructorSpec Source #

e.g. "foo" ≔ [''Int, ''Char]

Instance details

Defined in Observe.Event.DSL

Methods

(≔) :: a -> [Name] -> FieldConstructorSpec Source #

(a ~ ExplodedName, m ~ AnyQuote) => RecordField a (m Type) FieldConstructorSpec Source #

e.g. "foo" ≔ [t|Maybe Int]

Instance details

Defined in Observe.Event.DSL

Methods

(≔) :: a -> m Type -> FieldConstructorSpec Source #

(a ~ ExplodedName, m ~ AnyQuote) => RecordField a (m Type) SelectorConstructorSpec Source #

e.g. "foo" ≔ [t|Maybe Int|]

Instance details

Defined in Observe.Event.DSL

Miscellaneous helpers

Quote polymorphism

newtype AnyQuote a Source #

A concrete type for TH quotes that retains full Quote polymorphism

Prior to template-haskell 2.18, this is just an alias for Q

Constructors

AnyQuote 

Fields

  • toQuote :: forall m. Quote m => m a

    Extract this value in a particular Quote monad

    Prior to template-haskell 2.18, this projects into Q.

Instances

Instances details
Applicative AnyQuote Source # 
Instance details

Defined in Observe.Event.DSL

Methods

pure :: a -> AnyQuote a #

(<*>) :: AnyQuote (a -> b) -> AnyQuote a -> AnyQuote b #

liftA2 :: (a -> b -> c) -> AnyQuote a -> AnyQuote b -> AnyQuote c #

(*>) :: AnyQuote a -> AnyQuote b -> AnyQuote b #

(<*) :: AnyQuote a -> AnyQuote b -> AnyQuote a #

Functor AnyQuote Source # 
Instance details

Defined in Observe.Event.DSL

Methods

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

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

Monad AnyQuote Source # 
Instance details

Defined in Observe.Event.DSL

Methods

(>>=) :: AnyQuote a -> (a -> AnyQuote b) -> AnyQuote b #

(>>) :: AnyQuote a -> AnyQuote b -> AnyQuote b #

return :: a -> AnyQuote a #

Quote AnyQuote Source # 
Instance details

Defined in Observe.Event.DSL

toQuote :: AnyQuote a -> forall m. Quote m => m a Source #

Extract this value in a particular Quote monad

Prior to template-haskell 2.18, this projects into Q.

Names

data ExplodedName Source #

A name for some element, broken up into words.

Different elements will use this differently. For example, using [ "foo", "bar" ] in a SelectorSpec would result in a type named FooBarSelector, while using it in a FieldSpec might cause a renderer generator to give the field the key foo-bar.

Instances

Instances details
IsString ExplodedName Source #

A singleton ExplodedName.

Instance details

Defined in Observe.Event.DSL

IsList ExplodedName Source #

Must be non-empty.

Instance details

Defined in Observe.Event.DSL

Associated Types

type Item ExplodedName #

type Item ExplodedName Source # 
Instance details

Defined in Observe.Event.DSL

upperCamel :: (IsList a, Item a ~ NonEmptyString) => a -> String Source #

Convert an ExplodedName to UpperCamelCase.

lowerCamel :: ExplodedName -> String Source #

Convert an ExplodedName to lowerCamelCase

kebab :: ExplodedName -> String Source #

Convert an ExplodedName to kebab-case

data NonEmptyString where Source #

Self-explanatory

Bundled Patterns

pattern (:|:) :: Char -> String -> NonEmptyString 

Instances

Instances details
IsString NonEmptyString Source #

Must be non-empty

Instance details

Defined in Observe.Event.DSL

IsList NonEmptyString Source #

Must be non-empty

Instance details

Defined in Observe.Event.DSL

Associated Types

type Item NonEmptyString #

type Item NonEmptyString Source # 
Instance details

Defined in Observe.Event.DSL