concat-examples-0.3.0.0: Some examples of compiling to categories
Copyright(c) 2016 Conal Elliott
Maintainerconal@tabula.com
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

ConCat.RunCircuit

Description

Run a test: reify, CCC, circuit

Synopsis

Documentation

type Okay a b = (Uncurriable (:>) a b, GenBuses (UncDom a b), Ok (:>) (UncRan a b)) Source #

go :: Okay a b => String -> (a -> b) -> IO () Source #

go' :: Okay a b => String -> [Attr] -> (a -> b) -> IO () Source #

goSep :: Okay a b => String -> Double -> (a -> b) -> IO () Source #

run :: (GenBuses a, Ok (:>) b) => String -> [Attr] -> (a :> b) -> IO () Source #

runSep :: Ok2 (:>) a b => String -> Double -> (a :> b) -> IO () Source #

data a :> b infixl 1 Source #

Circuit category

Instances

Instances details
AssociativePCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

lassocP :: Ok3 (:>) a b c => Prod (:>) a (Prod (:>) b c) :> Prod (:>) (Prod (:>) a b) c Source #

rassocP :: Ok3 (:>) a b c => Prod (:>) (Prod (:>) a b) c :> Prod (:>) a (Prod (:>) b c) Source #

BoolCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

BraidedPCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

swapP :: Ok2 (:>) a b => Prod (:>) a b :> Prod (:>) b a Source #

Category (:>) Source # 
Instance details

Defined in ConCat.Circuit

Associated Types

type Ok (:>) :: Type -> Constraint Source #

Methods

id :: Ok (:>) a => a :> a Source #

(.) :: forall b c a. Ok3 (:>) a b c => (b :> c) -> (a :> b) -> a :> c Source #

ClosedCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

apply :: Ok2 (:>) a b => Prod (:>) (Exp (:>) a b) a :> b Source #

curry :: Ok3 (:>) a b c => (Prod (:>) a b :> c) -> a :> Exp (:>) b c Source #

uncurry :: Ok3 (:>) a b c => (a :> Exp (:>) b c) -> Prod (:>) a b :> c Source #

CoproductPCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

inlP :: Ok2 (:>) a b => a :> CoprodP (:>) a b Source #

inrP :: Ok2 (:>) a b => b :> CoprodP (:>) a b Source #

jamP :: Ok (:>) a => CoprodP (:>) a a :> a Source #

FiniteCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

unFinite :: forall (n :: Nat). KnownNat n => Finite n :> Int Source #

unsafeFinite :: forall (n :: Nat). KnownNat n => Int :> Finite n Source #

MonoidalPCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

(***) :: Ok4 (:>) a b c d => (a :> c) -> (b :> d) -> Prod (:>) a b :> Prod (:>) c d Source #

first :: forall a a' b. Ok3 (:>) a b a' => (a :> a') -> Prod (:>) a b :> Prod (:>) a' b Source #

second :: Ok3 (:>) a b b' => (b :> b') -> Prod (:>) a b :> Prod (:>) a b' Source #

ProductCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

exl :: Ok2 (:>) a b => Prod (:>) a b :> a Source #

exr :: Ok2 (:>) a b => Prod (:>) a b :> b Source #

dup :: Ok (:>) a => a :> Prod (:>) a a Source #

TerminalCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

it :: Ok (:>) a => a :> Unit (:>) Source #

UnitCat (:>) Source # 
Instance details

Defined in ConCat.Circuit

Methods

lunit :: Ok (:>) a => a :> Prod (:>) (Unit (:>)) a Source #

lcounit :: Ok (:>) a => Prod (:>) (Unit (:>)) a :> a Source #

runit :: Ok (:>) a => a :> Prod (:>) a (Unit (:>)) Source #

rcounit :: Ok (:>) a => Prod (:>) a (Unit (:>)) :> a Source #

GS Integer => ConstCat (:>) Integer Source # 
Instance details

Defined in ConCat.Circuit

GS () => ConstCat (:>) () Source # 
Instance details

Defined in ConCat.Circuit

Methods

const :: Ok (:>) a => () -> a :> ConstObj (:>) () Source #

unitArrow :: () -> Unit (:>) :> ConstObj (:>) () Source #

GS Bool => ConstCat (:>) Bool Source # 
Instance details

