| 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
Synopsis
- data Sort
- = BooleanSort
- | IntegralSort
- | ArraySort { }
- data family Sing (a :: k) :: *
- data DynamicSort where
- DynamicSort :: forall (s :: Sort). Sing s -> DynamicSort
- data DynamicallySorted (f :: (Sort -> *) -> Sort -> *) where
- DynamicallySorted :: forall (s :: Sort) f. Sing s -> IFix f s -> DynamicallySorted f
- parseSort :: Parser DynamicSort
- toDynamicallySorted :: forall f (s :: Sort). SingI s => IFix f s -> DynamicallySorted f
- toStaticSort :: forall (s :: Sort). SingI s => DynamicSort -> Maybe (Sing s)
- toStaticallySorted :: forall f (s :: Sort). 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 (a :: k) :: * #
The singleton kind-indexed data family.
Instances
data DynamicSort where Source #
Some sort (obtained for example during parsing)
Constructors
| DynamicSort :: forall (s :: Sort). Sing s -> DynamicSort |
Instances
| Eq DynamicSort Source # | |
Defined in Data.Expression.Sort | |
data DynamicallySorted (f :: (Sort -> *) -> Sort -> *) where Source #
An expression of some sort (obtained for example during parsing)
Constructors
| DynamicallySorted :: forall (s :: Sort) f. Sing s -> IFix f s -> DynamicallySorted f |
Instances
| IEq1 f => Eq (DynamicallySorted f) Source # | |
Defined in Data.Expression.Sort Methods (==) :: DynamicallySorted f -> DynamicallySorted f -> Bool # (/=) :: DynamicallySorted f -> DynamicallySorted f -> Bool # | |
| (IFunctor f, IShow f) => Show (DynamicallySorted f) Source # | |
Defined in Data.Expression.Sort Methods showsPrec :: Int -> DynamicallySorted f -> ShowS # show :: DynamicallySorted f -> String # showList :: [DynamicallySorted f] -> ShowS # | |
parseSort :: Parser DynamicSort Source #
Parser that accepts sort definitions such as bool, int, array int int, array int (array ...).
toDynamicallySorted :: forall f (s :: Sort). SingI s => IFix f s -> DynamicallySorted f Source #
Converts a statically sorted expression to a dynamically sorted one.
toStaticSort :: forall (s :: Sort). SingI s => DynamicSort -> Maybe (Sing s) Source #
Tries to convert some sort (DynamicSort) to a requested sort.
toStaticallySorted :: forall f (s :: Sort). 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.