drasil-lang-0.1.60.0: A framework for code and document generation for scientific software - Language SubPackage
Safe HaskellNone
LanguageHaskell2010

Language.Drasil

Description

The Drasil language, including expressions, chunks, sentences, references, classes, datatypes, and generally useful functions. Re-exports modules to simplify external use.

Synopsis

The Drasil Expression Language

Encodes mathematical and display related expressions. To see the code-related expressions, look in Language.Drasil.Code.

Base Expression Language

Defines the expression types and common operators.

data Expr Source #

Expression language where all terms are supposed to be 'well understood' (i.e., have a definite meaning). Right now, this coincides with "having a definite value", but should not be restricted to that.

Instances

Instances details
Eq Expr Source #

Expressions are equal if their constructors and contents are equal.

TODO: This needs to add more equality checks

Instance details

Defined in Language.Drasil.Expr.Lang

Methods

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

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

LiteralC Expr Source # 
Instance details

Defined in Language.Drasil.Expr.Lang

Express Expr Source #

Rewriting Exprs using the ModelExpr language.

Instance details

Defined in Language.Drasil.ExprClasses

ExprC Expr Source # 
Instance details

Defined in Language.Drasil.Expr.Class

Methods

lit :: Literal -> Expr Source #

($=) :: Expr -> Expr -> Expr Source #

($!=) :: Expr -> Expr -> Expr Source #

($<) :: Expr -> Expr -> Expr Source #

($>) :: Expr -> Expr -> Expr Source #

($<=) :: Expr -> Expr -> Expr Source #

($>=) :: Expr -> Expr -> Expr Source #

($.) :: Expr -> Expr -> Expr Source #

addI :: Expr -> Expr -> Expr Source #

addRe :: Expr -> Expr -> Expr Source #

mulI :: Expr -> Expr -> Expr Source #

mulRe :: Expr -> Expr -> Expr Source #

($-) :: Expr -> Expr -> Expr Source #

($/) :: Expr -> Expr -> Expr Source #

($^) :: Expr -> Expr -> Expr Source #

($=>) :: Expr -> Expr -> Expr Source #

($<=>) :: Expr -> Expr -> Expr Source #

($&&) :: Expr -> Expr -> Expr Source #

($||) :: Expr -> Expr -> Expr Source #

abs_ :: Expr -> Expr Source #

neg :: Expr -> Expr Source #

log :: Expr -> Expr Source #

ln :: Expr -> Expr Source #

sqrt :: Expr -> Expr Source #

sin :: Expr -> Expr Source #

cos :: Expr -> Expr Source #

tan :: Expr -> Expr Source #

sec :: Expr -> Expr Source #

csc :: Expr -> Expr Source #

cot :: Expr -> Expr Source #

arcsin :: Expr -> Expr Source #

arccos :: Expr -> Expr Source #

arctan :: Expr -> Expr Source #

exp :: Expr -> Expr Source #

dim :: Expr -> Expr Source #

norm :: Expr -> Expr Source #

negVec :: Expr -> Expr Source #

not_ :: Expr -> Expr Source #

idx :: Expr -> Expr -> Expr Source #

defint :: Symbol -> Expr -> Expr -> Expr -> Expr Source #

defsum :: Symbol -> Expr -> Expr -> Expr -> Expr Source #

defprod :: Symbol -> Expr -> Expr -> Expr -> Expr Source #

realInterval :: HasUID c => c -> RealInterval Expr Expr -> Expr Source #

euclidean :: [Expr] -> Expr Source #

cross :: Expr -> Expr -> Expr Source #

completeCase :: [(Expr, Expr)] -> Expr Source #

incompleteCase :: [(Expr, Expr)] -> Expr Source #

matrix :: [[Expr]] -> Expr Source #

m2x2 :: Expr -> Expr -> Expr -> Expr -> Expr Source #

vec2D :: Expr -> Expr -> Expr Source #

dgnl2x2 :: Expr -> Expr -> Expr Source #

apply :: (HasUID f, HasSymbol f) => f -> [Expr] -> Expr Source #

applyWithNamedArgs :: (HasUID f, HasSymbol f, HasUID a, IsArgumentName a) => f -> [Expr] -> [(a, Expr)] -> Expr Source #

sy :: (HasUID c, HasSymbol c) => c -> Expr Source #

class ExprC r where Source #

Methods

lit :: Literal -> r Source #

($=) :: r -> r -> r infixr 4 Source #

($!=) :: r -> r -> r Source #

($<) :: r -> r -> r Source #

Smart constructor for ordering two equations.

($>) :: r -> r -> r Source #

Smart constructor for ordering two equations.

($<=) :: r -> r -> r Source #

Smart constructor for ordering two equations.

($>=) :: r -> r -> r Source #

Smart constructor for ordering two equations.

($.) :: r -> r -> r Source #

Smart constructor for the dot product of two equations.

addI :: r -> r -> r Source #

Add two expressions (Integers).

addRe :: r -> r -> r Source #

Add two expressions (Real numbers).

mulI :: r -> r -> r Source #

Multiply two expressions (Integers).

mulRe :: r -> r -> r Source #

Multiply two expressions (Real numbers).

($-) :: r -> r -> r Source #

($/) :: r -> r -> r infixl 7 Source #

($^) :: r -> r -> r infixr 8 Source #

($=>) :: r -> r -> r Source #

($<=>) :: r -> r -> r Source #

($&&) :: r -> r -> r infixr 9 Source #

($||) :: r -> r -> r infixr 9 Source #

abs_ :: r -> r Source #

Smart constructor for taking the absolute value of an expression.

neg :: r -> r Source #

Smart constructor for negating an expression.

log :: r -> r Source #

Smart constructor to take the log of an expression.

ln :: r -> r Source #

Smart constructor to take the ln of an expression.

sqrt :: r -> r Source #

Smart constructor to take the square root of an expression.

sin :: r -> r Source #

Smart constructor to apply sin to an expression.

cos :: r -> r Source #

Smart constructor to apply cos to an expression.

tan :: r -> r Source #

Smart constructor to apply tan to an expression.

sec :: r -> r Source #

Smart constructor to apply sec to an expression.

csc :: r -> r Source #

Smart constructor to apply csc to an expression.

cot :: r -> r Source #

Smart constructor to apply cot to an expression.

arcsin :: r -> r Source #

Smart constructor to apply arcsin to an expression.

arccos :: r -> r Source #

Smart constructor to apply arccos to an expression.

arctan :: r -> r Source #

Smart constructor to apply arctan to an expression.

exp :: r -> r Source #

Smart constructor for the exponential (base e) function.

dim :: r -> r Source #

Smart constructor for calculating the dimension of a vector.

norm :: r -> r Source #

Smart constructor for calculating the normal form of a vector.

negVec :: r -> r Source #

Smart constructor for negating vectors.

not_ :: r -> r Source #

Smart constructor for applying logical negation to an expression.

idx :: r -> r -> r Source #

Smart constructor for indexing.

defint :: Symbol -> r -> r -> r -> r Source #

Smart constructor for the summation, product, and integral functions over an interval.

defsum :: Symbol -> r -> r -> r -> r Source #

Smart constructor for the summation, product, and integral functions over an interval.

defprod :: Symbol -> r -> r -> r -> r Source #

Smart constructor for the summation, product, and integral functions over an interval.

realInterval :: HasUID c => c -> RealInterval r r -> r Source #

Smart constructor for 'real interval' membership.

euclidean :: [r] -> r Source #

Euclidean function : takes a vector and returns the sqrt of the sum-of-squares.

cross :: r -> r -> r Source #

Smart constructor to cross product two expressions.

completeCase :: [(r, r)] -> r Source #

Smart constructor for case statements with a complete set of cases.

incompleteCase :: [(r, r)] -> r Source #

Smart constructor for case statements with an incomplete set of cases.

matrix :: [[r]] -> r Source #

Create a matrix. TODO: Re-work later.

m2x2 :: r -> r -> r -> r -> r Source #

Create a two-by-two matrix from four given values. For example:

>>> m2x2 1 2 3 4
[ [1,2],
  [3,4] ]

vec2D :: r -> r -> r Source #

Create a 2D vector (a matrix with two rows, one column). First argument is placed above the second.

dgnl2x2 :: r -> r -> r Source #

Creates a diagonal two-by-two matrix. For example:

>>> dgnl2x2 1 2
[ [1, 0],
  [0, 2] ]

apply :: (HasUID f, HasSymbol f) => f -> [r] -> r Source #

Applies a given function with a list of parameters.

applyWithNamedArgs :: (HasUID f, HasSymbol f, HasUID a, IsArgumentName a) => f -> [r] -> [(a, r)] -> r Source #

Similar to apply, but takes a relation to apply to FCall.

sy :: (HasUID c, HasSymbol c) => c -> r Source #

Create an Expr from a Symbolic Chunk.

Instances

Instances details
ExprC Expr Source # 
Instance details

Defined in Language.Drasil.Expr.Class

Methods

lit :: Literal -> Expr Source #

($=) :: Expr -> Expr -> Expr Source #

($!=) :: Expr -> Expr -> Expr Source #

($<) :: Expr -> Expr -> Expr Source #

($>) :: Expr -> Expr -> Expr Source #

($<=) :: Expr -> Expr -> Expr Source #

($>=) :: Expr -> Expr -> Expr Source #

($.) :: Expr -> Expr -> Expr Source #

addI :: Expr -> Expr -> Expr Source #

addRe :: Expr -> Expr -> Expr Source #

mulI :: Expr -> Expr -> Expr Source #

mulRe :: Expr -> Expr -> Expr Source #

($-) :: Expr -> Expr -> Expr Source #

($/) :: Expr -> Expr -> Expr Source #

($^) :: Expr -> Expr -> Expr Source #

($=>) :: Expr -> Expr -> Expr Source #

($<=>) :: Expr -> Expr -> Expr Source #

($&&) :: Expr -> Expr -> Expr Source #

($||) :: Expr -> Expr -> Expr Source #

abs_ :: Expr -> Expr Source #

neg :: Expr -> Expr Source #

log :: Expr -> Expr Source #

ln :: Expr -> Expr Source #

sqrt :: Expr -> Expr Source #

sin :: Expr -> Expr Source #

cos :: Expr -> Expr Source #

tan :: Expr -> Expr Source #

sec :: Expr -> Expr Source #

csc :: Expr -> Expr Source #

cot :: Expr -> Expr Source #

arcsin :: Expr -> Expr Source #

arccos :: Expr -> Expr Source #

arctan :: Expr -> Expr Source #

exp :: Expr -> Expr Source #

dim :: Expr -> Expr Source #

norm :: Expr -> Expr Source #

negVec :: Expr -> Expr Source #

not_ :: Expr -> Expr Source #

idx :: Expr -> Expr -> Expr Source #

defint :: Symbol -> Expr -> Expr -> Expr -> Expr Source #

defsum :: Symbol -> Expr -> Expr -> Expr -> Expr Source #

defprod :: Symbol -> Expr -> Expr -> Expr -> Expr Source #

realInterval :: HasUID c => c -> RealInterval Expr Expr -> Expr Source #

euclidean :: [Expr] -> Expr Source #

cross :: Expr -> Expr -> Expr Source #

completeCase :: [(Expr, Expr)] -> Expr Source #

incompleteCase :: [(Expr, Expr)] -> Expr Source #

matrix :: [[Expr]] -> Expr Source #

m2x2 :: Expr -> Expr -> Expr -> Expr -> Expr Source #

vec2D :: Expr -> Expr -> Expr Source #

dgnl2x2 :: Expr -> Expr -> Expr Source #

apply :: (HasUID f, HasSymbol f) => f -> [Expr] -> Expr Source #

applyWithNamedArgs :: (HasUID f, HasSymbol f, HasUID a, IsArgumentName a) => f -> [Expr] -> [(a, Expr)] -> Expr Source #

sy :: (HasUID c, HasSymbol c) => c -> Expr Source #

ExprC ModelExpr Source # 
Instance details

Defined in Language.Drasil.Expr.Class

Methods

lit :: Literal -> ModelExpr Source #

($=) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($!=) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($<) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($>) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($<=) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($>=) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($.) :: ModelExpr -> ModelExpr -> ModelExpr Source #

addI :: ModelExpr -> ModelExpr -> ModelExpr Source #

addRe :: ModelExpr -> ModelExpr -> ModelExpr Source #

mulI :: ModelExpr -> ModelExpr -> ModelExpr Source #

mulRe :: ModelExpr -> ModelExpr -> ModelExpr Source #

($-) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($/) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($^) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($=>) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($<=>) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($&&) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($||) :: ModelExpr -> ModelExpr -> ModelExpr Source #

abs_ :: ModelExpr -> ModelExpr Source #

neg :: ModelExpr -> ModelExpr Source #

log :: ModelExpr -> ModelExpr Source #

ln :: ModelExpr -> ModelExpr Source #

sqrt :: ModelExpr -> ModelExpr Source #

sin :: ModelExpr -> ModelExpr Source #

cos :: ModelExpr -> ModelExpr Source #

tan :: ModelExpr -> ModelExpr Source #

sec :: ModelExpr -> ModelExpr Source #

csc :: ModelExpr -> ModelExpr Source #

cot :: ModelExpr -> ModelExpr Source #

arcsin :: ModelExpr -> ModelExpr Source #

arccos :: ModelExpr -> ModelExpr Source #

arctan :: ModelExpr -> ModelExpr Source #

exp :: ModelExpr -> ModelExpr Source #

dim :: ModelExpr -> ModelExpr Source #

norm :: ModelExpr -> ModelExpr Source #

negVec :: ModelExpr -> ModelExpr Source #

not_ :: ModelExpr -> ModelExpr Source #

idx :: ModelExpr -> ModelExpr -> ModelExpr Source #

defint :: Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr Source #

defsum :: Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr Source #

defprod :: Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr Source #

realInterval :: HasUID c => c -> RealInterval ModelExpr ModelExpr -> ModelExpr Source #

euclidean :: [ModelExpr] -> ModelExpr Source #

cross :: ModelExpr -> ModelExpr -> ModelExpr Source #

completeCase :: [(ModelExpr, ModelExpr)] -> ModelExpr Source #

incompleteCase :: [(ModelExpr, ModelExpr)] -> ModelExpr Source #

matrix :: [[ModelExpr]] -> ModelExpr Source #

m2x2 :: ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr Source #

vec2D :: ModelExpr -> ModelExpr -> ModelExpr Source #

dgnl2x2 :: ModelExpr -> ModelExpr -> ModelExpr Source #

apply :: (HasUID f, HasSymbol f) => f -> [ModelExpr] -> ModelExpr Source #

applyWithNamedArgs :: (HasUID f, HasSymbol f, HasUID a, IsArgumentName a) => f -> [ModelExpr] -> [(a, ModelExpr)] -> ModelExpr Source #

sy :: (HasUID c, HasSymbol c) => c -> ModelExpr Source #

frac :: (ExprC r, LiteralC r) => Integer -> Integer -> r Source #

Smart constructor for fractions.

recip_ :: (ExprC r, LiteralC r) => r -> r Source #

Smart constructor for rational expressions (only in 1/x form).

square :: (ExprC r, LiteralC r) => r -> r Source #

Smart constructor to square a function.

half :: (ExprC r, LiteralC r) => r -> r Source #

Smart constructor to half a function exactly.

oneHalf :: (ExprC r, LiteralC r) => r Source #

1/2, as an expression.

oneThird :: (ExprC r, LiteralC r) => r Source #

1/3rd, as an expression.

apply1 :: (ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a) => f -> a -> r Source #

Similar to apply, but converts second argument into Symbols.

apply2 :: (ExprC r, HasUID f, HasSymbol f, HasUID a, HasSymbol a, HasUID b, HasSymbol b) => f -> a -> b -> r Source #

Similar to apply, but the applied function takes two parameters (which are both Symbols).

data Completeness Source #

For case expressions (either complete or incomplete).

Instances

Instances details
Eq Completeness Source # 
Instance details

Defined in Language.Drasil.Expr.Lang

type Relation = Expr Source #

A relation is just an expression (Expr).

Literals Language

data Literal Source #

Instances

Instances details
Eq Literal Source # 
Instance details

Defined in Language.Drasil.Literal.Lang

Methods

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

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

LiteralC Literal Source # 
Instance details

Defined in Language.Drasil.Literal.Class

Express Literal Source # 
Instance details

Defined in Language.Drasil.ExprClasses

Expression Modelling Language

Defines display-related expression functions. Used in models.

data ModelExpr Source #

Expression language where all terms are supposed to have a meaning, but that meaning may not be that of a definite value. For example, specification expressions, especially with quantifiers, belong here.

Instances

Instances details
Eq ModelExpr Source #

Expressions are equal if their constructors and contents are equal.

TODO: This needs to add more equality checks

Instance details

