hakaru-0.7.0: A probabilistic programming language
CopyrightCopyright (c) 2016 the Hakaru team
LicenseBSD3
Maintainerwren@community.haskell.org
Stabilityexperimental
PortabilityGHC-only
Safe HaskellNone
LanguageHaskell2010

Language.Hakaru.Syntax.IClasses

Description

A collection of classes generalizing standard classes in order to support indexed types.

TODO: DeriveDataTypeable for all our newtypes?

Synopsis

Showing indexed types

class Show1 (a :: k -> *) where Source #

Uniform variant of Show for k-indexed types. This differs from transformers:Show1 in being polykinded, like it ought to be.

Alas, I don't think there's any way to derive instances the way we can derive for Show.

Minimal complete definition

showsPrec1 | show1

Methods

showsPrec1 :: Int -> a i -> ShowS Source #

show1 :: a i -> String Source #

Instances

Instances details
Show1 Value Source # 
Instance details

Defined in Language.Hakaru.Syntax.Value

Methods

showsPrec1 :: forall (i :: k). Int -> Value i -> ShowS Source #

show1 :: forall (i :: k). Value i -> String Source #

Show1 Literal Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

showsPrec1 :: forall (i :: k). Int -> Literal i -> ShowS Source #

show1 :: forall (i :: k). Literal i -> String Source #

