fcf-containers-0.8.0: Data structures and algorithms for first-class-families
Copyright(c) gspia 2023-
LicenseBSD
Maintainergspia
Safe HaskellSafe-Inferred
LanguageHaskell2010

Fcf.Data.Symbol

Description

Fcf.Data.Symbol

This might should go to first-class-families.

Documentation

data CmpSymbol :: Symbol -> Symbol -> Exp Ordering Source #

Instances

Instances details
type Eval (CmpSymbol a b :: Ordering -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (CmpSymbol a b :: Ordering -> Type) = TypeError ('Text "CmpSymbol in 9.2.x or higher") :: Ordering

data CmpChar :: Char -> Char -> Exp Ordering Source #

Instances

Instances details
type Eval (CmpChar a b :: Ordering -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (CmpChar a b :: Ordering -> Type) = TypeError ('Text "CmpChar in 9.2.x or higher") :: Ordering

data UnconsSymbol :: Symbol -> Exp (Maybe (Char, Symbol)) Source #

Instances

Instances details
type Eval (UnconsSymbol a :: Maybe (Char, Symbol) -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (UnconsSymbol a :: Maybe (Char, Symbol) -> Type) = TypeError ('Text "UnconsSymbol in 9.2.x or higher") :: Maybe (Char, Symbol)

data CharToNat :: Char -> Exp Nat Source #

Instances

Instances details
type Eval (CharToNat c :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (CharToNat c :: Nat -> Type) = TypeError ('Text "CharToNat in 9.2.x or higher") :: Nat

data NatToChar :: Nat -> Exp Char Source #

Instances

Instances details
type Eval (NatToChar n :: Char -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (NatToChar n :: Char -> Type) = TypeError ('Text "NatToChar in 9.2.x or higher") :: Char

data ConsChar :: Char -> Symbol -> Exp Symbol Source #

Instances

Instances details
type Eval (ConsChar a b :: Symbol -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (ConsChar a b :: Symbol -> Type) = TypeError ('Text "ConsChar in 9.2.x or higher") :: Symbol

data ToCharList :: Symbol -> Exp [Char] Source #

Instances

Instances details
type Eval (ToCharList sym :: [Char] -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (ToCharList sym :: [Char] -> Type) = TypeError ('Text "ToCharList in 9.2.x or higher") :: [Char]

data CharToSymbol :: Char -> Exp Symbol Source #

Instances

Instances details
type Eval (CharToSymbol c :: Symbol -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (CharToSymbol c :: Symbol -> Type) = TypeError ('Text "CharToSymbol in 9.2.x or higher") :: Symbol

data Concat :: [Symbol] -> Exp Symbol Source #

Instances

Instances details
type Eval (Concat lst :: Symbol -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (Concat lst :: Symbol -> Type) = TypeError ('Text "Concat in 9.2.x or higher") :: Symbol

data ConcatChars :: [Char] -> Exp Symbol Source #

Instances

Instances details
type Eval (ConcatChars lst :: Symbol -> Type) Source # 
Instance details

Defined in Fcf.Data.Symbol

type Eval (ConcatChars lst :: Symbol -> Type) = TypeError ('Text "ConcatChars in 9.2.x or higher") :: Symbol