| Copyright | (C) 2017-18 Jakub Daniel |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Jakub Daniel <jakub.daniel@protonmail.com> |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Expression.Sort
Description
- data Sort
- = BooleanSort
- | IntegralSort
- | ArraySort { }
- data family Sing k (a :: k) :: *
- data DynamicSort where
- DynamicSort :: forall s. Sing s -> DynamicSort
- data DynamicallySorted f where
- DynamicallySorted :: forall s f. Sing s -> IFix f s -> DynamicallySorted f
- parseSort :: Parser DynamicSort
- toStaticSort :: forall s. SingI s => DynamicSort -> Maybe (Sing s)
- toStaticallySorted :: forall f s. SingI s => DynamicallySorted f -> Maybe (IFix f s)
Documentation
A universe of recognized sorts
Constructors
| BooleanSort | booleans (true, false) |
| IntegralSort | integers (..., -1, 0, 1, ...) |
| ArraySort | arrays indexed by |
Instances
data family Sing k (a :: k) :: * #
The singleton kind-indexed data family.
Instances
| data Sing Bool | |
| data Sing Ordering | |
| data Sing Nat | |
| data Sing Symbol | |
| data Sing () | |
| data Sing Sort # | |
| data Sing [a0] | |
| data Sing (Maybe a0) | |
| data Sing (NonEmpty a0) | |
| data Sing (Either a0 b0) | |
| data Sing (a0, b0) | |
| data Sing ((~>) k1 k2) | |
| data Sing (a0, b0, c0) | |
| data Sing (a0, b0, c0, d0) | |
| data Sing (a0, b0, c0, d0, e0) | |
| data Sing (a0, b0, c0, d0, e0, f0) | |
| data Sing (a0, b0, c0, d0, e0, f0, g0) | |
data DynamicSort where Source #
Some sort (obtained for example during parsing)
Constructors
| DynamicSort :: forall s. Sing s -> DynamicSort |
Instances
data DynamicallySorted f where Source #
An expression of some sort (obtained for example during parsing)
Constructors
| DynamicallySorted :: forall s f. Sing s -> IFix f s -> DynamicallySorted f |
parseSort :: Parser DynamicSort Source #
Parser that accepts sort definitions such as bool, int, array int int, array int (array ...).
toStaticSort :: forall s. SingI s => DynamicSort -> Maybe (Sing s) Source #
Tries to convert some sort (DynamicSort) to a requested sort.
toStaticallySorted :: forall f s. SingI s => DynamicallySorted f -> Maybe (IFix f s) Source #
Tries to convert an expression (DynamicallySorted) of some sort to an expression of requested sort.
Performs no conversions.