quantification-0.3: Rage against the quantification

Safe HaskellNone
LanguageHaskell2010

Topaz.Types

Documentation

data Elem rs r where Source #

Constructors

ElemHere :: Elem (r ': rs) r 
ElemThere :: Elem rs r -> Elem (s ': rs) r 

data Rec :: (k -> Type) -> [k] -> Type where Source #

Constructors

RecNil :: Rec f '[] 
RecCons :: f r -> Rec f rs -> Rec f (r ': rs) 

Instances

TestCoercion k f => TestCoercion [k] (Rec k f) Source # 

Methods

testCoercion :: f a -> f b -> Maybe (Coercion (Rec k f) a b) #

TestEquality k f => TestEquality [k] (Rec k f) Source # 

Methods

testEquality :: f a -> f b -> Maybe ((Rec k f :~: a) b) #

MonoidForall k f => MonoidForall [k] (Rec k f) Source # 

Methods

memptyForall :: Sing (Rec k f) a -> f a Source #

StorableForall k f => StorableForall [k] (Rec k f) Source # 

Methods

peekForall :: Sing (Rec k f) a -> Ptr (f a) -> IO (f a) Source #

pokeForall :: Ptr (f a) -> f a -> IO () Source #

sizeOfFunctorForall :: f a -> Int Source #

sizeOfForall :: Proxy (Rec k f -> Type) f -> Sing (Rec k f) a -> Int Source #

SemigroupForall k f => SemigroupForall [k] (Rec k f) Source # 

Methods

sappendForall :: f a -> f a -> f a Source #

FromJSONExists k f => FromJSONExists [k] (Rec k f) Source # 

Methods

parseJSONExists :: Value -> Parser (Exists (Rec k f) f) Source #

FromJSONForall k f => FromJSONForall [k] (Rec k f) Source # 

Methods

parseJSONForall :: Sing (Rec k f) a -> Value -> Parser (f a) Source #

ToJSONForall k f => ToJSONForall [k] (Rec k f) Source # 

Methods

toJSONForall :: f a -> Value Source #

HashableForall k f => HashableForall [k] (Rec k f) Source # 

Methods

hashWithSaltForall :: Int -> f a -> Int Source #

ShowForall k f => ShowForall [k] (Rec k f) Source # 

Methods

showsPrecForall :: Int -> f a -> ShowS Source #

OrdForall k f => OrdForall [k] (Rec k f) Source # 

Methods

compareForall :: f a -> f a -> Ordering Source #

EqForall k f => EqForall [k] (Rec k f) Source # 

Methods

eqForall :: f a -> f a -> Bool Source #

EqForall k f => Eq (Rec k f as) Source # 

Methods

(==) :: Rec k f as -> Rec k f as -> Bool #

(/=) :: Rec k f as -> Rec k f as -> Bool #

OrdForall k f => Ord (Rec k f as) Source # 

Methods

compare :: Rec k f as -> Rec k f as -> Ordering #

(<) :: Rec k f as -> Rec k f as -> Bool #

(<=) :: Rec k f as -> Rec k f as -> Bool #

(>) :: Rec k f as -> Rec k f as -> Bool #

(>=) :: Rec k f as -> Rec k f as -> Bool #

max :: Rec k f as -> Rec k f as -> Rec k f as #

min :: Rec k f as -> Rec k f as -> Rec k f as #

ShowForall k f => Show (Rec k f as) Source # 

Methods

showsPrec :: Int -> Rec k f as -> ShowS #

show :: Rec k f as -> String #

showList :: [Rec k f as] -> ShowS #

SemigroupForall k f => Semigroup (Rec k f as) Source # 

Methods

(<>) :: Rec k f as -> Rec k f as -> Rec k f as #

sconcat :: NonEmpty (Rec k f as) -> Rec k f as #

stimes :: Integral b => b -> Rec k f as -> Rec k f as #

(MonoidForall k f, Reify [k] as) => Monoid (Rec k f as) Source # 

Methods

mempty :: Rec k f as #

mappend :: Rec k f as -> Rec k f as -> Rec k f as #

mconcat :: [Rec k f as] -> Rec k f as #

HashableForall k f => Hashable (Rec k f as) Source # 

Methods

hashWithSalt :: Int -> Rec k f as -> Int #

hash :: Rec k f as -> Int #

(FromJSONForall k f, Reify [k] as) => FromJSON (Rec k f as) Source # 

Methods

parseJSON :: Value -> Parser (Rec k f as) #

parseJSONList :: Value -> Parser [Rec k f as] #

ToJSONForall k f => ToJSON (Rec k f as) Source # 

Methods

toJSON :: Rec k f as -> Value #

toEncoding :: Rec k f as -> Encoding #

toJSONList :: [Rec k f as] -> Value #

toEncodingList :: [Rec k f as] -> Encoding #

(StorableForall k f, Reify [k] as) => Storable (Rec k f as) Source # 

Methods

sizeOf :: Rec k f as -> Int #

alignment :: Rec k f as -> Int #

peekElemOff :: Ptr (Rec k f as) -> Int -> IO (Rec k f as) #

pokeElemOff :: Ptr (Rec k f as) -> Int -> Rec k f as -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec k f as) #

pokeByteOff :: Ptr b -> Int -> Rec k f as -> IO () #

peek :: Ptr (Rec k f as) -> IO (Rec k f as) #

poke :: Ptr (Rec k f as) -> Rec k f as -> IO () #

data NestRec :: (k -> Type) -> Nest k -> Type where Source #

Constructors

NestRec :: Rec f rs -> Rec (NestRec f) ns -> NestRec f (Nest ns rs) 

newtype Fix f Source #

Constructors

Fix (f (Fix f)) 

Instances

Semigroup1 f => Semigroup (Fix f) Source # 

Methods

(<>) :: Fix f -> Fix f -> Fix f #

sconcat :: NonEmpty (Fix f) -> Fix f #

stimes :: Integral b => b -> Fix f -> Fix f #

Monoid1 f => Monoid (Fix f) Source # 

Methods

mempty :: Fix f #

mappend :: Fix f -> Fix f -> Fix f #

mconcat :: [Fix f] -> Fix f #

newtype HFix h a Source #

Constructors

HFix (h (HFix h) a) 

Instances

TestEqualityHetero k k h => TestEquality k (HFix k h) Source # 

Methods

testEquality :: f a -> f b -> Maybe ((HFix k h :~: a) b) #

EqHetero k k h => EqForall k (HFix k h) Source # 

Methods

eqForall :: f a -> f a -> Bool Source #

EqHetero k k h => Eq (HFix k h a) Source # 

Methods

(==) :: HFix k h a -> HFix k h a -> Bool #

(/=) :: HFix k h a -> HFix k h a -> Bool #

data Nest a Source #

Constructors

Nest [Nest a] [a] 

class EqHetero h where Source #

Minimal complete definition

eqHetero

Methods

eqHetero :: (forall x. f x -> f x -> Bool) -> h f a -> h f a -> Bool Source #

class TestEqualityHetero h where Source #

Minimal complete definition

testEqualityHetero

Methods

testEqualityHetero :: (forall x y. f x -> f y -> Maybe (x :~: y)) -> h f a -> h f b -> Maybe (a :~: b) Source #

type family (as :: [k]) ++ (bs :: [k]) :: [k] where ... infixr 5 Source #

Equations

'[] ++ bs = bs 
(a ': as) ++ bs = a ': (as ++ bs)