Defined in ConCat.Circuit

GS Double => ConstCat (:>) Double Source # 
Instance details

Defined in ConCat.Circuit

GS Float => ConstCat (:>) Float Source # 
Instance details

Defined in ConCat.Circuit

GS Int => ConstCat (:>) Int Source # 
Instance details

Defined in ConCat.Circuit

(ConstCat (:>) a, NumCat (:>) a, Num a) => EnumCat (:>) a Source # 
Instance details

Defined in ConCat.Circuit

Methods

succC :: a :> a Source #

predC :: a :> a Source #

(Read Integer, Eq Integer, GenBuses Integer) => EqCat (:>) Integer Source # 
Instance details

Defined in ConCat.Circuit

EqCat (:>) () Source # 
Instance details

Defined in ConCat.Circuit

EqCat (:>) Bool Source # 
Instance details

Defined in ConCat.Circuit

(Read Double, Eq Double, GenBuses Double) => EqCat (:>) Double Source # 
Instance details

Defined in ConCat.Circuit

(Read Float, Eq Float, GenBuses Float) => EqCat (:>) Float Source # 
Instance details

Defined in ConCat.Circuit

(Read Int, Eq Int, GenBuses Int) => EqCat (:>) Int Source # 
Instance details

Defined in ConCat.Circuit

(Floating a, Read a, GS a) => FloatingCat (:>) a Source # 
Instance details

Defined in ConCat.Circuit

Methods

expC :: a :> a Source #

logC :: a :> a Source #

cosC :: a :> a Source #

sinC :: a :> a Source #

sqrtC :: a :> a Source #

tanhC :: a :> a Source #

(Fractional a, Read a, Eq a, GS a, SourceToBuses a) => FractionalCat (:>) a Source # 
Instance details

Defined in ConCat.Circuit

Methods

recipC :: a :> a Source #

divideC :: Prod (:>) a a :> a Source #

(Functor h, OkFunctor (:>) h) => FunctorCat (:>) h Source # 
Instance details

Defined in ConCat.Circuit

Methods

fmapC :: Ok2 (:>) a b => (a :> b) -> h a :> h b Source #

unzipC :: Ok2 (:>) a b => h (a :* b) :> (h a :* h b) Source #

(OkCAR All, IfCat (:>) (Rep All)) => IfCat (:>) All Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) All Source #

(OkCAR Any, IfCat (:>) (Rep Any)) => IfCat (:>) Any Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) Any Source #

IfCat (:>) Integer Source # 
Instance details

Defined in ConCat.Circuit

IfCat (:>) () Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) () Source #

IfCat (:>) Bool Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) Bool Source #

IfCat (:>) Double Source # 
Instance details

Defined in ConCat.Circuit

IfCat (:>) Float Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) Float Source #

IfCat (:>) Int Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) Int Source #

(Integral a, Read a, GS a, SourceToBuses a) => IntegralCat (:>) a Source # 
Instance details

Defined in ConCat.Circuit

Methods

divC :: Prod (:>) a a :> a Source #

modC :: Prod (:>) a a :> a Source #

(OkIxProd (:>) h, Representable h, Zip h, Traversable h, Show (Rep h), Show1 h) => IxCoproductPCat (:>) h Source # 
Instance details

Defined in ConCat.Circuit

Methods

inPF :: Ok (:>) a => h (a :> h a) Source #

joinPF :: Ok2 (:>) a b => h (b :> a) -> h b :> a Source #

jamPF :: Ok (:>) a => h a :> a Source #

(OkIxProd (:>) h, Functor h, Zip h, Traversable h, Show1 h) => IxMonoidalPCat (:>) h Source # 
Instance details

Defined in ConCat.Circuit

Methods

crossF :: Ok2 (:>) a b => h (a :> b) -> h a :> h b Source #

(IxMonoidalPCat (:>) h, Representable h, Show (Rep h)) => IxProductCat (:>) h Source # 
Instance details

Defined in ConCat.Circuit

Methods

exF :: Ok (:>) a => h (h a :> a) Source #

forkF :: Ok2 (:>) a b => h (a :> b) -> a :> h b Source #

replF :: Ok (:>) a => a :> h a Source #

Ok (:>) a => MinMaxCat (:>) a Source # 
Instance details

Defined in ConCat.Circuit

Methods

