| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Dino.Expression
Contents
Description
General tagless expressions
Synopsis
- class ConstExp e where
- true :: ConstExp e => e Bool
- false :: ConstExp e => e Bool
- text :: ConstExp e => Text -> e Text
- class NumExp e where- add :: Num a => e a -> e a -> e a
- sub :: Num a => e a -> e a -> e a
- mul :: Num a => e a -> e a -> e a
- absE :: Num a => e a -> e a
- signE :: Num a => e a -> e a
- fromIntegral :: (Integral a, DinoType b, Num b) => e a -> e b
- floor :: (RealFrac a, DinoType b, Integral b) => e a -> e b
- truncate :: (RealFrac a, DinoType b, Integral b) => e a -> e b
- roundN :: RealFrac a => Int -> e a -> e a
 
- fromInt :: (NumExp e, DinoType a, Num a) => e Integer -> e a
- class FracExp e where- fdiv :: (Fractional a, Eq a) => e a -> e a -> e a
 
- (./) :: (ConstExp e, FracExp e, CompareExp e, CondExpFO e, DinoType a, Fractional a) => e a -> e a -> e a
- class LogicExp e where
- (&&) :: LogicExp e => e Bool -> e Bool -> e Bool
- (||) :: LogicExp e => e Bool -> e Bool -> e Bool
- class CompareExp e where
- (==) :: (Eq a, CompareExp e) => e a -> e a -> e Bool
- (/=) :: (Eq a, CompareExp e) => e a -> e a -> e Bool
- (<) :: (Ord a, CompareExp e) => e a -> e a -> e Bool
- (>) :: (Ord a, CompareExp e) => e a -> e a -> e Bool
- (<=) :: (Ord a, CompareExp e) => e a -> e a -> e Bool
- (>=) :: (Ord a, CompareExp e) => e a -> e a -> e Bool
- (==!) :: (ConstExp e, CompareExp e, DinoType a) => e a -> a -> e Bool
- data a :-> b = a :-> b
- (-->) :: a -> b -> a :-> b
- data Otherwise = Otherwise
- class CondExpFO e where
- class CondExpFO e => CondExp e where
- default_partial_cases :: (CondExpFO e, HasCallStack) => [e Bool :-> e a] -> e a
- nothing :: (ConstExp e, DinoType a) => e (Maybe a)
- isJust :: (ConstExp e, CondExp e, DinoType a) => e (Maybe a) -> e Bool
- match :: CondExpFO e => a -> [(a -> e Bool) :-> e b] -> (Otherwise :-> e b) -> e b
- matchConst :: (ConstExp e, CompareExp e, CondExpFO e, DinoType a) => e a -> [a :-> e b] -> (Otherwise :-> e b) -> e b
- matchConstFull :: (ConstExp e, CompareExp e, CondExpFO e, DinoType a, Show a, Enum a, Bounded a, HasCallStack) => e a -> [a :-> e b] -> e b
- ifThenElse :: CondExpFO e => e Bool -> e a -> e a -> e a
- fromMaybe :: (CondExp e, DinoType a) => e a -> e (Maybe a) -> e a
- class ListExpFO e where
- class ListExpFO e => ListExp e where
- class TupleExp e where
- class LetExp e where
- share :: (LetExp e, DinoType a) => e a -> (e a -> e b) -> e b
- shared :: (LetExp e, DinoType a) => (e a -> e b) -> e a -> e b
- data Field (f :: Symbol) = Field
- class FieldExp e where- getField :: (KnownSymbol f, HasField f r a, DinoType a) => proxy f -> e r -> e a
 
- field :: (FieldExp e, KnownSymbol f, HasField f r a, DinoType a) => Field f -> e r -> e a
- (<.) :: (FieldExp e, KnownSymbol f, HasField f r a, DinoType a) => Field f -> e r -> e a
- class AnnExp ann e where- ann :: ann -> e a -> e a
 
