| Copyright | (C) 2021-2024 QBayLogic B.V. | 
|---|---|
| License | BSD2 (see the file LICENSE) | 
| Maintainer | QBayLogic B.V. <devops@qbaylogic.com> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Clash.Core.EqSolver
Description
Synopsis
- data TypeEqSolution- = Solution (TyVar, Type)
- | AbsurdSolution
- | NoSolution
 
- catSolutions :: [TypeEqSolution] -> [(TyVar, Type)]
- solveNonAbsurds :: TyConMap -> VarSet -> [(Type, Type)] -> [(TyVar, Type)]
- solveEq :: TyConMap -> VarSet -> (Type, Type) -> [TypeEqSolution]
- solveAdd :: VarSet -> (Type, Type) -> TypeEqSolution
- normalizeAdd :: (Type, Type) -> Maybe (Integer, Integer, Type)
- isAbsurdPat :: TyConMap -> Pat -> Bool
- isAbsurdEq :: TyConMap -> VarSet -> (Type, Type) -> Bool
- patEqs :: TyConMap -> Pat -> [(Type, Type)]
- typeEq :: TyConMap -> Type -> Maybe (Type, Type)
Documentation
data TypeEqSolution Source #
Data type that indicates what kind of solution (if any) was found
Constructors
| Solution (TyVar, Type) | Solution was found. Variable equals some integer. | 
| AbsurdSolution | A solution was found, but it involved negative naturals. | 
| NoSolution | Given type wasn't an equation, or it was unsolvable. | 
Instances
| Eq TypeEqSolution Source # | |
| Defined in Clash.Core.EqSolver Methods (==) :: TypeEqSolution -> TypeEqSolution -> Bool Source # (/=) :: TypeEqSolution -> TypeEqSolution -> Bool Source # | |
| Show TypeEqSolution Source # | |
| Defined in Clash.Core.EqSolver | |
catSolutions :: [TypeEqSolution] -> [(TyVar, Type)] Source #
solveNonAbsurds :: TyConMap -> VarSet -> [(Type, Type)] -> [(TyVar, Type)] Source #
Solve given equations and return all non-absurd solutions
solveEq :: TyConMap -> VarSet -> (Type, Type) -> [TypeEqSolution] Source #
Solve simple equalities such as:
- a ~ 3
- 3 ~ a
- SomeType a b ~ SomeType 3 5
- SomeType 3 5 ~ SomeType a b
- SomeType a 5 ~ SomeType 3 b
solveAdd :: VarSet -> (Type, Type) -> TypeEqSolution Source #
Solve equations supported by normalizeAdd. See documentation of
 TypeEqSolution to understand the return value.
normalizeAdd :: (Type, Type) -> Maybe (Integer, Integer, Type) Source #
Given the left and right side of an equation, normalize it such that equations of the following forms:
- 5 ~ n + 2
- 5 ~ 2 + n
- n + 2 ~ 5
- 2 + n ~ 5
are returned as (5, 2, n)
isAbsurdPat :: TyConMap -> Pat -> Bool Source #
Tests for nonsencical patterns due to types being "absurd". See
 isAbsurdEq for more info.
Determines if an "equation" obtained through patEqs or typeEq is
 absurd. That is, it tests if two types that are definitely not equal are
 asserted to be equal OR if the computation of the types yield some absurd
 (intermediate) result such as -1.