minC :: Prod (:>) a a :> a Source #

maxC :: Prod (:>) a a :> a Source #

(Num a, Read a, GS a, Eq a, SourceToBuses a) => NumCat (:>) a Source # 
Instance details

Defined in ConCat.Circuit

Methods

negateC :: a :> a Source #

addC :: Prod (:>) a a :> a Source #

subC :: Prod (:>) a a :> a Source #

mulC :: Prod (:>) a a :> a Source #

powIC :: Prod (:>) a Int :> a Source #

OkFunctor (:>) Par1 Source # 
Instance details

Defined in ConCat.Circuit

Methods

okFunctor :: Ok' (:>) a |- Ok' (:>) (Par1 a) Source #

OkFunctor (:>) Pair Source # 
Instance details

Defined in ConCat.Pair

Methods

okFunctor :: Ok' (:>) a |- Ok' (:>) (Pair a) Source #

OkIxProd (:>) Par1 Source # 
Instance details

Defined in ConCat.Circuit

Methods

okIxProd :: Ok' (:>) a |- Ok' (:>) (Par1 a) Source #

OrdCat (:>) Integer Source # 
Instance details

Defined in ConCat.Circuit

OrdCat (:>) () Source # 
Instance details

Defined in ConCat.Circuit

OrdCat (:>) Bool Source # 
Instance details

Defined in ConCat.Circuit

OrdCat (:>) Double Source # 
Instance details

Defined in ConCat.Circuit

OrdCat (:>) Float Source # 
Instance details

Defined in ConCat.Circuit

OrdCat (:>) Int Source # 
Instance details

Defined in ConCat.Circuit

(GenBuses (Rep f), OkFunctor (:>) f) => RepresentableCat (:>) f Source # 
Instance details

Defined in ConCat.Circuit

Methods

tabulateC :: Ok (:>) a => (Rep f -> a) :> f a Source #

indexC :: Ok (:>) a => f a :> (Rep f -> a) Source #

(Zip h, OkFunctor (:>) h) => ZipCat (:>) h Source # 
Instance details

Defined in ConCat.Circuit

Methods

zipC :: Ok2 (:>) a b => (h a :* h b) :> h (a :* b) Source #

(OkFunctor (:>) h, Additive a, Ok (:>) a) => AddCat (:>) h a Source # 
Instance details

Defined in ConCat.Circuit

Methods

sumAC :: h a :> a Source #

(OkFunctor (:>) g, OkFunctor (:>) f) => DistributiveCat (:>) g f Source # 
Instance details

Defined in ConCat.Circuit

Methods

distributeC :: Ok (:>) a => f (g a) :> g (f a) Source #

(OkFunctor (:>) h, Foldable h, Ord a, Ok (:>) a) => MinMaxFFunctorCat (:>) h a Source # 
Instance details

Defined in ConCat.Circuit

Methods

minimumCF :: h a -> a :* (h a :> a) Source #

maximumCF :: h a -> a :* (h a :> a) Source #

(OkFunctor (:>) h, Ord a, Ok (:>) a) => MinMaxFunctorCat (:>) h a Source # 
Instance details

Defined in ConCat.Circuit

Methods

minimumC :: h a :> a Source #

maximumC :: h a :> a Source #

(OkFunctor (:>) h, Ok (:>) a) => PointedCat (:>) h a Source # 
Instance details

Defined in ConCat.Circuit

Methods

pointC :: a :> h a Source #

(RealFrac a, Integral b, GS a, GS b, Read a) => RealFracCat (:>) a b Source # 
Instance details

Defined in ConCat.Circuit

Methods

floorC :: a :> b Source #

ceilingC :: a :> b Source #

truncateC :: a :> b Source #

(OkCAR a, r ~ Rep a) => RepCat (:>) (a :: Type) (r :: Type) Source # 
Instance details

Defined in ConCat.Circuit

Methods

reprC :: a :> r Source #

abstC :: r :> a Source #

Ok2 (:>) a b => BottomCat (:>) (a :: Type) (b :: Type) Source # 
Instance details

Defined in ConCat.Circuit

Methods

bottomC :: a :> b Source #

Ok2 (:>) a b => CoerceCat (:>) (a :: Type) (b :: Type) Source # 
Instance details

Defined in ConCat.Circuit

Methods

coerceC :: a :> b Source #

