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

Fcf.Data.Char

Description

Fcf.Data.Char

Synopsis

Documentation

 

data IsSpace :: Char -> Exp Bool Source #

IsSpace

Example

Expand
>>> :kind! Eval (IsSpace 'a')
Eval (IsSpace 'a') :: Bool
= 'False
>>> :kind! Eval (IsSpace ' ')
Eval (IsSpace ' ') :: Bool
= 'True

Instances

Instances details
type Eval (IsSpace s :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (IsSpace s :: Bool -> Type) = Eval (s == ' ')

data IsNewLine :: Char -> Exp Bool Source #

IsNewline

Example

Expand
>>> :kind! Eval (IsNewLine 'a')
Eval (IsNewLine 'a') :: Bool
= 'False
>>> :kind! Eval (IsNewLine '\n')
Eval (IsNewLine '\n') :: Bool
= 'True

Instances

Instances details
type Eval (IsNewLine s :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (IsNewLine s :: Bool -> Type) = Eval (s == '\n')

data IsTab :: Char -> Exp Bool Source #

IsTab

Example

Expand
>>> :kind! Eval (IsTab 'a')
Eval (IsTab 'a') :: Bool
= 'False
>>> :kind! Eval (IsTab '\t')
Eval (IsTab '\t') :: Bool
= 'True

Instances

Instances details
type Eval (IsTab s :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (IsTab s :: Bool -> Type) = Eval (s == '\t')

data IsSpaceDelim :: Char -> Exp Bool Source #

IsSpaceDelim

Example

Expand
>>> :kind! Eval (IsSpaceDelim 'a')
Eval (IsSpaceDelim 'a') :: Bool
= 'False
>>> :kind! Eval (IsSpaceDelim '\n')
Eval (IsSpaceDelim '\n') :: Bool
= 'True

Instances

Instances details
type Eval (IsSpaceDelim s :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (IsSpaceDelim s :: Bool -> Type) = Eval (Eval (IsSpace s) || Eval (Eval (IsNewLine s) || Eval (IsTab s)))

data IsDigit :: Char -> Exp Bool Source #

IsDigit

Example

Expand
>>> :kind! Eval (IsDigit '3')
Eval (IsDigit '3') :: Bool
= 'True
>>> :kind! Eval (IsDigit 'a')
Eval (IsDigit 'a') :: Bool
= 'False

Instances

Instances details
type Eval (IsDigit s :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (IsDigit s :: Bool -> Type) = Eval (Elem s '['0', '1', '2', '3', '4', '5', '6', '7', '8', '9'])

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

CharOrd - compare two symbols and give type-level Ordering ( $ 'LT $, $ 'EQ $ or $ 'GT $ ).

Example

Expand
>>> :kind! Eval (CharOrd 'a' 'b')
Eval (CharOrd 'a' 'b') :: Ordering
= 'LT

Instances

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

Defined in Fcf.Data.Char

type Eval (CharOrd a b :: Ordering -> Type) = CmpChar a b

data (<=) :: Char -> Char -> Exp Bool Source #

Less-than-or-equal comparison for symbols.

Example

Expand
>>> :kind! Eval ('b' <= 'a')
Eval ('b' <= 'a') :: Bool
= 'False

Instances

Instances details
type Eval (a <= b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (a <= b :: Bool -> Type) = Eval (Eval (TyEq (CmpChar a b) 'LT) || Eval (TyEq (CmpChar a b) 'EQ))

data (>=) :: Char -> Char -> Exp Bool Source #

Larger-than-or-equal comparison for symbols.

Example

Expand
>>> :kind! Eval ('b' >= 'a')
Eval ('b' >= 'a') :: Bool
= 'True

Instances

Instances details
type Eval (a >= b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (a >= b :: Bool -> Type) = Eval (Eval (TyEq (CmpChar a b) 'GT) || Eval (TyEq (CmpChar a b) 'EQ))

data (<) :: Char -> Char -> Exp Bool Source #

Less-than comparison for symbols.

Example

Expand
>>> :kind! Eval ('a' < 'b')
Eval ('a' < 'b') :: Bool
= 'True

Instances

Instances details
type Eval (a < b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (a < b :: Bool -> Type) = Eval (TyEq (CmpChar a b) 'LT)

data (>) :: Char -> Char -> Exp Bool Source #

Larger-than comparison for symbols.

Example

Expand
>>> :kind! Eval ('b' > 'a')
Eval ('b' > 'a') :: Bool
= 'True

Instances

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

Defined in Fcf.Data.Char

type Eval (a > b :: Bool -> Type) = Eval (TyEq (CmpChar a b) 'GT)

data (==) :: Char -> Char -> Exp Bool Source #

Equality of symbols

Example

Expand
>>> :kind! Eval ('b' == 'a')
Eval ('b' == 'a') :: Bool
= 'False

Instances

Instances details
type Eval (a == b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Char

type Eval (a == b :: Bool -> Type) = Eval (TyEq (CmpChar a b) 'EQ)