debruijn-0.1: de Bruijn indices and levels
Safe HaskellUnsafe
LanguageHaskell2010

DeBruijn.Internal.Lvl

Contents

Description

de Bruijn levels for well-scoped terms.

Synopsis

Levels

newtype Lvl ctx Source #

de Bruijn levels.

Constructors

UnsafeLvl Int 

Instances

Instances details
Sinkable Lvl Source # 
Instance details

Defined in DeBruijn.Internal.Lvl

Methods

mapLvl :: forall (ctx :: Ctx) (ctx' :: Ctx). Lte ctx ctx' -> Lvl ctx -> Lvl ctx' Source #

Show (Lvl ctx) Source # 
Instance details

Defined in DeBruijn.Internal.Lvl

Methods

showsPrec :: Int -> Lvl ctx -> ShowS #

show :: Lvl ctx -> String #

showList :: [Lvl ctx] -> ShowS #

Eq (Lvl ctx) Source # 
Instance details

Defined in DeBruijn.Internal.Lvl

Methods

(==) :: Lvl ctx -> Lvl ctx -> Bool #

(/=) :: Lvl ctx -> Lvl ctx -> Bool #

Ord (Lvl ctx) Source # 
Instance details

Defined in DeBruijn.Internal.Lvl

Methods

compare :: Lvl ctx -> Lvl ctx -> Ordering #

(<) :: Lvl ctx -> Lvl ctx -> Bool #

(<=) :: Lvl ctx -> Lvl ctx -> Bool #

(>) :: Lvl ctx -> Lvl ctx -> Bool #

(>=) :: Lvl ctx -> Lvl ctx -> Bool #

max :: Lvl ctx -> Lvl ctx -> Lvl ctx #

min :: Lvl ctx -> Lvl ctx -> Lvl ctx #

lvlToIdx :: Size ctx -> Lvl ctx -> Idx ctx Source #

Convert level to index.

>>> lvlToIdx S2 (lvlZ S1)
0

idxToLvl :: Size ctx -> Idx ctx -> Lvl ctx Source #

lvlZ :: Size ctx -> Lvl (S ctx) Source #

Last level.

>>> lvlZ S1
1
>>> lvlZ S5
5

sinkLvl :: Lvl n -> Lvl (S n) Source #

Sink Lvl into a larger context.

>>> sinkLvl (lvlZ S3)
3
>>> sink (lvlZ S3)
3
>>> mapLvl (LS LZ) (lvlZ S3)
3

class Sinkable t where Source #

Sinkable terms can be weakened (sunk) cheaply.

Methods

mapLvl :: Lte ctx ctx' -> t ctx -> t ctx' Source #

Instances

Instances details
Sinkable Lvl Source # 
Instance details

Defined in DeBruijn.Internal.Lvl

Methods

mapLvl :: forall (ctx :: Ctx) (ctx' :: Ctx). Lte ctx ctx' -> Lvl ctx -> Lvl ctx' Source #

Sinkable (Proxy :: Ctx -> Type) Source # 
Instance details

Defined in DeBruijn.Internal.Lvl

Methods

mapLvl :: forall (ctx :: Ctx) (ctx' :: Ctx). Lte ctx ctx' -> Proxy ctx -> Proxy ctx' Source #

sink :: Sinkable t => t ctx -> t (S ctx) Source #

Sink term.

mapSink :: (Functor f, Sinkable t) => f (t ctx) -> f (t (S ctx)) Source #

Essentially fmap sink

sinkSize :: Sinkable t => Size ctx -> t EmptyCtx -> t ctx Source #

Sink term from empty context to a context of given size.

mapSinkSize :: (Functor f, Sinkable t) => Size ctx -> f (t EmptyCtx) -> f (t ctx) Source #

Essentially fmap . sinkSize

sinkAdd :: Sinkable t => Add n ctx ctx' -> t ctx -> t ctx' Source #

mapSinkAdd :: (Functor f, Sinkable t) => Add n ctx ctx' -> f (t ctx) -> f (t ctx') Source #