Defined in Language.Drasil.ModelExpr.Lang

LiteralC ModelExpr Source # 
Instance details

Defined in Language.Drasil.ModelExpr.Lang

Express ModelExpr Source #

No change, it's already a ModelExpr.

Instance details

Defined in Language.Drasil.ExprClasses

ModelExprC ModelExpr Source # 
Instance details

Defined in Language.Drasil.ModelExpr.Class

ExprC ModelExpr Source # 
Instance details

Defined in Language.Drasil.Expr.Class

Methods

lit :: Literal -> ModelExpr Source #

($=) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($!=) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($<) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($>) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($<=) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($>=) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($.) :: ModelExpr -> ModelExpr -> ModelExpr Source #

addI :: ModelExpr -> ModelExpr -> ModelExpr Source #

addRe :: ModelExpr -> ModelExpr -> ModelExpr Source #

mulI :: ModelExpr -> ModelExpr -> ModelExpr Source #

mulRe :: ModelExpr -> ModelExpr -> ModelExpr Source #

($-) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($/) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($^) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($=>) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($<=>) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($&&) :: ModelExpr -> ModelExpr -> ModelExpr Source #

($||) :: ModelExpr -> ModelExpr -> ModelExpr Source #

abs_ :: ModelExpr -> ModelExpr Source #

neg :: ModelExpr -> ModelExpr Source #

log :: ModelExpr -> ModelExpr Source #

ln :: ModelExpr -> ModelExpr Source #

sqrt :: ModelExpr -> ModelExpr Source #

sin :: ModelExpr -> ModelExpr Source #

cos :: ModelExpr -> ModelExpr Source #

tan :: ModelExpr -> ModelExpr Source #

sec :: ModelExpr -> ModelExpr Source #

csc :: ModelExpr -> ModelExpr Source #

cot :: ModelExpr -> ModelExpr Source #

arcsin :: ModelExpr -> ModelExpr Source #

arccos :: ModelExpr -> ModelExpr Source #

arctan :: ModelExpr -> ModelExpr Source #

exp :: ModelExpr -> ModelExpr Source #

dim :: ModelExpr -> ModelExpr Source #

norm :: ModelExpr -> ModelExpr Source #

negVec :: ModelExpr -> ModelExpr Source #

not_ :: ModelExpr -> ModelExpr Source #

idx :: ModelExpr -> ModelExpr -> ModelExpr Source #

defint :: Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr Source #

defsum :: Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr Source #

defprod :: Symbol -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr Source #

realInterval :: HasUID c => c -> RealInterval ModelExpr ModelExpr -> ModelExpr Source #

euclidean :: [ModelExpr] -> ModelExpr Source #

cross :: ModelExpr -> ModelExpr -> ModelExpr Source #

completeCase :: [(ModelExpr, ModelExpr)] -> ModelExpr Source #

incompleteCase :: [(ModelExpr, ModelExpr)] -> ModelExpr Source #

matrix :: [[ModelExpr]] -> ModelExpr Source #

m2x2 :: ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr -> ModelExpr Source #

vec2D :: ModelExpr -> ModelExpr -> ModelExpr Source #

dgnl2x2 :: ModelExpr -> ModelExpr -> ModelExpr Source #

apply :: (HasUID f, HasSymbol f) => f -> [ModelExpr] -> ModelExpr Source #

applyWithNamedArgs :: (HasUID f, HasSymbol f, HasUID a, IsArgumentName a) => f -> [ModelExpr] -> [(a, ModelExpr)] -> ModelExpr Source #

sy :: (HasUID c, HasSymbol c) => c -> ModelExpr Source #

data DerivType Source #

Determines the type of the derivative (either a partial derivative or a total derivative).

Instances

Instances details
Eq DerivType Source # 
Instance details

Defined in Language.Drasil.ModelExpr.Lang

class ModelExprC r where Source #

Methods

deriv :: (HasUID c, HasSymbol c) => r -> c -> r Source #

Gets the derivative of an ModelExpr with respect to a Symbol.

pderiv :: (HasUID c, HasSymbol c) => r -> c -> r Source #

Gets the derivative of an ModelExpr with respect to a Symbol.

nthderiv :: (HasUID c, HasSymbol c) => Integer -> r -> c -> r Source #

Gets the nthderivative of an ModelExpr with respect to a Symbol.

nthpderiv :: (HasUID c, HasSymbol c) => Integer -> r -> c -> r Source #

Gets the nthderivative of an ModelExpr with respect to a Symbol.

defines :: r -> r -> r Source #

One expression is "defined" by another.

space :: Space -> r Source #

Space literals.

isIn :: r -> Space -> r Source #

Check if a value belongs to a Space.

equiv :: [r] -> r Source #

Binary associative Equivalence.

intAll :: Symbol -> r -> r Source #

Smart constructor for the summation, product, and integral functions over all Real numbers.

sumAll :: Symbol -> r -> r Source #

Smart constructor for the summation, product, and integral functions over all Real numbers.

prodAll :: Symbol -> r -> r Source #

Smart constructor for the summation, product, and integral functions over all Real numbers.

Unicode symbols

Some expressions need special unicode characters.

data Special Source #

Special characters include partial derivatives and the degree circle.

Constructors

Partial 
Circle 

Instances

Instances details
Eq Special Source # 
Instance details

Defined in Language.Drasil.Unicode

Methods

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

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

Ord Special Source # 
Instance details

Defined in Language.Drasil.Unicode

class RenderSpecial r where Source #

Class for rendering special characters.

Methods

special :: Special -> r Source #

The Drasil Language (Information Encoding)

This is the basis of the Drasil language for encoding information. Every chunk used in Drasil is defined here, along with some classes that help us to use these chunks.

Classes

Contains many of the classes used in Drasil, along with their methods.

Chunk-related

class HasUID c where Source #

The most basic item: having a unique identifier key, here a UID.

Methods

uid :: Lens' c UID Source #

Provides a unique id for internal Drasil use.

Instances

Instances details
HasUID Reference Source #

Finds the UID of a Reference.

Instance details

Defined in Language.Drasil.Reference

Methods

uid :: Lens' Reference UID Source #

HasUID NamedChunk Source #

Finds the UID of the NamedChunk.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Methods

uid :: Lens' NamedChunk UID Source #

HasUID IdeaDict Source #

Finds the UID of the NamedChunk used to make the IdeaDict.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Methods

uid :: Lens' IdeaDict UID Source #

HasUID DecRef Source #

Finds the UID of a Reference.

Instance details

Defined in Language.Drasil.DecoratedReference

Methods

uid :: Lens' DecRef UID Source #

HasUID Citation Source #

Finds UID of the Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

Methods

uid :: Lens' Citation UID Source #

HasUID LabelledContent Source #

Finds UID of the LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

Methods

uid :: Lens' LabelledContent UID Source #

HasUID Section Source #

Finds the UID of a Section.

Instance details

Defined in Language.Drasil.Document

Methods

uid :: Lens' Section UID Source #

HasUID CI Source #

Finds UID of the NamedChunk used to make the CI.

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

uid :: Lens' CI UID Source #

HasUID ConceptChunk Source #

Finds UID of the IdeaDict used to make the ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

uid :: Lens' ConceptChunk UID Source #

HasUID CommonConcept Source #

Finds UID of the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

uid :: Lens' CommonConcept UID Source #

HasUID ConceptInstance Source #

Finds UID of the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

uid :: Lens' ConceptInstance UID Source #

HasUID RelationConcept Source #

Finds the UID of the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

Methods

uid :: Lens' RelationConcept UID Source #

HasUID UnitDefn Source #

Finds UID of the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

uid :: Lens' UnitDefn UID Source #

HasUID QuantityDict Source #

Finds the UID of the IdeaDict used to make the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Methods

uid :: Lens' QuantityDict UID Source #

HasUID UnitaryChunk Source #

Finds UID of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Methods

uid :: Lens' UnitaryChunk UID Source #

HasUID DefinedQuantityDict Source #

Finds the UID of the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

HasUID UnitalChunk Source #

Finds UID of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

uid :: Lens' UnitalChunk UID Source #

HasUID ConstrainedChunk Source #

Finds UID of the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

uid :: Lens' ConstrainedChunk UID Source #

HasUID ConstrConcept Source #

Finds UID of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

uid :: Lens' ConstrConcept UID Source #

HasUID UncertainChunk Source #

Finds UID of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

uid :: Lens' UncertainChunk UID Source #

HasUID UncertQ Source #

Finds UID of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

uid :: Lens' UncertQ UID Source #

HasUID DifferentialModel Source #

Finds the UID of the ConceptChunk used to make the DifferentialModel.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Methods

uid :: Lens' DifferentialModel UID Source #

