| Copyright | Copyright 2022 Shea Levy. |
|---|---|
| License | Apache-2.0 |
| Maintainer | shea@shealevy.com |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
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
- data SelectorSpec = SelectorSpec !ExplodedName ![SelectorConstructorSpec]
- data SelectorConstructorSpec = SelectorConstructorSpec !ExplodedName !SelectorField
- data SelectorField
- data FieldSpec = FieldSpec !ExplodedName ![FieldConstructorSpec]
- data FieldConstructorSpec = FieldConstructorSpec !ExplodedName !(NonEmpty AnyType)
- class RecordField k v a where
- (≔) :: k -> v -> a
- newtype AnyQuote a = AnyQuote {}
- toQuote :: AnyQuote a -> forall m. Quote m => m a
- type AnyType = AnyQuote Type
- data ExplodedName
- upperCamel :: (IsList a, Item a ~ NonEmptyString) => a -> String
- lowerCamel :: ExplodedName -> String
- kebab :: ExplodedName -> String
- data NonEmptyString where
- pattern (:|:) :: Char -> String -> NonEmptyString
- nonEmptyToString :: NonEmptyString -> String
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
| a ~ ExplodedName => RecordField a FieldSpec SelectorConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL Methods (≔) :: a -> FieldSpec -> SelectorConstructorSpec Source # | |
| a ~ ExplodedName => RecordField a SelectorField SelectorConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL Methods (≔) :: a -> SelectorField -> SelectorConstructorSpec Source # | |
| a ~ ExplodedName => RecordField a Name SelectorConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL Methods (≔) :: a -> Name -> SelectorConstructorSpec Source # | |
| (a ~ ExplodedName, m ~ AnyQuote) => RecordField a (m Type) SelectorConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL Methods (≔) :: a -> m Type -> SelectorConstructorSpec Source # | |
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 |
| SimpleType !AnyType | The field type is simply a preexisting type, typically not eventuo11y-aware. End users probably want to use the |
| 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
| a ~ ExplodedName => RecordField a SelectorField SelectorConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL Methods (≔) :: a -> SelectorField -> SelectorConstructorSpec Source # | |
A specification for an Event field type.
Constructors
| FieldSpec | |
Fields
| |
Instances
| a ~ ExplodedName => RecordField a FieldSpec SelectorConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL Methods (≔) :: a -> FieldSpec -> SelectorConstructorSpec Source # | |
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
| a ~ ExplodedName => RecordField a Name FieldConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL Methods (≔) :: a -> Name -> FieldConstructorSpec Source # | |
| (a ~ ExplodedName, m ~ AnyQuote) => RecordField a (NonEmpty (m Type)) FieldConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL | |
| a ~ ExplodedName => RecordField a [Name] FieldConstructorSpec Source # | e.g. |
Defined in Observe.Event.DSL Methods (≔) :: a -> [Name] -> FieldConstructorSpec Source # | |
| (a ~ ExplodedName, m ~ AnyQuote) => RecordField a (m Type) FieldConstructorSpec Source # | e.g. |
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.
Instances
Miscellaneous helpers
Quote polymorphism
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 | |
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
| IsString ExplodedName Source # | A singleton |
Defined in Observe.Event.DSL Methods fromString :: String -> ExplodedName # | |
| IsList ExplodedName Source # | Must be non-empty. |
Defined in Observe.Event.DSL Associated Types type Item ExplodedName # Methods fromList :: [Item ExplodedName] -> ExplodedName # fromListN :: Int -> [Item ExplodedName] -> ExplodedName # toList :: ExplodedName -> [Item ExplodedName] # | |
| type Item ExplodedName Source # | |
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
| IsString NonEmptyString Source # | Must be non-empty |
Defined in Observe.Event.DSL Methods fromString :: String -> NonEmptyString # | |
| IsList NonEmptyString Source # | Must be non-empty |
Defined in Observe.Event.DSL Associated Types type Item NonEmptyString # Methods fromList :: [Item NonEmptyString] -> NonEmptyString # fromListN :: Int -> [Item NonEmptyString] -> NonEmptyString # toList :: NonEmptyString -> [Item NonEmptyString] # | |
| type Item NonEmptyString Source # | |
Defined in Observe.Event.DSL | |
nonEmptyToString :: NonEmptyString -> String Source #
Self-explanatory