expressions-0.5: Expressions and Formulae a la carte

Copyright(C) 2017-18 Jakub Daniel
LicenseBSD-style (see the file LICENSE)
MaintainerJakub Daniel <jakub.daniel@protonmail.com>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Data.Expression.Utils.Indexed.Eq

Description

 
Synopsis
  • class IEq (a :: i -> *) where
    • ieq :: forall j. a j -> a j -> Bool
  • class IEq1 (f :: (i -> *) -> i -> *) where

Documentation

class IEq (a :: i -> *) where Source #

Indexed types that can be equated

Methods

ieq :: forall j. a j -> a j -> Bool Source #

Instances
IEq1 f => IEq (IFix f :: i -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Functor

Methods

ieq :: IFix f j -> IFix f j -> Bool Source #

class IEq1 (f :: (i -> *) -> i -> *) where Source #

Type constructors (usually functors) that produce types that can be equated

Methods

ieq1 :: forall a j. IEq a => f a j -> f a j -> Bool Source #

Instances
IEq1 IfThenElseF Source # 
Instance details

Defined in Data.Expression.IfThenElse

Methods

ieq1 :: IEq a => IfThenElseF a j -> IfThenElseF a j -> Bool Source #

IEq1 ArrayF Source # 
Instance details

Defined in Data.Expression.Array

Methods

ieq1 :: IEq a => ArrayF a j -> ArrayF a j -> Bool Source #

IEq1 ArithmeticF Source # 
Instance details

Defined in Data.Expression.Arithmetic

Methods

ieq1 :: IEq a => ArithmeticF a j -> ArithmeticF a j -> Bool Source #

IEq1 NegationF Source # 
Instance details

Defined in Data.Expression

Methods

ieq1 :: IEq a => NegationF a j -> NegationF a j -> Bool Source #

IEq1 DisjunctionF Source # 
Instance details

Defined in Data.Expression

Methods

ieq1 :: IEq a => DisjunctionF a j -> DisjunctionF a j -> Bool Source #

IEq1 ConjunctionF Source # 
Instance details

Defined in Data.Expression

Methods

ieq1 :: IEq a => ConjunctionF a j -> ConjunctionF a j -> Bool Source #

IEq1 (EqualityF :: (Sort -> Type) -> Sort -> Type) Source # 
Instance details

Defined in Data.Expression.Equality

Methods

ieq1 :: IEq a => EqualityF a j -> EqualityF a j -> Bool Source #

IEq1 (ExistentialF v :: (Sort -> Type) -> Sort -> Type) Source # 
Instance details

Defined in Data.Expression

Methods

ieq1 :: IEq a => ExistentialF v a j -> ExistentialF v a j -> Bool Source #

IEq1 (UniversalF v :: (Sort -> Type) -> Sort -> Type) Source # 
Instance details

Defined in Data.Expression

Methods

ieq1 :: IEq a => UniversalF v a j -> UniversalF v a j -> Bool Source #

IEq1 (VarF :: (Sort -> Type) -> Sort -> Type) Source # 
Instance details

Defined in Data.Expression

Methods

ieq1 :: IEq a => VarF a j -> VarF a j -> Bool Source #

(IEq1 f, IEq1 g) => IEq1 (f :+: g :: (i -> Type) -> i -> Type) Source # 
Instance details

Defined in Data.Expression.Utils.Indexed.Sum

Methods

ieq1 :: IEq a => (f :+: g) a j -> (f :+: g) a j -> Bool Source #