HasUID (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

uid :: Lens' (QDefinition e) UID Source #

class HasSymbol c where Source #

A HasSymbol is anything which has a Symbol.

Methods

symbol :: c -> Stage -> Symbol Source #

Provides the Symbol for a particular stage of generation.

Instances

Instances details
HasSymbol QuantityDict Source #

Finds the Stage dependent Symbol of the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

HasSymbol UnitaryChunk Source #

Finds the Symbol of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

HasSymbol DefinedQuantityDict Source #

Finds the Stage -> Symbol of the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

HasSymbol UnitalChunk Source #

Finds the Symbol of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

HasSymbol ConstrainedChunk Source #

Finds the Symbol of the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasSymbol ConstrConcept Source #

Finds the Symbol of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasSymbol UncertainChunk Source #

Finds the Symbol of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

HasSymbol UncertQ Source #

Finds the Symbol of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

symbol :: UncertQ -> Stage -> Symbol Source #

HasSymbol (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

class HasUID c => NamedIdea c where Source #

A NamedIdea is a term that we've identified (has a UID) as being worthy of naming.

Methods

term :: Lens' c NP Source #

Lens to the term (a noun phrase).

Instances

Instances details
NamedIdea NamedChunk Source #

Finds the term (NP) of the NamedChunk.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Methods

term :: Lens' NamedChunk NP Source #

NamedIdea IdeaDict Source #

Finds the term (NP) of the NamedChunk used to make the IdeaDict.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Methods

term :: Lens' IdeaDict NP Source #

NamedIdea CI Source #

Finds term (NP) of the NamedChunk used to make the CI.

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

term :: Lens' CI NP Source #

NamedIdea ConceptChunk Source #

Finds term (NP) of the IdeaDict used to make the ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

term :: Lens' ConceptChunk NP Source #

NamedIdea CommonConcept Source #

Finds term (NP) of the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

term :: Lens' CommonConcept NP Source #

NamedIdea ConceptInstance Source #

Finds term (NP) of the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

term :: Lens' ConceptInstance NP Source #

NamedIdea RelationConcept Source #

Finds the term (NP) of the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

Methods

term :: Lens' RelationConcept NP Source #

NamedIdea UnitDefn Source #

Finds term (NP) of the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

term :: Lens' UnitDefn NP Source #

NamedIdea QuantityDict Source #

Finds the term (NP) of the IdeaDict used to make the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Methods

term :: Lens' QuantityDict NP Source #

NamedIdea UnitaryChunk Source #

Finds term (NP) of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Methods

term :: Lens' UnitaryChunk NP Source #

NamedIdea DefinedQuantityDict Source #

Finds the term (NP) of the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

NamedIdea UnitalChunk Source #

Finds term (NP) of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

term :: Lens' UnitalChunk NP Source #

NamedIdea ConstrainedChunk Source #

Finds term (NP) of the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

term :: Lens' ConstrainedChunk NP Source #

NamedIdea ConstrConcept Source #

Finds term (NP) of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

term :: Lens' ConstrConcept NP Source #

NamedIdea UncertainChunk Source #

Finds term (NP) of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

term :: Lens' UncertainChunk NP Source #

NamedIdea UncertQ Source #

Finds term (NP) of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

term :: Lens' UncertQ NP Source #

NamedIdea DifferentialModel Source #

Finds the term (NP) of the ConceptChunk used to make the DifferentialModel.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Methods

term :: Lens' DifferentialModel NP Source #

NamedIdea (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

term :: Lens' (QDefinition e) NP Source #

class NamedIdea c => Idea c where Source #

An Idea is the combination of a NamedIdea and a CommonIdea. In other words, it may have an acronym/abbreviation.

Methods

getA :: c -> Maybe String Source #

Gets the acronym/abbreviation.

Instances

Instances details
Idea NamedChunk Source #

Finds the idea of a NamedChunk (always Nothing).

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Idea IdeaDict Source #

Finds the abbreviation of the IdeaDict.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Idea CI Source #

Finds the idea of a CI (abbreviation).

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

getA :: CI -> Maybe String Source #

Idea ConceptChunk Source #

Finds the idea contained in the IdeaDict used to make the ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Idea CommonConcept Source #

Finds the idea contained in the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Idea ConceptInstance Source #

Finds the idea contained in the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Idea RelationConcept Source #

Finds the idea contained in the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

Idea UnitDefn Source #

Finds the idea contained in the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Idea QuantityDict Source #

Finds the idea contained in the IdeaDict used to make the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Idea UnitaryChunk Source #

Finds the idea contained in the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Idea DefinedQuantityDict Source #

Finds the idea contained in the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

Idea UnitalChunk Source #

Finds the idea contained in the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Idea ConstrainedChunk Source #

Finds the idea contained in the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Idea ConstrConcept Source #

Finds the idea contained in the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Idea UncertainChunk Source #

Finds the idea contained in the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Idea UncertQ Source #

Finds the idea contained in the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Idea DifferentialModel Source #

Finds the idea contained in the ConceptChunk used to make the DifferentialModel.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Idea (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

class NamedIdea c => CommonIdea c where Source #

CommonIdea is a NamedIdea with the additional constraint that it must have an abbreviation.

Methods

abrv :: c -> String Source #

Introduces abrv which necessarily provides an abbreviation.

Instances

Instances details
CommonIdea CI Source #

Finds the idea of a CI (abbreviation).

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

abrv :: CI -> String Source #

CommonIdea CommonConcept Source #

Finds the abbreviation contained in the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

class Definition c where Source #

Defines a chunk.

Methods

defn :: Lens' c Sentence Source #

Provides (a Lens to) the definition for a chunk.

Instances

Instances details
Definition ConceptChunk Source #

Finds definition of a ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Definition CommonConcept Source #

Finds definition of a CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Definition ConceptInstance Source #

Finds the definition contained in the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Definition RelationConcept Source #

Finds the definition contained in the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

Definition UnitDefn Source #

Finds definition of the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

defn :: Lens' UnitDefn Sentence Source #

Definition DefinedQuantityDict Source #

Finds the definition contained in the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

Definition UnitalChunk Source #

Finds definition of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

defn :: Lens' UnitalChunk Sentence Source #

Definition ConstrConcept Source #

Finds definition of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Definition UncertQ Source #

Finds definition of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

defn :: Lens' UncertQ Sentence Source #

Definition DifferentialModel Source #

Finds the definition contained in the ConceptChunk used to make the DifferentialModel.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Definition (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

defn :: Lens' (QDefinition e) Sentence Source #

class ConceptDomain c where Source #

Some concepts have a domain (related information encoded in UIDs to other chunks).

Methods

cdom :: c -> [UID] Source #

Provides Getter for the concept domain tags for a chunk

cdom should be exported for use by the Drasil framework, but should not be exported beyond that.

Instances

Instances details
ConceptDomain CI Source #

Finds the domain of a CI.

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

cdom :: CI -> [UID] Source #

ConceptDomain ConceptChunk Source #

Finds the domain of UIDs of a ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

cdom :: ConceptChunk -> [UID] Source #

ConceptDomain CommonConcept Source #

Finds the domain contained in the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

cdom :: CommonConcept -> [UID] Source #

ConceptDomain ConceptInstance Source #

Finds the domain contained in the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

ConceptDomain RelationConcept Source #

Finds the domain of the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

ConceptDomain UnitDefn Source #

Finds the domain contained in the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

cdom :: UnitDefn -> [UID] Source #

ConceptDomain DefinedQuantityDict Source #

Finds the domain of the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

ConceptDomain UnitalChunk Source #

Finds the domain contained in the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

cdom :: UnitalChunk -> [UID] Source #

ConceptDomain ConstrConcept Source #

Finds the domain contained in the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

cdom :: ConstrConcept -> [UID] Source #

ConceptDomain UncertQ Source #

Finds the domain contained in the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

cdom :: UncertQ -> [UID] Source #

ConceptDomain DifferentialModel Source # 
Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

ConceptDomain (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

cdom :: QDefinition e -> [UID] Source #

type Concept c = (Idea c, Definition c, ConceptDomain c) Source #

Concepts are Ideas with definitions and domains.

class HasSpace c where Source #

HasSpace is anything which has a Space.

Methods

typ :: Lens' c Space Source #

Provides a Lens to the Space.

Instances

Instances details
HasSpace QuantityDict Source #

Finds the Space of the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Methods

typ :: Lens' QuantityDict Space Source #

HasSpace UnitaryChunk Source #

Finds the Space of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Methods

typ :: Lens' UnitaryChunk Space Source #

HasSpace DefinedQuantityDict Source #

Finds the Space of the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

HasSpace UnitalChunk Source #

Finds the Space of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

typ :: Lens' UnitalChunk Space Source #

HasSpace ConstrainedChunk Source #

Finds the Space of the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasSpace ConstrConcept Source #

Finds the Space of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

typ :: Lens' ConstrConcept Space Source #

HasSpace UncertainChunk Source #

Finds the Space of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

typ :: Lens' UncertainChunk Space Source #

HasSpace UncertQ Source #

Finds the Space of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

typ :: Lens' UncertQ Space Source #

HasSpace (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

typ :: Lens' (QDefinition e) Space Source #

class HasUnitSymbol u where Source #

Some chunks store a unit symbol.

Methods

usymb :: u -> USymb Source #

Provides the ability to hold a unit symbol (USymb).

Instances

Instances details
HasUnitSymbol UnitDefn Source #

Finds unit symbol of the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

usymb :: UnitDefn -> USymb Source #

class (Idea c, HasSpace c, HasSymbol c) => Quantity c Source #

A Quantity is an Idea with a Space and a Symbol. In theory, it should also restrict to being a part of MayHaveUnit, but that causes all sorts of import cycles (or lots of orphans).

class HasReasVal c where Source #

A Quantity that could have a reasonable value.

Methods

reasVal :: Lens' c (Maybe Expr) Source #

Provides a Lens to the possible reasonable value.

Instances

Instances details
HasReasVal ConstrainedChunk Source #

Finds a reasonable value for the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasReasVal ConstrConcept Source #

Finds a reasonable value for the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasReasVal UncertainChunk Source #

Finds a reasonable value for the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

HasReasVal UncertQ Source #

Finds a reasonable value for the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

reasVal :: Lens' UncertQ (Maybe Expr) Source #

class Constrained c where Source #

The Constrained class is a Quantity that has value constraints. It does not enforce Quantity at this point.

Methods

constraints :: Lens' c [ConstraintE] Source #

Provides a Lens to the Constraints.

Instances

Instances details
Constrained ConstrainedChunk Source #

Finds the Constraints of a ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Constrained ConstrConcept Source #

Finds the Constraints of a ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Constrained UncertainChunk Source #

Finds the Constraints of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Constrained UncertQ Source #

Finds the Constraints of a ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

class HasAdditionalNotes c where Source #

Records any additional notes needed to avoid losing information

Methods

getNotes :: Lens' c [Sentence] Source #

Provides a Lens to the notes.

class HasDerivation c where Source #

A class that might have a Derivation.

Methods

derivations :: Lens' c (Maybe Derivation) Source #

Provides a Lens to a possible derivation.

class (Idea u, Definition u, HasUnitSymbol u) => IsUnit u where Source #

Units are Ideas with a Definition which store a unit symbol. They must also be explicitly declared to be instances of IsUnit.

Minimal complete definition

udefn, getUnits

Methods

getUnits :: u -> [UID] Source #

Holds units as a list of UID.

Instances

Instances details
IsUnit UnitDefn Source #

Gets the UnitDefn and contributing units.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

class DefiningExpr c where Source #

Methods

defnExpr :: Lens' (c e) e Source #

Provides a Lens to the expression. TODO: Well, technically, e doesn't need to be an "expression" of any sorts. It just needs to be _something_, and it would have approximately have same meaning.

Instances

Instances details
DefiningExpr QDefinition Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

defnExpr :: Lens' (QDefinition e) e Source #

class Express c where Source #

Data that can be expressed using ModelExpr.

Methods

express :: c -> ModelExpr Source #

Instances

Instances details
Express Literal Source # 
Instance details

Defined in Language.Drasil.ExprClasses

Express Expr Source #

Rewriting Exprs using the ModelExpr language.

Instance details

Defined in Language.Drasil.ExprClasses

Express ModelExpr Source #

No change, it's already a ModelExpr.

Instance details

Defined in Language.Drasil.ExprClasses

Express RelationConcept Source #

Convert the RelationConcept into the model expression language.

Instance details

Defined in Language.Drasil.Chunk.Relation

Express QuantityDict Source #

Convert the symbol of the QuantityDict to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Express DefinedQuantityDict Source #

Convert the symbol of the DefinedQuantityDict to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

Express UnitalChunk Source #

Convert the symbol of the UnitalChunk to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.Unital

Express ConstrConcept Source #

Convert the symbol of the ConstrConcept to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Express UncertQ Source #

Convert the symbol of the UncertQ to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Express DifferentialModel Source #

Finds the domain of the ConceptChunk used to make the DifferentialModel. | Convert the DifferentialModel into the model expression language. | Set Canonical form of ODE to Zero, e.g. ax0 + bx1 + cx2 + .... + c = 0

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Express e => Express (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

References

class HasRefAddress b where Source #

Members must have a reference address.

Methods

getRefAdd :: b -> LblType Source #

Provides the ability to hold a reference address.

Instances

Instances details
HasRefAddress Reference Source #

Finds the reference address contained in a Reference (through a LblType).

Instance details

Defined in Language.Drasil.Reference

HasRefAddress DecRef Source #

Finds the reference address contained in a Reference (through a LblType).

Instance details

Defined in Language.Drasil.DecoratedReference

HasRefAddress Citation Source #

Gets the reference address of a Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

HasRefAddress LabelledContent Source #

Finds the reference address contained in the Reference of LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

HasRefAddress Section Source #

Finds the reference address of a Section.

Instance details

Defined in Language.Drasil.Document

HasRefAddress ConceptInstance Source #

Finds the reference address contained in a ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

class (HasUID s, HasRefAddress s) => Referable s where Source #

Members of this class have the ability to be referenced.

Methods

refAdd :: s -> String Source #

The referencing address (what we're linking to). Only visible in the source (tex/html).

renderRef :: s -> LblType Source #

Alternate form of reference.

Instances

Instances details
Referable Citation Source #

Gets the reference information of a Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

Referable LabelledContent Source #

Finds the reference information of LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

Referable Section Source #

Finds the reference information of a Section.

Instance details

Defined in Language.Drasil.Document

Referable ConceptInstance Source #

Finds the reference information contained in a ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

class HasReference c where Source #

A class that contains a list of References.

Methods

getReferences :: Lens' c [Reference] Source #

Provides a Lens to the References.

Programming-related

class HasSymbol c => Callable c Source #

Some chunks can be called like functions.

class HasSymbol c => IsArgumentName c Source #

Members must have a named argument.

Types

Contains helper functions and smart constructors for each type. Similar types are grouped together.

Basic types

data UID Source #

A UID is a 'unique identifier' for things that we will put into our database of information. We use a newtype wrapper to make sure we are only using UIDs where desired.

Instances

Instances details
Eq UID Source # 
Instance details

Defined in Language.Drasil.UID

Methods

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

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

Ord UID Source # 
Instance details

Defined in Language.Drasil.UID

Methods

compare :: UID -> UID -> Ordering #

(<) :: UID -> UID -> Bool #

(<=) :: UID -> UID -> Bool #

(>) :: UID -> UID -> Bool #

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

max :: UID -> UID -> UID #

min :: UID -> UID -> UID #

Show UID Source # 
Instance details

Defined in Language.Drasil.UID

Methods

showsPrec :: Int -> UID -> ShowS #

show :: UID -> String #

showList :: [UID] -> ShowS #

mkUid :: String -> UID Source #

Smart constructor for making a UID from a String.

(+++) :: HasUID a => a -> String -> UID Source #

For when we need to modify a UID. We first take the base chunk's UID and then append a suffix to it.

(+++.) :: UID -> String -> UID Source #

For when we need to append something to a UID.

(+++!) :: (HasUID a, HasUID b) => a -> b -> UID Source #

data NamedChunk Source #

Used for anything worth naming. Note that a NamedChunk does not have an acronym/abbreviation as that's a CommonIdea, which has its own representation. Contains a UID and a term that we can capitalize or pluralize (NP).

Ex. Anything worth naming must start out somewhere. Before we can assign equations and values and symbols to something like the arm of a pendulum, we must first give it a name.

Instances

Instances details
Eq NamedChunk Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

HasUID NamedChunk Source #

Finds the UID of the NamedChunk.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Methods

uid :: Lens' NamedChunk UID Source #

Idea NamedChunk Source #

Finds the idea of a NamedChunk (always Nothing).

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

NamedIdea NamedChunk Source #

Finds the term (NP) of the NamedChunk.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Methods

term :: Lens' NamedChunk NP Source #

nc :: String -> NP -> NamedChunk Source #

NamedChunk constructor, takes a String for its UID and a term.

ncUID :: UID -> NP -> NamedChunk Source #

Similar to nc, but takes in the UID in the form of a UID rather than a String.

data IdeaDict Source #

IdeaDict is the canonical dictionary associated to an Idea. Contains a NamedChunk that could have an abbreviation (Maybe String).

Ex. The project name "Double Pendulum" may have the abbreviation DblPendulum.

Instances

Instances details
Eq IdeaDict Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

HasUID IdeaDict Source #

Finds the UID of the NamedChunk used to make the IdeaDict.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Methods

uid :: Lens' IdeaDict UID Source #

Idea IdeaDict Source #

Finds the abbreviation of the IdeaDict.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

NamedIdea IdeaDict Source #

Finds the term (NP) of the NamedChunk used to make the IdeaDict.

Instance details

Defined in Language.Drasil.Chunk.NamedIdea

Methods

term :: Lens' IdeaDict NP Source #

mkIdea :: String -> NP -> Maybe String -> IdeaDict Source #

IdeaDict constructor, takes a UID, NP, and an abbreviation in the form of Maybe String.

nw :: Idea c => c -> IdeaDict Source #

Historical name: nw comes from 'named wrapped' from when NamedIdea exported getA (now in Idea). But there are no more wrappers, instead we have explicit dictionaries. Unwraps an Idea and places its UID and NP into an IdeaDict with Nothing for an abbreviation.

data CI Source #

The common idea (with NounPhrase) data type. It must have a UID, NounPhrase for its term, an abbreviation (String), and a domain ([UID]). It is similar to NamedChunk and IdeaDict in the sense that these are for things worth naming, but this type also carries an abbreviation and related domains of knowledge.

Ex. The term "Operating System" has the abbreviation OS and comes from the domain of computer science.

Instances

Instances details
HasUID CI Source #

Finds UID of the NamedChunk used to make the CI.

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

uid :: Lens' CI UID Source #

Idea CI Source #

Finds the idea of a CI (abbreviation).

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

getA :: CI -> Maybe String Source #

NamedIdea CI Source #

Finds term (NP) of the NamedChunk used to make the CI.

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

term :: Lens' CI NP Source #

CommonIdea CI Source #

Finds the idea of a CI (abbreviation).

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

abrv :: CI -> String Source #

ConceptDomain CI Source #

Finds the domain of a CI.

Instance details

Defined in Language.Drasil.Chunk.CommonIdea

Methods

cdom :: CI -> [UID] Source #

commonIdea :: String -> NP -> String -> [UID] -> CI Source #

The commonIdea smart constructor requires a chunk id (String), a term (NP), an abbreviation (String), and a domain ([UID]).

getAcc :: CI -> Sentence Source #

Get abbreviation in Sentence form from a CI.

getAccStr :: CI -> String Source #

Get abbreviation in String form from a CI.

commonIdeaWithDict :: String -> NP -> String -> [IdeaDict] -> CI Source #

Similar to commonIdea, but takes a list of IdeaDict (often a domain).

prependAbrv :: CommonIdea c => c -> String -> String Source #

Prepends the abbreviation from a CommonIdea to a String.

Concepts

data ConceptChunk Source #

The ConceptChunk datatype records a concept that contains an idea (IdeaDict), a definition (Sentence), and an associated domain of knowledge ([UID]).

Ex. The concept of Accuracy may be defined as the quality or state of being correct or precise.

Instances

Instances details
Eq ConceptChunk Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

HasUID ConceptChunk Source #

Finds UID of the IdeaDict used to make the ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

uid :: Lens' ConceptChunk UID Source #

Idea ConceptChunk Source #

Finds the idea contained in the IdeaDict used to make the ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

NamedIdea ConceptChunk Source #

Finds term (NP) of the IdeaDict used to make the ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

term :: Lens' ConceptChunk NP Source #

ConceptDomain ConceptChunk Source #

Finds the domain of UIDs of a ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

cdom :: ConceptChunk -> [UID] Source #

Definition ConceptChunk Source #

Finds definition of a ConceptChunk.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

data CommonConcept Source #

Contains a common idea (CI) with a definition (Sentence). Similar to ConceptChunk, but must have an abbreviation.

Instances

Instances details
Eq CommonConcept Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

HasUID CommonConcept Source #

Finds UID of the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

uid :: Lens' CommonConcept UID Source #

Idea CommonConcept Source #

Finds the idea contained in the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

NamedIdea CommonConcept Source #

Finds term (NP) of the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

term :: Lens' CommonConcept NP Source #

CommonIdea CommonConcept Source #

Finds the abbreviation contained in the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

ConceptDomain CommonConcept Source #

Finds the domain contained in the CI used to make the CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

cdom :: CommonConcept -> [UID] Source #

Definition CommonConcept Source #

Finds definition of a CommonConcept.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

data ConceptInstance Source #

Contains a ConceptChunk, reference address, and a ShortName. It is a concept that can be referred to, or rather, a instance of where a concept is applied. Often used in Goal Statements, Assumptions, Requirements, etc.

Ex. Something like the assumption that gravity is 9.81 m/s. When we write our equations, we can then link this assumption so that we do not have to explicitly define that assumption when needed to verify our work.

Instances

Instances details
Eq ConceptInstance Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

HasUID ConceptInstance Source #

Finds UID of the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

uid :: Lens' ConceptInstance UID Source #

Referable ConceptInstance Source #

Finds the reference information contained in a ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

HasRefAddress ConceptInstance Source #

Finds the reference address contained in a ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

HasShortName ConceptInstance Source #

Finds the ShortName contained in a ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Idea ConceptInstance Source #

Finds the idea contained in the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

NamedIdea ConceptInstance Source #

Finds term (NP) of the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Methods

term :: Lens' ConceptInstance NP Source #

ConceptDomain ConceptInstance Source #

Finds the domain contained in the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

Definition ConceptInstance Source #

Finds the definition contained in the ConceptChunk used to make the ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

sDom :: [UID] -> UID Source #

Check if something has one domain. Throws an error if there is more than one.

dcc :: String -> NP -> String -> ConceptChunk Source #

Smart constructor for creating concept chunks given a UID, NounPhrase (NP) and definition (as a String).

Concept domain tagging is not yet implemented in this constructor.

dcc' :: String -> NP -> String -> String -> CommonConcept Source #

Identical to dcc, but takes an abbreviation (String) and returns a CommonConcept instead.

dccWDS :: String -> NP -> Sentence -> ConceptChunk Source #

Similar to dcc, except the definition takes a Sentence.

dccWDS' :: String -> NP -> Sentence -> String -> CommonConcept Source #

Similar to dcc, except the definition is a Sentence, takes an abbreviation (String) and returns a CommonConcept instead.

cc :: Idea c => c -> String -> ConceptChunk Source #

Constructor for projecting an idea into a ConceptChunk. Takes the definition of the ConceptChunk as a String. Does not allow concept domain tagging.

cc' :: Idea c => c -> Sentence -> ConceptChunk Source #

Same as cc, except definition is a Sentence.

ccs :: (Idea c, Concept d) => c -> Sentence -> [d] -> ConceptChunk Source #

Similar to cc', but allows explicit domain tagging.

cw :: Concept c => c -> ConceptChunk Source #

For projecting out to the ConceptChunk data-type.

cic :: Concept c => String -> Sentence -> String -> c -> ConceptInstance Source #

Constructor for a ConceptInstance. Takes in the Reference Address (String), a definition (Sentence), a short name (String), and a domain (for explicit tagging).

data RelationConcept Source #

For a concept (ConceptChunk) that also has a Relation (ModelExpr) attached.

Ex. We can describe a pendulum arm and then apply an associated equation so that we know its behaviour.

Instances

Instances details
Eq RelationConcept Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.Relation

HasUID RelationConcept Source #

Finds the UID of the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

Methods

uid :: Lens' RelationConcept UID Source #

Express RelationConcept Source #

Convert the RelationConcept into the model expression language.

Instance details

Defined in Language.Drasil.Chunk.Relation

Idea RelationConcept Source #

Finds the idea contained in the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

NamedIdea RelationConcept Source #

Finds the term (NP) of the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

Methods

term :: Lens' RelationConcept NP Source #

ConceptDomain RelationConcept Source #

Finds the domain of the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

Definition RelationConcept Source #

Finds the definition contained in the ConceptChunk used to make the RelationConcept.

Instance details

Defined in Language.Drasil.Chunk.Relation

makeRC :: Express e => String -> NP -> Sentence -> e -> RelationConcept Source #

Create a RelationConcept from a given UID, term (NP), definition (Sentence), and Relation.

addRelToCC :: (Express e, Concept c) => c -> String -> e -> RelationConcept Source #

Create a new RelationConcept from an old Concept. Takes a Concept, new UID and relation.

data DifferentialModel Source #

Instances

Instances details
Eq DifferentialModel Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

HasUID DifferentialModel Source #

Finds the UID of the ConceptChunk used to make the DifferentialModel.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Methods

uid :: Lens' DifferentialModel UID Source #

Express DifferentialModel Source #

Finds the domain of the ConceptChunk used to make the DifferentialModel. | Convert the DifferentialModel into the model expression language. | Set Canonical form of ODE to Zero, e.g. ax0 + bx1 + cx2 + .... + c = 0

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Idea DifferentialModel Source #

Finds the idea contained in the ConceptChunk used to make the DifferentialModel.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

NamedIdea DifferentialModel Source #

Finds the term (NP) of the ConceptChunk used to make the DifferentialModel.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Methods

term :: Lens' DifferentialModel NP Source #

ConceptDomain DifferentialModel Source # 
Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

Definition DifferentialModel Source #

Finds the definition contained in the ConceptChunk used to make the DifferentialModel.

Instance details

Defined in Language.Drasil.Chunk.DifferentialModel

($*) :: Expr -> Int -> CoeffDeriv Source #

makeLinear :: UnitalChunk -> ConstrConcept -> [CoeffDeriv] -> Expr -> String -> NP -> Sentence -> DifferentialModel Source #

Create a DifferentialModel from a given indepVar (UnitalChunk), DepVar (ModelExpr), | Coefficients ('[Expr]'), Constant (Expr), UID (String), term (NP), definition (Sentence).

Quantities and Units

data QuantityDict Source #

QuantityDict is a combination of an IdeaDict with a quantity. Contains an IdeaDict, Space, a function from Stage -> Symbol, and Maybe a UnitDefn.

Ex. A pendulum arm does not necessarily have to be defined as a concept before we assign a space (Real numbers), a symbol (l), or units (cm, m, etc.).

Instances

Instances details
Eq QuantityDict Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.Quantity

HasUID QuantityDict Source #

Finds the UID of the IdeaDict used to make the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Methods

uid :: Lens' QuantityDict UID Source #

HasSymbol QuantityDict Source #

Finds the Stage dependent Symbol of the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

HasSpace QuantityDict Source #

Finds the Space of the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Methods

typ :: Lens' QuantityDict Space Source #

Express QuantityDict Source #

Convert the symbol of the QuantityDict to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Idea QuantityDict Source #

Finds the idea contained in the IdeaDict used to make the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

NamedIdea QuantityDict Source #

Finds the term (NP) of the IdeaDict used to make the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

Methods

term :: Lens' QuantityDict NP Source #

Quantity QuantityDict Source #

QuantityDicts have a Quantity.

Instance details

Defined in Language.Drasil.Chunk.Quantity

MayHaveUnit QuantityDict Source #

Finds the units of the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

qw :: (Quantity q, MayHaveUnit q) => q -> QuantityDict Source #

Smart constructor for a QuantityDict from another Quantity with units.

mkQuant :: String -> NP -> Symbol -> Space -> Maybe UnitDefn -> Maybe String -> QuantityDict Source #

Make a QuantityDict from a UID, NP, Symbol, Space, Maybe UnitDefn, and an abbreviation (Maybe String).

mkQuant' :: String -> NP -> Maybe String -> Space -> (Stage -> Symbol) -> Maybe UnitDefn -> QuantityDict Source #

Similar to mkQuant, but the abbreviation is moved to the third argument (Maybe String), and the Symbol is now dependent on Stage.

codeVC :: Idea c => c -> Symbol -> Space -> QuantityDict Source #

Makes a QuantityDict from an Idea, Symbol, and Space. Symbol is implementation-only.

implVar :: String -> NP -> Space -> Symbol -> QuantityDict Source #

Makes a variable that is implementation-only.

implVar' :: String -> NP -> Maybe String -> Space -> Symbol -> Maybe UnitDefn -> QuantityDict Source #

Similar to implVar but allows specification of abbreviation and unit.

implVarUID :: UID -> NP -> Space -> Symbol -> QuantityDict Source #

Similar to implVar but takes in a UID rather than a String.

implVarUID' :: UID -> NP -> Maybe String -> Space -> Symbol -> Maybe UnitDefn -> QuantityDict Source #

Similar to implVar' but takes in a UID rather than a String.

vc :: String -> NP -> Symbol -> Space -> QuantityDict Source #

Creates a QuantityDict from a UID, term (NP), Symbol, and Space.

vc'' :: Idea c => c -> Symbol -> Space -> QuantityDict Source #

Creates a QuantityDict from an Idea, Symbol, and Space.

vcSt :: String -> NP -> (Stage -> Symbol) -> Space -> QuantityDict Source #

Similar to vc, but creates a QuantityDict from something that knows about Stages.

vcUnit :: String -> NP -> Symbol -> Space -> UnitDefn -> QuantityDict Source #

Creates a QuantityDict from a UID, term (NP), Symbol, Space, and unit (UnitDefn).

data QDefinition e Source #

Instances

Instances details
DefiningExpr QDefinition Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

defnExpr :: Lens' (QDefinition e) e Source #

Eq (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

HasUID (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

uid :: Lens' (QDefinition e) UID Source #

HasSymbol (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

HasSpace (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

typ :: Lens' (QDefinition e) Space Source #

Express e => Express (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Idea (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

NamedIdea (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

term :: Lens' (QDefinition e) NP Source #

Quantity (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

ConceptDomain (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

cdom :: QDefinition e -> [UID] Source #

Definition (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Methods

defn :: Lens' (QDefinition e) Sentence Source #

MayHaveUnit (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

fromEqn :: IsUnit u => String -> NP -> Sentence -> Symbol -> Space -> u -> e -> QDefinition e Source #

Create a QDefinition with a UID (as a String), term (NP), definition (Sentence), Symbol, Space, unit, and defining expression.

fromEqn' :: String -> NP -> Sentence -> Symbol -> Space -> e -> QDefinition e Source #

Same as fromEqn, but has no units.

fromEqnSt :: IsUnit u => UID -> NP -> Sentence -> (Stage -> Symbol) -> Space -> u -> e -> QDefinition e Source #

Same as fromEqn, but symbol depends on stage.

fromEqnSt' :: UID -> NP -> Sentence -> (Stage -> Symbol) -> Space -> e -> QDefinition e Source #

Same as fromEqn, but symbol depends on stage and has no units.

fromEqnSt'' :: String -> NP -> Sentence -> (Stage -> Symbol) -> Space -> e -> QDefinition e Source #

Same as fromEqnSt', but takes a String instead of a UID.

mkQDefSt :: UID -> NP -> Sentence -> (Stage -> Symbol) -> Space -> Maybe UnitDefn -> e -> QDefinition e Source #

Wrapper for fromEqnSt and fromEqnSt'

mkQuantDef :: (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e Source #

Used to help make QDefinitions when UID, term, and Symbol come from the same source.

mkQuantDef' :: (Quantity c, MayHaveUnit c) => c -> NP -> e -> QDefinition e Source #

Used to help make QDefinitions when UID and Symbol come from the same source, with the term separate.

ec :: (Quantity c, MayHaveUnit c) => c -> e -> QDefinition e Source #

Smart constructor for QDefinitions. Requires a quantity and its defining equation.

mkFuncDef :: (HasUID f, HasSymbol f, HasSpace f, HasUID i, HasSymbol i, HasSpace i, IsUnit u) => f -> NP -> Sentence -> u -> [i] -> e -> QDefinition e Source #

Create a QDefinition function with a symbol, name, term, list of inputs, resultant units, and a defining Expr

mkFuncDef' :: (HasUID f, HasSymbol f, HasSpace f, HasUID i, HasSymbol i, HasSpace i) => f -> NP -> Sentence -> [i] -> e -> QDefinition e Source #

Create a QDefinition function with a symbol, name, term, list of inputs, and a defining Expr

mkFuncDefByQ :: (Quantity c, MayHaveUnit c, HasSpace c, Quantity i, HasSpace i) => c -> [i] -> e -> QDefinition e Source #

Create a QDefinition functions using a symbol, list of inputs, and a defining Expr

class Quantity c => Unitary c where Source #

A Unitary is a Quantity that must have a unit.

Methods

unit :: c -> UnitDefn Source #

Instances

Instances details
Unitary UnitaryChunk Source #

Finds the unit definition of a UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Unitary UnitalChunk Source #

Finds the unit definition of a UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

data UnitaryChunk Source #

UnitaryChunks are for ideas with quantities that must have units. Contains a QuantityDict and a UnitDefn.

Ex. A pendulum arm is an idea associated with a symbol (l) and units (cm, m, etc.).

Instances

Instances details
HasUID UnitaryChunk Source #

Finds UID of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Methods

uid :: Lens' UnitaryChunk UID Source #

HasSymbol UnitaryChunk Source #

Finds the Symbol of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

HasSpace UnitaryChunk Source #

Finds the Space of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Methods

typ :: Lens' UnitaryChunk Space Source #

Idea UnitaryChunk Source #

Finds the idea contained in the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

NamedIdea UnitaryChunk Source #

Finds term (NP) of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Methods

term :: Lens' UnitaryChunk NP Source #

Quantity UnitaryChunk Source #

UnitaryChunks have a Quantity.

Instance details

Defined in Language.Drasil.Chunk.Unitary

MayHaveUnit UnitaryChunk Source #

Finds the units of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

Unitary UnitaryChunk Source #

Finds the unit definition of a UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

unitary :: IsUnit u => String -> NP -> Symbol -> u -> Space -> UnitaryChunk Source #

Builds the QuantityDict part from the UID, term (NP), Symbol, and Space. Assumes there's no abbreviation.

unitary' :: IsUnit u => String -> NP -> (Stage -> Symbol) -> u -> Space -> UnitaryChunk Source #

Same as unitary but with a Symbol that changes based on the Stage.

mkUnitary :: (Unitary u, MayHaveUnit u) => u -> UnitaryChunk Source #

Makes a UnitaryChunk from a quantity with a unit.

unit_symb :: Unitary c => c -> USymb Source #

Helper for getting the unit's Symbol from a chunk, as opposed to the symbols of the chunk itself.

data DefinedQuantityDict Source #

DefinedQuantityDict is the combination of a Concept and a Quantity. Contains a ConceptChunk, a Symbol dependent on Stage, a Space, and maybe a UnitDefn. Used when we want to assign a quantity to a concept. Includes the space, symbol, and units for that quantity.

Ex. A pendulum arm can be defined as a concept with a symbol (l), space (Real numbers), and units (cm, m, etc.).

Instances

Instances details
Eq DefinedQuantityDict Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

HasUID DefinedQuantityDict Source #

Finds the UID of the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

HasSymbol DefinedQuantityDict Source #

Finds the Stage -> Symbol of the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

HasSpace DefinedQuantityDict Source #

Finds the Space of the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

Express DefinedQuantityDict Source #

Convert the symbol of the DefinedQuantityDict to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

Idea DefinedQuantityDict Source #

Finds the idea contained in the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

NamedIdea DefinedQuantityDict Source #

Finds the term (NP) of the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

Quantity DefinedQuantityDict Source #

DefinedQuantityDicts have a Quantity.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

ConceptDomain DefinedQuantityDict Source #

Finds the domain of the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

Definition DefinedQuantityDict Source #

Finds the definition contained in the ConceptChunk used to make the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

MayHaveUnit DefinedQuantityDict Source #

Finds the units of the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

dqd :: IsUnit u => ConceptChunk -> Symbol -> Space -> u -> DefinedQuantityDict Source #

Smart constructor that creates a DefinedQuantityDict with a ConceptChunk, a Symbol independent of Stage, a Space, and a unit.

dqd' :: ConceptChunk -> (Stage -> Symbol) -> Space -> Maybe UnitDefn -> DefinedQuantityDict Source #

Similar to dqd, but the Symbol is now dependent on the Stage.

dqdNoUnit :: ConceptChunk -> Symbol -> Space -> DefinedQuantityDict Source #

Similar to dqd, but without any units.

dqdQd :: (Quantity c, MayHaveUnit c) => c -> ConceptChunk -> DefinedQuantityDict Source #

When we want to merge a quantity and a concept. This is suspicious.

dqdWr :: (Quantity c, Concept c, MayHaveUnit c) => c -> DefinedQuantityDict Source #

When the input already has all the necessary information. A projection operator from some a type with instances of listed classes to a DefinedQuantityDict.

data UnitalChunk Source #

Similar to a DefinedQuantityDict, UnitalChunks are concepts with quantities that must have a unit definition. Contains DefinedQuantityDicts and a UnitDefn.

Ex. A pendulum arm is a tangible object with a symbol (l) and units (cm, m, etc.).

Constructors

UC 

Instances

Instances details
Eq UnitalChunk Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.Unital

HasUID UnitalChunk Source #

Finds UID of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

uid :: Lens' UnitalChunk UID Source #

HasSymbol UnitalChunk Source #

Finds the Symbol of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

HasSpace UnitalChunk Source #

Finds the Space of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

typ :: Lens' UnitalChunk Space Source #

Express UnitalChunk Source #

Convert the symbol of the UnitalChunk to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.Unital

Idea UnitalChunk Source #

Finds the idea contained in the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

NamedIdea UnitalChunk Source #

Finds term (NP) of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

term :: Lens' UnitalChunk NP Source #

Quantity UnitalChunk Source #

UnitalChunks have a Quantity.

Instance details

Defined in Language.Drasil.Chunk.Unital

ConceptDomain UnitalChunk Source #

Finds the domain contained in the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

cdom :: UnitalChunk -> [UID] Source #

Definition UnitalChunk Source #

Finds definition of the DefinedQuantityDict used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Methods

defn :: Lens' UnitalChunk Sentence Source #

TempHasUnit UnitalChunk Source #

Finds the units used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

MayHaveUnit UnitalChunk Source #

Finds the units used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

Unitary UnitalChunk Source #

Finds the unit definition of a UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

makeUCWDS :: IsUnit u => String -> NP -> Sentence -> Symbol -> u -> UnitalChunk Source #

Creates a UnitalChunk in the same way as uc', but with a Sentence for the definition instead of a String.

uc :: (Concept c, IsUnit u) => c -> Symbol -> u -> UnitalChunk Source #

Used to create a UnitalChunk from a Concept, Symbol, and Unit. Assumes the Space is Real.

uc' :: IsUnit u => String -> NP -> String -> Symbol -> u -> UnitalChunk Source #

Similar to uc, except it builds the Concept portion of the UnitalChunk from a given UID, term, and definition (which are the first three arguments).

ucStaged :: IsUnit u => String -> NP -> String -> (Stage -> Symbol) -> u -> UnitalChunk Source #

Similar to uc', but Symbol is dependent on the Stage.

ucs :: IsUnit u => String -> NP -> String -> Symbol -> Space -> u -> UnitalChunk Source #

Similar to uc', but does not assume the Space.

ucs' :: (Concept c, IsUnit u) => c -> Symbol -> Space -> u -> UnitalChunk Source #

Similar to uc but does not assume the Space.

ucsWS :: IsUnit u => String -> NP -> Sentence -> Symbol -> Space -> u -> UnitalChunk Source #

Similar to ucs, but uses a Sentence for description.

ucuc :: (Quantity c, Concept c, MayHaveUnit c) => c -> UnitDefn -> UnitalChunk Source #

Attach units to a chunk that has a symbol and definition.

ucw :: (Unitary c, Concept c, MayHaveUnit c) => c -> UnitalChunk Source #

Constructs a UnitalChunk from a Concept with Units.

data UnitDefn Source #

For defining units. It has a ConceptChunk (that defines what kind of unit it is), a unit symbol, maybe another (when it is a synonym), perhaps a definition, and a list of UID of the units that make up the definition.

Ex. Meter is a unit of length defined by the symbol (m).

Constructors

UD 

Fields

Instances

Instances details
Eq UnitDefn Source #

Equal if Symbols are equal.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

HasUID UnitDefn Source #

Finds UID of the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

uid :: Lens' UnitDefn UID Source #

Idea UnitDefn Source #

Finds the idea contained in the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

NamedIdea UnitDefn Source #

Finds term (NP) of the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

term :: Lens' UnitDefn NP Source #

IsUnit UnitDefn Source #

Gets the UnitDefn and contributing units.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

HasUnitSymbol UnitDefn Source #

Finds unit symbol of the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

usymb :: UnitDefn -> USymb Source #

ConceptDomain UnitDefn Source #

Finds the domain contained in the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

cdom :: UnitDefn -> [UID] Source #

Definition UnitDefn Source #

Finds definition of the ConceptChunk used to make the UnitDefn.

Instance details

Defined in Language.Drasil.Chunk.UnitDefn

Methods

defn :: Lens' UnitDefn Sentence Source #

fromUDefn :: UDefn -> USymb Source #

Generates a default unit symbol.

unitCon :: String -> ConceptChunk Source #

Helper for fundamental unit concept chunk creation. Uses the same String for the identifier, term, and definition.

makeDerU :: ConceptChunk -> UnitEquation -> UnitDefn Source #

Create a derived unit chunk from a concept and a unit equation.

(^:) :: UnitDefn -> Integer -> UnitEquation Source #

Combinator for raising a unit to a power.

(/:) :: UnitDefn -> UnitDefn -> UnitEquation Source #

Combinator for dividing one unit by another.

(*:) :: UnitDefn -> UnitDefn -> UnitEquation Source #

Combinator for multiplying two units together.

(*$) :: UnitDefn -> UnitEquation -> UnitEquation Source #

Combinator for multiplying a unit and a symbol.

(/$) :: UnitDefn -> UnitEquation -> UnitEquation Source #

Combinator for dividing a unit and a symbol.

(^$) :: UnitEquation -> UnitEquation -> UnitEquation Source #

Combinator for mulitiplying two unit equations.

newUnit :: String -> UnitEquation -> UnitDefn Source #

Smart constructor for new derived units from existing units.

scale :: IsUnit s => Double -> s -> UDefn Source #

Combinator for scaling one unit by some number.

shift :: IsUnit s => Double -> s -> UDefn Source #

Combinator for shifting one unit by some number.

derUC :: String -> String -> String -> Symbol -> UDefn -> UnitDefn Source #

Uses self-plural term.

Create a derived unit chunk from a UID, term (String), definition, Symbol, and unit equation.

derUC' :: String -> String -> String -> Symbol -> UDefn -> UnitDefn Source #

Uses term that pluralizes by adding "s" to the end.

Create a derived unit chunk from a UID, term (String), definition, Symbol, and unit equation.

derUC'' :: String -> NP -> String -> Symbol -> UDefn -> UnitDefn Source #

Create a derived unit chunk from a UID, term (NP), definition, Symbol, and unit equation.

fund :: String -> String -> String -> UnitDefn Source #

Smart constructor for a "fundamental" unit.

fund' :: String -> String -> Symbol -> UnitDefn Source #

Variant of the fund, useful for degree.

compUnitDefn :: UnitDefn -> UnitDefn -> Ordering Source #

We don't want an Ord on units, but this still allows us to compare them.

derCUC :: String -> String -> String -> Symbol -> UnitEquation -> UnitDefn Source #

Create a SI_Unit with two Symbol representations. The created NP is self-plural.

derCUC' :: String -> String -> String -> Symbol -> UnitEquation -> UnitDefn Source #

Similar to derCUC, but the created NP has the AddS plural rule.

derCUC'' :: String -> NP -> String -> Symbol -> UnitEquation -> UnitDefn Source #

Create a derived unit chunk from a UID, term (NP), definition, Symbol, and unit equation.

unitWrapper :: IsUnit u => u -> UnitDefn Source #

For allowing lists to mix together chunks that are units by projecting them into a UnitDefn. For now, this only works on UnitDefns.

getCu :: UnitEquation -> [UID] Source #

Get a list of UID of the units that make up the UnitEquation.

class MayHaveUnit u where Source #

Types may contain a unit (UnitDefn).

Methods

getUnit :: u -> Maybe UnitDefn Source #

Instances

Instances details
MayHaveUnit QuantityDict Source #

Finds the units of the QuantityDict.

Instance details

Defined in Language.Drasil.Chunk.Quantity

MayHaveUnit UnitaryChunk Source #

Finds the units of the QuantityDict used to make the UnitaryChunk.

Instance details

Defined in Language.Drasil.Chunk.Unitary

MayHaveUnit DefinedQuantityDict Source #

Finds the units of the DefinedQuantityDict.

Instance details

Defined in Language.Drasil.Chunk.DefinedQuantity

MayHaveUnit UnitalChunk Source #

Finds the units used to make the UnitalChunk.

Instance details

Defined in Language.Drasil.Chunk.Unital

MayHaveUnit ConstrainedChunk Source #

Finds units contained in the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

MayHaveUnit ConstrConcept Source #

Finds the units of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

MayHaveUnit UncertainChunk Source #

Finds units contained in the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

MayHaveUnit UncertQ Source #

Finds the units of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

MayHaveUnit (QDefinition e) Source # 
Instance details

Defined in Language.Drasil.Chunk.Eq

Constrained and Uncertain Values

data ConstraintReason Source #

The reason behind the constraint's existence.

Constructors

Physical 
Software 

data Constraint a where Source #

Holds constraints. May occur between an interval of Expr, a list of Doubles, or a list of Strings.

Constructors

Range :: ConstraintReason -> RealInterval a a -> Constraint a

By default, physical and software constraints are ranges.

physc :: RealInterval Expr Expr -> ConstraintE Source #

Smart constructor for range of Physical constraints between two given expressions.

sfwrc :: RealInterval Expr Expr -> ConstraintE Source #

Smart constructor for range of Software constraints between two given expressions.

isPhysC :: Constraint e -> Bool Source #

Helpful for filtering for Physical constraints. True if constraint is Physical.

isSfwrC :: Constraint e -> Bool Source #

Helpful for filtering for Software constraints. True if constraint is Software.

data ConstrainedChunk Source #

ConstrainedChunks are symbolic quantities (QuantityDict) with Constraints and maybe a typical value (Maybe Expr).

Ex. Measuring the length of a pendulum would have some reasonable value (between 1 cm and 2 m) and the constraint that the length cannot be a negative value.

Instances

Instances details
Eq ConstrainedChunk Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasUID ConstrainedChunk Source #

Finds UID of the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

uid :: Lens' ConstrainedChunk UID Source #

HasSymbol ConstrainedChunk Source #

Finds the Symbol of the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasSpace ConstrainedChunk Source #

Finds the Space of the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Idea ConstrainedChunk Source #

Finds the idea contained in the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

NamedIdea ConstrainedChunk Source #

Finds term (NP) of the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

term :: Lens' ConstrainedChunk NP Source #

Quantity ConstrainedChunk Source #

ConstrainedChunks have a Quantity.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasReasVal ConstrainedChunk Source #

Finds a reasonable value for the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Constrained ConstrainedChunk Source #

Finds the Constraints of a ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

MayHaveUnit ConstrainedChunk Source #

Finds units contained in the QuantityDict used to make the ConstrainedChunk.

Instance details

Defined in Language.Drasil.Chunk.Constrained

data ConstrConcept Source #

ConstrConcepts are conceptual symbolic quantities (DefinedQuantityDict) with Constraints and maybe a reasonable value (no units!). Similar to ConstrainedChunk but includes a definition and domain.

Ex. Measuring the length of a pendulum arm could be a concept that has some reasonable value (between 1 cm and 2 m) and the constraint that the length cannot be a negative value.

Instances

Instances details
Eq ConstrConcept Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasUID ConstrConcept Source #

Finds UID of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

uid :: Lens' ConstrConcept UID Source #

HasSymbol ConstrConcept Source #

Finds the Symbol of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasSpace ConstrConcept Source #

Finds the Space of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

typ :: Lens' ConstrConcept Space Source #

Express ConstrConcept Source #

Convert the symbol of the ConstrConcept to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Idea ConstrConcept Source #

Finds the idea contained in the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

NamedIdea ConstrConcept Source #

Finds term (NP) of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

term :: Lens' ConstrConcept NP Source #

Quantity ConstrConcept Source #

ConstrConcepts have a Quantity.

Instance details

Defined in Language.Drasil.Chunk.Constrained

HasReasVal ConstrConcept Source #

Finds a reasonable value for the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Constrained ConstrConcept Source #

Finds the Constraints of a ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

ConceptDomain ConstrConcept Source #

Finds the domain contained in the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

Methods

cdom :: ConstrConcept -> [UID] Source #

Definition ConstrConcept Source #

Finds definition of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

MayHaveUnit ConstrConcept Source #

Finds the units of the DefinedQuantityDict used to make the ConstrConcept.

Instance details

Defined in Language.Drasil.Chunk.Constrained

cuc :: IsUnit u => String -> NP -> Symbol -> u -> Space -> [ConstraintE] -> Expr -> ConstrainedChunk Source #

Creates a constrained unitary chunk from a UID, term (NP), Symbol, unit, Space, Constraints, and an Expr.

cvc :: String -> NP -> Symbol -> Space -> [ConstraintE] -> Maybe Expr -> ConstrainedChunk Source #

Creates a constrained unitary chunk from a UID, term (NP), Symbol, Space, Constraints, and a Maybe Expr (Similar to cuc but no units).

constrained' :: (Concept c, MayHaveUnit c, Quantity c) => c -> [ConstraintE] -> Expr -> ConstrConcept Source #

Creates a ConstrConcept with a quantitative concept, a list of Constraints and an Expr.

cuc' :: IsUnit u => String -> NP -> String -> Symbol -> u -> Space -> [ConstraintE] -> Expr -> ConstrConcept Source #

Creates a constrained unitary chunk from a UID, term (NP), description (String), Symbol, unit, Space, Constraints, and an Expr.

cuc'' :: IsUnit u => String -> NP -> String -> (Stage -> Symbol) -> u -> Space -> [ConstraintE] -> Expr -> ConstrConcept Source #

Similar to cuc', but Symbol is dependent on Stage.

cnstrw :: (Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) => c -> ConstrainedChunk Source #

Creates a new ConstrainedChunk from either a ConstrainedChunk, ConstrConcept, UncertainChunk, or an UncertQ.

cnstrw' :: (Quantity c, Concept c, Constrained c, HasReasVal c, MayHaveUnit c) => c -> ConstrConcept Source #

Similar to cnstrw, but types must also have a Concept.

data UncertainChunk Source #

UncertainChunk is a symbolic quantity with constraints, a typical value, and an uncertainty. Contains a ConstrainedChunk and an Uncertainty.

Ex. Measuring the length of a pendulum arm may be recorded with an uncertainty value.

Constructors

UCh 

Instances

Instances details
Eq UncertainChunk Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

HasUID UncertainChunk Source #

Finds UID of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

uid :: Lens' UncertainChunk UID Source #

HasUncertainty UncertainChunk Source #

Finds the uncertainty of an UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

HasSymbol UncertainChunk Source #

Finds the Symbol of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

HasSpace UncertainChunk Source #

Finds the Space of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

typ :: Lens' UncertainChunk Space Source #

Idea UncertainChunk Source #

Finds the idea contained in the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

NamedIdea UncertainChunk Source #

Finds term (NP) of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

term :: Lens' UncertainChunk NP Source #

Quantity UncertainChunk Source #

UncertainChunks have a Quantity.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

HasReasVal UncertainChunk Source #

Finds a reasonable value for the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Constrained UncertainChunk Source #

Finds the Constraints of the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

MayHaveUnit UncertainChunk Source #

Finds units contained in the ConstrainedChunk used to make the UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

data UncertQ Source #

UncertQs are conceptual symbolic quantities with constraints and an Uncertainty. Contains a ConstrConcept and an Uncertainty.

Ex. Measuring the length of a pendulum arm may be recorded with an uncertainty value.

Instances

Instances details
Eq UncertQ Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

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

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

HasUID UncertQ Source #

Finds UID of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

uid :: Lens' UncertQ UID Source #

HasUncertainty UncertQ Source #

Finds the uncertainty of an UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

unc :: Lens' UncertQ Uncertainty Source #

HasSymbol UncertQ Source #

Finds the Symbol of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

symbol :: UncertQ -> Stage -> Symbol Source #

HasSpace UncertQ Source #

Finds the Space of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

typ :: Lens' UncertQ Space Source #

Express UncertQ Source #

Convert the symbol of the UncertQ to a ModelExpr.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Idea UncertQ Source #

Finds the idea contained in the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

NamedIdea UncertQ Source #

Finds term (NP) of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

term :: Lens' UncertQ NP Source #

Quantity UncertQ Source #

UncertQs have a Quantity.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

HasReasVal UncertQ Source #

Finds a reasonable value for the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

reasVal :: Lens' UncertQ (Maybe Expr) Source #

Constrained UncertQ Source #

Finds the Constraints of a ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

ConceptDomain UncertQ Source #

Finds the domain contained in the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

cdom :: UncertQ -> [UID] Source #

Definition UncertQ Source #

Finds definition of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

defn :: Lens' UncertQ Sentence Source #

MayHaveUnit UncertQ Source #

Finds the units of the ConstrConcept used to make the UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

uq :: (Quantity c, Constrained c, Concept c, HasReasVal c, MayHaveUnit c) => c -> Uncertainty -> UncertQ Source #

Smart constructor that requires a Quantity, a percentage, and a typical value with an Uncertainty.

uqc :: IsUnit u => String -> NP -> String -> Symbol -> u -> Space -> [ConstraintE] -> Expr -> Uncertainty -> UncertQ Source #

Uncertainty quantity (uq) but with a constraint.

uqcND :: IsUnit u => String -> NP -> Symbol -> u -> Space -> [ConstraintE] -> Expr -> Uncertainty -> UncertQ Source #

Uncertainty quantity constraint (uqc) without a description.

uncrtnChunk :: (Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) => c -> Uncertainty -> UncertainChunk Source #

Smart constructor that can project to an UncertainChunk (also given an Uncertainty).

uvc :: String -> NP -> Symbol -> Space -> [ConstraintE] -> Expr -> Uncertainty -> UncertainChunk Source #

Creates an uncertain variable chunk. Takes UID, term (NP), Symbol, Space, Constrains, Expr, and Uncertainty.

data Uncertainty Source #

Something that may contain an uncertainty value and a precision value.

uncty :: Double -> Maybe Int -> Uncertainty Source #

Smart constructor for values with uncertainty.

class HasUncertainty c where Source #

HasUncertainty is just a chunk with some uncertainty associated to it. This uncertainty is represented as a decimal value between 0 and 1 (percentage).

Methods

unc :: Lens' c Uncertainty Source #

Provides the Lens to an Uncertainty.

Instances

Instances details
HasUncertainty UncertainChunk Source #

Finds the uncertainty of an UncertainChunk.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

HasUncertainty UncertQ Source #

Finds the uncertainty of an UncertQ.

Instance details

Defined in Language.Drasil.Chunk.UncertainQuantity

Methods

unc :: Lens' UncertQ Uncertainty Source #

defaultUncrt :: Uncertainty Source #

The default uncertainty is set to 0.1.

uncVal :: HasUncertainty x => x -> Double Source #

Accessor for uncertainty value from something that has an uncertainty.

uncPrec :: HasUncertainty x => x -> Maybe Int Source #

Accessor for precision value from something that has an uncertainty.

exact :: Uncertainty Source #

Smart constructor for exact values (no uncertainty).

Referencing

getAdd :: LblType -> String Source #

Retrieves the String contained in a LblType.

prepend :: String -> IRefProg Source #

Prepends a String to an IRefProg.

data LblType Source #

Applying different pieces of information for a reference. An RP is a decorated internal reference. Citation is a citation. URI is for URLs and other external links.

data IRefProg Source #

Created for different forms of references. Used in LblType.

Constructors

Deferred UID

Deferred lookup; done later. Used for domains in a ConceptInstance.

RS String

Lifts a String into a RefProg.

RConcat IRefProg IRefProg

Concatenates with two subprograms.

Name

The Symbol to insert the ShortName directly.

data Reference Source #

A Reference contains the identifier (UID), a reference address (LblType), a human-readable shortname (ShortName), and any extra information about the reference (RefInfo).

Instances

Instances details
Eq Reference Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Reference

HasUID Reference Source #

Finds the UID of a Reference.

Instance details

Defined in Language.Drasil.Reference

Methods

uid :: Lens' Reference UID Source #

HasRefAddress Reference Source #

Finds the reference address contained in a Reference (through a LblType).

Instance details

Defined in Language.Drasil.Reference

HasShortName Reference Source #

Finds the shortname of the reference address used for the Reference.

Instance details

Defined in Language.Drasil.Reference

ref :: (HasUID r, HasRefAddress r, HasShortName r) => r -> Reference Source #

Projector function that creates a Reference from something Referable.

refS :: (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence Source #

Takes the reference UID and wraps it into a Sentence.

namedRef :: (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence -> Sentence Source #

Takes a Reference with a name to be displayed and wraps it into a Sentence. Does not overwrite the shortname contained in the reference, but will only display as the given Sentence.

complexRef :: (HasUID r, HasRefAddress r, HasShortName r) => r -> RefInfo -> Sentence Source #

Takes a Reference with additional display info. Uses the internal shortname for its display name.

namedComplexRef :: (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence -> RefInfo -> Sentence Source #

Takes a Reference with a name to be displayed and any additional information and wraps it into a Sentence. Does not overwrite the shortname contained in the reference, but will only display as the given Sentence along with the given RefInfo.

data DecRef Source #

For holding a Reference that is decorated with extra information (ex. page numbers, equation sources, etc.).

Instances

Instances details
Eq DecRef Source #

Equal if UIDs are equal.

Instance details

Defined in Language.Drasil.DecoratedReference

Methods

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

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

HasUID DecRef Source #

Finds the UID of a Reference.

Instance details

Defined in Language.Drasil.DecoratedReference

Methods

uid :: Lens' DecRef UID Source #

HasRefAddress DecRef Source #

Finds the reference address contained in a Reference (through a LblType).

Instance details

Defined in Language.Drasil.DecoratedReference

HasShortName DecRef Source #

Finds the shortname of the reference address used for the Reference.

Instance details

Defined in Language.Drasil.DecoratedReference

dRefInfo :: (HasUID r, HasRefAddress r, HasShortName r) => r -> RefInfo -> DecRef Source #

For creating a decorated reference (DecRef) with extra reference information (RefInfo).

dRef :: (HasUID r, HasRefAddress r, HasShortName r) => r -> DecRef Source #

Same as ref, but for DecRef instead of Reference.

class HasDecRef c where Source #

A class that contains a list of decorated references (DecRefs).

Methods

getDecRefs :: Lens' c [DecRef] Source #

Provides a Lens to the DecRefs.

Citations

type EntryID = String Source #

A String that should contain no spaces.

data Citation Source #

All citations require a unique identifier used by the Drasil chunk. We will re-use the UID part as an EntryID (String) used for creating reference links. Finally we will have the reference information (CitationKind, CiteFields, and a ShortName).

Ex. A reference to a thesis paper like Koothoor's "Document driven approach to certifying scientific computing software" would include the affiliated university, publishing year, and city.

Instances

Instances details
HasFields Citation Source #

Finds Fields of the Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

Methods

getFields :: Lens' Citation [CiteField] Source #

HasUID Citation Source #

Finds UID of the Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

Methods

uid :: Lens' Citation UID Source #

Referable Citation Source #

Gets the reference information of a Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

HasRefAddress Citation Source #

Gets the reference address of a Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

HasShortName Citation Source #

Finds ShortName of the Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

type BibRef = [Citation] Source #

A list of Citations.

class HasCitation c where Source #

Some documents, as well as some pieces of knowledge, have citations.

Methods

getCitations :: Lens' c [Citation] Source #

Provides a Lens to the citations.

class HasFields c where Source #

Citations should have a fields (CiteField).

Methods

getFields :: Lens' c [CiteField] Source #

Provides a Lens to CiteFields.

Instances

Instances details
HasFields Citation Source #

Finds Fields of the Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

Methods

getFields :: Lens' Citation [CiteField] Source #

cArticle :: People -> String -> String -> Int -> [CiteField] -> String -> Citation Source #

Article citation requires author(s), title, journal, year. Optional fields can be: volume, number, pages, month, and note. Implicitly uses the EntryID as the chunk id.

cBookA :: People -> String -> String -> Int -> [CiteField] -> String -> Citation Source #

Book citation by author.

Book citation requires author or editor, title, publisher, year. Optional fields can be volume or number, series, address, edition, month, and note. Implicitly uses the EntryID as the chunk id.

cBookE :: People -> String -> String -> Int -> [CiteField] -> String -> Citation Source #

Book citation by editor.

Book citation requires author or editor, title, publisher, year. Optional fields can be volume or number, series, address, edition, month, and note. Implicitly uses the EntryID as the chunk id.

cBooklet :: String -> [CiteField] -> String -> Citation Source #

Booklet citation requires title. Optional fields can be author, how published, address, month, year, note. Implicitly uses the EntryID as the chunk id.

cInBookACP :: People -> String -> Int -> [Int] -> String -> Int -> [CiteField] -> String -> Citation Source #

InBook citation by author.

InBook citation requires author or editor, title, chapter and/or pages, publisher, year. Optional fields can be volume or number, series, type, address, edition, month, and note. Implicitly uses the EntryID as the chunk id. This smart constructor includes both chapter and page numbers.

cInBookECP :: People -> String -> Int -> [Int] -> String -> Int -> [CiteField] -> String -> Citation Source #

InBook citation by editor.

InBook citation requires author or editor, title, chapter and/or pages, publisher, year. Optional fields can be volume or number, series, type, address, edition, month, and note. Implicitly uses the EntryID as the chunk id. This smart constructor includes both chapter and page numbers.

cInBookAC :: People -> String -> Int -> String -> Int -> [CiteField] -> String -> Citation Source #

Otherwise identical to cInBookACP.

InBook citation excluding page numbers.

cInBookEC :: People -> String -> Int -> String -> Int -> [CiteField] -> String -> Citation Source #

Otherwise identical to cInBookECP.

InBook citation excluding page numbers.

cInBookAP :: People -> String -> [Int] -> String -> Int -> [CiteField] -> String -> Citation Source #

Otherwise identical to cInBookACP.

InBook citation excluding chapter.

cInBookEP :: People -> String -> [Int] -> String -> Int -> [CiteField] -> String -> Citation Source #

Otherwise identical to cInBookECP.

InBook citation excluding chapter.

cInCollection :: People -> String -> String -> String -> Int -> [CiteField] -> String -> Citation Source #

InCollection citation requires author, title, bookTitle, publisher, year. Optional fields can be editor, volume or number, series, type, chapter, pages, address, edition, month, and note. Implicitly uses the EntryID as the chunk id.

cInProceedings :: People -> String -> String -> Int -> [CiteField] -> String -> Citation Source #

InProceedings citation requires author, title, bookTitle, year. Optional fields can be editor, volume or number, series, pages, address, month, organization, publisher, and note. Implicitly uses the EntryID as the chunk id.

cManual :: String -> [CiteField] -> String -> Citation Source #

Manual (technical documentation) citation requires title. Optional fields can be author, organization, address, edition, month, year, and note. Implicitly uses the EntryID as the chunk id.

cMThesis :: People -> String -> String -> Int -> [CiteField] -> String -> Citation Source #

Master's Thesis citation requires author, title, school, and year. Optional fields can be type, address, month, and note. Implicitly uses the EntryID as the chunk id.

cMisc :: [CiteField] -> String -> Citation Source #

Misc citation requires nothing. Optional fields can be author, title, howpublished, month, year, and note. Implicitly uses the EntryID as the chunk id.

cPhDThesis :: People -> String -> String -> Int -> [CiteField] -> String -> Citation Source #

PhD Thesis citation requires author, title, school, and year. Optional fields can be type, address, month, and note. Implicitly uses the EntryID as the chunk id.

cProceedings :: String -> Int -> [CiteField] -> String -> Citation Source #

Proceedings citation requires title and year. Optional fields can be editor, volume or number, series, address, publisher, note, month, and organization. Implicitly uses the EntryID as the chunk id.

cTechReport :: People -> String -> String -> Int -> [CiteField] -> String -> Citation Source #

Technical Report citation requires author, title, institution, and year. Optional fields can be type, number, address, month, and note. Implicitly uses the EntryID as the chunk id.

cUnpublished :: People -> String -> String -> [CiteField] -> String -> Citation Source #

Unpublished citation requires author, title, and note. Optional fields can be month and year. Implicitly uses the EntryID as the chunk id.

data Month Source #

Custom type for months (abbreviated).

Constructors

Jan 
Feb 
Mar 
Apr 
May 
Jun 
Jul 
Aug 
Sep 
Oct 
Nov 
Dec 

Instances

Instances details
Eq Month Source # 
Instance details

Defined in Language.Drasil.Data.Date

Methods

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

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

Ord Month Source # 
Instance details

Defined in Language.Drasil.Data.Date

Methods

compare :: Month -> Month -> Ordering #

(<) :: Month -> Month -> Bool #

(<=) :: Month -> Month -> Bool #

(>) :: Month -> Month -> Bool #

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

max :: Month -> Month -> Month #

min :: Month -> Month -> Month #

Show Month Source # 
Instance details

Defined in Language.Drasil.Data.Date

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

data CiteField Source #

Fields used in citations.

Constructors

Address String 
Author People 
BookTitle String

Used for InCollection references only.

Chapter Int 
Edition Int 
Editor People 
HowPublished HP

Can be published via URL or something else.

Institution String 
Journal String 
Month Month 
Note String 
Number Int 
Organization String 
Pages [Int]

Range of pages (ex1. 1-32; ex2. 7,31,52-55).

Publisher String 
School String 
Series String 
Title String 
Type String

BibTeX "type" field.

Volume Int 
Year Int 

data HP Source #

How something is published. Necessary for URLs to work properly.

Constructors

URL String 
Verb String 

data CitationKind Source #

External references come in many flavours. Articles, Books, etc. (we are using the types available in Bibtex).

author :: People -> CiteField Source #

Smart field constructor for a CiteField.

editor :: People -> CiteField Source #

Smart field constructor for a CiteField.

address :: String -> CiteField Source #

Smart field constructor for a CiteField.

bookTitle :: String -> CiteField Source #

Smart field constructor for a CiteField.

howPublished :: String -> CiteField Source #

Smart field constructor for a CiteField.

howPublishedU :: String -> CiteField Source #

URL version of howPublished.

Smart field constructor for a CiteField.

institution :: String -> CiteField Source #

Smart field constructor for a CiteField.

journal :: String -> CiteField Source #

Smart field constructor for a CiteField.

note :: String -> CiteField Source #

Smart field constructor for a CiteField.

organization :: String -> CiteField Source #

Smart field constructor for a CiteField.

publisher :: String -> CiteField Source #

Smart field constructor for a CiteField.

school :: String -> CiteField Source #

Smart field constructor for a CiteField.

series :: String -> CiteField Source #

Smart field constructor for a CiteField.

title :: String -> CiteField Source #

Smart field constructor for a CiteField.

typeField :: String -> CiteField Source #

Smart field constructor for a CiteField.

chapter :: Int -> CiteField Source #

Smart field constructor for a CiteField.

edition :: Int -> CiteField Source #

Smart field constructor for a CiteField.

number :: Int -> CiteField Source #

Smart field constructor for a CiteField.

volume :: Int -> CiteField Source #

Smart field constructor for a CiteField.

year :: Int -> CiteField Source #

Smart field constructor for a CiteField.

pages :: [Int] -> CiteField Source #

Smart field constructor for a CiteField.

month :: Month -> CiteField Source #

Smart field constructor for a CiteField.

type People = [Person] Source #

People is a synonymn for many Persons.

data Person Source #

A person can have a given name, middle name(s), and surname, as well as the naming convention they use.

Instances

Instances details
Eq Person Source # 
Instance details

Defined in Language.Drasil.People

Methods

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

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

HasName Person Source #

Gets the name of a Person. Adds a dot after any initials.

Instance details

Defined in Language.Drasil.People

person :: String -> String -> Person Source #

Constructor for a person using Western naming conventions. Used for a person with only a given name and surname. Arguments are in the order: given name, surname.

class HasName p Source #

Members of this class must have a name.

Minimal complete definition

nameStr

Instances

Instances details
HasName Person Source #

Gets the name of a Person. Adds a dot after any initials.

Instance details

Defined in Language.Drasil.People

name :: HasName n => n -> String Source #

Gets the name of a Person. Adds a dot after any initials.

person' :: String -> String -> Person Source #

Constructor for a person using Eastern naming conventions. Used for a person with only a given name and surname. Arguments are in the order: surname, given name.

personWM :: String -> [String] -> String -> Person Source #

Constructor for a person using Western naming conventions. Similar to the person constructor, except the middle argument is a list of middle names.

personWM' :: String -> [String] -> String -> Person Source #

Constructor for a person using Eastern naming conventions. Similar to the person' constructor, except the middle argument is a list of middle names.

mononym :: String -> Person Source #

Constructor for a person with a mononym (only one name).

nameStr :: HasName p => p -> String Source #

Provides the ability to hold a name.

rendPersLFM :: Person -> String Source #

Gets a Person's name in the form: Last, First Middle.

rendPersLFM' :: Person -> String Source #

Gets a Person's name in the form: Last, F. M.

rendPersLFM'' :: Person -> String Source #

Gets a Person's name in the form: Last, First M.

comparePeople :: [Person] -> [Person] -> Ordering Source #

Orderes different groups of Persons. If two lists are the same up to a point, the citation with more Persons will go last.

Sentences

Things like expressions and terms are displayed by using Sentences. We also use NounPhrases to record the proper pluralization and capitalization of terms.

data Sentence where Source #

For writing Sentences via combining smaller elements. Sentences are made up of some known vocabulary of things:

  • units (their visual representation)
  • words (via Strings)
  • special characters
  • accented letters
  • references to specific layout objects

Constructors

Ch :: SentenceStyle -> TermCapitalization -> UID -> Sentence

Ch looks up the term for a given UID and displays the term with a given SentenceStyle and CapitalizationRule. This allows Sentences to hold plural forms of NounPhrases and NamedIdeas.

SyCh :: UID -> Sentence

A branch of Ch dedicated to SymbolStyle only.

Sy :: USymb -> Sentence

Converts a unit symbol into a usable Sentence form.

S :: String -> Sentence

Constructor for Strings, used often for descriptions in Chunks.

P :: Symbol -> Sentence

Converts the graphical representation of a symbol into a usable Sentence form.

E :: ModelExpr -> Sentence

Lifts an expression into a Sentence.

Ref :: UID -> Sentence -> RefInfo -> Sentence

Takes a UID to a reference, a display name (Sentence), and any additional reference display information (RefInfo). Resolves the reference later (similar to Ch).

Quote :: Sentence -> Sentence

Adds quotation marks around a Sentence.

Percent :: Sentence

Used for a % symbol.

(:+:) :: Sentence -> Sentence -> Sentence infixr 5

Direct concatenation of two Sentences (no implicit spaces!).

EmptyS :: Sentence

Empty Sentence.

Instances

Instances details
Semigroup Sentence Source #

Sentences can be concatenated.

Instance details

Defined in Language.Drasil.Sentence

Monoid Sentence Source #

Sentences can be empty or directly concatenated.

Instance details

Defined in Language.Drasil.Sentence

data SentenceStyle Source #

Used in Ch constructor to determine the state of a term (can record whether something is in plural form, a singular term, or in short form).

data TermCapitalization Source #

Used in Ch constructor to determine the capitalization of a term. CapF is for capitalizing the first word from the UID of the given term. CapW is for capitalizing all words from the UID of the given term. Mirrors CapFirst and CapWords from CapitalizationRule.

Constructors

CapF 
CapW 
NoCap 

data RefInfo Source #

Holds any extra information needed for a Reference, be it an equation, pages, a note, or nothing.

Constructors

None 
Equation [Int] 
Page [Int] 
RefNote String 

(+:+) :: Sentence -> Sentence -> Sentence Source #

Helper for concatenating two Sentences with a space between them.

(+:+.) :: Sentence -> Sentence -> Sentence Source #

Helper which concatenates two Sentences using +:+ and appends a period.

(+:) :: Sentence -> Sentence -> Sentence Source #

Helper which concatenates two sentences using +:+ and appends a colon.

(!.) :: Sentence -> Sentence Source #

Helper which appends a period to the end of a Sentence (used often as a post-fix operator).

capSent :: Sentence -> Sentence Source #

Capitalizes a Sentence.

ch :: (HasUID c, HasSymbol c) => c -> Sentence Source #

Gets a symbol and places it in a Sentence.

eS' :: Express t => t -> Sentence Source #

sC :: Sentence -> Sentence -> Sentence Source #

Helper for concatenating two Sentences with a comma and space between them.

sDash :: Sentence -> Sentence -> Sentence Source #

Helper for concatenating two Sentences with a space-surrounded dash between them.

sParen :: Sentence -> Sentence Source #

Helper for wrapping Sentences in parentheses.

class NounPhrase n where Source #

Methods

phraseNP :: n -> Sentence Source #

Retrieves singular form of term. Ex. "the quick brown fox".

pluralNP :: n -> PluralForm Source #

Retrieves plural form of term. Ex. "the quick brown foxes".

sentenceCase :: n -> (NP -> Sentence) -> Capitalization Source #

Retrieves the singular form and applies a captalization rule (usually capitalizes the first word) to produce a Sentence. Ex. "The quick brown fox".

titleCase :: n -> (NP -> Sentence) -> Capitalization Source #

Retrieves the singular form and applies a captalization rule (usually capitalizes all words) to produce a Sentence. Ex. "The Quick Brown Fox".

Instances

Instances details
NounPhrase NP Source #

Defines NP as a NounPhrase. Default capitalization rules for proper and common nouns are CapFirst for sentence case and CapWords for title case. Also accepts a Phrase where the capitalization case may be specified.

Instance details

Defined in Language.Drasil.NounPhrase

Methods

phraseNP :: NP -> Sentence Source #

pluralNP :: NP -> PluralForm Source #

sentenceCase :: NP -> (NP -> Sentence) -> Capitalization Source #

titleCase :: NP -> (NP -> Sentence) -> Capitalization Source #

data NP Source #

For nouns and NounPhrases. May be constructed from a proper noun, common noun, or phrase (Sentence) and their respective pluralization and capitalization rules.

Instances

Instances details
NounPhrase NP Source #

Defines NP as a NounPhrase. Default capitalization rules for proper and common nouns are CapFirst for sentence case and CapWords for title case. Also accepts a Phrase where the capitalization case may be specified.

Instance details

Defined in Language.Drasil.NounPhrase

Methods

phraseNP :: NP -> Sentence Source #

pluralNP :: NP -> PluralForm Source #

sentenceCase :: NP -> (NP -> Sentence) -> Capitalization Source #

titleCase :: NP -> (NP -> Sentence) -> Capitalization Source #

pn :: String -> NP Source #

Self plural.

Constructs a Proper Noun, it is always capitalized as written.

pn' :: String -> NP Source #

Plural form simply adds "s" (ex. Henderson -> Hendersons).

Constructs a Proper Noun, it is always capitalized as written.

pn'' :: String -> NP Source #

Plural form adds "e".

Constructs a Proper Noun, it is always capitalized as written.

pn''' :: String -> NP Source #

Plural form adds "es" (ex. Bush -> Bushes).

Constructs a Proper Noun, it is always capitalized as written.

pnIrr :: String -> PluralRule -> NP Source #

Constructs a ProperNoun with a custom plural rule (using IrregPlur from PluralRule). First argument is the String representing the noun, second is the rule.

cn :: String -> NP Source #

Self plural.

Constructs a common noun which capitalizes the first letter of the first word at the beginning of a sentence.

cn' :: String -> NP Source #

Plural form simply adds "s" (ex. dog -> dogs).

Constructs a common noun which capitalizes the first letter of the first word at the beginning of a sentence.

cn'' :: String -> NP Source #

Plural form adds "e" (ex. formula -> formulae).

Constructs a common noun which capitalizes the first letter of the first word at the beginning of a sentence.

cn''' :: String -> NP Source #

Plural form adds "es" (ex. bush -> bushes).

Constructs a common noun which capitalizes the first letter of the first word at the beginning of a sentence.

cnIP :: String -> PluralRule -> NP Source #

Constructs a common noun that allows you to specify the pluralization rule (as in pnIrr).

cnIrr :: String -> PluralRule -> CapitalizationRule -> NP Source #

Common noun that allows you to specify both the pluralization rule and the capitalization rule for sentence case (if the noun is used at the beginning of a sentence).

cnIES :: String -> NP Source #

Constructs a common noun that pluralizes by dropping the last letter and adding an "ies" ending (ex. body -> bodies).

cnICES :: String -> NP Source #

Construct a common noun that pluralizes by dropping the last two letters and adding an "ices" ending (ex. matrix -> matrices).

cnIS :: String -> NP Source #

Constructs a common noun that pluralizes by dropping the last two letters and adding "es" (ex. analysis -> analyses).

cnUM :: String -> NP Source #

Constructs a common noun that pluralizes by dropping the last two letters and adding "a" (ex. datum -> data).

nounPhrase :: String -> PluralString -> NP Source #

Creates a NP with a given singular and plural form (as Strings) that capitalizes the first letter of the first word for sentence case.

nounPhrase' :: String -> PluralString -> CapitalizationRule -> NP Source #

Similar to nounPhrase, but takes a specified capitalization rule for the sentence case.

data CapitalizationRule Source #

Capitalization rules.

Constructors

CapFirst

Capitalize the first letter of the first word only.

CapWords

Capitalize the first letter of each word.

Replace Sentence

Replace the noun phrase with the given Sentence. Used for custom capitalization.

atStartNP :: NounPhrase n => n -> Capitalization Source #

Singular sentence case.

Helper function for getting the sentence case of a noun phrase.

atStartNP' :: NounPhrase n => n -> Capitalization Source #

Plural sentence case.

Helper function for getting the sentence case of a noun phrase.

data PluralRule Source #

Pluralization rules.

Constructors

AddS

Add "s" to the end of the noun phrase.

AddE

Add "e" to the end of the noun phrase.

AddES

Add "es" to the end of the noun phrase.

SelfPlur

The noun phrase is already plural.

IrregPlur (String -> String)

Apply the given function to the noun phrase to get the plural.

compoundPhrase :: (NounPhrase a, NounPhrase b) => a -> b -> NP Source #

Combine two noun phrases. The singular form becomes phrase from t1 followed by phrase of t2. The plural becomes phrase of t1 followed by plural of t2. Uses standard CapFirst sentence case and CapWords title case. For example: compoundPhrase system constraint will have singular form "system constraint" and plural "system constraints".

compoundPhrase' :: NP -> NP -> NP Source #

Similar to compoundPhrase, but the sentence case is the same as the title case (CapWords).

compoundPhrase'' :: (NP -> Sentence) -> (NP -> Sentence) -> NP -> NP -> NP Source #

Similar to compoundPhrase', but accepts two functions that will be used to construct the plural form. For example, compoundPhrase'' plural phrase system constraint would have the plural form "systems constraint".

compoundPhrase''' :: (NP -> Sentence) -> NP -> NP -> NP Source #

Similar to compoundPhrase, but used when you need a special function applied to the first term of both singular and pluralcases (eg. short or plural).

compoundPhraseP1 :: NP -> NP -> NP Source #

Similar to compoundPhrase, but pluralizes the first NP for both singular and plural cases.

titleizeNP :: NounPhrase n => n -> Capitalization Source #

Singular title case.

Helper function for getting the title case of a noun phrase.

titleizeNP' :: NounPhrase n => n -> Capitalization Source #

Plural title case.

Helper function for getting the title case of a noun phrase.

nounPhrase'' :: Sentence -> PluralForm -> CapitalizationRule -> CapitalizationRule -> NP Source #

Custom noun phrase constructor that takes a singular form (Sentence), plural form (Sentence), sentence case capitalization rule, and title case capitalization rule.

nounPhraseSP :: String -> NP Source #

For things that should not be pluralized (or are self-plural). Works like nounPhrase, but with only the first argument.

nounPhraseSent :: Sentence -> NP Source #

Similar to nounPhrase, except it only accepts one Sentence. Used for Requirements, Assumptions, LikelyChanges, etc. to allow for referencing. Plural case is just AddS.

introduceAbb :: Idea n => n -> Sentence Source #

Helper for common pattern of introducing the title-case version of a noun phrase (from an Idea) followed by its abbreviation in parentheses.

phrase :: (HasUID n, NamedIdea n) => n -> Sentence Source #

Helper for getting the phrase from a NamedIdea using it's UID.

plural :: (HasUID n, NamedIdea n) => n -> Sentence Source #

Helper for getting the plural of a phrase from a NamedIdea.

phrasePoss :: NamedIdea n => n -> Sentence Source #

Singular possesive function

Helper for getting the possesive cases from the term of a NamedIdea.

pluralPoss :: NamedIdea n => n -> Sentence Source #

Plural possesive function

Helper for getting the possesive cases from the term of a NamedIdea.

atStart :: NamedIdea n => n -> Sentence Source #

Singular sentence case.

Helper function for getting the sentence case of a noun phrase from a NamedIdea.

atStart' :: NamedIdea n => n -> Sentence Source #

Plural sentence case.

Helper function for getting the sentence case of a noun phrase from a NamedIdea.

titleize :: NamedIdea n => n -> Sentence Source #

Singular title case.

Helper function for getting the title case of a noun phrase from a NamedIdea.

titleize' :: NamedIdea n => n -> Sentence Source #

Plural title case.

Helper function for getting the title case of a noun phrase from a NamedIdea.

short :: (Idea c, HasUID c) => c -> Sentence Source #

Get short form (if it exists), else get term of an Idea.

data ShortName Source #

Used for holding the short form of a name (as a Sentence with a wrapper).

shortname' :: Sentence -> ShortName Source #

Smart constructor for making a Sentence into a ShortName.

getSentSN :: ShortName -> Sentence Source #

Pulls the short form (as a Sentence) out of a ShortName.

class HasShortName s where Source #

A ShortName is the text to be displayed for a link.

Used for referencing within a document that can include symbols and whatnot if required. Visible in the typeset documents (pdf).

Methods

shortname :: s -> ShortName Source #

Instances

Instances details
HasShortName Reference Source #

Finds the shortname of the reference address used for the Reference.

Instance details

Defined in Language.Drasil.Reference

HasShortName DecRef Source #

Finds the shortname of the reference address used for the Reference.

Instance details

Defined in Language.Drasil.DecoratedReference

HasShortName Citation Source #

Finds ShortName of the Citation.

Instance details

Defined in Language.Drasil.Chunk.Citation

HasShortName LabelledContent Source #

Find the shortname of the reference address used for the LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

HasShortName Section Source #

Finds the short name of a Section.

Instance details

Defined in Language.Drasil.Document

HasShortName ConceptInstance Source #

Finds the ShortName contained in a ConceptInstance.

Instance details

Defined in Language.Drasil.Chunk.Concept.Core

data Derivation Source #

Derivations are an ordered list of sentences and expressions. They are rendered in order as paragraphs and equation blocks to display the derivation.

Constructors

Derivation Sentence [Sentence] 

mkDeriv :: Sentence -> [Sentence] -> Derivation Source #

Smart constructor for creating a Derivation.

mkDerivName :: Sentence -> [Sentence] -> Derivation Source #

Similar to mkDeriv, but prepends "Detailed derivation of" to the header.

mkDerivNoHeader :: [Sentence] -> Derivation Source #

Similar to mkDeriv, but without a header Sentence.

Sentence Fold-type utilities.

From Utils.Drasil.Fold. Defines many general fold functions for use with Drasil-related types.

Folding Options as Types

data EnumType Source #

Type that helps determine enumeration method. Can use either numbers, uppercase letters, or lowercase letters.

Constructors

Numb 
Upper 
Lower 

data WrapType Source #

Type to help wrap a sentence with parenthesis or to add a period at the end.

Constructors

Parens 
Period 

data SepType Source #

Type to help separate words with commas or semicolons.

Constructors

Comma 
SemiCol 

data FoldType Source #

Type to help fold differently between listed items, or if there are options (ex. using "and" or "or" at the end of a list of words).

Constructors

List 
Options 

Folding functions

Expression-related

foldConstraints :: Quantity c => c -> [ConstraintE] -> Sentence Source #

Helper for formatting a list of constraints.

Sentence-related

foldlEnumList :: EnumType -> WrapType -> SepType -> FoldType -> [Sentence] -> Sentence Source #

Creates a list of elements with "enumerators" in "wrappers" using foldlList.

foldlList :: SepType -> FoldType -> [Sentence] -> Sentence Source #

Creates a list of elements separated by a "separator", ending with "and" or "or".

foldlSP :: [Sentence] -> Contents Source #

Fold sentences then turns into content using foldlSent.

foldlSent :: [Sentence] -> Sentence Source #

Partial function application of foldle for sentences specifically. Folds with spaces and adds a period (".") at the end.

foldlSent_ :: [Sentence] -> Sentence Source #

foldlSent but does not add a period.

foldlSentCol :: [Sentence] -> Sentence Source #

foldlSent but ends with colon.

foldlsC :: [Sentence] -> Sentence Source #

Folds a list of elements separated by commas, including the last element.

foldNums :: String -> [Int] -> Sentence Source #

Parses a list of integers into a nice sentence (ie. S "1, 4-7, and 13").

numList :: String -> [Int] -> [String] Source #

Parses a list of integers into a list of strings (ie. ["1", "4-7", "13"]).

Basic Document Language

Holds all the types and helper functions needed especially in drasil-docLang Language.Drasil.Document

data Document Source #

A Document has a Title (Sentence), Author(s) (Sentence), and Sections which hold the contents of the document.

data ShowTableOfContents Source #

Determines whether or not the table of contents appears on the generated artifacts.

Constructors

ToC 
NoToC 

data DType Source #

Types of definitions (general, instance, theory, or data).

Constructors

General 
Instance 
Theory 
Data 

data Section Source #

Sections have a title (Sentence), a list of contents (SecCons) and a shortname (Reference).

Constructors

Section 

Fields

Instances

Instances details
Eq Section Source #

Sections are equal if UIDs are equal.

Instance details

Defined in Language.Drasil.Document

Methods

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

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

HasUID Section Source #

Finds the UID of a Section.

Instance details

Defined in Language.Drasil.Document

Methods

uid :: Lens' Section UID Source #

Referable Section Source #

Finds the reference information of a Section.

Instance details

Defined in Language.Drasil.Document

HasRefAddress Section Source #

Finds the reference address of a Section.

Instance details

Defined in Language.Drasil.Document

HasShortName Section Source #

Finds the short name of a Section.

Instance details

Defined in Language.Drasil.Document

data Contents Source #

Contents may be labelled or unlabelled.

Instances

Instances details
HasContents Contents Source #

Access the RawContent within Contents.

Instance details

Defined in Language.Drasil.Document.Core

data SecCons Source #

Section Contents are split into subsections or contents, where contents are standard layout objects (see Contents).

Constructors

Sub Section 
Con Contents 

data ListType Source #

Denotes the different possible types that can be used as a list.

Constructors

Bullet [(ItemType, Maybe String)]

Bulleted list.

Numeric [(ItemType, Maybe String)]

Enumerated list.

Simple [ListTuple]

Simple list with items denoted by :. Renders as "Title: Item"

Desc [ListTuple]

Descriptive list, renders as "Title: Item" (see ListTuple).

Definitions [ListTuple]

Renders a list of "Title is the Item".

data ItemType Source #

Denotes how something should behave in a list (ListType).

Constructors

Flat Sentence

Standard singular item.

Nested Header ListType

Nest a list (ListType) as an item.

type ListTuple Source #

Arguments

 = (Title, ItemType, Maybe String)

Formats as Title: Item. For use in lists.

data LabelledContent Source #

Contains a Reference and RawContent.

Constructors

LblC 

Instances

Instances details
Eq LabelledContent Source #

LabelledContents are equal if their reference UIDs are equal.

Instance details

Defined in Language.Drasil.Document.Core

HasUID LabelledContent Source #

Finds UID of the LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

Methods

uid :: Lens' LabelledContent UID Source #

Referable LabelledContent Source #

Finds the reference information of LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

HasRefAddress LabelledContent Source #

Finds the reference address contained in the Reference of LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

HasShortName LabelledContent Source #

Find the shortname of the reference address used for the LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

HasContents LabelledContent Source #

Access the RawContent within the LabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

newtype UnlabelledContent Source #

Only contains RawContent.

Constructors

UnlblC 

Fields

Instances

Instances details
HasContents UnlabelledContent Source #

Access the RawContent within the UnlabelledContent.

Instance details

Defined in Language.Drasil.Document.Core

extractSection :: Document -> [Section] Source #

Smart constructor for retrieving the contents (Sections) from a Document.

mkParagraph :: Sentence -> Contents Source #

Smart constructor that wraps UnlabelledContent into Contents.

mkRawLC :: RawContent -> Reference -> LabelledContent Source #

Smart constructor similar to llcc, but takes in RawContent first.

checkToC :: Document -> Document Source #

Manually removes the first section of a document (table of contents section). temp fix for Notebook (see if we need this in notebook later)

llcc :: Reference -> RawContent -> LabelledContent Source #

Smart constructor for labelled content chunks.

ulcc :: RawContent -> UnlabelledContent Source #

Smart constructor for unlabelled content chunks (no Reference).

section :: Sentence -> [Contents] -> [Section] -> Reference -> Section Source #

Smart constructor for creating Sections with a title (Sentence), introductory contents (ie. paragraphs, tables, etc.), a list of subsections, and a shortname (Reference).

fig :: Lbl -> Filepath -> RawContent Source #

Figure smart constructor with a Lbl and a Filepath. Assumes 100% of page width as max width.

figWithWidth :: Lbl -> Filepath -> MaxWidthPercent -> RawContent Source #

Figure smart constructor that allows for customized max widths.

type MaxWidthPercent = Float Source #

MaxWidthPercent should be kept in the range 1-100. Values outside this range may have unexpected results. Used for specifying max figure width as pagewidth*MaxWidthPercent/100.

class HasContents c where Source #

Members of this class must have RawContent.

Methods

accessContents :: Lens' c RawContent Source #

Provides a Lens to the RawContent.

data RawContent Source #

Types of layout objects we deal with explicitly.

Constructors

Table [Sentence] [[Sentence]] Title Bool

table has: header-row, data(rows), label/caption, and a bool that determines whether or not to show label.

Paragraph Sentence

Paragraphs are just sentences.

EqnBlock ModelExpr

Block of Equations holds an expression.

DerivBlock Sentence [RawContent]

Grants the ability to label a group of RawContent.

Enumeration ListType

For enumerated lists.

Defini DType [(Identifier, [Contents])]

Defines something with a type, identifier, and Contents.

Figure Lbl Filepath MaxWidthPercent

For creating figures in a document. Should use relative file path.

Bib BibRef

Grants the ability to reference something.

Graph [(Sentence, Sentence)] (Maybe Width) (Maybe Height) Lbl

Contain a graph with coordinates (Sentences), maybe a width and height, and a label (Sentence). | CodeBlock CodeExpr -- ^ Block for codes TODO: Fill this one in.

mkFig :: Reference -> RawContent -> Contents Source #

Smart constructor that wraps LabelledContent into Contents.

makeTabRef :: String -> Reference Source #

Create a reference for a table. Takes in the name of a table (which will also be used for its shortname).

makeFigRef :: String -> Reference Source #

Create a reference for a figure. Takes in the name of a figure (which will also be used for its shortname).

makeSecRef :: String -> Sentence -> Reference Source #

Create a reference for a section. Takes in the name of a section and a shortname for the section.

makeEqnRef :: String -> Reference Source #

Create a reference for a equation. Takes in the name of the equation (which will also be used for its shortname).

makeURI :: String -> String -> ShortName -> Reference Source #

Create a reference for a URI. Takes in a UID (as a String), a reference address, and a shortname.

makeTabRef' :: UID -> Reference Source #

Variants of makeTabRef that takes a UID instead of a String.

makeFigRef' :: UID -> Reference Source #

Variants of makeFigRef that takes a UID instead of a String.

makeSecRef' :: UID -> Sentence -> Reference Source #

Variants of makeSecRef that takes a UID instead of a String.

makeEqnRef' :: UID -> Reference Source #

Variants of makeEqnRef that takes a UID instead of a String.

makeURI' :: UID -> String -> ShortName -> Reference Source #

Variants of makeURI that takes a UID instead of a String.

Language.Drasil.Document.Contents

enumBullet :: Reference -> [Sentence] -> LabelledContent Source #

Creates a bulleted list.

enumBulletU :: [Sentence] -> Contents Source #

Same as enumBullet but unlabelled.

enumSimple :: Reference -> Integer -> Sentence -> [Sentence] -> LabelledContent Source #

Currently Unused. Creates a simple bulleted list that labels things with a title and number:

  • lb - Reference,
  • s - start index for the enumeration,
  • t - title of the list,
  • l - list to be enumerated.

For example, if we want to create a list of data definitions, we could call the function as follows:

enumSimple _ 2 (S "DD") [def1, def2, ...]

And the resulting LabelledContent would be rendered as:

  • DD2: def1
  • DD3: def2
  • DD4: def3 ...

enumSimpleU :: Integer -> Sentence -> [Sentence] -> Contents Source #

Same as enumSimple but unlabelled.

mkEnumSimpleD :: (Referable c, HasShortName c, Definition c) => [c] -> [Contents] Source #

Convenience function for transforming referable concepts into a bulleted list. Used in drasil-docLang in making the assumptions, goals, and requirements sections. Output is of the kind Concept Name: definition of concept.

lbldExpr :: ModelExpr -> Reference -> LabelledContent Source #

Displays a given expression and attaches a Reference to it.

unlbldExpr :: ModelExpr -> Contents Source #

Same as eqUnR except content is unlabelled (does not attach a Reference).

Document combinators

From Language.Drasil.Document.Combinators. General sorting functions, useful combinators, and various functions to work with Drasil Chunk types.

Reference-related functions

Attach a Reference and a Sentence in different ways.

chgsStart :: (HasShortName x, Referable x) => x -> Sentence -> Sentence Source #

Output is of the form "reference - sentence".

definedIn :: (Referable r, HasShortName r, HasSymbol r) => r -> Sentence Source #

Takes a HasSymbol that is also Referable and outputs as a Sentence: "symbol is defined in reference."

definedIn' :: (Referable r, HasShortName r, HasSymbol r) => r -> Sentence -> Sentence Source #

Same as definedIn, but allows for additional information to be appended to the Sentence.

definedIn'' :: (Referable r, HasShortName r) => r -> Sentence Source #

Takes a Referable and outputs as a Sentence "defined in reference" (no HasSymbol).

definedIn''' :: (HasSymbol q, HasUID q, Referable r, HasShortName r) => q -> r -> Sentence Source #

Takes a Symbol and its Reference (does not append a period at the end!). Outputs as "symbol is defined in source".

eqnWSource :: (Referable r, HasShortName r) => ModelExpr -> r -> Sentence Source #

Takes an expression and a Referable and outputs as a Sentence "expression (source)".

fromReplace :: (Referable r, HasShortName r) => r -> UnitalChunk -> Sentence Source #

Takes a Referable source and a UnitalChunk and outputs as a Sentence: "From source we can replace symbol:".

fromSource :: (Referable r, HasShortName r) => r -> Sentence Source #

Wraps "from reference" in parentheses.

fromSources :: (Referable r, HasShortName r) => [r] -> Sentence Source #

Similar to fromSource but takes a list of references instead of one.

fmtU :: MayHaveUnit a => Sentence -> a -> Sentence Source #

Takes an amount as a Sentence and appends a unit to it.

follows :: (Referable r, HasShortName r) => Sentence -> r -> Sentence Source #

Appends "following reference" to the end of a Sentence.

makeListRef :: [a] -> Section -> [Sentence] Source #

Takes a list and a Section, then generates a list of that section's reference to match the length of the list.

Sentence-related functions

See Reference-related functions as well.

addPercent :: Show a => a -> Sentence Source #

Converts input to a Sentence and appends %.

displayStrConstrntsAsSet :: Quantity a => a -> [String] -> Sentence Source #

Produces a Sentence that displays the constraints in a set {}.

displayDblConstrntsAsSet :: Quantity a => a -> [Double] -> Sentence Source #

Produces a Sentence that displays the constraints in a set {}.

eqN :: Int -> Sentence Source #

Prepends the word Equation to an Int.

checkValidStr :: String -> String -> Either String String Source #

Uses an Either type to check if a String is valid - Left with error message if there is an invalid Char in String, else Right with String.

getTandS :: Quantity a => a -> Sentence Source #

Used when you want to say a term followed by its symbol. ex. "...using the Force F in...".

maybeChanged :: Sentence -> Sentence -> Sentence Source #

Helper functions for making likely change statements. Uses form likelyFrame parameter1 _ parameter2.

maybeExpanded :: Sentence -> Sentence -> Sentence Source #

Helper functions for making likely change statements. Uses form likelyFrame parameter1 _ parameter2.

maybeWOVerb :: Sentence -> Sentence -> Sentence Source #

Helper functions for making likely change statements. Uses form likelyFrame parameter1 _ parameter2.

showingCxnBw :: NamedIdea c => c -> Sentence -> Sentence Source #

Returns the Sentence "(titleize aNamedIdea) Showing the Connections Between contents".

substitute :: (Referable r, HasShortName r, HasSymbol r) => [r] -> Sentence Source #

Takes a list of Referables and Symbols and outputs as a Sentence "By substituting symbols, this can be written as:".

typUncr :: HasUncertainty c => c -> Sentence Source #

Extracts the typical uncertainty to be displayed from something that has an uncertainty.

underConsidertn :: ConceptChunk -> Sentence Source #

Returns the Sentence "The chunk under consideration is chunkDefinition".

unwrap :: Maybe UnitDefn -> Sentence Source #

Get a unit symbol if there is one.

fterms :: (NamedIdea c, NamedIdea d) => (NP -> NP -> t) -> c -> d -> t Source #

Apply a binary function to the terms of two named ideas, instead of to the named ideas themselves. Ex. fterms compoundPhrase t1 t2 instead of compoundPhrase (t1 ^. term) (t2 ^. term).

List-related functions

bulletFlat :: [Sentence] -> ListType Source #

Applies Bullet and Flat to a list.

bulletNested :: [Sentence] -> [ListType] -> ListType Source #

Applies Bullets and headers to a Nested ListType. The first argument is the headers of the Nested lists.

itemRefToSent :: String -> Sentence -> Sentence Source #

Makes Sentences from an item and its reference. Takes the title of reference as a String and a Sentence containing the full reference. Wraps the full reference in parenthesis.

makeTMatrix :: Eq a => [Sentence] -> [[a]] -> [a] -> [[Sentence]] Source #

Makes a traceability matrix from a list of row titles, a list of rows of "checked" columns, and a list of columns.

mkEnumAbbrevList :: Integer -> Sentence -> [Sentence] -> [(Sentence, ItemType)] Source #

Zip helper function enumerates abbreviations and zips it with list of ItemType:

  • s - the number from which the enumeration should start from (Integer),
  • t - the title of the list (Sentence),
  • l - the list to be enumerated ([Sentence]).

mkTableFromColumns :: [(Sentence, [Sentence])] -> ([Sentence], [[Sentence]]) Source #

Helper for making a table from a columns.

noRefs :: [ItemType] -> [(ItemType, Maybe String)] Source #

Converts lists of simple ItemTypes into a list which may be used in Contents but is not directly referable.

refineChain :: NamedIdea c => [(c, Section)] -> Sentence Source #

Create a list in the pattern of "The __ are refined to the __". Note: Order matters!

sortBySymbol :: HasSymbol a => [a] -> [a] Source #

Sorts a list of HasSymbols by Symbol.

sortBySymbolTuple :: HasSymbol a => [(a, b)] -> [(a, b)] Source #

Sorts a tuple list of HasSymbols by first Symbol in the tuple.

tAndDOnly :: Concept s => s -> ItemType Source #

Helpful combinators for making Sentences into Terminologies with Definitions. Returns of the form: "term - termDefinition".

tAndDWAcc :: Concept s => s -> ItemType Source #

Helpful combinators for making Sentences into Terminologies with Definitions. Returns of the form: "term (abbreviation) - termDefinition".

tAndDWSym :: (Concept s, Quantity a) => s -> a -> ItemType Source #

Helpful combinators for making Sentences into Terminologies with Definitions. Returns of the form: "term (symbol) - termDefinition".

zipSentList :: [[Sentence]] -> [Sentence] -> [[Sentence]] -> [[Sentence]] Source #

Distributes a list of Sentences by prepending individual Sentences once to an existing list of Sentences.

For example:

>>> zipSentList [S "Hi", S "Hey", S "Hi"] [[S "Hello"], [S "World"], [S "Hello", S "World"]]
[[S "Hi", S "Hello"], [S "Hey", S "World"], [S "Hi", S "Hello", S "World"]]

Symbols, Stages, Spaces

Used for rendering mathematical symbols in Drasil.

data Space Source #

The difference kinds of spaces that may exist. This type holds numerical spaces (such as the set of integers, rationals, etc.), a space for booleans, a space for characters, dimensional spaces (vectors, arrays, etc.), a space for Actors, discrete sets (both for numbers and strings), and a void space.

Instances

Instances details
Eq Space Source # 
Instance details

Defined in Language.Drasil.Space

Methods

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

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

Show Space Source # 
Instance details

Defined in Language.Drasil.Space

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

data RealInterval a b where Source #

A RealInterval is a subset of Real (as a Space). These come in different flavours. For now, we embed Expr for the bounds, but that will change as well.

Constructors

Bounded 

Fields

UpTo 

Fields

UpFrom 

Fields

data Inclusive Source #

Inclusive or exclusive bounds.

Constructors

Inc 
Exc 

data DomainDesc (tplgy :: RTopology) a b where Source #

Describes the domain of a Symbol given a topology. Can be bounded or encase all of the domain.

Constructors

BoundedDD :: Symbol -> RTopology -> a -> b -> DomainDesc 'Discrete a b 
AllDD :: Symbol -> RTopology -> DomainDesc 'Continuous a b 

data RTopology Source #

Topology of a subset of reals.

Constructors

Continuous 
Discrete 

getActorName :: Space -> String Source #

Gets the name of an Actor.

getInnerSpace :: Space -> Space Source #

Gets the inner Space of a vector.

data Decoration Source #

Decorations on symbols/characters such as hats or Vector representations (determines bolding, italics, etc).

data Symbol Source #

A Symbol is actually going to be a graphical description of what gets rendered as a (unique) symbol. This is actually NOT based on semantics at all, but just a description of how things look.

Symbols can be:

  • Variable (string such as "x" that represent a value that can vary)
  • Label (strings such as "max" or "target" that represent a single idea)
  • Special characters (ex. unicode)
  • Decorated symbols using Atop
  • Concatenations of symbols, including subscripts and superscripts
  • Empty! (this is to give this a monoid-like flavour)

Instances

Instances details
Eq Symbol Source # 
Instance details

Defined in Language.Drasil.Symbol

Methods

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

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

Semigroup Symbol Source #

Symbols may be concatenated.

Instance details

Defined in Language.Drasil.Symbol

Monoid Symbol Source #

Symbols can be empty or concatenated.

Instance details

Defined in Language.Drasil.Symbol

newtype USymb Source #

Language of units (how to build them up into a unit symbol). Of the form (Symbol ^ Integer). The Integer may be negative, but should not be zero.

Constructors

US [(Symbol, Integer)] 

Instances

Instances details
Eq USymb Source # 
Instance details

Defined in Language.Drasil.UnitLang

Methods

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

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

mkTable :: [a -> b] -> [a] -> [[b]] Source #

Create a table body (not including header row) by applying the given functions to the column elements of the table rows (in order). The first argument is a list of functions to be applied (one per column). This essentially creates the rows. The second argument is a list of elements apply the functions to.

For example, mkTable [id, *5] [1,2,3] should produce a table:

| 1 |  5 |
| 2 | 10 |
| 3 | 15 |

data Stage Source #

Stages correspond to what we're trying to look up. They range from abstract to concrete. Equational stages are more theoretical and oriented towards abstract design while the Implementation stages are more oriented towards detailed design.

Constructors

Equational 
Implementation 

Instances

Instances details
Show Stage Source #

For better error messages.

Instance details

Defined in Language.Drasil.Stages

Methods

showsPrec :: Int -> Stage -> ShowS #

show :: Stage -> String #

showList :: [Stage] -> ShowS #

eqSymb :: HasSymbol q => q -> Symbol Source #

Helper function for getting a symbol in the Equational Stage.

codeSymb :: HasSymbol q => q -> Symbol Source #

Helper function for getting a symbol in the Implementation Stage.

hasStageSymbol :: HasSymbol q => q -> Stage -> Bool Source #

Finds if a Stage symbol is real or Empty. True if real.

autoStage :: Symbol -> Stage -> Symbol Source #

Helper for creating a symbol with Unicode in it.

hat :: Symbol -> Symbol Source #

Helper for creating a symbol with a hat ("^") atop it.

prime :: Symbol -> Symbol Source #

Helper for creating a Vector symbol.

staged :: Symbol -> Symbol -> Stage -> Symbol Source #

Helper for creating a symbol that depends on the stage.

sub :: Symbol -> Symbol -> Symbol Source #

Helper for creating a symbol with a subscript to the right. Arguments: Base symbol, then subscripted symbol.

subStr :: Symbol -> String -> Symbol Source #

Helper for a common case of subscript, with a string Arguments: Base symbol, then subscript String.

sup :: Symbol -> Symbol -> Symbol Source #

Helper for creating a symbol with a superscript to the right. Arguments: Base symbol, then superscripted symbol.

unicodeConv :: Symbol -> Symbol Source #

Helper for autoStage that applies unicodeString to all Symbols with Strings.

upperLeft :: Symbol -> Symbol -> Symbol Source #

Helper for creating a symbol with a superscript on the left side of the symbol. Arguments: Base symbol, then superscripted symbol.

vec :: Symbol -> Symbol Source #

Helper for creating a Vector symbol.

label :: String -> Symbol Source #

Label smart constructor, requires non-empty labels

variable :: String -> Symbol Source #

Variable smart constructor, requires non-empty variables

Type Synonyms

type ConstQDef = QDefinition Literal Source #

Commonly used type for QDefinitions containing Literals.

type SimpleQDef = QDefinition Expr Source #

Commonly used type for QDefinitions containing Exprs.

type ModelQDef = QDefinition ModelExpr Source #

Commonly used type for QDefinitions containing ModelExprs.

type PExpr = forall r. (ExprC r, LiteralC r) => r Source #

Commonly used type for polymorphic Exprs.