Show1 (Sing :: Symbol -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

showsPrec1 :: forall (i :: k). Int -> Sing i -> ShowS Source #

show1 :: forall (i :: k). Sing i -> String Source #

Show1 (Sing :: k -> Type) => Show1 (Variable :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Variable

Methods

showsPrec1 :: forall (i :: k0). Int -> Variable i -> ShowS Source #

show1 :: forall (i :: k0). Variable i -> String Source #

Show1 (Sing :: HakaruCon -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

showsPrec1 :: forall (i :: k). Int -> Sing i -> ShowS Source #

show1 :: forall (i :: k). Sing i -> String Source #

Show1 (Sing :: HakaruFun -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

showsPrec1 :: forall (i :: k). Int -> Sing i -> ShowS Source #

show1 :: forall (i :: k). Sing i -> String Source #

Show1 (Sing :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

showsPrec1 :: forall (i :: k). Int -> Sing i -> ShowS Source #

show1 :: forall (i :: k). Sing i -> String Source #

Show1 (Pattern vars :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> Pattern vars i -> ShowS Source #

show1 :: forall (i :: k). Pattern vars i -> String Source #

Show1 ast => Show1 (Datum ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> Datum ast i -> ShowS Source #

show1 :: forall (i :: k). Datum ast i -> String Source #

Show2 abt => Show1 (LC_ abt :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

showsPrec1 :: forall (i :: k). Int -> LC_ abt i -> ShowS Source #

show1 :: forall (i :: k). LC_ abt i -> String Source #

Show2 abt => Show1 (Term abt :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

showsPrec1 :: forall (i :: k). Int -> Term abt i -> ShowS Source #

show1 :: forall (i :: k). Term abt i -> String Source #

Show1 (Sing :: Untyped -> Type) Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

showsPrec1 :: forall (i :: k). Int -> Sing i -> ShowS Source #

show1 :: forall (i :: k). Sing i -> String Source #

Show a => Show1 (Lift1 a :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i :: k0). Int -> Lift1 a i -> ShowS Source #

show1 :: forall (i :: k0). Lift1 a i -> String Source #

Show2 abt => Show1 (Branch a abt :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> Branch a abt i -> ShowS Source #

show1 :: forall (i :: k). Branch a abt i -> String Source #

Show1 (PDatumFun x vars :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> PDatumFun x vars i -> ShowS Source #

show1 :: forall (i :: k). PDatumFun x vars i -> String Source #

Show1 (PDatumStruct xs vars :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> PDatumStruct xs vars i -> ShowS Source #

show1 :: forall (i :: k). PDatumStruct xs vars i -> String Source #

Show1 (PDatumCode xss vars :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> PDatumCode xss vars i -> ShowS Source #

show1 :: forall (i :: k). PDatumCode xss vars i -> String Source #

Show1 ast => Show1 (DatumFun x ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> DatumFun x ast i -> ShowS Source #

show1 :: forall (i :: k). DatumFun x ast i -> String Source #

Show1 ast => Show1 (DatumStruct xs ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> DatumStruct xs ast i -> ShowS Source #

show1 :: forall (i :: k). DatumStruct xs ast i -> String Source #

Show1 ast => Show1 (DatumCode xss ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec1 :: forall (i :: k). Int -> DatumCode xss ast i -> ShowS Source #

show1 :: forall (i :: k). DatumCode xss ast i -> String Source #

(Show1 ast, Show2 abt) => Show1 (MatchResult ast abt :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.DatumCase

Methods

showsPrec1 :: forall (i :: k). Int -> MatchResult ast abt i -> ShowS Source #

show1 :: forall (i :: k). MatchResult ast abt i -> String Source #

(Show1 a, Show1 b) => Show1 (Pair1 a b :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i :: k0). Int -> Pair1 a b i -> ShowS Source #

show1 :: forall (i :: k0). Pair1 a b i -> String Source #

(Show1 (Sing :: k -> Type), Show1 (syn (MemoizedABT syn))) => Show1 (MemoizedABT syn xs :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

showsPrec1 :: forall (i :: k0). Int -> MemoizedABT syn xs i -> ShowS Source #

show1 :: forall (i :: k0). MemoizedABT syn xs i -> String Source #

(Show1 (Sing :: k -> Type), Show1 (syn (TrivialABT syn))) => Show1 (TrivialABT syn xs :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

showsPrec1 :: forall (i :: k0). Int -> TrivialABT syn xs i -> ShowS Source #

show1 :: forall (i :: k0). TrivialABT syn xs i -> String Source #

(Show1 (Sing :: k -> Type), Show1 rec) => Show1 (View rec xs :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

showsPrec1 :: forall (i :: k0). Int -> View rec xs i -> ShowS Source #

show1 :: forall (i :: k0). View rec xs i -> String Source #

Show a => Show1 (Lift2 a i :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i0 :: k0). Int -> Lift2 a i i0 -> ShowS Source #

show1 :: forall (i0 :: k0). Lift2 a i i0 -> String Source #

(Show1 (Sing :: k -> Type), Show1 (syn (MetaABT meta syn)), Show meta) => Show1 (MetaABT meta syn xs :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

showsPrec1 :: forall (i :: k0). Int -> MetaABT meta syn xs i -> ShowS Source #

show1 :: forall (i :: k0). MetaABT meta syn xs i -> String Source #

(Show2 a, Show2 b) => Show1 (Pair2 a b i :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i0 :: k0). Int -> Pair2 a b i i0 -> ShowS Source #

show1 :: forall (i0 :: k0). Pair2 a b i i0 -> String Source #

Show1 (Sing :: [[HakaruFun]] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

showsPrec1 :: forall (i :: k). Int -> Sing i -> ShowS Source #

show1 :: forall (i :: k). Sing i -> String Source #

Show2 abt => Show1 (SArgs abt :: [([Hakaru], Hakaru)] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.SArgs

Methods

showsPrec1 :: forall (i :: k). Int -> SArgs abt i -> ShowS Source #

show1 :: forall (i :: k). SArgs abt i -> String Source #

Show1 (Sing :: [HakaruFun] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

showsPrec1 :: forall (i :: k). Int -> Sing i -> ShowS Source #

show1 :: forall (i :: k). Sing i -> String Source #

Show1 a => Show1 (List1 a :: [k] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i :: k0). Int -> List1 a i -> ShowS Source #

show1 :: forall (i :: k0). List1 a i -> String Source #

shows1 :: Show1 a => a i -> ShowS Source #

showList1 :: Show1 a => [a i] -> ShowS Source #

class Show2 (a :: k1 -> k2 -> *) where Source #

Minimal complete definition

showsPrec2 | show2

Methods

showsPrec2 :: Int -> a i j -> ShowS Source #

show2 :: a i j -> String Source #

Instances

Instances details
Show a => Show2 (Lift2 a :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec2 :: forall (i :: k10) (j :: k20). Int -> Lift2 a i j -> ShowS Source #

show2 :: forall (i :: k10) (j :: k20). Lift2 a i j -> String Source #

(Show2 a, Show2 b) => Show2 (Pair2 a b :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec2 :: forall (i :: k10) (j :: k20). Int -> Pair2 a b i j -> ShowS Source #

show2 :: forall (i :: k10) (j :: k20). Pair2 a b i j -> String Source #

Show2 Pattern Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec2 :: forall (i :: k1) (j :: k2). Int -> Pattern i j -> ShowS Source #

show2 :: forall (i :: k1) (j :: k2). Pattern i j -> String Source #

Show2 (PDatumFun x :: [Hakaru] -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec2 :: forall (i :: k1) (j :: k2). Int -> PDatumFun x i j -> ShowS Source #

show2 :: forall (i :: k1) (j :: k2). PDatumFun x i j -> String Source #

Show2 (PDatumStruct xs :: [Hakaru] -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec2 :: forall (i :: k1) (j :: k2). Int -> PDatumStruct xs i j -> ShowS Source #

show2 :: forall (i :: k1) (j :: k2). PDatumStruct xs i j -> String Source #

Show2 (PDatumCode xss :: [Hakaru] -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

showsPrec2 :: forall (i :: k1) (j :: k2). Int -> PDatumCode xss i j -> ShowS Source #

show2 :: forall (i :: k1) (j :: k2). PDatumCode xss i j -> String Source #

(Show1 (Sing :: k -> Type), Show1 (syn (MemoizedABT syn))) => Show2 (MemoizedABT syn :: [k] -> k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

showsPrec2 :: forall (i :: k1) (j :: k2). Int -> MemoizedABT syn i j -> ShowS Source #

show2 :: forall (i :: k1) (j :: k2). MemoizedABT syn i j -> String Source #

(Show1 (Sing :: k -> Type), Show1 (syn (TrivialABT syn))) => Show2 (TrivialABT syn :: [k] -> k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

showsPrec2 :: forall (i :: k1) (j :: k2). Int -> TrivialABT syn i j -> ShowS Source #

show2 :: forall (i :: k1) (j :: k2). TrivialABT syn i j -> String Source #

(Show1 (Sing :: k -> Type), Show1 rec) => Show2 (View rec :: [k] -> k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

showsPrec2 :: forall (i :: k1) (j :: k2). Int -> View rec i j -> ShowS Source #

show2 :: forall (i :: k1) (j :: k2). View rec i j -> String Source #

(Show1 (Sing :: k -> Type), Show1 (syn (MetaABT meta syn)), Show meta) => Show2 (MetaABT meta syn :: [k] -> k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

showsPrec2 :: forall (i :: k1) (j :: k2). Int -> MetaABT meta syn i j -> ShowS Source #

show2 :: forall (i :: k1) (j :: k2). MetaABT meta syn i j -> String Source #

shows2 :: Show2 a => a i j -> ShowS Source #

showList2 :: Show2 a => [a i j] -> ShowS Source #

Some more-generic helper functions for showing things

showListWith :: (a -> ShowS) -> [a] -> ShowS Source #

some helpers for implementing the instances

showParen_0 :: Show a => Int -> String -> a -> ShowS Source #

showParen_1 :: Show1 a => Int -> String -> a i -> ShowS Source #

showParen_2 :: Show2 a => Int -> String -> a i j -> ShowS Source #

showParen_01 :: (Show b, Show1 a) => Int -> String -> b -> a i -> ShowS Source #

showParen_02 :: (Show b, Show2 a) => Int -> String -> b -> a i j -> ShowS Source #

showParen_11 :: (Show1 a, Show1 b) => Int -> String -> a i -> b j -> ShowS Source #

showParen_12 :: (Show1 a, Show2 b) => Int -> String -> a i -> b j l -> ShowS Source #

showParen_22 :: (Show2 a, Show2 b) => Int -> String -> a i1 j1 -> b i2 j2 -> ShowS Source #

showParen_010 :: (Show a, Show1 b, Show c) => Int -> String -> a -> b i -> c -> ShowS Source #

showParen_011 :: (Show a, Show1 b, Show1 c) => Int -> String -> a -> b i -> c j -> ShowS Source #

showParen_111 :: (Show1 a, Show1 b, Show1 c) => Int -> String -> a i -> b j -> c k -> ShowS Source #

Equality

class Eq1 (a :: k -> *) where Source #

Uniform variant of Eq for homogeneous k-indexed types. N.B., we keep this separate from the JmEq1 class because for some types we may be able to decide eq1 while not being able to decide jmEq1 (e.g., if using phantom types rather than GADTs). N.B., this function returns value/term equality! That is, the following four laws must hold relating the Eq1 class to the Eq class:

  1. if eq1 x y == True, then x and y have the same type index and (x == y) == True
  2. if eq1 x y == False where x and y have the same type index, then (x == y) == False
  3. if (x == y) == True, then eq1 x y == True
  4. if (x == y) == False, then eq1 x y == False

Alas, I don't think there's any way to derive instances the way we can derive for Eq.

Methods

eq1 :: a i -> a i -> Bool Source #

Instances

Instances details
Eq1 HContinuous Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

eq1 :: forall (i :: k). HContinuous i -> HContinuous i -> Bool Source #

Eq1 HDiscrete Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

eq1 :: forall (i :: k). HDiscrete i -> HDiscrete i -> Bool Source #

Eq1 HIntegrable Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

eq1 :: forall (i :: k). HIntegrable i -> HIntegrable i -> Bool Source #

Eq1 HRadical Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

eq1 :: forall (i :: k). HRadical i -> HRadical i -> Bool Source #

Eq1 HFractional Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

eq1 :: forall (i :: k). HFractional i -> HFractional i -> Bool Source #

Eq1 HRing Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

eq1 :: forall (i :: k). HRing i -> HRing i -> Bool Source #

Eq1 HSemiring Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

eq1 :: forall (i :: k). HSemiring i -> HSemiring i -> Bool Source #

Eq1 Value Source # 
Instance details

Defined in Language.Hakaru.Syntax.Value

Methods

eq1 :: forall (i :: k). Value i -> Value i -> Bool Source #

Eq1 NaryOp Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

eq1 :: forall (i :: k). NaryOp i -> NaryOp i -> Bool Source #

Eq1 Literal Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

eq1 :: forall (i :: k). Literal i -> Literal i -> Bool Source #

Eq1 (Sing :: Symbol -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

eq1 :: forall (i :: k). Sing i -> Sing i -> Bool Source #

Eq1 (Variable :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Variable

Methods

eq1 :: forall (i :: k0). Variable i -> Variable i -> Bool Source #

Eq1 (Sing :: HakaruCon -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

eq1 :: forall (i :: k). Sing i -> Sing i -> Bool Source #

Eq1 (Sing :: HakaruFun -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

eq1 :: forall (i :: k). Sing i -> Sing i -> Bool Source #

Eq1 (Sing :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

eq1 :: forall (i :: k). Sing i -> Sing i -> Bool Source #

Eq1 (Coercion a :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Coercion

Methods

eq1 :: forall (i :: k). Coercion a i -> Coercion a i -> Bool Source #

Eq1 (PrimCoercion a :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Coercion

Methods

eq1 :: forall (i :: k). PrimCoercion a i -> PrimCoercion a i -> Bool Source #

Eq1 (Pattern vars :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). Pattern vars i -> Pattern vars i -> Bool Source #

Eq1 ast => Eq1 (Datum ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). Datum ast i -> Datum ast i -> Bool Source #

(ABT Term abt, JmEq2 abt) => Eq1 (Term abt :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST.Eq

Methods

eq1 :: forall (i :: k). Term abt i -> Term abt i -> Bool Source #

Eq1 (MeasureOp typs :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

eq1 :: forall (i :: k). MeasureOp typs i -> MeasureOp typs i -> Bool Source #

Eq1 (ArrayOp args :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

eq1 :: forall (i :: k). ArrayOp args i -> ArrayOp args i -> Bool Source #

Eq1 (PrimOp args :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

eq1 :: forall (i :: k). PrimOp args i -> PrimOp args i -> Bool Source #

Eq1 (Sing :: Untyped -> Type) Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

eq1 :: forall (i :: k). Sing i -> Sing i -> Bool Source #

Eq a => Eq1 (Lift1 a :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

eq1 :: forall (i :: k0). Lift1 a i -> Lift1 a i -> Bool Source #

Eq2 abt => Eq1 (Reducer abt xs :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Reducer

Methods

eq1 :: forall (i :: k). Reducer abt xs i -> Reducer abt xs i -> Bool Source #

Eq2 abt => Eq1 (Branch a abt :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). Branch a abt i -> Branch a abt i -> Bool Source #

Eq1 (PDatumFun x vars :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). PDatumFun x vars i -> PDatumFun x vars i -> Bool Source #

Eq1 (PDatumStruct xs vars :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). PDatumStruct xs vars i -> PDatumStruct xs vars i -> Bool Source #

Eq1 (PDatumCode xss vars :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). PDatumCode xss vars i -> PDatumCode xss vars i -> Bool Source #

Eq1 ast => Eq1 (DatumFun x ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). DatumFun x ast i -> DatumFun x ast i -> Bool Source #

Eq1 ast => Eq1 (DatumStruct xs ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). DatumStruct xs ast i -> DatumStruct xs ast i -> Bool Source #

Eq1 ast => Eq1 (DatumCode xss ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq1 :: forall (i :: k). DatumCode xss ast i -> DatumCode xss ast i -> Bool Source #

(Show1 (Sing :: k -> Type), JmEq1 (Sing :: k -> Type), Foldable21 syn, JmEq1 (syn (TrivialABT syn))) => Eq1 (TrivialABT syn xs :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST.Eq

Methods

eq1 :: forall (i :: k0). TrivialABT syn xs i -> TrivialABT syn xs i -> Bool Source #

Eq a => Eq1 (Lift2 a i :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

eq1 :: forall (i0 :: k0). Lift2 a i i0 -> Lift2 a i i0 -> Bool Source #

Eq1 (Sing :: [[HakaruFun]] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

eq1 :: forall (i :: k). Sing i -> Sing i -> Bool Source #

Eq2 abt => Eq1 (SArgs abt :: [([Hakaru], Hakaru)] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.SArgs

Methods

eq1 :: forall (i :: k). SArgs abt i -> SArgs abt i -> Bool Source #

Eq1 (Sing :: [HakaruFun] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

eq1 :: forall (i :: k). Sing i -> Sing i -> Bool Source #

Eq1 a => Eq1 (List1 a :: [k] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

eq1 :: forall (i :: k0). List1 a i -> List1 a i -> Bool Source #

class Eq2 (a :: k1 -> k2 -> *) where Source #

Methods

eq2 :: a i j -> a i j -> Bool Source #

Instances

Instances details
Eq2 Coercion Source # 
Instance details

Defined in Language.Hakaru.Types.Coercion

Methods

eq2 :: forall (i :: k1) (j :: k2). Coercion i j -> Coercion i j -> Bool Source #

Eq2 PrimCoercion Source # 
Instance details

Defined in Language.Hakaru.Types.Coercion

Methods

eq2 :: forall (i :: k1) (j :: k2). PrimCoercion i j -> PrimCoercion i j -> Bool Source #

Eq a => Eq2 (Lift2 a :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

eq2 :: forall (i :: k10) (j :: k20). Lift2 a i j -> Lift2 a i j -> Bool Source #

Eq2 Pattern Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq2 :: forall (i :: k1) (j :: k2). Pattern i j -> Pattern i j -> Bool Source #

Eq2 MeasureOp Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

eq2 :: forall (i :: k1) (j :: k2). MeasureOp i j -> MeasureOp i j -> Bool Source #

Eq2 ArrayOp Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

eq2 :: forall (i :: k1) (j :: k2). ArrayOp i j -> ArrayOp i j -> Bool Source #

Eq2 PrimOp Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

eq2 :: forall (i :: k1) (j :: k2). PrimOp i j -> PrimOp i j -> Bool Source #

Eq2 (PDatumFun x :: [Hakaru] -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq2 :: forall (i :: k1) (j :: k2). PDatumFun x i j -> PDatumFun x i j -> Bool Source #

Eq2 (PDatumStruct xs :: [Hakaru] -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq2 :: forall (i :: k1) (j :: k2). PDatumStruct xs i j -> PDatumStruct xs i j -> Bool Source #

Eq2 (PDatumCode xss :: [Hakaru] -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

eq2 :: forall (i :: k1) (j :: k2). PDatumCode xss i j -> PDatumCode xss i j -> Bool Source #

(Show1 (Sing :: k -> Type), JmEq1 (Sing :: k -> Type), Foldable21 syn, JmEq1 (syn (TrivialABT syn))) => Eq2 (TrivialABT syn :: [k] -> k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST.Eq

Methods

eq2 :: forall (i :: k1) (j :: k2). TrivialABT syn i j -> TrivialABT syn i j -> Bool Source #

data TypeEq :: k -> k -> * where Source #

Concrete proofs of type equality. In order to make use of a proof p :: TypeEq a b, you must pattern-match on the Refl constructor in order to show GHC that the types a and b are equal.

Constructors

Refl :: TypeEq a a 

Instances

Instances details
Category (TypeEq :: k -> k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

id :: forall (a :: k0). TypeEq a a #

(.) :: forall (b :: k0) (c :: k0) (a :: k0). TypeEq b c -> TypeEq a b -> TypeEq a c #

symmetry :: TypeEq a b -> TypeEq b a Source #

Type equality is symmetric.

transitivity :: TypeEq a b -> TypeEq b c -> TypeEq a c Source #

Type equality is transitive. N.B., this is has a more general type than (.)

congruence :: TypeEq a b -> TypeEq (f a) (f b) Source #

Type constructors are extensional.

class Eq1 a => JmEq1 (a :: k -> *) where Source #

Uniform variant of Eq for heterogeneous k-indexed types. N.B., this function returns value/term equality! That is, the following four laws must hold relating the JmEq1 class to the Eq1 class:

  1. if jmEq1 x y == Just Refl, then x and y have the same type index and eq1 x y == True
  2. if jmEq1 x y == Nothing where x and y have the same type index, then eq1 x y == False
  3. if eq1 x y == True, then jmEq1 x y == Just Refl
  4. if eq1 x y == False, then jmEq1 x y == Nothing

Alas, I don't think there's any way to derive instances the way we can derive for Eq.

Methods

jmEq1 :: a i -> a j -> Maybe (TypeEq i j) Source #

Instances

Instances details
JmEq1 HContinuous Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

jmEq1 :: forall (i :: k) (j :: k). HContinuous i -> HContinuous j -> Maybe (TypeEq i j) Source #

JmEq1 HDiscrete Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

jmEq1 :: forall (i :: k) (j :: k). HDiscrete i -> HDiscrete j -> Maybe (TypeEq i j) Source #

JmEq1 HIntegrable Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

jmEq1 :: forall (i :: k) (j :: k). HIntegrable i -> HIntegrable j -> Maybe (TypeEq i j) Source #

JmEq1 HRadical Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

jmEq1 :: forall (i :: k) (j :: k). HRadical i -> HRadical j -> Maybe (TypeEq i j) Source #

JmEq1 HFractional Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

jmEq1 :: forall (i :: k) (j :: k). HFractional i -> HFractional j -> Maybe (TypeEq i j) Source #

JmEq1 HRing Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

jmEq1 :: forall (i :: k) (j :: k). HRing i -> HRing j -> Maybe (TypeEq i j) Source #

JmEq1 HSemiring Source # 
Instance details

Defined in Language.Hakaru.Types.HClasses

Methods

jmEq1 :: forall (i :: k) (j :: k). HSemiring i -> HSemiring j -> Maybe (TypeEq i j) Source #

JmEq1 NaryOp Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

jmEq1 :: forall (i :: k) (j :: k). NaryOp i -> NaryOp j -> Maybe (TypeEq i j) Source #

JmEq1 Literal Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

jmEq1 :: forall (i :: k) (j :: k). Literal i -> Literal j -> Maybe (TypeEq i j) Source #

JmEq1 (Sing :: Symbol -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

jmEq1 :: forall (i :: k) (j :: k). Sing i -> Sing j -> Maybe (TypeEq i j) Source #

JmEq1 (Sing :: HakaruCon -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

jmEq1 :: forall (i :: k) (j :: k). Sing i -> Sing j -> Maybe (TypeEq i j) Source #

JmEq1 (Sing :: HakaruFun -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

jmEq1 :: forall (i :: k) (j :: k). Sing i -> Sing j -> Maybe (TypeEq i j) Source #

JmEq1 (Sing :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

jmEq1 :: forall (i :: k) (j :: k). Sing i -> Sing j -> Maybe (TypeEq i j) Source #

JmEq1 (PrimCoercion a :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Coercion

Methods

jmEq1 :: forall (i :: k) (j :: k). PrimCoercion a i -> PrimCoercion a j -> Maybe (TypeEq i j) Source #

Eq1 ast => JmEq1 (Datum ast :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

jmEq1 :: forall (i :: k) (j :: k). Datum ast i -> Datum ast j -> Maybe (TypeEq i j) Source #

(ABT Term abt, JmEq2 abt) => JmEq1 (Term abt :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST.Eq

Methods

jmEq1 :: forall (i :: k) (j :: k). Term abt i -> Term abt j -> Maybe (TypeEq i j) Source #

JmEq1 (Sing :: Untyped -> Type) Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

jmEq1 :: forall (i :: k) (j :: k). Sing i -> Sing j -> Maybe (TypeEq i j) Source #

JmEq2 abt => JmEq1 (Reducer abt xs :: Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Reducer

Methods

jmEq1 :: forall (i :: k) (j :: k). Reducer abt xs i -> Reducer abt xs j -> Maybe (TypeEq i j) Source #

(Show1 (Sing :: k -> Type), JmEq1 (Sing :: k -> Type), JmEq1 (syn (TrivialABT syn)), Foldable21 syn) => JmEq1 (TrivialABT syn xs :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST.Eq

Methods

jmEq1 :: forall (i :: k0) (j :: k0). TrivialABT syn xs i -> TrivialABT syn xs j -> Maybe (TypeEq i j) Source #

JmEq1 (Sing :: [[HakaruFun]] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

jmEq1 :: forall (i :: k) (j :: k). Sing i -> Sing j -> Maybe (TypeEq i j) Source #

JmEq2 abt => JmEq1 (SArgs abt :: [([Hakaru], Hakaru)] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST.Eq

Methods

jmEq1 :: forall (i :: k) (j :: k). SArgs abt i -> SArgs abt j -> Maybe (TypeEq i j) Source #

JmEq1 (Sing :: [HakaruFun] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Types.Sing

Methods

jmEq1 :: forall (i :: k) (j :: k). Sing i -> Sing j -> Maybe (TypeEq i j) Source #

JmEq1 a => JmEq1 (List1 a :: [k] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

jmEq1 :: forall (i :: k0) (j :: k0). List1 a i -> List1 a j -> Maybe (TypeEq i j) Source #

class Eq2 a => JmEq2 (a :: k1 -> k2 -> *) where Source #

Methods

jmEq2 :: a i1 j1 -> a i2 j2 -> Maybe (TypeEq i1 i2, TypeEq j1 j2) Source #

Instances

Instances details
JmEq2 PrimCoercion Source # 
Instance details

Defined in Language.Hakaru.Types.Coercion

Methods

jmEq2 :: forall (i1 :: k1) (j1 :: k2) (i2 :: k1) (j2 :: k2). PrimCoercion i1 j1 -> PrimCoercion i2 j2 -> Maybe (TypeEq i1 i2, TypeEq j1 j2) Source #

JmEq2 MeasureOp Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

jmEq2 :: forall (i1 :: k1) (j1 :: k2) (i2 :: k1) (j2 :: k2). MeasureOp i1 j1 -> MeasureOp i2 j2 -> Maybe (TypeEq i1 i2, TypeEq j1 j2) Source #

JmEq2 ArrayOp Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

jmEq2 :: forall (i1 :: k1) (j1 :: k2) (i2 :: k1) (j2 :: k2). ArrayOp i1 j1 -> ArrayOp i2 j2 -> Maybe (TypeEq i1 i2, TypeEq j1 j2) Source #

JmEq2 PrimOp Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

jmEq2 :: forall (i1 :: k1) (j1 :: k2) (i2 :: k1) (j2 :: k2). PrimOp i1 j1 -> PrimOp i2 j2 -> Maybe (TypeEq i1 i2, TypeEq j1 j2) Source #

(Show1 (Sing :: k -> Type), JmEq1 (Sing :: k -> Type), JmEq1 (syn (TrivialABT syn)), Foldable21 syn) => JmEq2 (TrivialABT syn :: [k] -> k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST.Eq

Methods

jmEq2 :: forall (i1 :: k1) (j1 :: k2) (i2 :: k1) (j2 :: k2). TrivialABT syn i1 j1 -> TrivialABT syn i2 j2 -> Maybe (TypeEq i1 i2, TypeEq j1 j2) Source #

Generalized abstract nonsense

class Functor11 (f :: (k1 -> *) -> k2 -> *) where Source #

A functor on the category of k-indexed types (i.e., from k-indexed types to k-indexed types). We unify the two indices, because that seems the most helpful for what we're doing; we could, of course, offer a different variant that maps k1-indexed types to k2-indexed types...

Alas, I don't think there's any way to derive instances the way we can derive for Functor.

Methods

fmap11 :: (forall i. a i -> b i) -> f a j -> f b j Source #

Instances

Instances details
Functor11 Datum Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fmap11 :: forall a b (j :: k2). (forall (i :: k1). a i -> b i) -> Datum a j -> Datum b j Source #

Functor11 (DatumFun x :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fmap11 :: forall a b (j :: k2). (forall (i :: k1). a i -> b i) -> DatumFun x a j -> DatumFun x b j Source #

Functor11 (DatumStruct xs :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fmap11 :: forall a b (j :: k2). (forall (i :: k1). a i -> b i) -> DatumStruct xs a j -> DatumStruct xs b j Source #

Functor11 (DatumCode xss :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fmap11 :: forall a b (j :: k2). (forall (i :: k1). a i -> b i) -> DatumCode xss a j -> DatumCode xss b j Source #

Functor11 (List1 :: (k1 -> Type) -> [k1] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

fmap11 :: forall a b (j :: k2). (forall (i :: k10). a i -> b i) -> List1 a j -> List1 b j Source #

newtype Fix11 (f :: (k -> *) -> k -> *) (i :: k) Source #

Constructors

Fix11 

Fields

cata11 :: forall f a j. Functor11 f => (forall i. f a i -> a i) -> Fix11 f j -> a j Source #

ana11 :: forall f a j. Functor11 f => (forall i. a i -> f a i) -> a j -> Fix11 f j Source #

hylo11 :: forall f a b j. Functor11 f => (forall i. a i -> f a i) -> (forall i. f b i -> b i) -> a j -> b j Source #

class Functor12 (f :: (k1 -> *) -> k2 -> k3 -> *) where Source #

Methods

fmap12 :: (forall i. a i -> b i) -> f a j l -> f b j l Source #

Instances

Instances details
Functor12 (View :: (k3 -> Type) -> [k3] -> k3 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

fmap12 :: forall a b (j :: k2) (l :: k30). (forall (i :: k1). a i -> b i) -> View a j l -> View b j l Source #

class Functor21 (f :: (k1 -> k2 -> *) -> k3 -> *) where Source #

A functor from (k1,k2)-indexed types to k3-indexed types.

Methods

fmap21 :: (forall h i. a h i -> b h i) -> f a j -> f b j Source #

Instances

Instances details
Functor21 Term Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

fmap21 :: forall a b (j :: k3). (forall (h :: k1) (i :: k2). a h i -> b h i) -> Term a j -> Term b j Source #

Functor21 Head Source # 
Instance details

Defined in Language.Hakaru.Evaluation.Types

Methods

fmap21 :: forall a b (j :: k3). (forall (h :: k1) (i :: k2). a h i -> b h i) -> Head a j -> Head b j Source #

Functor21 Term Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

fmap21 :: forall a b (j :: k3). (forall (h :: k1) (i :: k2). a h i -> b h i) -> Term a j -> Term b j Source #

Functor21 (Branch a :: ([Hakaru] -> Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fmap21 :: forall a0 b (j :: k3). (forall (h :: k1) (i :: k2). a0 h i -> b h i) -> Branch a a0 j -> Branch a b j Source #

Functor21 (Reducer xs :: ([Untyped] -> Untyped -> Type) -> Untyped -> Type) Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

fmap21 :: forall a b (j :: k3). (forall (h :: k1) (i :: k2). a h i -> b h i) -> Reducer xs a j -> Reducer xs b j Source #

Functor21 SArgs Source # 
Instance details

Defined in Language.Hakaru.Syntax.SArgs

Methods

fmap21 :: forall a b (j :: k3). (forall (h :: k1) (i :: k2). a h i -> b h i) -> SArgs a j -> SArgs b j Source #

Functor21 (SArgs :: ([Untyped] -> Untyped -> Type) -> [([k], k)] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

fmap21 :: forall a b (j :: k3). (forall (h :: k1) (i :: k2). a h i -> b h i) -> SArgs a j -> SArgs b j Source #

class Functor22 (f :: (k1 -> k2 -> *) -> k3 -> k4 -> *) where Source #

A functor from (k1,k2)-indexed types to (k3,k4)-indexed types.

Methods

fmap22 :: (forall h i. a h i -> b h i) -> f a j l -> f b j l Source #

Instances

Instances details
Functor22 Reducer Source # 
Instance details

Defined in Language.Hakaru.Syntax.Reducer

Methods

fmap22 :: forall a b (j :: k3) (l :: k4). (forall (h :: k1) (i :: k2). a h i -> b h i) -> Reducer a j l -> Reducer b j l Source #

class Functor11 f => Foldable11 (f :: (k1 -> *) -> k2 -> *) where Source #

A foldable functor on the category of k-indexed types.

Alas, I don't think there's any way to derive instances the way we can derive for Foldable.

Minimal complete definition

fold11 | foldMap11

Methods

fold11 :: Monoid m => f (Lift1 m) i -> m Source #

foldMap11 :: Monoid m => (forall i. a i -> m) -> f a j -> m Source #

Instances

Instances details
Foldable11 Datum Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fold11 :: forall m (i :: k2). Monoid m => Datum (Lift1 m) i -> m Source #

foldMap11 :: forall m a (j :: k2). Monoid m => (forall (i :: k1). a i -> m) -> Datum a j -> m Source #

Foldable11 (DatumFun x :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fold11 :: forall m (i :: k2). Monoid m => DatumFun x (Lift1 m) i -> m Source #

foldMap11 :: forall m a (j :: k2). Monoid m => (forall (i :: k1). a i -> m) -> DatumFun x a j -> m Source #

Foldable11 (DatumStruct xs :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fold11 :: forall m (i :: k2). Monoid m => DatumStruct xs (Lift1 m) i -> m Source #

foldMap11 :: forall m a (j :: k2). Monoid m => (forall (i :: k1). a i -> m) -> DatumStruct xs a j -> m Source #

Foldable11 (DatumCode xss :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fold11 :: forall m (i :: k2). Monoid m => DatumCode xss (Lift1 m) i -> m Source #

foldMap11 :: forall m a (j :: k2). Monoid m => (forall (i :: k1). a i -> m) -> DatumCode xss a j -> m Source #

Foldable11 (List1 :: (k1 -> Type) -> [k1] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

fold11 :: forall m (i :: k2). Monoid m => List1 (Lift1 m) i -> m Source #

foldMap11 :: forall m a (j :: k2). Monoid m => (forall (i :: k10). a i -> m) -> List1 a j -> m Source #

newtype Lift1 (a :: *) (i :: k) Source #

Any unindexed type can be lifted to be (trivially) k-indexed.

Constructors

Lift1 

Fields

Instances

Instances details
Eq a => Eq1 (Lift1 a :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

eq1 :: forall (i :: k0). Lift1 a i -> Lift1 a i -> Bool Source #

Show a => Show1 (Lift1 a :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i :: k0). Int -> Lift1 a i -> ShowS Source #

show1 :: forall (i :: k0). Lift1 a i -> String Source #

Eq a => Eq (Lift1 a i) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

(==) :: Lift1 a i -> Lift1 a i -> Bool #

(/=) :: Lift1 a i -> Lift1 a i -> Bool #

Ord a => Ord (Lift1 a i) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

compare :: Lift1 a i -> Lift1 a i -> Ordering #

(<) :: Lift1 a i -> Lift1 a i -> Bool #

(<=) :: Lift1 a i -> Lift1 a i -> Bool #

(>) :: Lift1 a i -> Lift1 a i -> Bool #

(>=) :: Lift1 a i -> Lift1 a i -> Bool #

max :: Lift1 a i -> Lift1 a i -> Lift1 a i #

min :: Lift1 a i -> Lift1 a i -> Lift1 a i #

Read a => Read (Lift1 a i) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Show a => Show (Lift1 a i) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec :: Int -> Lift1 a i -> ShowS #

show :: Lift1 a i -> String #

showList :: [Lift1 a i] -> ShowS #

class Functor12 f => Foldable12 (f :: (k1 -> *) -> k2 -> k3 -> *) where Source #

Minimal complete definition

fold12 | foldMap12

Methods

fold12 :: Monoid m => f (Lift1 m) j l -> m Source #

foldMap12 :: Monoid m => (forall i. a i -> m) -> f a j l -> m Source #

Instances

Instances details
Foldable12 (View :: (k3 -> Type) -> [k3] -> k3 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

fold12 :: forall m (j :: k2) (l :: k30). Monoid m => View (Lift1 m) j l -> m Source #

foldMap12 :: forall m a (j :: k2) (l :: k30). Monoid m => (forall (i :: k1). a i -> m) -> View a j l -> m Source #

class Functor21 f => Foldable21 (f :: (k1 -> k2 -> *) -> k3 -> *) where Source #

Minimal complete definition

fold21 | foldMap21

Methods

fold21 :: Monoid m => f (Lift2 m) j -> m Source #

foldMap21 :: Monoid m => (forall h i. a h i -> m) -> f a j -> m Source #

Instances

Instances details
Foldable21 Term Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

fold21 :: forall m (j :: k3). Monoid m => Term (Lift2 m) j -> m Source #

foldMap21 :: forall m a (j :: k3). Monoid m => (forall (h :: k1) (i :: k2). a h i -> m) -> Term a j -> m Source #

Foldable21 Head Source # 
Instance details

Defined in Language.Hakaru.Evaluation.Types

Methods

fold21 :: forall m (j :: k3). Monoid m => Head (Lift2 m) j -> m Source #

foldMap21 :: forall m a (j :: k3). Monoid m => (forall (h :: k1) (i :: k2). a h i -> m) -> Head a j -> m Source #

Foldable21 Term Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

fold21 :: forall m (j :: k3). Monoid m => Term (Lift2 m) j -> m Source #

foldMap21 :: forall m a (j :: k3). Monoid m => (forall (h :: k1) (i :: k2). a h i -> m) -> Term a j -> m Source #

Foldable21 (Branch a :: ([Hakaru] -> Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

fold21 :: forall m (j :: k3). Monoid m => Branch a (Lift2 m) j -> m Source #

foldMap21 :: forall m a0 (j :: k3). Monoid m => (forall (h :: k1) (i :: k2). a0 h i -> m) -> Branch a a0 j -> m Source #

Foldable21 (Reducer xs :: ([Untyped] -> Untyped -> Type) -> Untyped -> Type) Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

fold21 :: forall m (j :: k3). Monoid m => Reducer xs (Lift2 m) j -> m Source #

foldMap21 :: forall m a (j :: k3). Monoid m => (forall (h :: k1) (i :: k2). a h i -> m) -> Reducer xs a j -> m Source #

Foldable21 SArgs Source # 
Instance details

Defined in Language.Hakaru.Syntax.SArgs

Methods

fold21 :: forall m (j :: k3). Monoid m => SArgs (Lift2 m) j -> m Source #

foldMap21 :: forall m a (j :: k3). Monoid m => (forall (h :: k1) (i :: k2). a h i -> m) -> SArgs a j -> m Source #

Foldable21 (SArgs :: ([Untyped] -> Untyped -> Type) -> [([k], k)] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Parser.AST

Methods

fold21 :: forall m (j :: k3). Monoid m => SArgs (Lift2 m) j -> m Source #

foldMap21 :: forall m a (j :: k3). Monoid m => (forall (h :: k1) (i :: k2). a h i -> m) -> SArgs a j -> m Source #

newtype Lift2 (a :: *) (i :: k1) (j :: k2) Source #

Any unindexed type can be lifted to be (trivially) (k1,k2)-indexed.

Constructors

Lift2 

Fields

Instances

Instances details
Eq a => Eq2 (Lift2 a :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

eq2 :: forall (i :: k10) (j :: k20). Lift2 a i j -> Lift2 a i j -> Bool Source #

Show a => Show2 (Lift2 a :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec2 :: forall (i :: k10) (j :: k20). Int -> Lift2 a i j -> ShowS Source #

show2 :: forall (i :: k10) (j :: k20). Lift2 a i j -> String Source #

Eq a => Eq1 (Lift2 a i :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

eq1 :: forall (i0 :: k0). Lift2 a i i0 -> Lift2 a i i0 -> Bool Source #

Show a => Show1 (Lift2 a i :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i0 :: k0). Int -> Lift2 a i i0 -> ShowS Source #

show1 :: forall (i0 :: k0). Lift2 a i i0 -> String Source #

Eq a => Eq (Lift2 a i j) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

(==) :: Lift2 a i j -> Lift2 a i j -> Bool #

(/=) :: Lift2 a i j -> Lift2 a i j -> Bool #

Ord a => Ord (Lift2 a i j) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

compare :: Lift2 a i j -> Lift2 a i j -> Ordering #

(<) :: Lift2 a i j -> Lift2 a i j -> Bool #

(<=) :: Lift2 a i j -> Lift2 a i j -> Bool #

(>) :: Lift2 a i j -> Lift2 a i j -> Bool #

(>=) :: Lift2 a i j -> Lift2 a i j -> Bool #

max :: Lift2 a i j -> Lift2 a i j -> Lift2 a i j #

min :: Lift2 a i j -> Lift2 a i j -> Lift2 a i j #

Read a => Read (Lift2 a i j) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

readsPrec :: Int -> ReadS (Lift2 a i j) #

readList :: ReadS [Lift2 a i j] #

readPrec :: ReadPrec (Lift2 a i j) #

readListPrec :: ReadPrec [Lift2 a i j] #

Show a => Show (Lift2 a i j) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec :: Int -> Lift2 a i j -> ShowS #

show :: Lift2 a i j -> String #

showList :: [Lift2 a i j] -> ShowS #

class Functor22 f => Foldable22 (f :: (k1 -> k2 -> *) -> k3 -> k4 -> *) where Source #

Minimal complete definition

fold22 | foldMap22

Methods

fold22 :: Monoid m => f (Lift2 m) j l -> m Source #

foldMap22 :: Monoid m => (forall h i. a h i -> m) -> f a j l -> m Source #

Instances

Instances details
Foldable22 Reducer Source # 
Instance details

Defined in Language.Hakaru.Syntax.Reducer

Methods

fold22 :: forall m (j :: k3) (l :: k4). Monoid m => Reducer (Lift2 m) j l -> m Source #

foldMap22 :: forall m a (j :: k3) (l :: k4). Monoid m => (forall (h :: k1) (i :: k2). a h i -> m) -> Reducer a j l -> m Source #

class Foldable11 t => Traversable11 (t :: (k1 -> *) -> k2 -> *) where Source #

Methods

traverse11 :: Applicative f => (forall i. a i -> f (b i)) -> t a j -> f (t b j) Source #

Instances

Instances details
Traversable11 Datum Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

traverse11 :: forall f a b (j :: k2). Applicative f => (forall (i :: k1). a i -> f (b i)) -> Datum a j -> f (Datum b j) Source #

Traversable11 (DatumFun x :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

traverse11 :: forall f a b (j :: k2). Applicative f => (forall (i :: k1). a i -> f (b i)) -> DatumFun x a j -> f (DatumFun x b j) Source #

Traversable11 (DatumStruct xs :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

traverse11 :: forall f a b (j :: k2). Applicative f => (forall (i :: k1). a i -> f (b i)) -> DatumStruct xs a j -> f (DatumStruct xs b j) Source #

Traversable11 (DatumCode xss :: (Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

traverse11 :: forall f a b (j :: k2). Applicative f => (forall (i :: k1). a i -> f (b i)) -> DatumCode xss a j -> f (DatumCode xss b j) Source #

Traversable11 (List1 :: (k1 -> Type) -> [k1] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

traverse11 :: forall f a b (j :: k2). Applicative f => (forall (i :: k10). a i -> f (b i)) -> List1 a j -> f (List1 b j) Source #

class Foldable12 t => Traversable12 (t :: (k1 -> *) -> k2 -> k3 -> *) where Source #

Methods

traverse12 :: Applicative f => (forall i. a i -> f (b i)) -> t a j l -> f (t b j l) Source #

Instances

Instances details
Traversable12 (View :: (k3 -> Type) -> [k3] -> k3 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.ABT

Methods

traverse12 :: forall f a b (j :: k2) (l :: k30). Applicative f => (forall (i :: k1). a i -> f (b i)) -> View a j l -> f (View b j l) Source #

class Foldable21 t => Traversable21 (t :: (k1 -> k2 -> *) -> k3 -> *) where Source #

Methods

traverse21 :: Applicative f => (forall h i. a h i -> f (b h i)) -> t a j -> f (t b j) Source #

Instances

Instances details
Traversable21 Term Source # 
Instance details

Defined in Language.Hakaru.Syntax.AST

Methods

traverse21 :: forall f a b (j :: k3). Applicative f => (forall (h :: k1) (i :: k2). a h i -> f (b h i)) -> Term a j -> f (Term b j) Source #

Traversable21 Head Source # 
Instance details

Defined in Language.Hakaru.Evaluation.Types

Methods

traverse21 :: forall f a b (j :: k3). Applicative f => (forall (h :: k1) (i :: k2). a h i -> f (b h i)) -> Head a j -> f (Head b j) Source #

Traversable21 (Branch a :: ([Hakaru] -> Hakaru -> Type) -> Hakaru -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Datum

Methods

traverse21 :: forall f a0 b (j :: k3). Applicative f => (forall (h :: k1) (i :: k2). a0 h i -> f (b h i)) -> Branch a a0 j -> f (Branch a b j) Source #

Traversable21 SArgs Source # 
Instance details

Defined in Language.Hakaru.Syntax.SArgs

Methods

traverse21 :: forall f a b (j :: k3). Applicative f => (forall (h :: k1) (i :: k2). a h i -> f (b h i)) -> SArgs a j -> f (SArgs b j) Source #

class Foldable22 t => Traversable22 (t :: (k1 -> k2 -> *) -> k3 -> k4 -> *) where Source #

Methods

traverse22 :: Applicative f => (forall h i. a h i -> f (b h i)) -> t a j l -> f (t b j l) Source #

Instances

Instances details
Traversable22 Reducer Source # 
Instance details

Defined in Language.Hakaru.Syntax.Reducer

Methods

traverse22 :: forall f a b (j :: k3) (l :: k4). Applicative f => (forall (h :: k1) (i :: k2). a h i -> f (b h i)) -> Reducer a j l -> f (Reducer b j l) Source #

Helper types

data Some1 (a :: k -> *) Source #

Existentially quantify over a single index. TODO: replace SomeVariable with (Some1 Variable)

Constructors

forall i. Some1 !(a i) 

Instances

Instances details
JmEq1 a => Eq (Some1 a) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

(==) :: Some1 a -> Some1 a -> Bool #

(/=) :: Some1 a -> Some1 a -> Bool #

Show1 a => Show (Some1 a) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec :: Int -> Some1 a -> ShowS #

show :: Some1 a -> String #

showList :: [Some1 a] -> ShowS #

data Some2 (a :: k1 -> k2 -> *) Source #

Existentially quantify over two indices.

Constructors

forall i j. Some2 !(a i j) 

Instances

Instances details
Eq (Some2 Transform) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Transform

JmEq2 a => Eq (Some2 a) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

(==) :: Some2 a -> Some2 a -> Bool #

(/=) :: Some2 a -> Some2 a -> Bool #

Read (Some2 Transform) Source # 
Instance details

Defined in Language.Hakaru.Syntax.Transform

Show2 a => Show (Some2 a) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec :: Int -> Some2 a -> ShowS #

show :: Some2 a -> String #

showList :: [Some2 a] -> ShowS #

data Pair1 (a :: k -> *) (b :: k -> *) (i :: k) Source #

A lazy pairing of identically k-indexed values.

Constructors

Pair1 (a i) (b i) 

Instances

Instances details
(Show1 a, Show1 b) => Show1 (Pair1 a b :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i :: k0). Int -> Pair1 a b i -> ShowS Source #

show1 :: forall (i :: k0). Pair1 a b i -> String Source #

(Show1 a, Show1 b) => Show (Pair1 a b i) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec :: Int -> Pair1 a b i -> ShowS #

show :: Pair1 a b i -> String #

showList :: [Pair1 a b i] -> ShowS #

fst1 :: Pair1 a b i -> a i Source #

snd1 :: Pair1 a b i -> b i Source #

data Pair2 (a :: k1 -> k2 -> *) (b :: k1 -> k2 -> *) (i :: k1) (j :: k2) Source #

A lazy pairing of identically (k1,k2)-indexed values.

Constructors

Pair2 (a i j) (b i j) 

Instances

Instances details
(Show2 a, Show2 b) => Show2 (Pair2 a b :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec2 :: forall (i :: k10) (j :: k20). Int -> Pair2 a b i j -> ShowS Source #

show2 :: forall (i :: k10) (j :: k20). Pair2 a b i j -> String Source #

(Show2 a, Show2 b) => Show1 (Pair2 a b i :: k -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i0 :: k0). Int -> Pair2 a b i i0 -> ShowS Source #

show1 :: forall (i0 :: k0). Pair2 a b i i0 -> String Source #

(Show2 a, Show2 b) => Show (Pair2 a b i j) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec :: Int -> Pair2 a b i j -> ShowS #

show :: Pair2 a b i j -> String #

showList :: [Pair2 a b i j] -> ShowS #

fst2 :: Pair2 a b i j -> a i j Source #

snd2 :: Pair2 a b i j -> b i j Source #

data Pointwise (f :: k0 -> *) (g :: k1 -> *) (x :: k0) (y :: k1) where Source #

Constructors

Pw :: f x -> g y -> Pointwise f g x y 

data PointwiseP (f :: k0 -> *) (g :: k1 -> *) (xy :: (k0, k1)) where Source #

Constructors

PwP :: f x -> g y -> PointwiseP f g '(x, y) 

List types

type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ... Source #

Equations

'[] ++ ys = ys 
(x ': xs) ++ ys = x ': (xs ++ ys) 

eqAppendIdentity :: proxy xs -> TypeEq xs (xs ++ '[]) Source #

The empty list is (also) a right-identity for (++). Because we define (++) by induction on the first argument, this identity doesn't come for free but rather must be proven.

eqAppendAssoc :: proxy1 xs -> proxy2 ys -> proxy3 zs -> TypeEq ((xs ++ ys) ++ zs) (xs ++ (ys ++ zs)) Source #

(++) is associative. This identity doesn't come for free but rather must be proven.

data List1 :: (k -> *) -> [k] -> * where Source #

A lazy list of k-indexed elements, itself indexed by the list of indices

Constructors

Nil1 :: List1 a '[] 
Cons1 :: a x -> List1 a xs -> List1 a (x ': xs) infixr 5 

Instances

Instances details
Traversable11 (List1 :: (k1 -> Type) -> [k1] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

traverse11 :: forall f a b (j :: k2). Applicative f => (forall (i :: k10). a i -> f (b i)) -> List1 a j -> f (List1 b j) Source #

Foldable11 (List1 :: (k1 -> Type) -> [k1] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

fold11 :: forall m (i :: k2). Monoid m => List1 (Lift1 m) i -> m Source #

foldMap11 :: forall m a (j :: k2). Monoid m => (forall (i :: k10). a i -> m) -> List1 a j -> m Source #

Functor11 (List1 :: (k1 -> Type) -> [k1] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

fmap11 :: forall a b (j :: k2). (forall (i :: k10). a i -> b i) -> List1 a j -> List1 b j Source #

JmEq1 a => JmEq1 (List1 a :: [k] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

jmEq1 :: forall (i :: k0) (j :: k0). List1 a i -> List1 a j -> Maybe (TypeEq i j) Source #

Eq1 a => Eq1 (List1 a :: [k] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

eq1 :: forall (i :: k0). List1 a i -> List1 a i -> Bool Source #

Show1 a => Show1 (List1 a :: [k] -> Type) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec1 :: forall (i :: k0). Int -> List1 a i -> ShowS Source #

show1 :: forall (i :: k0). List1 a i -> String Source #

Eq1 a => Eq (List1 a xs) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

(==) :: List1 a xs -> List1 a xs -> Bool #

(/=) :: List1 a xs -> List1 a xs -> Bool #

Show1 a => Show (List1 a xs) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

showsPrec :: Int -> List1 a xs -> ShowS #

show :: List1 a xs -> String #

showList :: [List1 a xs] -> ShowS #

append1 :: List1 a xs -> List1 a ys -> List1 a (xs ++ ys) Source #

data List2 :: (k0 -> k1 -> *) -> [k0] -> [k1] -> * where Source #

Lifting of relations pointwise to lists

Constructors

Nil2 :: List2 f '[] '[] 
Cons2 :: f x y -> List2 f xs ys -> List2 f (x ': xs) (y ': ys) 

newtype DList1 a xs Source #

A difference-list variant of List1.

Constructors

DList1 

Fields

toList1 :: DList1 a xs -> List1 a xs Source #

fromList1 :: List1 a xs -> DList1 a xs Source #

dnil1 :: DList1 a '[] Source #

dcons1 :: a x -> DList1 a xs -> DList1 a (x ': xs) Source #

dsnoc1 :: DList1 a xs -> a x -> DList1 a (xs ++ '[x]) Source #

dsingleton1 :: a x -> DList1 a '[x] Source #

dappend1 :: DList1 a xs -> DList1 a ys -> DList1 a (xs ++ ys) Source #

Constraints

class All (c :: k -> Constraint) (xs :: [k]) where Source #

Methods

allHolds :: List1 (Holds c) xs Source #

Instances

Instances details
All (c :: k -> Constraint) ('[] :: [k]) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

allHolds :: List1 (Holds c) '[] Source #

(All c xs, c x) => All (c :: a -> Constraint) (x ': xs :: [a]) Source # 
Instance details

Defined in Language.Hakaru.Syntax.IClasses

Methods

allHolds :: List1 (Holds c) (x ': xs) Source #

data Holds (c :: k -> Constraint) (x :: k) where Source #

Constructors

Holds :: c x => Holds c x