cmdargs-0.10.21: Command line argument processing
Safe HaskellNone
LanguageHaskell2010

System.Console.CmdArgs.Annotate

Description

This module captures annotations on a value, and builds a Capture value. This module has two ways of writing annotations:

Impure: The impure method of writing annotations is susceptible to over-optimisation by GHC - sometimes {-# OPTIONS_GHC -fno-cse #-} will be required.

Pure: The pure method is more verbose, and lacks some type safety.

As an example of the two styles:

data Foo = Foo {foo :: Int, bar :: Int}
 impure = capture $ Foo {foo = 12, bar = many [1 &= "inner", 2]} &= "top"
 pure = capture_ $ record Foo{} [foo := 12, bar :=+ [atom 1 += "inner", atom 2]] += "top"

Both evaluate to:

Capture (Ann "top") (Ctor (Foo 12 1) [Value 12, Many [Ann "inner" (Value 1), Value 2]]
Synopsis

Capture framework

data Capture ann Source #

The result of capturing some annotations.

Constructors

Many [Capture ann]

Many values collapsed (many or many_)

Ann ann (Capture ann)

An annotation attached to a value (&= or +=)

Value Any

A value (just a value, or atom)

Missing Any

A missing field (a RecConError exception, or missing from record)

Ctor Any [Capture ann]

A constructor (a constructor, or record)

Instances

Instances details
Functor Capture Source # 
Instance details

Defined in System.Console.CmdArgs.Annotate

Methods

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

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

Show ann => Show (Capture ann) Source # 
Instance details

Defined in System.Console.CmdArgs.Annotate

Methods

showsPrec :: Int -> Capture ann -> ShowS #

show :: Capture ann -> String #

showList :: [Capture ann] -> ShowS #

data Any Source #

Any value, with a Data dictionary.

Constructors

forall a.Data a => Any a 

Instances

Instances details
Show Any Source # 
Instance details

Defined in Data.Generics.Any

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

fromCapture :: Capture ann -> Any Source #

Return the value inside a capture.

defaultMissing :: Capture ann -> Capture ann Source #

Remove all Missing values by using any previous instances as default values

Impure

capture :: (Data val, Data ann) => val -> Capture ann Source #

Capture a value. Note that if the value is evaluated more than once the result may be different, i.e.

capture x /= capture x

many :: Data val => [val] -> val Source #

Collapse multiple values in to one.

(&=) :: (Data val, Data ann) => val -> ann -> val infixl 2 Source #

Add an annotation to a value.

It is recommended that anyone making use of this function redefine it with a more restrictive type signature to control the type of the annotation (the second argument). Any redefinitions of this function should add an INLINE pragma, to reduce the chance of incorrect optimisations.

Pure

capture_ :: Show a => Annotate a -> Capture a Source #

Capture the annotations from an annotated value.

many_ :: [Annotate a] -> Annotate a Source #

Collapse many annotated values in to one.

(+=) :: Annotate ann -> ann -> Annotate ann infixl 2 Source #

Add an annotation to a value.

atom :: Data val => val -> Annotate ann Source #

Lift a pure value to an annotation.

record :: Data a => a -> [Annotate ann] -> Annotate ann Source #

Create a constructor/record. The first argument should be the type of field, the second should be a list of fields constructed originally defined by := or :=+.

This operation is not type safe, and may raise an exception at runtime if any field has the wrong type or label.

data Annotate ann Source #

This type represents an annotated value. The type of the underlying value is not specified.

Constructors

forall c f.(Data c, Data f) => (c -> f) := f infix 3

Construct a field, fieldname := value.

forall c f.(Data c, Data f) => (c -> f) :=+ [Annotate ann]

Add annotations to a field.