constraints-0.13.4: Constraint manipulation
Safe HaskellNone
LanguageHaskell2010

Data.Constraint.Symbol

Description

Utilities for working with KnownSymbol constraints.

This module is only available on GHC 8.0 or later.

Synopsis

Documentation

type family AppendSymbol (a :: Symbol) (b :: Symbol) :: Symbol where ... #

Concatenation of type-level symbols.

Since: base-4.10.0.0

type (++) (m :: Symbol) (n :: Symbol) = AppendSymbol m n infixr 5 Source #

An infix synonym for AppendSymbol.

type family Take :: Nat -> Symbol -> Symbol where ... Source #

type family Drop :: Nat -> Symbol -> Symbol where ... Source #

type family Length :: Symbol -> Nat where ... Source #

appendUnit1 :: forall a. Dict (AppendSymbol "" a ~ a) Source #

appendUnit2 :: forall a. Dict (AppendSymbol a "" ~ a) Source #

takeAppendDrop :: forall n a. Dict (AppendSymbol (Take n a) (Drop n a) ~ a) Source #

takeLength :: forall n a. (Length a <= n) :- (Take n a ~ a) Source #

take0 :: forall a. Dict (Take 0 a ~ "") Source #

takeEmpty :: forall n. Dict (Take n "" ~ "") Source #

dropLength :: forall n a. (Length a <= n) :- (Drop n a ~ "") Source #

drop0 :: forall a. Dict (Drop 0 a ~ a) Source #

dropEmpty :: forall n. Dict (Drop n "" ~ "") Source #

lengthTake :: forall n a. Dict (Length (Take n a) <= n) Source #

lengthDrop :: forall n a. Dict (Length a <= (Length (Drop n a) + n)) Source #

dropDrop :: forall n m a. Dict (Drop n (Drop m a) ~ Drop (n + m) a) Source #

takeTake :: forall n m a. Dict (Take n (Take m a) ~ Take (Min n m) a) Source #