(Ok (:>) a, Integral a, Num b, Read a, GS b) => FromIntegralCat (:>) (a :: Type) (b :: Type) Source # 
Instance details

Defined in ConCat.Circuit

Ok2 (:>) a b => UnknownCat (:>) (a :: Type) (b :: Type) Source # 
Instance details

Defined in ConCat.Circuit

Methods

unknownC :: a :> b Source #

GS (Finite n) => ConstCat (:>) (Finite n) Source # 
Instance details

Defined in ConCat.Circuit

(OkCAR (Complex a), IfCat (:>) (Rep (Complex a))) => IfCat (:>) (Complex a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Complex a) Source #

(OkCAR (Identity a), IfCat (:>) (Rep (Identity a))) => IfCat (:>) (Identity a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Identity a) Source #

(OkCAR (Product a), IfCat (:>) (Rep (Product a))) => IfCat (:>) (Product a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Product a) Source #

(OkCAR (Sum a), IfCat (:>) (Rep (Sum a))) => IfCat (:>) (Sum a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Sum a) Source #

(OkCAR (Par1 p), IfCat (:>) (Rep (Par1 p))) => IfCat (:>) (Par1 p) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Par1 p) Source #

(OkCAR (Add a), IfCat (:>) (Rep (Add a))) => IfCat (:>) (Add a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Add a) Source #

(OkCAR (Del a), IfCat (:>) (Rep (Del a))) => IfCat (:>) (Del a) Source # 
Instance details

Defined in ConCat.Incremental

Methods

ifC :: IfT (:>) (Del a) Source #

KnownNat n => IfCat (:>) (Finite n) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Finite n) Source #

(OkCAR (Maybe a), IfCat (:>) (Rep (Maybe a))) => IfCat (:>) (Maybe a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Maybe a) Source #

OkFunctor (:>) (U1 :: Type -> Type) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okFunctor :: Ok' (:>) a |- Ok' (:>) (U1 a) Source #

HasFin' a => OkFunctor (:>) (Arr a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okFunctor :: Ok' (:>) a0 |- Ok' (:>) (Arr a a0) Source #

KnownNat i => OkFunctor (:>) (Vector i) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okFunctor :: Ok' (:>) a |- Ok' (:>) (Vector i a) Source #

OkIxProd (:>) (U1 :: Type -> Type) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okIxProd :: Ok' (:>) a |- Ok' (:>) (U1 a) Source #

KnownNat i => OkIxProd (:>) (Vector i) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okIxProd :: Ok' (:>) a |- Ok' (:>) (Vector i a) Source #