- class AssertExp e where
- newtype Exp e a = Exp {- unExp :: e a
 
- sumE :: (ConstExp e, NumExp e, ListExp e, DinoType a, Num a) => e [a] -> e a
- andE :: (ConstExp e, LogicExp e, ListExp e) => e [Bool] -> e Bool
- orE :: (ConstExp e, LogicExp e, ListExp e) => e [Bool] -> e Bool
- allE :: (ConstExp e, LogicExp e, ListExp e, DinoType a) => (e a -> e Bool) -> e [a] -> e Bool
- anyE :: (ConstExp e, LogicExp e, ListExp e, DinoType a) => (e a -> e Bool) -> e [a] -> e Bool
- find :: (LogicExp e, ListExp e, DinoType a) => (e a -> e Bool) -> e [a] -> e (Maybe a)
- (<++>) :: ListExpFO e => e [a] -> e [a] -> e [a]
- and :: (ConstExp e, LogicExp e) => [e Bool] -> e Bool
- or :: (ConstExp e, LogicExp e) => [e Bool] -> e Bool
- all :: (ConstExp e, LogicExp e) => (a -> e Bool) -> [a] -> e Bool
- any :: (ConstExp e, LogicExp e) => (a -> e Bool) -> [a] -> e Bool
- data Optional e a where
- suppose :: DinoType a => e (Maybe a) -> Optional e (e a)
- optional :: (ConstExp e, CondExp e, LetExp e, DinoType a, DinoType b) => e b -> (e a -> e b) -> Optional e (e a) -> e b
- runOptional :: (ConstExp e, CondExp e, LetExp e, DinoType a) => Optional e (e a) -> e (Maybe a)
- fromOptional :: (ConstExp e, CondExp e, LetExp e, DinoType a) => e a -> Optional e (e a) -> e a
Expression classes and constructs
Constants
class ConstExp e where Source #
Constant expressions
The default implementation is for Applicative interpretations.
Minimal complete definition
Nothing
Methods
lit :: DinoType a => a -> e a Source #
Make a Dino literal from a Haskell value
lit :: Applicative e => a -> e a Source #
Make a Dino literal from a Haskell value
Instances
text :: ConstExp e => Text -> e Text Source #
Constant text expression
With OverloadedStrings enabled, text literals can be written simply as
 "...".
Numeric expressions
Numeric expressions
The default implementations are for Applicative interpretations.
Minimal complete definition
Nothing
Methods
add :: Num a => e a -> e a -> e a Source #
sub :: Num a => e a -> e a -> e a Source #
mul :: Num a => e a -> e a -> e a Source #
absE :: Num a => e a -> e a Source #
signE :: Num a => e a -> e a Source #
fromIntegral :: (Integral a, DinoType b, Num b) => e a -> e b Source #
Convert an integer to any numeric type
floor :: (RealFrac a, DinoType b, Integral b) => e a -> e b Source #
floor xx
truncate :: (RealFrac a, DinoType b, Integral b) => e a -> e b Source #
truncate xx between zero and x
roundN :: RealFrac a => Int -> e a -> e a Source #
Round to the specified number of decimals
add :: (Applicative e, Num a) => e a -> e a -> e a Source #
sub :: (Applicative e, Num a) => e a -> e a -> e a Source #
mul :: (Applicative e, Num a) => e a -> e a -> e a Source #
absE :: (Applicative e, Num a) => e a -> e a Source #
signE :: (Applicative e, Num a) => e a -> e a Source #
fromIntegral :: (Applicative e, Integral a, Num b) => e a -> e b Source #
Convert an integer to any numeric type
floor :: (Applicative e, RealFrac a, Integral b) => e a -> e b Source #
floor xx
truncate :: (Applicative e, RealFrac a, Integral b) => e a -> e b Source #
truncate xx between zero and x
roundN :: (Applicative e, RealFrac a) => Int -> e a -> e a Source #
Round to the specified number of decimals
Instances
fromInt :: (NumExp e, DinoType a, Num a) => e Integer -> e a Source #
Convert an Integer to any numeric type
class FracExp e where Source #
Fractional expressions
The default implementation is for Applicative interpretations.
Minimal complete definition
Nothing
Methods
fdiv :: (Fractional a, Eq a) => e a -> e a -> e a Source #
Division
fdiv :: (Applicative e, Fractional a) => e a -> e a -> e a Source #
Division
Instances
(./) :: (ConstExp e, FracExp e, CompareExp e, CondExpFO e, DinoType a, Fractional a) => e a -> e a -> e a Source #
Division that returns 0 when the denominator is 0
Logic expressions
class LogicExp e where Source #
Logic expressions
The default implementations are for Applicative interpretations.
Minimal complete definition
Nothing
Methods
not :: e Bool -> e Bool Source #
conj :: e Bool -> e Bool -> e Bool Source #
disj :: e Bool -> e Bool -> e Bool Source #
xor :: e Bool -> e Bool -> e Bool Source #
not :: Applicative e => e Bool -> e Bool Source #
conj :: Applicative e => e Bool -> e Bool -> e Bool Source #
disj :: Applicative e => e Bool -> e Bool -> e Bool Source #
Instances
Comparisons
class CompareExp e where Source #
Comparisons
The default implementations are for Applicative interpretations.
Minimal complete definition
Nothing
Methods
eq :: Eq a => e a -> e a -> e Bool Source #
neq :: Eq a => e a -> e a -> e Bool Source #
lt :: Ord a => e a -> e a -> e Bool Source #
gt :: Ord a => e a -> e a -> e Bool Source #
lte :: Ord a => e a -> e a -> e Bool Source #
gte :: Ord a => e a -> e a -> e Bool Source #
min :: Ord a => e a -> e a -> e a Source #
max :: Ord a => e a -> e a -> e a Source #
eq :: (Applicative e, Eq a) => e a -> e a -> e Bool Source #
neq :: (Applicative e, Eq a) => e a -> e a -> e Bool Source #
lt :: (Applicative e, Ord a) => e a -> e a -> e Bool Source #
gt :: (Applicative e, Ord a) => e a -> e a -> e Bool Source #
lte :: (Applicative e, Ord a) => e a -> e a -> e Bool Source #
gte :: (Applicative e, Ord a) => e a -> e a -> e Bool Source #
min :: (Applicative e, Ord a) => e a -> e a -> e a Source #
max :: (Applicative e, Ord a) => e a -> e a -> e a Source #
Instances
(==!) :: (ConstExp e, CompareExp e, DinoType a) => e a -> a -> e Bool infix 4 Source #
Check equality against a constant value
Conditionals
Representation of a case in cases
Constructors
| a :-> b infix 1 | 
Instances
| Bifunctor (:->) Source # | |
| Functor ((:->) a) Source # | |
| Foldable ((:->) a) Source # | |
| Defined in Dino.Expression Methods fold :: Monoid m => (a :-> m) -> m # foldMap :: Monoid m => (a0 -> m) -> (a :-> a0) -> m # foldr :: (a0 -> b -> b) -> b -> (a :-> a0) -> b # foldr' :: (a0 -> b -> b) -> b -> (a :-> a0) -> b # foldl :: (b -> a0 -> b) -> b -> (a :-> a0) -> b # foldl' :: (b -> a0 -> b) -> b -> (a :-> a0) -> b # foldr1 :: (a0 -> a0 -> a0) -> (a :-> a0) -> a0 # foldl1 :: (a0 -> a0 -> a0) -> (a :-> a0) -> a0 # toList :: (a :-> a0) -> [a0] # elem :: Eq a0 => a0 -> (a :-> a0) -> Bool # maximum :: Ord a0 => (a :-> a0) -> a0 # minimum :: Ord a0 => (a :-> a0) -> a0 # | |
| Traversable ((:->) a) Source # | |
| (Eq a, Eq b) => Eq (a :-> b) Source # | |
| (Show a, Show b) => Show (a :-> b) Source # | |
class CondExpFO e where Source #
Helper class to CondExp containing only first-order constructs
The reason for having this class is that there are types for which
 CondExpFO can be derived but CondExp cannot.
Minimal complete definition
Nothing
Methods
just :: e a -> e (Maybe a) Source #
Construct an optional value that is present
Case expression
Arguments
| :: HasCallStack | |
| => [e Bool :-> e a] | Guarded expressions | 
| -> e a | 
Case expression without fall-through
Evaluation may fail if the cases are not complete.
just :: Applicative e => e a -> e (Maybe a) Source #
Construct an optional value that is present
Arguments
| :: Monad e | |
| => [e Bool :-> e a] | Guarded expressions | 
| -> (Otherwise :-> e a) | Fall-through case | 
| -> e a | 
Case expression
Arguments
| :: (Monad e, HasCallStack) | |
| => [e Bool :-> e a] | Guarded expressions | 
| -> e a | 
Case expression without fall-through
Evaluation may fail if the cases are not complete.
Instances
class CondExpFO e => CondExp e where Source #
Expressions supporting conditionals
The default implementations are for monadic interpretations.
Minimal complete definition
Nothing
Methods
Arguments
| :: DinoType a | |
| => e b | Result when  | 
| -> (e a -> e b) | Result when  | 
| -> e (Maybe a) | Value to deconstruct | 
| -> e b | 
Deconstruct an optional value
Arguments
| :: Monad e | |
| => e b | Result when  | 
| -> (e a -> e b) | Result when  | 
| -> e (Maybe a) | Value to deconstruct | 
| -> e b | 
Deconstruct an optional value
Instances
default_partial_cases :: (CondExpFO e, HasCallStack) => [e Bool :-> e a] -> e a Source #
nothing :: (ConstExp e, DinoType a) => e (Maybe a) Source #
Construct an optional value that is missing
Arguments
| :: CondExpFO e | |
| => a | Scrutinee | 
| -> [(a -> e Bool) :-> e b] | Cases | 
| -> (Otherwise :-> e b) | Fall-through case | 
| -> e b | 
Case expression using Boolean functions for matching
Arguments
| :: (ConstExp e, CompareExp e, CondExpFO e, DinoType a, Show a, Enum a, Bounded a, HasCallStack) | |
| => e a | Scrutinee | 
| -> [a :-> e b] | Cases | 
| -> e b | 
A Version of matchConst for enumerations where the cases cover the whole
 domain
An error is thrown if the cases do not cover the whole domain.
Conditional expression
Enable RebindableSyntax to use the standard syntax if a then b else c
 for calling this function.
Lists
class ListExpFO e where Source #
Helper class to ListExp containing only first-order constructs
The reason for having this class is that there are types for which
 ListExpFO can be derived but ListExp cannot.
Minimal complete definition
Nothing
Methods
Arguments
| :: Enum a | |
| => e a | Lower bound (inclusive) | 
| -> e a | Upper bound (inclusive) | 
| -> e [a] | 
list :: DinoType a => [e a] -> e [a] Source #
headE :: e [a] -> e (Maybe a) Source #
append :: e [a] -> e [a] -> e [a] Source #
Arguments
| :: (Applicative e, Enum a) | |
| => e a | Lower bound (inclusive) | 
| -> e a | Upper bound (inclusive) | 
| -> e [a] | 
list :: Applicative e => [e a] -> e [a] Source #
headE :: Applicative e => e [a] -> e (Maybe a) Source #
append :: Applicative e => e [a] -> e [a] -> e [a] Source #
Instances
class ListExpFO e => ListExp e where Source #
Minimal complete definition
Nothing
Methods
mapE :: DinoType a => (e a -> e b) -> e [a] -> e [b] Source #
dropWhileE :: DinoType a => (e a -> e Bool) -> e [a] -> e [a] Source #
Arguments
| :: (DinoType a, DinoType b) | |
| => (e a -> e b -> e a) | Reducer function | 
| -> e a | Initial value | 
| -> e [b] | List to reduce (traversed left-to-right) | 
| -> e a | 
Left fold
mapE :: Monad e => (e a -> e b) -> e [a] -> e [b] Source #
dropWhileE :: Monad e => (e a -> e Bool) -> e [a] -> e [a] Source #
Arguments
| :: Monad e | |
| => (e a -> e b -> e a) | Reducer function | 
| -> e a | Initial value | 
| -> e [b] | List to reduce (traversed left-to-right) | 
| -> e a | 
Left fold
Instances
Tuples
class TupleExp e where Source #
Minimal complete definition
Nothing
Methods
pair :: e a -> e b -> e (a, b) Source #
fstE :: e (a, b) -> e a Source #
sndE :: e (a, b) -> e b Source #
pair :: Applicative e => e a -> e b -> e (a, b) Source #
fstE :: Applicative e => e (a, b) -> e a Source #
sndE :: Applicative e => e (a, b) -> e b Source #
Instances
Let bindings
Minimal complete definition
Nothing
Methods
Share a value in a calculation
The default implementation of letE implements call-by-value.
Share a value in a calculation
The default implementation of letE implements call-by-value.
Instances
Share a value in a calculation
Like letE but with the variable base name fixed to "share".
Records
class FieldExp e where Source #
Minimal complete definition
Nothing
Methods
getField :: (KnownSymbol f, HasField f r a, DinoType a) => proxy f -> e r -> e a Source #
getField :: forall proxy f r a. (Applicative e, KnownSymbol f, HasField f r a) => proxy f -> e r -> e a Source #
Instances
field :: (FieldExp e, KnownSymbol f, HasField f r a, DinoType a) => Field f -> e r -> e a Source #
Extract a field from a record
Use as follows (with OverloadedLabels):
field #name $ field #driver car
(<.) :: (FieldExp e, KnownSymbol f, HasField f r a, DinoType a) => Field f -> e r -> e a infixr 9 Source #
Extract a field from a record
Use as follows (with OverloadedLabels):
#name <. #driver <. car
Annotations
class AnnExp ann e where Source #
Minimal complete definition
Nothing
Instances
Assertions
class AssertExp e where Source #
Minimal complete definition
Nothing
Methods
Arguments
| :: Text | Assertion label | 
| -> e Bool | Condition that should be true | 
| -> e a | Expression to attach the assertion to | 
| -> e a | 
Assert that a condition is true
Interpretations can choose whether to ignore the assertion or to check its validity. The default implementation ignores the assertion.
The following must hold for any monadic interpretation:
assertlab c a==(assertlab c (return())>>returna)
Arguments
| :: (Eq a, Show a) | |
| => Text | Assertion label | 
| -> e a | Reference expression | 
| -> e a | Actual expression | 
| -> e a | 
Assert that an expression is semantically equivalent to a reference expression
Interpretations can choose whether to ignore the assertion or to check its validity. The default implementation ignores the assertion.
The following must hold for any monadic interpretation:
assertEqlab ref act==( do a <- actassertEqlab ref (returna) return a )
Instances
Concrete expression wrapper
Useful wrapper to get a concrete type for tagless DSL expressions
The problem solved by this type can be explained as follows:
Suppose you write a numeric expression with the most general type:
myExp1 :: Num e => e myExp1 = 1+2
And suppose you define an evaluation function as follows:
eval1 :: (forall e . (ConstExp e, NumExp e) => e a) -> a eval1 = runIdentity
The problem is that we cannot pass myExp1 to eval1:
test1 :: Int test1 = eval1 myExp1
This leads to:
• Could not deduce (Num (e Int)) ...
And we don't want to change eval1 to
eval1 :: (forall e . (ConstExp e, NumExp e, Num (e a)) => e a) -> a
since this requires the expression to return a number (and not e.g. a
 Boolean), and it also doesn't help to satisfy any internal numeric
 expressions that may use a different type than a.
Instead, the solution is to use Exp as follows:
myExp2 :: (ConstExp e, NumExp e, Num a) => Exp e a myExp2 = 1+2 eval2 :: (forall e . (ConstExp e, NumExp e) => Exp e a) -> a eval2 = runIdentity . unExp test2 :: Int test2 = eval2 myExp2
The trick is that there exists an instance
instance (Num a, ConstExp e, NumExp e) => Num (Exp e a)
So it is enough for eval2 to supply constraints on e, and it will
 automatically imply the availability of the Num instance.
Instances
Derived operations
Operations on Dino lists
allE :: (ConstExp e, LogicExp e, ListExp e, DinoType a) => (e a -> e Bool) -> e [a] -> e Bool Source #
anyE :: (ConstExp e, LogicExp e, ListExp e, DinoType a) => (e a -> e Bool) -> e [a] -> e Bool Source #
Operations on Haskell lists
Optional monad
data Optional e a where Source #
Optional expressions with a Monad instance
Optional is handy to avoid nested uses of maybe. As an example, here is a
 safe division function:
safeDiv :: _ => e a -> e a -> Optional e (e a)
safeDiv a b = suppose $
  if (b /= lit 0)
    then just (fdiv a b)
    else nothingAnd here is a calculation that defaults to 0 if any of the divisions fails:
foo :: _ => Exp e Double -> Exp e Double -> Exp e Double foo a b = fromOptional 0 $ do x <- safeDiv a b y <- safeDiv b x safeDiv x y
Constructors
| Return :: a -> Optional e a | |
| Bind :: DinoType a => e (Maybe a) -> (e a -> Optional e b) -> Optional e b | 
suppose :: DinoType a => e (Maybe a) -> Optional e (e a) Source #
Lift an optional expression to Optional
Arguments
| :: (ConstExp e, CondExp e, LetExp e, DinoType a, DinoType b) | |
| => e b | Result if missing | 
| -> (e a -> e b) | Result if present | 
| -> Optional e (e a) | Value to examine | 
| -> e b | 
Convert from Optional value to an optional expression