datafix-0.0.1.0: Fixing data-flow problems

Copyright(c) Sebastian Graf 2017-2020
LicenseISC
Maintainersgraf1337@gmail.com
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Datafix

Description

This is the top-level, import-all, kitchen sink module.

Look at Datafix.Tutorial for a tour guided by use cases.

Synopsis

Documentation

type family MonoMap k = (r :: * -> *) | r -> k Source #

The particular ordered map implementation to use for the key type k.

The default implementation delegates to POMap.

Instances
type MonoMap Int Source # 
Instance details

Defined in Datafix.MonoMap

type MonoMap () Source # 
Instance details

Defined in Datafix.MonoMap

type MonoMap () = Maybe

type family Apply (t :: Function k l -> *) (u :: k) :: l Source #

Instances
type Apply (Constant1 a :: Function k Type -> Type) (b :: k) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (Constant1 a :: Function k Type -> Type) (b :: k) = a
type Apply (ConsMap1 f a2 :: Function [a1] [a1] -> Type) (tl :: [a1]) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (ConsMap1 f a2 :: Function [a1] [a1] -> Type) (tl :: [a1]) = Apply f a2 ': tl
type Apply (ConsMap0 f :: Function k (Function [l] [l] -> Type) -> Type) (a :: k) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (ConsMap0 f :: Function k (Function [l] [l] -> Type) -> Type) (a :: k) = ConsMap1 f a
type Apply (Constant0 :: Function Type (Function b Type -> Type) -> Type) (a :: Type) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (Constant0 :: Function Type (Function b Type -> Type) -> Type) (a :: Type) = (Constant1 a :: Function b Type -> Type)

data Constant1 :: * -> Function b a -> * Source #

Instances
type Apply (Constant1 a :: Function k Type -> Type) (b :: k) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (Constant1 a :: Function k Type -> Type) (b :: k) = a

data Constant0 :: Function a (Function b a -> *) -> * Source #

Instances
type Apply (Constant0 :: Function Type (Function b Type -> Type) -> Type) (a :: Type) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (Constant0 :: Function Type (Function b Type -> Type) -> Type) (a :: Type) = (Constant1 a :: Function b Type -> Type)

data Function :: * -> * -> * Source #

Instances
type Apply (ConsMap0 f :: Function k (Function [l] [l] -> Type) -> Type) (a :: k) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (ConsMap0 f :: Function k (Function [l] [l] -> Type) -> Type) (a :: k) = ConsMap1 f a
type Apply (Constant0 :: Function Type (Function b Type -> Type) -> Type) (a :: Type) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (Constant0 :: Function Type (Function b Type -> Type) -> Type) (a :: Type) = (Constant1 a :: Function b Type -> Type)

class Currying as b where Source #

Currying as b witnesses the isomorphism between Arrows as b and Products as -> b. It is defined as a type class rather than by recursion on a singleton for as so all of that these conversions are inlined at compile time for concrete arguments.

Methods

uncurrys :: Arrows as b -> Products as -> b Source #

currys :: (Products as -> b) -> Arrows as b Source #

Instances
Currying ([] :: [Type]) b Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

Methods

uncurrys :: Arrows [] b -> Products [] -> b Source #

currys :: (Products [] -> b) -> Arrows [] b Source #

Currying (a2 ': as) b => Currying (a1 ': (a2 ': as)) b Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

Methods

uncurrys :: Arrows (a1 ': (a2 ': as)) b -> Products (a1 ': (a2 ': as)) -> b Source #

currys :: (Products (a1 ': (a2 ': as)) -> b) -> Arrows (a1 ': (a2 ': as)) b Source #

Currying (a ': ([] :: [Type])) b Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

Methods

uncurrys :: Arrows (a ': []) b -> Products (a ': []) -> b Source #

currys :: (Products (a ': []) -> b) -> Arrows (a ': []) b Source #

type family ReturnType' (t :: *) :: * where ... Source #

Equations

ReturnType' (a -> t) = ReturnType t 

type family ReturnType (t :: *) :: * where ... Source #

Equations

ReturnType t = If (IsBase t) t (ReturnType' t) 

type family ParamTypes' (t :: *) :: [*] where ... Source #

Equations

ParamTypes' (a -> t) = a ': ParamTypes t 

type family ParamTypes (t :: *) :: [*] where ... Source #

Using IsBase we can define notions of ParamTypes and ReturnTypes which *reduce* under positive information IsBase t ~ 'True even though the shape of t is not formally exposed

Equations

ParamTypes t = If (IsBase t) '[] (ParamTypes' t) 

type family IsBase (t :: *) :: Bool where ... Source #

IsBase t is 'True whenever t is *not* a function space.

Equations

IsBase (a -> t) = False 
IsBase a = True 

type family Products (as :: [*]) where ... Source #

Products [] corresponds to (), Products [a] corresponds to a, Products [a1,..,an] corresponds to (a1, (..,( an)..)).

So, not quite a right fold, because we want to optimize for the empty, singleton and pair case.

Equations

Products '[] = () 
Products '[a] = a 
Products (a ': as) = (a, Products as) 

type Arrows (as :: [*]) (r :: *) = Foldr (->) r as Source #

Arrows [a1,..,an] r corresponds to a1 -> .. -> an -> r

type family Constant (b :: l) (as :: [k]) :: [l] where ... Source #

Equations

Constant b as = Map (Constant1 b) as 

data ConsMap1 :: (Function k l -> *) -> k -> Function [l] [l] -> * Source #

Instances
type Apply (ConsMap1 f a2 :: Function [a1] [a1] -> Type) (tl :: [a1]) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (ConsMap1 f a2 :: Function [a1] [a1] -> Type) (tl :: [a1]) = Apply f a2 ': tl

data ConsMap0 :: (Function k l -> *) -> Function k (Function [l] [l] -> *) -> * Source #

Instances
type Apply (ConsMap0 f :: Function k (Function [l] [l] -> Type) -> Type) (a :: k) Source # 
Instance details

Defined in Datafix.Utils.TypeLevel

type Apply (ConsMap0 f :: Function k (Function [l] [l] -> Type) -> Type) (a :: k) = ConsMap1 f a

type family Foldr' (c :: Function k (Function l l -> *) -> *) (n :: l) (as :: [k]) :: l where ... Source #

Version of Foldr taking a defunctionalised argument so that we can use partially applied functions.

Equations

Foldr' c n '[] = n 
Foldr' c n (a ': as) = Apply (Apply c a) (Foldr' c n as) 

type family Foldr (c :: k -> l -> l) (n :: l) (as :: [k]) :: l where ... Source #

On Lists

Equations

Foldr c n '[] = n 
Foldr c n (a ': as) = c a (Foldr c n as) 

type family If (b :: Bool) (l :: k) (r :: k) :: k where ... Source #

On Booleans

Equations

If True l r = l 
If False l r = r 

type family All (p :: k -> Constraint) (as :: [k]) :: Constraint where ... Source #

All p as ensures that the constraint p is satisfied by all the types in as. (Types is between scare-quotes here because the code is actually kind polymorphic)

Equations

All p '[] = () 
All p (a ': as) = (p a, All p as)