GS (Vector n a) => ConstCat (:>) (Vector n a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

const :: Ok (:>) a0 => Vector n a -> a0 :> ConstObj (:>) (Vector n a) Source #

unitArrow :: Vector n a -> Unit (:>) :> ConstObj (:>) (Vector n a) Source #

(Read (a :+ b), Eq (a :+ b), GenBuses (a :+ b)) => EqCat (:>) (a :+ b) Source # 
Instance details

Defined in ConCat.Circuit

Methods

equal :: Prod (:>) (a :+ b) (a :+ b) :> BoolOf (:>) Source #

notEqual :: Prod (:>) (a :+ b) (a :+ b) :> BoolOf (:>) Source #

(OkCAR (U1 p), IfCat (:>) (Rep (U1 p))) => IfCat (:>) (U1 p) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (U1 p) Source #

(IfCat (:>) a, IfCat (:>) b) => IfCat (:>) (a :* b) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (a :* b) Source #

(OkCAR (a -+> b), IfCat (:>) (Rep (a -+> b))) => IfCat (:>) (a -+> b) Source # 
Instance details

Defined in ConCat.AdditiveFun

Methods

ifC :: IfT (:>) (a -+> b) Source #

(OkCAR (a -#> b), IfCat (:>) (Rep (a -#> b))) => IfCat (:>) (a -#> b) Source # 
Instance details

Defined in ConCat.Incremental

Methods

ifC :: IfT (:>) (a -#> b) Source #

(OkCAR (Arr a b), IfCat (:>) (Rep (Arr a b))) => IfCat (:>) (Arr a b) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Arr a b) Source #

(GenBuses b, KnownNat n) => IfCat (:>) (Vector n b) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (Vector n b) Source #

(Ok (:>) a, IfCat (:>) b) => IfCat (:>) (a -> b) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (a -> b) Source #

(OkCAR (Dual k a b), IfCat (:>) (Rep (Dual k a b))) => IfCat (:>) (Dual k a b) Source # 
Instance details

Defined in ConCat.Dual

Methods

ifC :: IfT (:>) (Dual k a b) Source #

(OkCAR (Affine s a b), IfCat (:>) (Rep (Affine s a b))) => IfCat (:>) (Affine s a b) Source # 
Instance details

Defined in ConCat.Free.Affine

Methods

ifC :: IfT (:>) (Affine s a b) Source #

(OkCAR (L s a b), IfCat (:>) (Rep (L s a b))) => IfCat (:>) (L s a b) Source # 
Instance details

Defined in ConCat.Free.LinearRow

Methods

ifC :: IfT (:>) (L s a b) Source #

(OkCAR (GD k a b), IfCat (:>) (Rep (GD k a b))) => IfCat (:>) (GD k a b) Source # 
Instance details

Defined in ConCat.GAD

Methods

ifC :: IfT (:>) (GD k a b) Source #

(OkCAR (ReaderT e m a), IfCat (:>) (Rep (ReaderT e m a))) => IfCat (:>) (ReaderT e m a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (ReaderT e m a) Source #

(OkCAR (StateT s m a), IfCat (:>) (Rep (StateT s m a))) => IfCat (:>) (StateT s m a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (StateT s m a) Source #

(OkCAR (WriterT w m a), IfCat (:>) (Rep (WriterT w m a))) => IfCat (:>) (WriterT w m a) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (WriterT w m a) Source #

(OkCAR (a, b, c), IfCat (:>) (Rep (a, b, c))) => IfCat (:>) (a, b, c) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (a, b, c) Source #

(OkFunctor (:>) f, OkFunctor (:>) g) => OkFunctor (:>) (f :*: g) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okFunctor :: Ok' (:>) a |- Ok' (:>) ((f :*: g) a) Source #

(OkIxProd (:>) f, OkIxProd (:>) g) => OkIxProd (:>) (f :*: g) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okIxProd :: Ok' (:>) a |- Ok' (:>) ((f :*: g) a) Source #

(OkCAR ((f :*: g) p), IfCat (:>) (Rep ((f :*: g) p))) => IfCat (:>) ((f :*: g) p) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) ((f :*: g) p) Source #

(OkCAR ((f :+: g) p), IfCat (:>) (Rep ((f :+: g) p))) => IfCat (:>) ((f :+: g) p) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) ((f :+: g) p) Source #

(OkCAR (K1 i c p), IfCat (:>) (Rep (K1 i c p))) => IfCat (:>) (K1 i c p) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (K1 i c p) Source #

(OkCAR (a, b, c, d), IfCat (:>) (Rep (a, b, c, d))) => IfCat (:>) (a, b, c, d) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (a, b, c, d) Source #

(OkFunctor (:>) f, OkFunctor (:>) g) => OkFunctor (:>) (g :.: f) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okFunctor :: Ok' (:>) a |- Ok' (:>) ((g :.: f) a) Source #

(OkIxProd (:>) f, OkIxProd (:>) g) => OkIxProd (:>) (g :.: f) Source # 
Instance details

Defined in ConCat.Circuit

Methods

okIxProd :: Ok' (:>) a |- Ok' (:>) ((g :.: f) a) Source #

(OkCAR ((f :.: g) p), IfCat (:>) (Rep ((f :.: g) p))) => IfCat (:>) ((f :.: g) p) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) ((f :.: g) p) Source #

(OkCAR (M1 i c f p), IfCat (:>) (Rep (M1 i c f p))) => IfCat (:>) (M1 i c f p) Source # 
Instance details

Defined in ConCat.Circuit

Methods

ifC :: IfT (:>) (M1 i c f p) Source #

(GenBuses a, Ok2 (:>) a b) => Show (a :> b) Source # 
Instance details

Defined in ConCat.Circuit

Methods

showsPrec :: Int -> (a :> b) -> ShowS Source #

show :: (a :> b) -> String Source #

showList :: [a :> b] -> ShowS Source #

type Ok (:>) Source # 
Instance details

Defined in ConCat.Circuit