data-debruijn-0.1.0.0: Fast and safe implementation of common compiler machinery.
Safe HaskellNone
LanguageGHC2021

Data.DeBruijn.Thinning.Fast

Synopsis

Thinnings

data (n :: Nat) :<= (m :: Nat) where Source #

Bundled Patterns

pattern KeepAll :: () => n ~ m => n :<= m 
pattern KeepOne :: () => (Pos n, Pos m) => (Pred n :<= Pred m) -> n :<= m 
pattern DropOne :: forall m n. () => Pos m => (n :<= Pred m) -> n :<= m 

Instances

Instances details
Thin ((:<=) l) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

thin :: forall (n :: Nat) (m :: Nat). (n :<= m) -> (l :<= n) -> l :<= m Source #

thick :: forall (n :: Nat) (m :: Nat). (n :<= m) -> (l :<= m) -> Maybe (l :<= n) Source #

Show (n :<= m) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

showsPrec :: Int -> (n :<= m) -> ShowS #

show :: (n :<= m) -> String #

showList :: [n :<= m] -> ShowS #

NFData (n :<= m) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

rnf :: (n :<= m) -> () #

Eq (n :<= m) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

(==) :: (n :<= m) -> (n :<= m) -> Bool #

(/=) :: (n :<= m) -> (n :<= m) -> Bool #

dropAll :: forall (m :: Nat). SNat m -> 'Z :<= m Source #

Drop all entries.

toBools :: forall (n :: Nat) (m :: Nat). (n :<= m) -> [Bool] Source #

Convert a thinning into a list of booleans.

fromTh :: forall bs (n :: Nat) (m :: Nat). Bits bs => (n :<= m) -> bs Source #

Convert a thinning into a bit sequence.

fromThRaw :: forall (n :: Nat) (m :: Nat). (n :<= m) -> ThRep Source #

Existential Wrapper

data SomeTh Source #

Constructors

SomeTh 

Fields

Instances

Instances details
Show SomeTh Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

NFData SomeTh Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

rnf :: SomeTh -> () #

Eq SomeTh Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

(==) :: SomeTh -> SomeTh -> Bool #

(/=) :: SomeTh -> SomeTh -> Bool #

fromBools :: Integral i => i -> [Bool] -> SomeTh Source #

toSomeTh :: (Integral i, Bits bs) => (i, bs) -> SomeTh Source #

fromSomeTh :: (Integral i, Bits bs) => SomeTh -> (i, bs) Source #

Convert a thinning into a bit sequence.

The action of thinnings on Nat-indexed types

class Thin (f :: Nat -> Type) where Source #

The actions of thinnings on natural-indexed data types.

Methods

thin :: forall (n :: Nat) (m :: Nat). (n :<= m) -> f n -> f m Source #

thick :: forall (n :: Nat) (m :: Nat). (n :<= m) -> f m -> Maybe (f n) Source #

Instances

Instances details
Thin Ix Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

thin :: forall (n :: Nat) (m :: Nat). (n :<= m) -> Ix n -> Ix m Source #

thick :: forall (n :: Nat) (m :: Nat). (n :<= m) -> Ix m -> Maybe (Ix n) Source #

Thin ((:<=) l) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

thin :: forall (n :: Nat) (m :: Nat). (n :<= m) -> (l :<= n) -> l :<= m Source #

thick :: forall (n :: Nat) (m :: Nat). (n :<= m) -> (l :<= m) -> Maybe (l :<= n) Source #

Fast

bitsToThRep :: Bits bs => bs -> ThRep Source #

thRepToBits :: Bits bs => ThRep -> bs Source #

newtype (n :: Nat) :<= (m :: Nat) Source #

Constructors

UnsafeTh 

Fields

Instances

Instances details
Thin ((:<=) l) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

thin :: forall (n :: Nat) (m :: Nat). (n :<= m) -> (l :<= n) -> l :<= m Source #

thick :: forall (n :: Nat) (m :: Nat). (n :<= m) -> (l :<= m) -> Maybe (l :<= n) Source #

Show (n :<= m) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

showsPrec :: Int -> (n :<= m) -> ShowS #

show :: (n :<= m) -> String #

showList :: [n :<= m] -> ShowS #

NFData (n :<= m) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

rnf :: (n :<= m) -> () #

Eq (n :<= m) Source # 
Instance details

Defined in Data.DeBruijn.Thinning.Fast

Methods

(==) :: (n :<= m) -> (n :<= m) -> Bool #

(/=) :: (n :<= m) -> (n :<= m) -> Bool #