| Copyright | (c) Murdoch J. Gabbay 2020 |
|---|---|
| License | GPL-3 |
| Maintainer | murdoch.gabbay@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Language.Nominal.Abs
Contents
Description
Name-abstraction, nominal style. This captures the "a." in "λa.ab".
Examples of practical usage are in Language.Nominal.Examples.SystemF, e.g. the type and term datatypes Typ and Trm.
Synopsis
- data KAbs n a
- type Abs t a = KAbs (KName Tom t) a
- abst :: (Typeable s, Swappable t, Swappable a) => KName s t -> a -> KAbs (KName s t) a
- abst' :: (Typeable s, Swappable t, Swappable a) => t -> KAtom s -> a -> KAbs (KName s t) a
- pattern (:@>) :: (Typeable s, Swappable t, Swappable a) => KName s t -> a -> KAbs (KName s t) a
- fuse :: (KAbs (KName s t) a1, KAbs (KName s t) a2) -> KAbs (KName s t) (a1, a2)
- unfuse :: KAbs (KName s t) (a, b) -> (KAbs (KName s t) a, KAbs (KName s t) b)
- absLabel :: KAbs (KName s t) a -> t
- conc :: BinderConc ctxbody ctx body s a => ctxbody -> a -> body
- absToNom :: (Typeable s, Swappable t, Swappable a) => KAbs (KName s t) a -> KNom s (KName s t, a)
- nomToAbs :: (Typeable s, Swappable t, Swappable a) => KNom s (KName s t, a) -> KAbs (KName s t) a
- absFresh :: (Typeable s, Swappable t, Swappable a) => t -> (KName s t -> a) -> KAbs (KName s t) a
- absFresh' :: (Typeable s, Swappable t, Swappable a, Default t) => (KName s t -> a) -> KAbs (KName s t) a
- absFuncOut :: (Typeable s, Swappable t, Swappable a, Swappable b, Default t) => (KAbs (KName s t) a -> KAbs (KName s t) b) -> KAbs (KName s t) (a -> b)
Name-abstraction
A datatype for name-abstractions.
KAbs n ais a type for abstractions ofas byn-names, where we intend thatn = KName s tfor somes-atoms (atoms of types) andt-labels (labels of typet).Abs t ais a type for abstractions ofas byt-labelled-atoms.Tom
Under the hood an abstraction is just an element of (n, n -> a), but we do not expose this. What makes the type interesting is its constructor, , which is the only way to build an abstraction. abst :: KName s t -> a -> KAbs (KName s t) a
It's possible to implement using KAbs — see KNom and absToNom — but this requires a nomToAbs typeclass constraint on KSwappablea, which we prefer to avoid so that e.g. can be a KAbs. Functor
Instances
| (KSupport s a, KSupport s t) => KSupport s (KAbs (KName s t) a) Source # | Support of a :@> x is the support of x minus a |
| (Typeable s, KUnifyPerm s t, KUnifyPerm s a) => KUnifyPerm s (KAbs (KName s t) a) Source # | Unify |
| Functor (KAbs n) Source # | |
| Default t => Applicative (KAbs (KName s t)) Source # | |
Defined in Language.Nominal.Abs Methods pure :: a -> KAbs (KName s t) a # (<*>) :: KAbs (KName s t) (a -> b) -> KAbs (KName s t) a -> KAbs (KName s t) b # liftA2 :: (a -> b -> c) -> KAbs (KName s t) a -> KAbs (KName s t) b -> KAbs (KName s t) c # (*>) :: KAbs (KName s t) a -> KAbs (KName s t) b -> KAbs (KName s t) b # (<*) :: KAbs (KName s t) a -> KAbs (KName s t) b -> KAbs (KName s t) a # | |
| (Typeable s, Swappable t, Eq t, Eq a) => Eq (KAbs (KName s t) a) Source # | Abstractions are equal up to fusing their abstracted names. |
| (Typeable s, Swappable t, Swappable a, Show t, Show a) => Show (KAbs (KName s t) a) Source # | We show an abstraction by evaluating the function inside |
| Generic (KAbs n a) Source # | |
| (Typeable s, Swappable t, Swappable a, Arbitrary (KName s t), Arbitrary a) => Arbitrary (KAbs (KName s t) a) Source # | |
| (Swappable n, Swappable a) => Swappable (KAbs n a) Source # | Spelling out the generic swapping action for clarity, where we write |
| Binder (KAbs n a) n a s => BinderConc (KAbs n a) n a s n Source # | Concretes an abstraction at a particular name. Unsafe if the name is not fresh. (abst a x) `conc` a == x abst a (x `conc` a) == x -- provided a is suitably fresh. new' $ \a -> abst a (x `conc` a) == x |
| (Typeable s, Typeable u, KSub (KName s n) x t, KSub (KName s n) x y, Swappable t, Swappable y) => KSub (KName s n) x (KAbs (KName u t) y) Source # | sub on a nominal abstraction substitutes in the label, and substitutes capture-avoidingly in the body |
| (Typeable s, Swappable t, Swappable a) => Binder (KAbs (KName s t) a) (KName s t) a s Source # | Acts on an abstraction |
| (Typeable s, Swappable n, Swappable x, Swappable y, KSub (KName s n) x y) => BinderConc (KAbs (KName s n) y) (KName s n) y s x Source # | Nameless form of substitution, where the name for which we substitute is packaged in a |
| type Rep (KAbs n a) Source # | |
Defined in Language.Nominal.Abs type Rep (KAbs n a) = D1 (MetaData "KAbs" "Language.Nominal.Abs" "nom-0.1.0.2-Cei0dwnsIrWHLKrPA11A4S" False) (C1 (MetaCons "AbsWrapper" PrefixI True) (S1 (MetaSel (Just "absName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n) :*: S1 (MetaSel (Just "absApp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (n -> a)))) | |
Abstractions (basic functions)
pattern (:@>) :: (Typeable s, Swappable t, Swappable a) => KName s t -> a -> KAbs (KName s t) a infixr 0 Source #
The abstraction pattern '(:>)' is just an instance of '(:@!)' for KAbs. Thus,
n :@> x -> f n x
is synonymous with
x' -> x' @@! f
Because '(:>)' is a concrete instance of '(:!)', we can declare it COMPLETE@.
fuse :: (KAbs (KName s t) a1, KAbs (KName s t) a2) -> KAbs (KName s t) (a1, a2) Source #
Fuse abstractions, taking label of abstracted name from first argument. Should satisfy:
fuse (n @> x) (n @> y) = n @> (x, y)
unfuse :: KAbs (KName s t) (a, b) -> (KAbs (KName s t) a, KAbs (KName s t) b) Source #
Split two abstractions. Should satisfy:
unfuse (n @> (x,y)) = (n @> x, n @> y)
absLabel :: KAbs (KName s t) a -> t Source #
Return the label of an abstraction.
Note: For reasons having to do with the Haskell type system it's convenient to store this label in the underlying representation of the abstraction, using a "dummy name". However, we do not export access to this name, we only export access to its label, using absLabel.
conc :: BinderConc ctxbody ctx body s a => ctxbody -> a -> body Source #
The bijection between Abs and KNom
AbsKNomabsToNom :: (Typeable s, Swappable t, Swappable a) => KAbs (KName s t) a -> KNom s (KName s t, a) Source #
Bijection between Nom and Abs. Just an instance of binderToNom.
nomToAbs :: (Typeable s, Swappable t, Swappable a) => KNom s (KName s t, a) -> KAbs (KName s t) a Source #
Bijection between Nom and Abs. Just an instance of nomToBinder.
Unpacking name-contexts and abstractions
absFresh :: (Typeable s, Swappable t, Swappable a) => t -> (KName s t -> a) -> KAbs (KName s t) a Source #
Apply f to a fresh element with label t
absFresh' :: (Typeable s, Swappable t, Swappable a, Default t) => (KName s t -> a) -> KAbs (KName s t) a Source #
Apply f to a fresh element with default label
absFuncOut :: (Typeable s, Swappable t, Swappable a, Swappable b, Default t) => (KAbs (KName s t) a -> KAbs (KName s t) b) -> KAbs (KName s t) (a -> b) Source #
Near inverse to applicative distribution.
absFuncIn . absFuncOut = id but not necessarily other way around
Tests
Property-based tests are in Language.Nominal.Properties.AbsSpec.