{-# OPTIONS_GHC -Wno-missing-methods #-}
{-# OPTIONS_GHC -Wno-overlapping-patterns -Wno-inaccessible-code #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# LANGUAGE DefaultSignatures #-}
module Control.Monad.Foil.Internal where
import Control.DeepSeq (NFData (..))
import Data.Bifunctor
import Data.Coerce (coerce)
import Data.IntMap
import qualified Data.IntMap as IntMap
import Data.IntSet
import qualified Data.IntSet as IntSet
import Data.Kind (Type)
import qualified Data.Type.Equality as Type
import Generics.Kind
import Unsafe.Coerce
import Control.Monad.Foil.Internal.ValidNameBinders
data S
= VoidS
newtype Scope (n :: S) = UnsafeScope RawScope
deriving newtype Scope n -> ()
(Scope n -> ()) -> NFData (Scope n)
forall a. (a -> ()) -> NFData a
forall (n :: S). Scope n -> ()
$crnf :: forall (n :: S). Scope n -> ()
rnf :: Scope n -> ()
NFData
newtype Name (n :: S) = UnsafeName RawName
deriving newtype (Name n -> ()
(Name n -> ()) -> NFData (Name n)
forall a. (a -> ()) -> NFData a
forall (n :: S). Name n -> ()
$crnf :: forall (n :: S). Name n -> ()
rnf :: Name n -> ()
NFData, Name n -> Name n -> Bool
(Name n -> Name n -> Bool)
-> (Name n -> Name n -> Bool) -> Eq (Name n)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (n :: S). Name n -> Name n -> Bool
$c== :: forall (n :: S). Name n -> Name n -> Bool
== :: Name n -> Name n -> Bool
$c/= :: forall (n :: S). Name n -> Name n -> Bool
/= :: Name n -> Name n -> Bool
Eq, Eq (Name n)
Eq (Name n) =>
(Name n -> Name n -> Ordering)
-> (Name n -> Name n -> Bool)
-> (Name n -> Name n -> Bool)
-> (Name n -> Name n -> Bool)
-> (Name n -> Name n -> Bool)
-> (Name n -> Name n -> Name n)
-> (Name n -> Name n -> Name n)
-> Ord (Name n)
Name n -> Name n -> Bool
Name n -> Name n -> Ordering
Name n -> Name n -> Name n
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (n :: S). Eq (Name n)
forall (n :: S). Name n -> Name n -> Bool
forall (n :: S). Name n -> Name n -> Ordering
forall (n :: S). Name n -> Name n -> Name n
$ccompare :: forall (n :: S). Name n -> Name n -> Ordering
compare :: Name n -> Name n -> Ordering
$c< :: forall (n :: S). Name n -> Name n -> Bool
< :: Name n -> Name n -> Bool
$c<= :: forall (n :: S). Name n -> Name n -> Bool
<= :: Name n -> Name n -> Bool
$c> :: forall (n :: S). Name n -> Name n -> Bool
> :: Name n -> Name n -> Bool
$c>= :: forall (n :: S). Name n -> Name n -> Bool
>= :: Name n -> Name n -> Bool
$cmax :: forall (n :: S). Name n -> Name n -> Name n
max :: Name n -> Name n -> Name n
$cmin :: forall (n :: S). Name n -> Name n -> Name n
min :: Name n -> Name n -> Name n
Ord, RawName -> Name n -> ShowS
[Name n] -> ShowS
Name n -> String
(RawName -> Name n -> ShowS)
-> (Name n -> String) -> ([Name n] -> ShowS) -> Show (Name n)
forall a.
(RawName -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
forall (n :: S). RawName -> Name n -> ShowS
forall (n :: S). [Name n] -> ShowS
forall (n :: S). Name n -> String
$cshowsPrec :: forall (n :: S). RawName -> Name n -> ShowS
showsPrec :: RawName -> Name n -> ShowS
$cshow :: forall (n :: S). Name n -> String
show :: Name n -> String
$cshowList :: forall (n :: S). [Name n] -> ShowS
showList :: [Name n] -> ShowS
Show)
nameId :: Name l -> Id
nameId :: forall (l :: S). Name l -> RawName
nameId (UnsafeName RawName
i) = RawName
i
newtype NameBinder (n :: S) (l :: S) =
UnsafeNameBinder (Name l)
deriving newtype (NameBinder n l -> ()
(NameBinder n l -> ()) -> NFData (NameBinder n l)
forall a. (a -> ()) -> NFData a
forall (n :: S) (l :: S). NameBinder n l -> ()
$crnf :: forall (n :: S) (l :: S). NameBinder n l -> ()
rnf :: NameBinder n l -> ()
NFData, NameBinder n l -> NameBinder n l -> Bool
(NameBinder n l -> NameBinder n l -> Bool)
-> (NameBinder n l -> NameBinder n l -> Bool)
-> Eq (NameBinder n l)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (n :: S) (l :: S). NameBinder n l -> NameBinder n l -> Bool
$c== :: forall (n :: S) (l :: S). NameBinder n l -> NameBinder n l -> Bool
== :: NameBinder n l -> NameBinder n l -> Bool
$c/= :: forall (n :: S) (l :: S). NameBinder n l -> NameBinder n l -> Bool
/= :: NameBinder n l -> NameBinder n l -> Bool
Eq, Eq (NameBinder n l)
Eq (NameBinder n l) =>
(NameBinder n l -> NameBinder n l -> Ordering)
-> (NameBinder n l -> NameBinder n l -> Bool)
-> (NameBinder n l -> NameBinder n l -> Bool)
-> (NameBinder n l -> NameBinder n l -> Bool)
-> (NameBinder n l -> NameBinder n l -> Bool)
-> (NameBinder n l -> NameBinder n l -> NameBinder n l)
-> (NameBinder n l -> NameBinder n l -> NameBinder n l)
-> Ord (NameBinder n l)
NameBinder n l -> NameBinder n l -> Bool
NameBinder n l -> NameBinder n l -> Ordering
NameBinder n l -> NameBinder n l -> NameBinder n l
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (n :: S) (l :: S). Eq (NameBinder n l)
forall (n :: S) (l :: S). NameBinder n l -> NameBinder n l -> Bool
forall (n :: S) (l :: S).
NameBinder n l -> NameBinder n l -> Ordering
forall (n :: S) (l :: S).
NameBinder n l -> NameBinder n l -> NameBinder n l
$ccompare :: forall (n :: S) (l :: S).
NameBinder n l -> NameBinder n l -> Ordering
compare :: NameBinder n l -> NameBinder n l -> Ordering
$c< :: forall (n :: S) (l :: S). NameBinder n l -> NameBinder n l -> Bool
< :: NameBinder n l -> NameBinder n l -> Bool
$c<= :: forall (n :: S) (l :: S). NameBinder n l -> NameBinder n l -> Bool
<= :: NameBinder n l -> NameBinder n l -> Bool
$c> :: forall (n :: S) (l :: S). NameBinder n l -> NameBinder n l -> Bool
> :: NameBinder n l -> NameBinder n l -> Bool
$c>= :: forall (n :: S) (l :: S). NameBinder n l -> NameBinder n l -> Bool
>= :: NameBinder n l -> NameBinder n l -> Bool
$cmax :: forall (n :: S) (l :: S).
NameBinder n l -> NameBinder n l -> NameBinder n l
max :: NameBinder n l -> NameBinder n l -> NameBinder n l
$cmin :: forall (n :: S) (l :: S).
NameBinder n l -> NameBinder n l -> NameBinder n l
min :: NameBinder n l -> NameBinder n l -> NameBinder n l
Ord, RawName -> NameBinder n l -> ShowS
[NameBinder n l] -> ShowS
NameBinder n l -> String
(RawName -> NameBinder n l -> ShowS)
-> (NameBinder n l -> String)
-> ([NameBinder n l] -> ShowS)
-> Show (NameBinder n l)
forall a.
(RawName -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
forall (n :: S) (l :: S). RawName -> NameBinder n l -> ShowS
forall (n :: S) (l :: S). [NameBinder n l] -> ShowS
forall (n :: S) (l :: S). NameBinder n l -> String
$cshowsPrec :: forall (n :: S) (l :: S). RawName -> NameBinder n l -> ShowS
showsPrec :: RawName -> NameBinder n l -> ShowS
$cshow :: forall (n :: S) (l :: S). NameBinder n l -> String
show :: NameBinder n l -> String
$cshowList :: forall (n :: S) (l :: S). [NameBinder n l] -> ShowS
showList :: [NameBinder n l] -> ShowS
Show)
emptyScope :: Scope VoidS
emptyScope :: Scope 'VoidS
emptyScope = RawScope -> Scope 'VoidS
forall (n :: S). RawScope -> Scope n
UnsafeScope RawScope
IntSet.empty
member :: Name l -> Scope n -> Bool
member :: forall (l :: S) (n :: S). Name l -> Scope n -> Bool
member (UnsafeName RawName
name) (UnsafeScope RawScope
s) = RawName -> RawScope -> Bool
rawMember RawName
name RawScope
s
extendScope :: NameBinder n l -> Scope n -> Scope l
extendScope :: forall (n :: S) (l :: S). NameBinder n l -> Scope n -> Scope l
extendScope (UnsafeNameBinder (UnsafeName RawName
name)) (UnsafeScope RawScope
scope) =
RawScope -> Scope l
forall (n :: S). RawScope -> Scope n
UnsafeScope (RawName -> RawScope -> RawScope
IntSet.insert RawName
name RawScope
scope)
extendScopePattern
:: (Distinct n, CoSinkable pattern)
=> pattern n l -> Scope n -> Scope l
extendScopePattern :: forall (n :: S) (pattern :: S -> S -> *) (l :: S).
(Distinct n, CoSinkable pattern) =>
pattern n l -> Scope n -> Scope l
extendScopePattern pattern n l
pat Scope n
scope = (forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
ExtendScope x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
ExtendScope x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
ExtendScope x y z z'
-> ExtendScope y y' z' z'' -> ExtendScope x y' z z'')
-> Scope n
-> pattern n l
-> (forall (o' :: S).
DExt n o' =>
ExtendScope n l n o' -> pattern n o' -> Scope l)
-> Scope l
forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern
(\Scope z
_scope' NameBinder x y
binder forall (z' :: S).
DExt z z' =>
ExtendScope x y z z' -> NameBinder z z' -> r'
k ->
NameBinder x y -> (DExt z Any => NameBinder z Any -> r') -> r'
forall (n :: S) (l :: S) (n' :: S) (l' :: S) r.
NameBinder n l -> (DExt n' l' => NameBinder n' l' -> r) -> r
unsafeAssertFresh NameBinder x y
binder ((DExt z Any => NameBinder z Any -> r') -> r')
-> (DExt z Any => NameBinder z Any -> r') -> r'
forall a b. (a -> b) -> a -> b
$ \NameBinder z Any
binder' ->
ExtendScope x y z Any -> NameBinder z Any -> r'
forall (z' :: S).
DExt z z' =>
ExtendScope x y z z' -> NameBinder z z' -> r'
k ((Scope x -> Scope y) -> ExtendScope x y z Any
forall (n :: S) (l :: S) (o :: S) (o' :: S).
(Scope n -> Scope l) -> ExtendScope n l o o'
ExtendScope (NameBinder x y -> Scope x -> Scope y
forall (n :: S) (l :: S). NameBinder n l -> Scope n -> Scope l
extendScope NameBinder x y
binder)) NameBinder z Any
binder')
ExtendScope x x z z'
forall (n :: S) (o :: S) (o' :: S). ExtendScope n n o o'
forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
ExtendScope x x z z'
idExtendScope
ExtendScope x y z z'
-> ExtendScope y y' z' z'' -> ExtendScope x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
ExtendScope x y z z'
-> ExtendScope y y' z' z'' -> ExtendScope x y' z z''
forall (n :: S) (i :: S) (o :: S) (o' :: S) (l :: S) (o'' :: S).
ExtendScope n i o o'
-> ExtendScope i l o' o'' -> ExtendScope n l o o''
compExtendScope
Scope n
scope
pattern n l
pat
(\(ExtendScope Scope n -> Scope l
extend) pattern n o'
_ -> Scope n -> Scope l
extend Scope n
scope)
newtype ExtendScope n l (o :: S) (o' :: S) = ExtendScope (Scope n -> Scope l)
idExtendScope :: ExtendScope n n o o'
idExtendScope :: forall (n :: S) (o :: S) (o' :: S). ExtendScope n n o o'
idExtendScope = (Scope n -> Scope n) -> ExtendScope n n o o'
forall (n :: S) (l :: S) (o :: S) (o' :: S).
(Scope n -> Scope l) -> ExtendScope n l o o'
ExtendScope Scope n -> Scope n
forall a. a -> a
id
compExtendScope
:: ExtendScope n i o o'
-> ExtendScope i l o' o''
-> ExtendScope n l o o''
compExtendScope :: forall (n :: S) (i :: S) (o :: S) (o' :: S) (l :: S) (o'' :: S).
ExtendScope n i o o'
-> ExtendScope i l o' o'' -> ExtendScope n l o o''
compExtendScope (ExtendScope Scope n -> Scope i
f) (ExtendScope Scope i -> Scope l
g)
= (Scope n -> Scope l) -> ExtendScope n l o o''
forall (n :: S) (l :: S) (o :: S) (o' :: S).
(Scope n -> Scope l) -> ExtendScope n l o o'
ExtendScope (Scope i -> Scope l
g (Scope i -> Scope l) -> (Scope n -> Scope i) -> Scope n -> Scope l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scope n -> Scope i
f)
nameOf :: NameBinder n l -> Name l
nameOf :: forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf (UnsafeNameBinder Name l
name) = Name l
name
namesOfPattern
:: forall pattern n l. (Distinct n, CoSinkable pattern) => pattern n l -> [Name l]
namesOfPattern :: forall (pattern :: S -> S -> *) (n :: S) (l :: S).
(Distinct n, CoSinkable pattern) =>
pattern n l -> [Name l]
namesOfPattern pattern n l
pat = forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern @_ @n
(\Scope z
_scope' NameBinder x y
binder forall (z' :: S).
DExt z z' =>
NamesOf x y z z' -> NameBinder z z' -> r'
k ->
NameBinder x y -> (DExt z Any => NameBinder z Any -> r') -> r'
forall (n :: S) (l :: S) (n' :: S) (l' :: S) r.
NameBinder n l -> (DExt n' l' => NameBinder n' l' -> r) -> r
unsafeAssertFresh NameBinder x y
binder ((DExt z Any => NameBinder z Any -> r') -> r')
-> (DExt z Any => NameBinder z Any -> r') -> r'
forall a b. (a -> b) -> a -> b
$ \NameBinder z Any
binder' ->
NamesOf x y z Any -> NameBinder z Any -> r'
forall (z' :: S).
DExt z z' =>
NamesOf x y z z' -> NameBinder z z' -> r'
k ([Name y] -> NamesOf x y z Any
forall (n :: S) (l :: S) (o :: S) (o' :: S).
[Name l] -> NamesOf n l o o'
NamesOf [NameBinder x y -> Name y
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder x y
binder]) NameBinder z Any
binder')
NamesOf x x z z'
forall (n :: S) (o :: S) (o' :: S). NamesOf n n o o'
forall (x :: S) (z :: S) (z' :: S). DExt z z' => NamesOf x x z z'
idNamesOf NamesOf x y z z' -> NamesOf y y' z' z'' -> NamesOf x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
NamesOf x y z z' -> NamesOf y y' z' z'' -> NamesOf x y' z z''
forall (n :: S) (i :: S) (o :: S) (o' :: S) (l :: S) (o'' :: S).
NamesOf n i o o' -> NamesOf i l o' o'' -> NamesOf n l o o''
compNamesOf (String -> Scope n
forall a. HasCallStack => String -> a
error String
"impossible") pattern n l
pat
(\(NamesOf [Name l]
names) pattern n o'
_ -> [Name l]
names)
newtype NamesOf (n :: S) l (o :: S) (o' :: S) = NamesOf [Name l]
idNamesOf :: NamesOf n n o o'
idNamesOf :: forall (n :: S) (o :: S) (o' :: S). NamesOf n n o o'
idNamesOf = [Name n] -> NamesOf n n o o'
forall (n :: S) (l :: S) (o :: S) (o' :: S).
[Name l] -> NamesOf n l o o'
NamesOf []
compNamesOf :: NamesOf n i o o' -> NamesOf i l o' o'' -> NamesOf n l o o''
compNamesOf :: forall (n :: S) (i :: S) (o :: S) (o' :: S) (l :: S) (o'' :: S).
NamesOf n i o o' -> NamesOf i l o' o'' -> NamesOf n l o o''
compNamesOf (NamesOf [Name i]
xs) (NamesOf [Name l]
ys) =
[Name l] -> NamesOf n l o o''
forall (n :: S) (l :: S) (o :: S) (o' :: S).
[Name l] -> NamesOf n l o o'
NamesOf ([Name i] -> [Name l]
forall a b. Coercible a b => a -> b
coerce [Name i]
xs [Name l] -> [Name l] -> [Name l]
forall a. [a] -> [a] -> [a]
++ [Name l]
ys)
withFreshBinder
:: Scope n
-> (forall l. NameBinder n l -> r) -> r
withFreshBinder :: forall (n :: S) r.
Scope n -> (forall (l :: S). NameBinder n l -> r) -> r
withFreshBinder (UnsafeScope RawScope
scope) forall (l :: S). NameBinder n l -> r
cont =
NameBinder n Any -> r
forall (l :: S). NameBinder n l -> r
cont NameBinder n Any
binder
where
binder :: NameBinder n Any
binder = Name Any -> NameBinder n Any
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder (RawName -> Name Any
forall (n :: S). RawName -> Name n
UnsafeName (RawScope -> RawName
rawFreshName RawScope
scope))
withFresh
:: Distinct n => Scope n
-> (forall l. DExt n l => NameBinder n l -> r) -> r
withFresh :: forall (n :: S) r.
Distinct n =>
Scope n -> (forall (l :: S). DExt n l => NameBinder n l -> r) -> r
withFresh Scope n
scope forall (l :: S). DExt n l => NameBinder n l -> r
cont = Scope n -> (forall (l :: S). NameBinder n l -> r) -> r
forall (n :: S) r.
Scope n -> (forall (l :: S). NameBinder n l -> r) -> r
withFreshBinder Scope n
scope (NameBinder n l -> (DExt n Any => NameBinder n Any -> r) -> r
forall (n :: S) (l :: S) (n' :: S) (l' :: S) r.
NameBinder n l -> (DExt n' l' => NameBinder n' l' -> r) -> r
`unsafeAssertFresh` DExt n Any => NameBinder n Any -> r
NameBinder n Any -> r
forall (l :: S). DExt n l => NameBinder n l -> r
cont)
withFreshPattern
:: (Distinct o, CoSinkable pattern, Sinkable e, InjectName e)
=> Scope o
-> pattern n l
-> (forall o'. DExt o o' => (Substitution e n o -> Substitution e l o') -> pattern o o' -> r)
-> r
withFreshPattern :: forall (o :: S) (pattern :: S -> S -> *) (e :: S -> *) (n :: S)
(l :: S) r.
(Distinct o, CoSinkable pattern, Sinkable e, InjectName e) =>
Scope o
-> pattern n l
-> (forall (o' :: S).
DExt o o' =>
(Substitution e n o -> Substitution e l o') -> pattern o o' -> r)
-> r
withFreshPattern Scope o
scope pattern n l
pattern forall (o' :: S).
DExt o o' =>
(Substitution e n o -> Substitution e l o') -> pattern o o' -> r
cont = (forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
WithRefreshedPattern e x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
WithRefreshedPattern e x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
WithRefreshedPattern e x y z z'
-> WithRefreshedPattern e y y' z' z''
-> WithRefreshedPattern e x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S).
DExt o o' =>
WithRefreshedPattern e n l o o' -> pattern o o' -> r)
-> r
forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern
(\Scope z
scope' NameBinder x y
binder forall (z' :: S).
DExt z z' =>
WithRefreshedPattern e x y z z' -> NameBinder z z' -> r'
f -> Scope z
-> (forall (l :: S). DExt z l => NameBinder z l -> r') -> r'
forall (n :: S) r.
Distinct n =>
Scope n -> (forall (l :: S). DExt n l => NameBinder n l -> r) -> r
withFresh Scope z
scope'
(\NameBinder z l
binder' -> WithRefreshedPattern e x y z l -> NameBinder z l -> r'
forall (z' :: S).
DExt z z' =>
WithRefreshedPattern e x y z z' -> NameBinder z z' -> r'
f ((Substitution e x z -> Substitution e y l)
-> WithRefreshedPattern e x y z l
forall (e :: S -> *) (n :: S) (l :: S) (o :: S) (o' :: S).
(Substitution e n o -> Substitution e l o')
-> WithRefreshedPattern e n l o o'
WithRefreshedPattern (\Substitution e x z
subst -> Substitution e x l
-> NameBinder x y -> Name l -> Substitution e y l
forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
InjectName e =>
Substitution e i o
-> NameBinder i i' -> Name o -> Substitution e i' o
addRename (Substitution e x z -> Substitution e x l
forall (e :: S -> *) (n :: S) (l :: S).
(Sinkable e, DExt n l) =>
e n -> e l
sink Substitution e x z
subst) NameBinder x y
binder (NameBinder z l -> Name l
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder z l
binder'))) NameBinder z l
binder'))
WithRefreshedPattern e x x z z'
forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
WithRefreshedPattern e x x z z'
forall (e :: S -> *) (o :: S) (o' :: S) (n :: S).
(Sinkable e, DExt o o') =>
WithRefreshedPattern e n n o o'
idWithRefreshedPattern
WithRefreshedPattern e x y z z'
-> WithRefreshedPattern e y y' z' z''
-> WithRefreshedPattern e x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
WithRefreshedPattern e x y z z'
-> WithRefreshedPattern e y y' z' z''
-> WithRefreshedPattern e x y' z z''
forall (o :: S) (o' :: S) (o'' :: S) (e :: S -> *) (n :: S)
(i :: S) (l :: S).
(DExt o o', DExt o' o'') =>
WithRefreshedPattern e n i o o'
-> WithRefreshedPattern e i l o' o''
-> WithRefreshedPattern e n l o o''
compWithRefreshedPattern
Scope o
scope
pattern n l
pattern
(\(WithRefreshedPattern Substitution e n o -> Substitution e l o'
f) pattern o o'
pattern' -> (Substitution e n o -> Substitution e l o') -> pattern o o' -> r
forall (o' :: S).
DExt o o' =>
(Substitution e n o -> Substitution e l o') -> pattern o o' -> r
cont Substitution e n o -> Substitution e l o'
f pattern o o'
pattern')
withRefreshed
:: Distinct o
=> Scope o
-> Name i
-> (forall o'. DExt o o' => NameBinder o o' -> r)
-> r
withRefreshed :: forall (o :: S) (i :: S) r.
Distinct o =>
Scope o
-> Name i
-> (forall (o' :: S). DExt o o' => NameBinder o o' -> r)
-> r
withRefreshed scope :: Scope o
scope@(UnsafeScope RawScope
rawScope) name :: Name i
name@(UnsafeName RawName
rawName) forall (o' :: S). DExt o o' => NameBinder o o' -> r
cont
| RawName -> RawScope -> Bool
IntSet.member RawName
rawName RawScope
rawScope = Scope o
-> (forall (o' :: S). DExt o o' => NameBinder o o' -> r) -> r
forall (n :: S) r.
Distinct n =>
Scope n -> (forall (l :: S). DExt n l => NameBinder n l -> r) -> r
withFresh Scope o
scope NameBinder o l -> r
forall (o' :: S). DExt o o' => NameBinder o o' -> r
cont
| Bool
otherwise = NameBinder Any i -> (DExt o Any => NameBinder o Any -> r) -> r
forall (n :: S) (l :: S) (n' :: S) (l' :: S) r.
NameBinder n l -> (DExt n' l' => NameBinder n' l' -> r) -> r
unsafeAssertFresh (Name i -> NameBinder Any i
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder Name i
name) DExt o Any => NameBinder o Any -> r
NameBinder o Any -> r
forall (o' :: S). DExt o o' => NameBinder o o' -> r
cont
withRefreshedPattern
:: (Distinct o, CoSinkable pattern, Sinkable e, InjectName e)
=> Scope o
-> pattern n l
-> (forall o'. DExt o o' => (Substitution e n o -> Substitution e l o') -> pattern o o' -> r)
-> r
withRefreshedPattern :: forall (o :: S) (pattern :: S -> S -> *) (e :: S -> *) (n :: S)
(l :: S) r.
(Distinct o, CoSinkable pattern, Sinkable e, InjectName e) =>
Scope o
-> pattern n l
-> (forall (o' :: S).
DExt o o' =>
(Substitution e n o -> Substitution e l o') -> pattern o o' -> r)
-> r
withRefreshedPattern Scope o
scope pattern n l
pattern forall (o' :: S).
DExt o o' =>
(Substitution e n o -> Substitution e l o') -> pattern o o' -> r
cont = (forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
WithRefreshedPattern e x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
WithRefreshedPattern e x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
WithRefreshedPattern e x y z z'
-> WithRefreshedPattern e y y' z' z''
-> WithRefreshedPattern e x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S).
DExt o o' =>
WithRefreshedPattern e n l o o' -> pattern o o' -> r)
-> r
forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern
(\Scope z
scope' NameBinder x y
binder forall (z' :: S).
DExt z z' =>
WithRefreshedPattern e x y z z' -> NameBinder z z' -> r'
f -> Scope z
-> Name y
-> (forall (o' :: S). DExt z o' => NameBinder z o' -> r')
-> r'
forall (o :: S) (i :: S) r.
Distinct o =>
Scope o
-> Name i
-> (forall (o' :: S). DExt o o' => NameBinder o o' -> r)
-> r
withRefreshed Scope z
scope' (NameBinder x y -> Name y
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder x y
binder)
(\NameBinder z o'
binder' -> WithRefreshedPattern e x y z o' -> NameBinder z o' -> r'
forall (z' :: S).
DExt z z' =>
WithRefreshedPattern e x y z z' -> NameBinder z z' -> r'
f ((Substitution e x z -> Substitution e y o')
-> WithRefreshedPattern e x y z o'
forall (e :: S -> *) (n :: S) (l :: S) (o :: S) (o' :: S).
(Substitution e n o -> Substitution e l o')
-> WithRefreshedPattern e n l o o'
WithRefreshedPattern (\Substitution e x z
subst -> Substitution e x o'
-> NameBinder x y -> Name o' -> Substitution e y o'
forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
InjectName e =>
Substitution e i o
-> NameBinder i i' -> Name o -> Substitution e i' o
addRename (Substitution e x z -> Substitution e x o'
forall (e :: S -> *) (n :: S) (l :: S).
(Sinkable e, DExt n l) =>
e n -> e l
sink Substitution e x z
subst) NameBinder x y
binder (NameBinder z o' -> Name o'
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder z o'
binder'))) NameBinder z o'
binder'))
WithRefreshedPattern e x x z z'
forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
WithRefreshedPattern e x x z z'
forall (e :: S -> *) (o :: S) (o' :: S) (n :: S).
(Sinkable e, DExt o o') =>
WithRefreshedPattern e n n o o'
idWithRefreshedPattern
WithRefreshedPattern e x y z z'
-> WithRefreshedPattern e y y' z' z''
-> WithRefreshedPattern e x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
WithRefreshedPattern e x y z z'
-> WithRefreshedPattern e y y' z' z''
-> WithRefreshedPattern e x y' z z''
forall (o :: S) (o' :: S) (o'' :: S) (e :: S -> *) (n :: S)
(i :: S) (l :: S).
(DExt o o', DExt o' o'') =>
WithRefreshedPattern e n i o o'
-> WithRefreshedPattern e i l o' o''
-> WithRefreshedPattern e n l o o''
compWithRefreshedPattern
Scope o
scope
pattern n l
pattern
(\(WithRefreshedPattern Substitution e n o -> Substitution e l o'
f) pattern o o'
pattern' -> (Substitution e n o -> Substitution e l o') -> pattern o o' -> r
forall (o' :: S).
DExt o o' =>
(Substitution e n o -> Substitution e l o') -> pattern o o' -> r
cont Substitution e n o -> Substitution e l o'
f pattern o o'
pattern')
withRefreshedPattern'
:: (CoSinkable pattern, Distinct o, InjectName e, Sinkable e)
=> Scope o
-> pattern n l
-> (forall o'. DExt o o' => ((Name n -> e o) -> Name l -> e o') -> pattern o o' -> r) -> r
withRefreshedPattern' :: forall (pattern :: S -> S -> *) (o :: S) (e :: S -> *) (n :: S)
(l :: S) r.
(CoSinkable pattern, Distinct o, InjectName e, Sinkable e) =>
Scope o
-> pattern n l
-> (forall (o' :: S).
DExt o o' =>
((Name n -> e o) -> Name l -> e o') -> pattern o o' -> r)
-> r
withRefreshedPattern' Scope o
scope pattern n l
pattern forall (o' :: S).
DExt o o' =>
((Name n -> e o) -> Name l -> e o') -> pattern o o' -> r
cont = (forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
WithRefreshedPattern' e x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
WithRefreshedPattern' e x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
WithRefreshedPattern' e x y z z'
-> WithRefreshedPattern' e y y' z' z''
-> WithRefreshedPattern' e x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S).
DExt o o' =>
WithRefreshedPattern' e n l o o' -> pattern o o' -> r)
-> r
forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern
(\Scope z
scope' NameBinder x y
binder forall (z' :: S).
DExt z z' =>
WithRefreshedPattern' e x y z z' -> NameBinder z z' -> r'
f -> Scope z
-> Name y
-> (forall (o' :: S). DExt z o' => NameBinder z o' -> r')
-> r'
forall (o :: S) (i :: S) r.
Distinct o =>
Scope o
-> Name i
-> (forall (o' :: S). DExt o o' => NameBinder o o' -> r)
-> r
withRefreshed Scope z
scope' (NameBinder x y -> Name y
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder x y
binder)
(\NameBinder z o'
binder' ->
let k :: (Name x -> e z) -> Name y -> e o'
k Name x -> e z
subst Name y
name = case NameBinder x y -> Name y -> Maybe (Name x)
forall (n :: S) (l :: S).
NameBinder n l -> Name l -> Maybe (Name n)
unsinkName NameBinder x y
binder Name y
name of
Maybe (Name x)
Nothing -> Name o' -> e o'
forall (n :: S). Name n -> e n
forall (e :: S -> *) (n :: S). InjectName e => Name n -> e n
injectName (NameBinder z o' -> Name o'
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder z o'
binder')
Just Name x
name' -> e z -> e o'
forall (e :: S -> *) (n :: S) (l :: S).
(Sinkable e, DExt n l) =>
e n -> e l
sink (Name x -> e z
subst Name x
name')
in WithRefreshedPattern' e x y z o' -> NameBinder z o' -> r'
forall (z' :: S).
DExt z z' =>
WithRefreshedPattern' e x y z z' -> NameBinder z z' -> r'
f (((Name x -> e z) -> Name y -> e o')
-> WithRefreshedPattern' e x y z o'
forall (e :: S -> *) (n :: S) (l :: S) (o :: S) (o' :: S).
((Name n -> e o) -> Name l -> e o')
-> WithRefreshedPattern' e n l o o'
WithRefreshedPattern' (Name x -> e z) -> Name y -> e o'
k) NameBinder z o'
binder'))
WithRefreshedPattern' e x x z z'
forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
WithRefreshedPattern' e x x z z'
forall (e :: S -> *) (o :: S) (o' :: S) (n :: S).
(Sinkable e, DExt o o') =>
WithRefreshedPattern' e n n o o'
idWithRefreshedPattern'
WithRefreshedPattern' e x y z z'
-> WithRefreshedPattern' e y y' z' z''
-> WithRefreshedPattern' e x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
WithRefreshedPattern' e x y z z'
-> WithRefreshedPattern' e y y' z' z''
-> WithRefreshedPattern' e x y' z z''
forall (o :: S) (o' :: S) (o'' :: S) (e :: S -> *) (n :: S)
(i :: S) (l :: S).
(DExt o o', DExt o' o'') =>
WithRefreshedPattern' e n i o o'
-> WithRefreshedPattern' e i l o' o''
-> WithRefreshedPattern' e n l o o''
compWithRefreshedPattern'
Scope o
scope
pattern n l
pattern
(\(WithRefreshedPattern' (Name n -> e o) -> Name l -> e o'
f) pattern o o'
pattern' -> ((Name n -> e o) -> Name l -> e o') -> pattern o o' -> r
forall (o' :: S).
DExt o o' =>
((Name n -> e o) -> Name l -> e o') -> pattern o o' -> r
cont (Name n -> e o) -> Name l -> e o'
f pattern o o'
pattern')
unsafeAssertFresh :: forall n l n' l' r. NameBinder n l
-> (DExt n' l' => NameBinder n' l' -> r) -> r
unsafeAssertFresh :: forall (n :: S) (l :: S) (n' :: S) (l' :: S) r.
NameBinder n l -> (DExt n' l' => NameBinder n' l' -> r) -> r
unsafeAssertFresh NameBinder n l
binder DExt n' l' => NameBinder n' l' -> r
cont =
case forall (n :: S). DistinctEvidence n
unsafeDistinct @l' of
DistinctEvidence l'
Distinct -> case forall (n :: S) (l :: S). ExtEvidence n l
unsafeExt @n' @l' of
ExtEvidence n' l'
Ext -> DExt n' l' => NameBinder n' l' -> r
NameBinder n' l' -> r
cont (NameBinder n l -> NameBinder n' l'
forall a b. a -> b
unsafeCoerce NameBinder n l
binder)
newtype WithRefreshedPattern e n l o o' = WithRefreshedPattern (Substitution e n o -> Substitution e l o')
idWithRefreshedPattern :: (Sinkable e, DExt o o') => WithRefreshedPattern e n n o o'
idWithRefreshedPattern :: forall (e :: S -> *) (o :: S) (o' :: S) (n :: S).
(Sinkable e, DExt o o') =>
WithRefreshedPattern e n n o o'
idWithRefreshedPattern = (Substitution e n o -> Substitution e n o')
-> WithRefreshedPattern e n n o o'
forall (e :: S -> *) (n :: S) (l :: S) (o :: S) (o' :: S).
(Substitution e n o -> Substitution e l o')
-> WithRefreshedPattern e n l o o'
WithRefreshedPattern Substitution e n o -> Substitution e n o'
forall (e :: S -> *) (n :: S) (l :: S).
(Sinkable e, DExt n l) =>
e n -> e l
sink
compWithRefreshedPattern
:: (DExt o o', DExt o' o'')
=> WithRefreshedPattern e n i o o'
-> WithRefreshedPattern e i l o' o''
-> WithRefreshedPattern e n l o o''
compWithRefreshedPattern :: forall (o :: S) (o' :: S) (o'' :: S) (e :: S -> *) (n :: S)
(i :: S) (l :: S).
(DExt o o', DExt o' o'') =>
WithRefreshedPattern e n i o o'
-> WithRefreshedPattern e i l o' o''
-> WithRefreshedPattern e n l o o''
compWithRefreshedPattern (WithRefreshedPattern Substitution e n o -> Substitution e i o'
f) (WithRefreshedPattern Substitution e i o' -> Substitution e l o''
g) =
(Substitution e n o -> Substitution e l o'')
-> WithRefreshedPattern e n l o o''
forall (e :: S -> *) (n :: S) (l :: S) (o :: S) (o' :: S).
(Substitution e n o -> Substitution e l o')
-> WithRefreshedPattern e n l o o'
WithRefreshedPattern (Substitution e i o' -> Substitution e l o''
g (Substitution e i o' -> Substitution e l o'')
-> (Substitution e n o -> Substitution e i o')
-> Substitution e n o
-> Substitution e l o''
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Substitution e n o -> Substitution e i o'
f)
newtype WithRefreshedPattern' e n l (o :: S) (o' :: S) = WithRefreshedPattern' ((Name n -> e o) -> Name l -> e o')
idWithRefreshedPattern' :: (Sinkable e, DExt o o') => WithRefreshedPattern' e n n o o'
idWithRefreshedPattern' :: forall (e :: S -> *) (o :: S) (o' :: S) (n :: S).
(Sinkable e, DExt o o') =>
WithRefreshedPattern' e n n o o'
idWithRefreshedPattern' = ((Name n -> e o) -> Name n -> e o')
-> WithRefreshedPattern' e n n o o'
forall (e :: S -> *) (n :: S) (l :: S) (o :: S) (o' :: S).
((Name n -> e o) -> Name l -> e o')
-> WithRefreshedPattern' e n l o o'
WithRefreshedPattern' (\Name n -> e o
f Name n
n -> e o -> e o'
forall (e :: S -> *) (n :: S) (l :: S).
(Sinkable e, DExt n l) =>
e n -> e l
sink (Name n -> e o
f Name n
n))
compWithRefreshedPattern'
:: (DExt o o', DExt o' o'')
=> WithRefreshedPattern' e n i o o'
-> WithRefreshedPattern' e i l o' o''
-> WithRefreshedPattern' e n l o o''
compWithRefreshedPattern' :: forall (o :: S) (o' :: S) (o'' :: S) (e :: S -> *) (n :: S)
(i :: S) (l :: S).
(DExt o o', DExt o' o'') =>
WithRefreshedPattern' e n i o o'
-> WithRefreshedPattern' e i l o' o''
-> WithRefreshedPattern' e n l o o''
compWithRefreshedPattern' (WithRefreshedPattern' (Name n -> e o) -> Name i -> e o'
f) (WithRefreshedPattern' (Name i -> e o') -> Name l -> e o''
g) =
((Name n -> e o) -> Name l -> e o'')
-> WithRefreshedPattern' e n l o o''
forall (e :: S -> *) (n :: S) (l :: S) (o :: S) (o' :: S).
((Name n -> e o) -> Name l -> e o')
-> WithRefreshedPattern' e n l o o'
WithRefreshedPattern' ((Name i -> e o') -> Name l -> e o''
g ((Name i -> e o') -> Name l -> e o'')
-> ((Name n -> e o) -> Name i -> e o')
-> (Name n -> e o)
-> Name l
-> e o''
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name n -> e o) -> Name i -> e o'
f)
data DistinctEvidence (n :: S) where
Distinct :: Distinct n => DistinctEvidence n
data ExtEvidence (n :: S) (l :: S) where
Ext :: Ext n l => ExtEvidence n l
assertDistinct :: (Distinct n, CoSinkable pattern) => pattern n l -> DistinctEvidence l
assertDistinct :: forall (n :: S) (pattern :: S -> S -> *) (l :: S).
(Distinct n, CoSinkable pattern) =>
pattern n l -> DistinctEvidence l
assertDistinct pattern n l
_ = DistinctEvidence l
forall (n :: S). DistinctEvidence n
unsafeDistinct
assertExt :: CoSinkable pattern => pattern n l -> ExtEvidence n l
assertExt :: forall (pattern :: S -> S -> *) (n :: S) (l :: S).
CoSinkable pattern =>
pattern n l -> ExtEvidence n l
assertExt pattern n l
_ = ExtEvidence n l
forall (n :: S) (l :: S). ExtEvidence n l
unsafeExt
unsafeDistinct :: DistinctEvidence n
unsafeDistinct :: forall (n :: S). DistinctEvidence n
unsafeDistinct = DistinctEvidence 'VoidS -> DistinctEvidence n
forall a b. a -> b
unsafeCoerce (DistinctEvidence 'VoidS
forall (n :: S). Distinct n => DistinctEvidence n
Distinct :: DistinctEvidence VoidS)
unsafeExt :: ExtEvidence n l
unsafeExt :: forall (n :: S) (l :: S). ExtEvidence n l
unsafeExt = ExtEvidence 'VoidS 'VoidS -> ExtEvidence n l
forall a b. a -> b
unsafeCoerce (ExtEvidence 'VoidS 'VoidS
forall (n :: S) (l :: S). Ext n l => ExtEvidence n l
Ext :: ExtEvidence VoidS VoidS)
unsinkName :: NameBinder n l -> Name l -> Maybe (Name n)
unsinkName :: forall (n :: S) (l :: S).
NameBinder n l -> Name l -> Maybe (Name n)
unsinkName NameBinder n l
binder name :: Name l
name@(UnsafeName RawName
raw)
| NameBinder n l -> Name l
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder n l
binder Name l -> Name l -> Bool
forall a. Eq a => a -> a -> Bool
== Name l
name = Maybe (Name n)
forall a. Maybe a
Nothing
| Bool
otherwise = Name n -> Maybe (Name n)
forall a. a -> Maybe a
Just (RawName -> Name n
forall (n :: S). RawName -> Name n
UnsafeName RawName
raw)
unsinkNamePattern
:: forall pattern n l. (Distinct n, CoSinkable pattern)
=> pattern n l -> Name l -> Maybe (Name n)
unsinkNamePattern :: forall (pattern :: S -> S -> *) (n :: S) (l :: S).
(Distinct n, CoSinkable pattern) =>
pattern n l -> Name l -> Maybe (Name n)
unsinkNamePattern pattern n l
pat = forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern @_ @n
(\Scope z
_scope' NameBinder x y
binder forall (z' :: S).
DExt z z' =>
UnsinkName x y z z' -> NameBinder z z' -> r'
k ->
NameBinder x y -> (DExt z Any => NameBinder z Any -> r') -> r'
forall (n :: S) (l :: S) (n' :: S) (l' :: S) r.
NameBinder n l -> (DExt n' l' => NameBinder n' l' -> r) -> r
unsafeAssertFresh NameBinder x y
binder ((DExt z Any => NameBinder z Any -> r') -> r')
-> (DExt z Any => NameBinder z Any -> r') -> r'
forall a b. (a -> b) -> a -> b
$ \NameBinder z Any
binder' ->
UnsinkName x y z Any -> NameBinder z Any -> r'
forall (z' :: S).
DExt z z' =>
UnsinkName x y z z' -> NameBinder z z' -> r'
k ((Name y -> Maybe (Name x)) -> UnsinkName x y z Any
forall (n :: S) (l :: S) (o :: S) (o' :: S).
(Name l -> Maybe (Name n)) -> UnsinkName n l o o'
UnsinkName (NameBinder x y -> Name y -> Maybe (Name x)
forall (n :: S) (l :: S).
NameBinder n l -> Name l -> Maybe (Name n)
unsinkName NameBinder x y
binder)) NameBinder z Any
binder')
UnsinkName x x z z'
forall (n :: S) (o :: S) (o' :: S). UnsinkName n n o o'
forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
UnsinkName x x z z'
idUnsinkName
UnsinkName x y z z'
-> UnsinkName y y' z' z'' -> UnsinkName x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
UnsinkName x y z z'
-> UnsinkName y y' z' z'' -> UnsinkName x y' z z''
forall (n :: S) (i :: S) (o :: S) (o' :: S) (l :: S) (o'' :: S).
UnsinkName n i o o'
-> UnsinkName i l o' o'' -> UnsinkName n l o o''
compUnsinkName
(String -> Scope n
forall a. HasCallStack => String -> a
error String
"impossible")
pattern n l
pat
(\(UnsinkName Name l -> Maybe (Name n)
unsink) pattern n o'
_ -> Name l -> Maybe (Name n)
unsink)
newtype UnsinkName n l (o :: S) (o' :: S) = UnsinkName (Name l -> Maybe (Name n))
idUnsinkName :: UnsinkName n n o o'
idUnsinkName :: forall (n :: S) (o :: S) (o' :: S). UnsinkName n n o o'
idUnsinkName = (Name n -> Maybe (Name n)) -> UnsinkName n n o o'
forall (n :: S) (l :: S) (o :: S) (o' :: S).
(Name l -> Maybe (Name n)) -> UnsinkName n l o o'
UnsinkName Name n -> Maybe (Name n)
forall a. a -> Maybe a
Just
compUnsinkName
:: UnsinkName n i o o'
-> UnsinkName i l o' o''
-> UnsinkName n l o o''
compUnsinkName :: forall (n :: S) (i :: S) (o :: S) (o' :: S) (l :: S) (o'' :: S).
UnsinkName n i o o'
-> UnsinkName i l o' o'' -> UnsinkName n l o o''
compUnsinkName (UnsinkName Name i -> Maybe (Name n)
f) (UnsinkName Name l -> Maybe (Name i)
g)
= (Name l -> Maybe (Name n)) -> UnsinkName n l o o''
forall (n :: S) (l :: S) (o :: S) (o' :: S).
(Name l -> Maybe (Name n)) -> UnsinkName n l o o'
UnsinkName (\Name l
name -> Name l -> Maybe (Name i)
g Name l
name Maybe (Name i) -> (Name i -> Maybe (Name n)) -> Maybe (Name n)
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Name i -> Maybe (Name n)
f)
data UnifyNameBinders (pattern :: S -> S -> Type) n l r where
SameNameBinders
:: NameBinders n l
-> UnifyNameBinders pattern n l l
RenameLeftNameBinder
:: NameBinders n r
-> (NameBinder n l -> NameBinder n r)
-> UnifyNameBinders pattern n l r
RenameRightNameBinder
:: NameBinders n l
-> (NameBinder n r -> NameBinder n l)
-> UnifyNameBinders pattern n l r
RenameBothBinders
:: NameBinders n lr
-> (NameBinder n l -> NameBinder n lr)
-> (NameBinder n r -> NameBinder n lr)
-> UnifyNameBinders pattern n l r
NotUnifiable :: UnifyNameBinders pattern n l r
unifyNameBinders
:: forall i l r pattern. Distinct i
=> NameBinder i l
-> NameBinder i r
-> UnifyNameBinders pattern i l r
unifyNameBinders :: forall (i :: S) (l :: S) (r :: S) (pattern :: S -> S -> *).
Distinct i =>
NameBinder i l -> NameBinder i r -> UnifyNameBinders pattern i l r
unifyNameBinders l :: NameBinder i l
l@(UnsafeNameBinder (UnsafeName RawName
i1)) r :: NameBinder i r
r@(UnsafeNameBinder (UnsafeName RawName
i2))
| RawName
i1 RawName -> RawName -> Bool
forall a. Eq a => a -> a -> Bool
== RawName
i2 = case NameBinder i l -> DistinctEvidence l
forall (n :: S) (pattern :: S -> S -> *) (l :: S).
(Distinct n, CoSinkable pattern) =>
pattern n l -> DistinctEvidence l
assertDistinct NameBinder i l
l of
DistinctEvidence l
Distinct -> UnifyNameBinders Any i l l -> UnifyNameBinders pattern i l r
forall a b. a -> b
unsafeCoerce (NameBinders i l -> UnifyNameBinders Any i l l
forall (n :: S) (l :: S) (pattern :: S -> S -> *).
NameBinders n l -> UnifyNameBinders pattern n l l
SameNameBinders (NameBinder i l -> NameBinders i l
forall (n :: S) (l :: S). NameBinder n l -> NameBinders n l
nameBindersSingleton NameBinder i l
l))
| RawName
i1 RawName -> RawName -> Bool
forall a. Ord a => a -> a -> Bool
< RawName
i2 = NameBinders i l
-> (NameBinder i r -> NameBinder i l)
-> UnifyNameBinders pattern i l r
forall (n :: S) (l :: S) (r :: S) (pattern :: S -> S -> *).
NameBinders n l
-> (NameBinder n r -> NameBinder n l)
-> UnifyNameBinders pattern n l r
RenameRightNameBinder (NameBinder i l -> NameBinders i l
forall (n :: S) (l :: S). NameBinder n l -> NameBinders n l
nameBindersSingleton NameBinder i l
l) ((NameBinder i r -> NameBinder i l)
-> UnifyNameBinders pattern i l r)
-> (NameBinder i r -> NameBinder i l)
-> UnifyNameBinders pattern i l r
forall a b. (a -> b) -> a -> b
$ \(UnsafeNameBinder (UnsafeName RawName
i'')) ->
if RawName
i'' RawName -> RawName -> Bool
forall a. Eq a => a -> a -> Bool
== RawName
i2 then Name l -> NameBinder i l
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder (RawName -> Name l
forall (n :: S). RawName -> Name n
UnsafeName RawName
i1) else Name l -> NameBinder i l
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder (RawName -> Name l
forall (n :: S). RawName -> Name n
UnsafeName RawName
i'')
| Bool
otherwise = NameBinders i r
-> (NameBinder i l -> NameBinder i r)
-> UnifyNameBinders pattern i l r
forall (n :: S) (r :: S) (l :: S) (pattern :: S -> S -> *).
NameBinders n r
-> (NameBinder n l -> NameBinder n r)
-> UnifyNameBinders pattern n l r
RenameLeftNameBinder (NameBinder i r -> NameBinders i r
forall (n :: S) (l :: S). NameBinder n l -> NameBinders n l
nameBindersSingleton NameBinder i r
r) ((NameBinder i l -> NameBinder i r)
-> UnifyNameBinders pattern i l r)
-> (NameBinder i l -> NameBinder i r)
-> UnifyNameBinders pattern i l r
forall a b. (a -> b) -> a -> b
$ \(UnsafeNameBinder (UnsafeName RawName
i')) ->
if RawName
i' RawName -> RawName -> Bool
forall a. Eq a => a -> a -> Bool
== RawName
i1 then Name r -> NameBinder i r
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder (RawName -> Name r
forall (n :: S). RawName -> Name n
UnsafeName RawName
i2) else Name r -> NameBinder i r
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder (RawName -> Name r
forall (n :: S). RawName -> Name n
UnsafeName RawName
i')
unsafeMergeUnifyBinders :: UnifyNameBinders pattern a a' a'' -> UnifyNameBinders pattern a''' b' b'' -> UnifyNameBinders pattern a b' b''
unsafeMergeUnifyBinders :: forall (pattern :: S -> S -> *) (a :: S) (a' :: S) (a'' :: S)
(a''' :: S) (b' :: S) (b'' :: S).
UnifyNameBinders pattern a a' a''
-> UnifyNameBinders pattern a''' b' b''
-> UnifyNameBinders pattern a b' b''
unsafeMergeUnifyBinders = \case
SameNameBinders NameBinders a a'
x -> \case
SameNameBinders NameBinders a''' b'
y -> NameBinders a b' -> UnifyNameBinders pattern a b' b'
forall (n :: S) (l :: S) (pattern :: S -> S -> *).
NameBinders n l -> UnifyNameBinders pattern n l l
SameNameBinders (NameBinders a a'
x NameBinders a a' -> NameBinders a''' b' -> NameBinders a b'
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b'
y)
RenameLeftNameBinder NameBinders a''' b''
y NameBinder a''' b' -> NameBinder a''' b''
f -> NameBinders a b''
-> (NameBinder a b' -> NameBinder a b'')
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (r :: S) (l :: S) (pattern :: S -> S -> *).
NameBinders n r
-> (NameBinder n l -> NameBinder n r)
-> UnifyNameBinders pattern n l r
RenameLeftNameBinder (NameBinders a a'
x NameBinders a a' -> NameBinders a''' b'' -> NameBinders a b''
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b''
y) ((NameBinder a''' b' -> NameBinder a''' b'')
-> NameBinder a b' -> NameBinder a b''
forall a b. a -> b
unsafeCoerce NameBinder a''' b' -> NameBinder a''' b''
f)
RenameRightNameBinder NameBinders a''' b'
y NameBinder a''' b'' -> NameBinder a''' b'
g -> NameBinders a b'
-> (NameBinder a b'' -> NameBinder a b')
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (l :: S) (r :: S) (pattern :: S -> S -> *).
NameBinders n l
-> (NameBinder n r -> NameBinder n l)
-> UnifyNameBinders pattern n l r
RenameRightNameBinder (NameBinders a a'
x NameBinders a a' -> NameBinders a''' b' -> NameBinders a b'
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b'
y) ((NameBinder a''' b'' -> NameBinder a''' b')
-> NameBinder a b'' -> NameBinder a b'
forall a b. a -> b
unsafeCoerce NameBinder a''' b'' -> NameBinder a''' b'
g)
RenameBothBinders NameBinders a''' lr
y NameBinder a''' b' -> NameBinder a''' lr
f NameBinder a''' b'' -> NameBinder a''' lr
g -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a a'
x NameBinders a a' -> NameBinders a''' lr -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' lr
y) ((NameBinder a''' b' -> NameBinder a''' lr)
-> NameBinder a b' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b' -> NameBinder a''' lr
f) ((NameBinder a''' b'' -> NameBinder a''' lr)
-> NameBinder a b'' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b'' -> NameBinder a''' lr
g)
UnifyNameBinders pattern a''' b' b''
NotUnifiable -> UnifyNameBinders pattern a b' b''
forall (pattern :: S -> S -> *) (n :: S) (l :: S) (r :: S).
UnifyNameBinders pattern n l r
NotUnifiable
RenameLeftNameBinder NameBinders a a''
x NameBinder a a' -> NameBinder a a''
f -> \case
SameNameBinders NameBinders a''' b'
y -> NameBinders a b''
-> (NameBinder a b' -> NameBinder a b'')
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (r :: S) (l :: S) (pattern :: S -> S -> *).
NameBinders n r
-> (NameBinder n l -> NameBinder n r)
-> UnifyNameBinders pattern n l r
RenameLeftNameBinder (NameBinders a a''
x NameBinders a a'' -> NameBinders a''' b' -> NameBinders a b''
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b'
y) ((NameBinder a a' -> NameBinder a a'')
-> NameBinder a b' -> NameBinder a b''
forall a b. a -> b
unsafeCoerce NameBinder a a' -> NameBinder a a''
f)
RenameLeftNameBinder NameBinders a''' b''
y NameBinder a''' b' -> NameBinder a''' b''
g -> NameBinders a b''
-> (NameBinder a b' -> NameBinder a b'')
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (r :: S) (l :: S) (pattern :: S -> S -> *).
NameBinders n r
-> (NameBinder n l -> NameBinder n r)
-> UnifyNameBinders pattern n l r
RenameLeftNameBinder (NameBinders a a''
x NameBinders a a'' -> NameBinders a''' b'' -> NameBinders a b''
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b''
y) ((NameBinder a a' -> NameBinder a a'') -> Any -> NameBinder a b''
forall a b. a -> b
unsafeCoerce NameBinder a a' -> NameBinder a a''
f (Any -> NameBinder a b'')
-> (NameBinder a b' -> Any) -> NameBinder a b' -> NameBinder a b''
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NameBinder a''' b' -> NameBinder a''' b'')
-> NameBinder a b' -> Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b' -> NameBinder a''' b''
g)
RenameRightNameBinder NameBinders a''' b'
y NameBinder a''' b'' -> NameBinder a''' b'
g -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a a''
x NameBinders a a'' -> NameBinders a''' b' -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b'
y) ((NameBinder a a' -> NameBinder a a'')
-> NameBinder a b' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a' -> NameBinder a a''
f) ((NameBinder a''' b'' -> NameBinder a''' b')
-> NameBinder a b'' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b'' -> NameBinder a''' b'
g)
RenameBothBinders NameBinders a''' lr
y NameBinder a''' b' -> NameBinder a''' lr
f' NameBinder a''' b'' -> NameBinder a''' lr
g -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a a''
x NameBinders a a'' -> NameBinders a''' lr -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' lr
y) ((NameBinder a a' -> NameBinder a a'') -> Any -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a' -> NameBinder a a''
f (Any -> NameBinder a Any)
-> (NameBinder a b' -> Any) -> NameBinder a b' -> NameBinder a Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NameBinder a''' b' -> NameBinder a''' lr)
-> NameBinder a b' -> Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b' -> NameBinder a''' lr
f') ((NameBinder a''' b'' -> NameBinder a''' lr)
-> NameBinder a b'' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b'' -> NameBinder a''' lr
g)
UnifyNameBinders pattern a''' b' b''
NotUnifiable -> UnifyNameBinders pattern a b' b''
forall (pattern :: S -> S -> *) (n :: S) (l :: S) (r :: S).
UnifyNameBinders pattern n l r
NotUnifiable
RenameRightNameBinder NameBinders a a'
x NameBinder a a'' -> NameBinder a a'
g -> \case
SameNameBinders NameBinders a''' b'
y -> NameBinders a b'
-> (NameBinder a b'' -> NameBinder a b')
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (l :: S) (r :: S) (pattern :: S -> S -> *).
NameBinders n l
-> (NameBinder n r -> NameBinder n l)
-> UnifyNameBinders pattern n l r
RenameRightNameBinder (NameBinders a a'
x NameBinders a a' -> NameBinders a''' b' -> NameBinders a b'
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b'
y) ((NameBinder a a'' -> NameBinder a a')
-> NameBinder a b'' -> NameBinder a b'
forall a b. a -> b
unsafeCoerce NameBinder a a'' -> NameBinder a a'
g)
RenameLeftNameBinder NameBinders a''' b''
y NameBinder a''' b' -> NameBinder a''' b''
f -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a a'
x NameBinders a a' -> NameBinders a''' b'' -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b''
y) ((NameBinder a''' b' -> NameBinder a''' b'')
-> NameBinder a b' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b' -> NameBinder a''' b''
f) ((NameBinder a a'' -> NameBinder a a')
-> NameBinder a b'' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a'' -> NameBinder a a'
g)
RenameRightNameBinder NameBinders a''' b'
y NameBinder a''' b'' -> NameBinder a''' b'
g' -> NameBinders a b'
-> (NameBinder a b'' -> NameBinder a b')
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (l :: S) (r :: S) (pattern :: S -> S -> *).
NameBinders n l
-> (NameBinder n r -> NameBinder n l)
-> UnifyNameBinders pattern n l r
RenameRightNameBinder (NameBinders a a'
x NameBinders a a' -> NameBinders a''' b' -> NameBinders a b'
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b'
y) ((NameBinder a a'' -> NameBinder a a') -> Any -> NameBinder a b'
forall a b. a -> b
unsafeCoerce NameBinder a a'' -> NameBinder a a'
g (Any -> NameBinder a b')
-> (NameBinder a b'' -> Any) -> NameBinder a b'' -> NameBinder a b'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NameBinder a''' b'' -> NameBinder a''' b')
-> NameBinder a b'' -> Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b'' -> NameBinder a''' b'
g')
RenameBothBinders NameBinders a''' lr
y NameBinder a''' b' -> NameBinder a''' lr
f NameBinder a''' b'' -> NameBinder a''' lr
g' -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a a'
x NameBinders a a' -> NameBinders a''' lr -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' lr
y) ((NameBinder a''' b' -> NameBinder a''' lr)
-> NameBinder a b' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b' -> NameBinder a''' lr
f) ((NameBinder a a'' -> NameBinder a a') -> Any -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a'' -> NameBinder a a'
g (Any -> NameBinder a Any)
-> (NameBinder a b'' -> Any)
-> NameBinder a b''
-> NameBinder a Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NameBinder a''' b'' -> NameBinder a''' lr)
-> NameBinder a b'' -> Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b'' -> NameBinder a''' lr
g')
UnifyNameBinders pattern a''' b' b''
NotUnifiable -> UnifyNameBinders pattern a b' b''
forall (pattern :: S -> S -> *) (n :: S) (l :: S) (r :: S).
UnifyNameBinders pattern n l r
NotUnifiable
RenameBothBinders NameBinders a lr
x NameBinder a a' -> NameBinder a lr
f NameBinder a a'' -> NameBinder a lr
g -> \case
SameNameBinders NameBinders a''' b'
y -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a lr
x NameBinders a lr -> NameBinders a''' b' -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b'
y) ((NameBinder a a' -> NameBinder a lr)
-> NameBinder a b' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a' -> NameBinder a lr
f) ((NameBinder a a'' -> NameBinder a lr)
-> NameBinder a b'' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a'' -> NameBinder a lr
g)
RenameLeftNameBinder NameBinders a''' b''
y NameBinder a''' b' -> NameBinder a''' b''
f' -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a lr
x NameBinders a lr -> NameBinders a''' b'' -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b''
y) ((NameBinder a a' -> NameBinder a lr) -> Any -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a' -> NameBinder a lr
f (Any -> NameBinder a Any)
-> (NameBinder a b' -> Any) -> NameBinder a b' -> NameBinder a Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NameBinder a''' b' -> NameBinder a''' b'')
-> NameBinder a b' -> Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b' -> NameBinder a''' b''
f') ((NameBinder a a'' -> NameBinder a lr)
-> NameBinder a b'' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a'' -> NameBinder a lr
g)
RenameRightNameBinder NameBinders a''' b'
y NameBinder a''' b'' -> NameBinder a''' b'
g' -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a lr
x NameBinders a lr -> NameBinders a''' b' -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' b'
y) ((NameBinder a a' -> NameBinder a lr)
-> NameBinder a b' -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a' -> NameBinder a lr
f) ((NameBinder a a'' -> NameBinder a lr) -> Any -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a'' -> NameBinder a lr
g (Any -> NameBinder a Any)
-> (NameBinder a b'' -> Any)
-> NameBinder a b''
-> NameBinder a Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NameBinder a''' b'' -> NameBinder a''' b')
-> NameBinder a b'' -> Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b'' -> NameBinder a''' b'
g')
RenameBothBinders NameBinders a''' lr
y NameBinder a''' b' -> NameBinder a''' lr
f' NameBinder a''' b'' -> NameBinder a''' lr
g' -> NameBinders a Any
-> (NameBinder a b' -> NameBinder a Any)
-> (NameBinder a b'' -> NameBinder a Any)
-> UnifyNameBinders pattern a b' b''
forall (n :: S) (k :: S) (l :: S) (r :: S)
(pattern :: S -> S -> *).
NameBinders n k
-> (NameBinder n l -> NameBinder n k)
-> (NameBinder n r -> NameBinder n k)
-> UnifyNameBinders pattern n l r
RenameBothBinders (NameBinders a lr
x NameBinders a lr -> NameBinders a''' lr -> NameBinders a Any
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
`unsafeMergeNameBinders` NameBinders a''' lr
y) ((NameBinder a a' -> NameBinder a lr) -> Any -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a' -> NameBinder a lr
f (Any -> NameBinder a Any)
-> (NameBinder a b' -> Any) -> NameBinder a b' -> NameBinder a Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NameBinder a''' b' -> NameBinder a''' lr)
-> NameBinder a b' -> Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b' -> NameBinder a''' lr
f') ((NameBinder a a'' -> NameBinder a lr) -> Any -> NameBinder a Any
forall a b. a -> b
unsafeCoerce NameBinder a a'' -> NameBinder a lr
g (Any -> NameBinder a Any)
-> (NameBinder a b'' -> Any)
-> NameBinder a b''
-> NameBinder a Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NameBinder a''' b'' -> NameBinder a''' lr)
-> NameBinder a b'' -> Any
forall a b. a -> b
unsafeCoerce NameBinder a''' b'' -> NameBinder a''' lr
g')
UnifyNameBinders pattern a''' b' b''
NotUnifiable -> UnifyNameBinders pattern a b' b''
forall (pattern :: S -> S -> *) (n :: S) (l :: S) (r :: S).
UnifyNameBinders pattern n l r
NotUnifiable
UnifyNameBinders pattern a a' a''
NotUnifiable -> UnifyNameBinders pattern a b' b''
-> UnifyNameBinders pattern a''' b' b''
-> UnifyNameBinders pattern a b' b''
forall a b. a -> b -> a
const (UnifyNameBinders pattern a b' b''
forall (pattern :: S -> S -> *) (n :: S) (l :: S) (r :: S).
UnifyNameBinders pattern n l r
NotUnifiable)
andThenUnifyPatterns
:: (UnifiablePattern pattern, Distinct l, Distinct l')
=> UnifyNameBinders pattern n l l'
-> (pattern l r, pattern l' r')
-> UnifyNameBinders pattern n r r'
andThenUnifyPatterns :: forall (pattern :: S -> S -> *) (l :: S) (l' :: S) (n :: S)
(r :: S) (r' :: S).
(UnifiablePattern pattern, Distinct l, Distinct l') =>
UnifyNameBinders pattern n l l'
-> (pattern l r, pattern l' r') -> UnifyNameBinders pattern n r r'
andThenUnifyPatterns UnifyNameBinders pattern n l l'
u (pattern l r
l, pattern l' r'
r) = UnifyNameBinders pattern n l l'
-> UnifyNameBinders pattern l' r r'
-> UnifyNameBinders pattern n r r'
forall (pattern :: S -> S -> *) (a :: S) (a' :: S) (a'' :: S)
(a''' :: S) (b' :: S) (b'' :: S).
UnifyNameBinders pattern a a' a''
-> UnifyNameBinders pattern a''' b' b''
-> UnifyNameBinders pattern a b' b''
unsafeMergeUnifyBinders UnifyNameBinders pattern n l l'
u (pattern l' r -> pattern l' r' -> UnifyNameBinders pattern l' r r'
forall (n :: S) (l :: S) (r :: S).
Distinct n =>
pattern n l -> pattern n r -> UnifyNameBinders pattern n l r
forall (pattern :: S -> S -> *) (n :: S) (l :: S) (r :: S).
(UnifiablePattern pattern, Distinct n) =>
pattern n l -> pattern n r -> UnifyNameBinders pattern n l r
unifyPatterns (pattern l r -> pattern l' r
forall a b. a -> b
unsafeCoerce pattern l r
l) pattern l' r'
r)
andThenUnifyNameBinders
:: (UnifiablePattern pattern, Distinct l, Distinct l')
=> UnifyNameBinders pattern n l l'
-> (NameBinder l r, NameBinder l' r')
-> UnifyNameBinders pattern n r r'
andThenUnifyNameBinders :: forall (pattern :: S -> S -> *) (l :: S) (l' :: S) (n :: S)
(r :: S) (r' :: S).
(UnifiablePattern pattern, Distinct l, Distinct l') =>
UnifyNameBinders pattern n l l'
-> (NameBinder l r, NameBinder l' r')
-> UnifyNameBinders pattern n r r'
andThenUnifyNameBinders UnifyNameBinders pattern n l l'
u (NameBinder l r
l, NameBinder l' r'
r) = UnifyNameBinders pattern n l l'
-> UnifyNameBinders pattern l' r r'
-> UnifyNameBinders pattern n r r'
forall (pattern :: S -> S -> *) (a :: S) (a' :: S) (a'' :: S)
(a''' :: S) (b' :: S) (b'' :: S).
UnifyNameBinders pattern a a' a''
-> UnifyNameBinders pattern a''' b' b''
-> UnifyNameBinders pattern a b' b''
unsafeMergeUnifyBinders UnifyNameBinders pattern n l l'
u (NameBinder l' r
-> NameBinder l' r' -> UnifyNameBinders pattern l' r r'
forall (i :: S) (l :: S) (r :: S) (pattern :: S -> S -> *).
Distinct i =>
NameBinder i l -> NameBinder i r -> UnifyNameBinders pattern i l r
unifyNameBinders (NameBinder l r -> NameBinder l' r
forall a b. a -> b
unsafeCoerce NameBinder l r
l) NameBinder l' r'
r)
newtype NameBinders (n :: S) (l :: S) = UnsafeNameBinders IntSet
unsafeMergeNameBinders :: NameBinders a b -> NameBinders c d -> NameBinders n l
unsafeMergeNameBinders :: forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
unsafeMergeNameBinders (UnsafeNameBinders RawScope
x) (UnsafeNameBinders RawScope
y) = RawScope -> NameBinders n l
forall (n :: S) (l :: S). RawScope -> NameBinders n l
UnsafeNameBinders (RawScope
x RawScope -> RawScope -> RawScope
forall a. Semigroup a => a -> a -> a
<> RawScope
y)
emptyNameBinders :: NameBinders n n
emptyNameBinders :: forall (n :: S). NameBinders n n
emptyNameBinders = RawScope -> NameBinders n n
forall (n :: S) (l :: S). RawScope -> NameBinders n l
UnsafeNameBinders RawScope
IntSet.empty
mergeNameBinders :: NameBinders n i -> NameBinders i l -> NameBinders n l
mergeNameBinders :: forall (n :: S) (i :: S) (l :: S).
NameBinders n i -> NameBinders i l -> NameBinders n l
mergeNameBinders = NameBinders n i -> NameBinders i l -> NameBinders n l
forall (a :: S) (b :: S) (c :: S) (d :: S) (n :: S) (l :: S).
NameBinders a b -> NameBinders c d -> NameBinders n l
unsafeMergeNameBinders
nameBindersSingleton :: NameBinder n l -> NameBinders n l
NameBinder n l
binder = RawScope -> NameBinders n l
forall (n :: S) (l :: S). RawScope -> NameBinders n l
UnsafeNameBinders (RawName -> RawScope
IntSet.singleton (Name l -> RawName
forall (l :: S). Name l -> RawName
nameId (NameBinder n l -> Name l
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder n l
binder)))
data NameBinderList n l where
NameBinderListEmpty :: NameBinderList n n
NameBinderListCons
:: NameBinder n i
-> NameBinderList i l
-> NameBinderList n l
nameBindersList :: NameBinders n l -> NameBinderList n l
nameBindersList :: forall (n :: S) (l :: S). NameBinders n l -> NameBinderList n l
nameBindersList (UnsafeNameBinders RawScope
names) = [RawName] -> NameBinderList n l
forall {i :: S} {l :: S}. [RawName] -> NameBinderList i l
go (RawScope -> [RawName]
IntSet.toList RawScope
names)
where
go :: [RawName] -> NameBinderList i l
go [] = NameBinderList Any Any -> NameBinderList i l
forall a b. a -> b
unsafeCoerce NameBinderList Any Any
forall (n :: S). NameBinderList n n
NameBinderListEmpty
go (RawName
x:[RawName]
xs) = NameBinder i i -> NameBinderList i l -> NameBinderList i l
forall (n :: S) (k :: S) (l :: S).
NameBinder n k -> NameBinderList k l -> NameBinderList n l
NameBinderListCons (Name i -> NameBinder i i
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder (RawName -> Name i
forall (n :: S). RawName -> Name n
UnsafeName RawName
x)) ([RawName] -> NameBinderList i l
go [RawName]
xs)
fromNameBindersList :: NameBinderList n l -> NameBinders n l
fromNameBindersList :: forall (n :: S) (l :: S). NameBinderList n l -> NameBinders n l
fromNameBindersList = RawScope -> NameBinders n l
forall (n :: S) (l :: S). RawScope -> NameBinders n l
UnsafeNameBinders (RawScope -> NameBinders n l)
-> (NameBinderList n l -> RawScope)
-> NameBinderList n l
-> NameBinders n l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [RawName] -> RawScope
IntSet.fromList ([RawName] -> RawScope)
-> (NameBinderList n l -> [RawName])
-> NameBinderList n l
-> RawScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameBinderList n l -> [RawName]
forall (n :: S) (l :: S). NameBinderList n l -> [RawName]
go
where
go :: NameBinderList n l -> [RawName]
go :: forall (n :: S) (l :: S). NameBinderList n l -> [RawName]
go NameBinderList n l
NameBinderListEmpty = []
go (NameBinderListCons NameBinder n i
binder NameBinderList i l
binders) = Name i -> RawName
forall (l :: S). Name l -> RawName
nameId (NameBinder n i -> Name i
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder n i
binder) RawName -> [RawName] -> [RawName]
forall a. a -> [a] -> [a]
: NameBinderList i l -> [RawName]
forall (n :: S) (l :: S). NameBinderList n l -> [RawName]
go NameBinderList i l
binders
instance CoSinkable NameBinders where
coSinkabilityProof :: forall (n :: S) (n' :: S) (l :: S) r.
(Name n -> Name n')
-> NameBinders n l
-> (forall (l' :: S).
(Name l -> Name l') -> NameBinders n' l' -> r)
-> r
coSinkabilityProof Name n -> Name n'
_rename (UnsafeNameBinders RawScope
names) forall (l' :: S). (Name l -> Name l') -> NameBinders n' l' -> r
cont =
(Name l -> Name Any) -> NameBinders n' Any -> r
forall (l' :: S). (Name l -> Name l') -> NameBinders n' l' -> r
cont Name l -> Name Any
forall a b. a -> b
unsafeCoerce (RawScope -> NameBinders n' Any
forall (n :: S) (l :: S). RawScope -> NameBinders n l
UnsafeNameBinders RawScope
names)
withPattern :: forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> NameBinders n l
-> (forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinders o o' -> r)
-> r
withPattern forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
withBinder forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
unit forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
comp Scope o
scope NameBinders n l
binders forall (o' :: S). DExt o o' => f n l o o' -> NameBinders o o' -> r
cont =
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> NameBinderList n l
-> (forall {o' :: S}.
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r)
-> r
forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> NameBinderList n l
-> (forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r)
-> r
forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
withBinder f x x z z'
forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
unit f x y z z' -> f y y' z' z'' -> f x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
comp Scope o
scope (NameBinders n l -> NameBinderList n l
forall (n :: S) (l :: S). NameBinders n l -> NameBinderList n l
nameBindersList NameBinders n l
binders) ((forall {o' :: S}.
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r)
-> r)
-> (forall {o' :: S}.
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \f n l o o'
f NameBinderList o o'
binders' ->
f n l o o' -> NameBinders o o' -> r
forall (o' :: S). DExt o o' => f n l o o' -> NameBinders o o' -> r
cont f n l o o'
f (NameBinderList o o' -> NameBinders o o'
forall (n :: S) (l :: S). NameBinderList n l -> NameBinders n l
fromNameBindersList NameBinderList o o'
binders')
instance CoSinkable NameBinderList where
coSinkabilityProof :: forall (n :: S) (n' :: S) (l :: S) r.
(Name n -> Name n')
-> NameBinderList n l
-> (forall (l' :: S).
(Name l -> Name l') -> NameBinderList n' l' -> r)
-> r
coSinkabilityProof Name n -> Name n'
rename NameBinderList n l
NameBinderListEmpty forall (l' :: S). (Name l -> Name l') -> NameBinderList n' l' -> r
cont = (Name l -> Name n') -> NameBinderList n' n' -> r
forall (l' :: S). (Name l -> Name l') -> NameBinderList n' l' -> r
cont Name n -> Name n'
Name l -> Name n'
rename NameBinderList n' n'
forall (n :: S). NameBinderList n n
NameBinderListEmpty
coSinkabilityProof Name n -> Name n'
rename (NameBinderListCons NameBinder n i
binder NameBinderList i l
binders) forall (l' :: S). (Name l -> Name l') -> NameBinderList n' l' -> r
cont =
(Name n -> Name n')
-> NameBinder n i
-> (forall {l' :: S}. (Name i -> Name l') -> NameBinder n' l' -> r)
-> r
forall (n :: S) (n' :: S) (l :: S) r.
(Name n -> Name n')
-> NameBinder n l
-> (forall (l' :: S). (Name l -> Name l') -> NameBinder n' l' -> r)
-> r
forall (pattern :: S -> S -> *) (n :: S) (n' :: S) (l :: S) r.
CoSinkable pattern =>
(Name n -> Name n')
-> pattern n l
-> (forall (l' :: S). (Name l -> Name l') -> pattern n' l' -> r)
-> r
coSinkabilityProof Name n -> Name n'
rename NameBinder n i
binder ((forall {l' :: S}. (Name i -> Name l') -> NameBinder n' l' -> r)
-> r)
-> (forall {l' :: S}. (Name i -> Name l') -> NameBinder n' l' -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \Name i -> Name l'
rename' NameBinder n' l'
binder' ->
(Name i -> Name l')
-> NameBinderList i l
-> (forall {l' :: S}.
(Name l -> Name l') -> NameBinderList l' l' -> r)
-> r
forall (n :: S) (n' :: S) (l :: S) r.
(Name n -> Name n')
-> NameBinderList n l
-> (forall (l' :: S).
(Name l -> Name l') -> NameBinderList n' l' -> r)
-> r
forall (pattern :: S -> S -> *) (n :: S) (n' :: S) (l :: S) r.
CoSinkable pattern =>
(Name n -> Name n')
-> pattern n l
-> (forall (l' :: S). (Name l -> Name l') -> pattern n' l' -> r)
-> r
coSinkabilityProof Name i -> Name l'
rename' NameBinderList i l
binders ((forall {l' :: S}.
(Name l -> Name l') -> NameBinderList l' l' -> r)
-> r)
-> (forall {l' :: S}.
(Name l -> Name l') -> NameBinderList l' l' -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \Name l -> Name l'
rename'' NameBinderList l' l'
binders' ->
(Name l -> Name l') -> NameBinderList n' l' -> r
forall (l' :: S). (Name l -> Name l') -> NameBinderList n' l' -> r
cont Name l -> Name l'
rename'' (NameBinder n' l' -> NameBinderList l' l' -> NameBinderList n' l'
forall (n :: S) (k :: S) (l :: S).
NameBinder n k -> NameBinderList k l -> NameBinderList n l
NameBinderListCons NameBinder n' l'
binder' NameBinderList l' l'
binders')
withPattern :: forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> NameBinderList n l
-> (forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r)
-> r
withPattern forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
withBinder forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
unit forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
comp Scope o
scope NameBinderList n l
binders forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r
cont = case NameBinderList n l
binders of
NameBinderList n l
NameBinderListEmpty -> f n l o o -> NameBinderList o o -> r
forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r
cont f n l o o
f l l o o
forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
unit NameBinderList o o
forall (n :: S). NameBinderList n n
NameBinderListEmpty
NameBinderListCons NameBinder n i
x NameBinderList i l
xs ->
Scope o
-> NameBinder n i
-> (forall {z' :: S}.
DExt o z' =>
f n i o z' -> NameBinder o z' -> r)
-> r
forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
withBinder Scope o
scope NameBinder n i
x ((forall {z' :: S}.
DExt o z' =>
f n i o z' -> NameBinder o z' -> r)
-> r)
-> (forall {z' :: S}.
DExt o z' =>
f n i o z' -> NameBinder o z' -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \f n i o z'
f NameBinder o z'
x' ->
let scope' :: Scope z'
scope' = NameBinder o z' -> Scope o -> Scope z'
forall (n :: S) (pattern :: S -> S -> *) (l :: S).
(Distinct n, CoSinkable pattern) =>
pattern n l -> Scope n -> Scope l
extendScopePattern NameBinder o z'
x' Scope o
scope
in (forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope z'
-> NameBinderList i l
-> (forall {o' :: S}.
DExt z' o' =>
f i l z' o' -> NameBinderList z' o' -> r)
-> r
forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> NameBinderList n l
-> (forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r)
-> r
forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
withBinder f x x z z'
forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
unit f x y z z' -> f y y' z' z'' -> f x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
comp Scope z'
scope' NameBinderList i l
xs ((forall {o' :: S}.
DExt z' o' =>
f i l z' o' -> NameBinderList z' o' -> r)
-> r)
-> (forall {o' :: S}.
DExt z' o' =>
f i l z' o' -> NameBinderList z' o' -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \f i l z' o'
f' NameBinderList z' o'
xs' ->
f n l o o' -> NameBinderList o o' -> r
forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinderList o o' -> r
cont (f n i o z' -> f i l z' o' -> f n l o o'
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
comp f n i o z'
f f i l z' o'
f') (NameBinder o z' -> NameBinderList z' o' -> NameBinderList o o'
forall (n :: S) (k :: S) (l :: S).
NameBinder n k -> NameBinderList k l -> NameBinderList n l
NameBinderListCons NameBinder o z'
x' NameBinderList z' o'
xs')
data V2 (n :: S) (l :: S)
absurd2 :: V2 n l -> a
absurd2 :: forall (n :: S) (l :: S) a. V2 n l -> a
absurd2 V2 n l
v2 = case V2 n l
v2 of {}
instance CoSinkable V2 where
coSinkabilityProof :: forall (n :: S) (n' :: S) (l :: S) r.
(Name n -> Name n')
-> V2 n l
-> (forall (l' :: S). (Name l -> Name l') -> V2 n' l' -> r)
-> r
coSinkabilityProof Name n -> Name n'
_ V2 n l
v2 forall (l' :: S). (Name l -> Name l') -> V2 n' l' -> r
_ = V2 n l -> r
forall (n :: S) (l :: S) a. V2 n l -> a
absurd2 V2 n l
v2
withPattern :: forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> V2 n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> V2 o o' -> r)
-> r
withPattern forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
_ forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
_ forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
_ Scope o
_ V2 n l
v2 forall (o' :: S). DExt o o' => f n l o o' -> V2 o o' -> r
_ = V2 n l -> r
forall (n :: S) (l :: S) a. V2 n l -> a
absurd2 V2 n l
v2
instance UnifiablePattern V2 where
unifyPatterns :: forall (n :: S) (l :: S) (r :: S).
Distinct n =>
V2 n l -> V2 n r -> UnifyNameBinders V2 n l r
unifyPatterns = V2 n l -> V2 n r -> UnifyNameBinders V2 n l r
forall (n :: S) (l :: S) a. V2 n l -> a
absurd2
data U2 (n :: S) (l :: S) where
U2 :: U2 n n
instance CoSinkable U2 where
coSinkabilityProof :: forall (n :: S) (n' :: S) (l :: S) r.
(Name n -> Name n')
-> U2 n l
-> (forall (l' :: S). (Name l -> Name l') -> U2 n' l' -> r)
-> r
coSinkabilityProof Name n -> Name n'
rename U2 n l
U2 forall (l' :: S). (Name l -> Name l') -> U2 n' l' -> r
cont = (Name l -> Name n') -> U2 n' n' -> r
forall (l' :: S). (Name l -> Name l') -> U2 n' l' -> r
cont Name n -> Name n'
Name l -> Name n'
rename U2 n' n'
forall (n :: S). U2 n n
U2
withPattern :: forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> U2 n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> U2 o o' -> r)
-> r
withPattern forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
_withBinder forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
unit forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
_combine Scope o
_scope U2 n l
U2 forall (o' :: S). DExt o o' => f n l o o' -> U2 o o' -> r
cont = f n l o o -> U2 o o -> r
forall (o' :: S). DExt o o' => f n l o o' -> U2 o o' -> r
cont f n l o o
f l l o o
forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
unit U2 o o
forall (n :: S). U2 n n
U2
instance UnifiablePattern U2 where
unifyPatterns :: forall (n :: S) (l :: S) (r :: S).
Distinct n =>
U2 n l -> U2 n r -> UnifyNameBinders U2 n l r
unifyPatterns U2 n l
U2 U2 n r
U2 = NameBinders n l -> UnifyNameBinders U2 n l l
forall (n :: S) (l :: S) (pattern :: S -> S -> *).
NameBinders n l -> UnifyNameBinders pattern n l l
SameNameBinders NameBinders n n
NameBinders n l
forall (n :: S). NameBinders n n
emptyNameBinders
class CoSinkable pattern => UnifiablePattern pattern where
unifyPatterns :: Distinct n => pattern n l -> pattern n r -> UnifyNameBinders pattern n l r
default unifyPatterns
:: (CoSinkable pattern, Distinct n)
=> pattern n l -> pattern n r -> UnifyNameBinders pattern n l r
unifyPatterns pattern n l
l pattern n r
r = UnifyNameBinders NameBinderList n l r
-> UnifyNameBinders pattern n l r
forall a b. Coercible a b => a -> b
coerce (NameBinderList n l
-> NameBinderList n r -> UnifyNameBinders NameBinderList n l r
forall (n :: S) (l :: S) (r :: S).
Distinct n =>
NameBinderList n l
-> NameBinderList n r -> UnifyNameBinders NameBinderList n l r
forall (pattern :: S -> S -> *) (n :: S) (l :: S) (r :: S).
(UnifiablePattern pattern, Distinct n) =>
pattern n l -> pattern n r -> UnifyNameBinders pattern n l r
unifyPatterns (pattern n l -> NameBinderList n l
forall (binder :: S -> S -> *) (n :: S) (l :: S).
CoSinkable binder =>
binder n l -> NameBinderList n l
nameBinderListOf pattern n l
l) (pattern n r -> NameBinderList n r
forall (binder :: S -> S -> *) (n :: S) (l :: S).
CoSinkable binder =>
binder n l -> NameBinderList n l
nameBinderListOf pattern n r
r))
instance UnifiablePattern NameBinderList where
unifyPatterns :: forall (n :: S) (l :: S) (r :: S).
Distinct n =>
NameBinderList n l
-> NameBinderList n r -> UnifyNameBinders NameBinderList n l r
unifyPatterns NameBinderList n l
NameBinderListEmpty NameBinderList n r
NameBinderListEmpty = NameBinders n l -> UnifyNameBinders NameBinderList n l l
forall (n :: S) (l :: S) (pattern :: S -> S -> *).
NameBinders n l -> UnifyNameBinders pattern n l l
SameNameBinders NameBinders n n
NameBinders n l
forall (n :: S). NameBinders n n
emptyNameBinders
unifyPatterns (NameBinderListCons NameBinder n i
x NameBinderList i l
xs) (NameBinderListCons NameBinder n i
y NameBinderList i r
ys) =
case (NameBinder n i -> DistinctEvidence i
forall (n :: S) (pattern :: S -> S -> *) (l :: S).
(Distinct n, CoSinkable pattern) =>
pattern n l -> DistinctEvidence l
assertDistinct NameBinder n i
x, NameBinder n i -> DistinctEvidence i
forall (n :: S) (pattern :: S -> S -> *) (l :: S).
(Distinct n, CoSinkable pattern) =>
pattern n l -> DistinctEvidence l
assertDistinct NameBinder n i
y) of
(DistinctEvidence i
Distinct, DistinctEvidence i
Distinct) -> NameBinder n i
-> NameBinder n i -> UnifyNameBinders NameBinderList n i i
forall (i :: S) (l :: S) (r :: S) (pattern :: S -> S -> *).
Distinct i =>
NameBinder i l -> NameBinder i r -> UnifyNameBinders pattern i l r
unifyNameBinders NameBinder n i
x NameBinder n i
y UnifyNameBinders NameBinderList n i i
-> (NameBinderList i l, NameBinderList i r)
-> UnifyNameBinders NameBinderList n l r
forall (pattern :: S -> S -> *) (l :: S) (l' :: S) (n :: S)
(r :: S) (r' :: S).
(UnifiablePattern pattern, Distinct l, Distinct l') =>
UnifyNameBinders pattern n l l'
-> (pattern l r, pattern l' r') -> UnifyNameBinders pattern n r r'
`andThenUnifyPatterns` (NameBinderList i l
xs, NameBinderList i r
ys)
class UnifiableInPattern a where
unifyInPattern :: a -> a -> Bool
default unifyInPattern :: Eq a => a -> a -> Bool
unifyInPattern = a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
instance UnifiablePattern NameBinder where
unifyPatterns :: forall (n :: S) (l :: S) (r :: S).
Distinct n =>
NameBinder n l
-> NameBinder n r -> UnifyNameBinders NameBinder n l r
unifyPatterns = NameBinder n l
-> NameBinder n r -> UnifyNameBinders NameBinder n l r
forall (i :: S) (l :: S) (r :: S) (pattern :: S -> S -> *).
Distinct i =>
NameBinder i l -> NameBinder i r -> UnifyNameBinders pattern i l r
unifyNameBinders
unsafeEqPattern :: (UnifiablePattern pattern, Distinct n) => pattern n l -> pattern n' l' -> Bool
unsafeEqPattern :: forall (pattern :: S -> S -> *) (n :: S) (l :: S) (n' :: S)
(l' :: S).
(UnifiablePattern pattern, Distinct n) =>
pattern n l -> pattern n' l' -> Bool
unsafeEqPattern pattern n l
l pattern n' l'
r =
case pattern n l -> pattern n Any -> UnifyNameBinders pattern n l Any
forall (n :: S) (l :: S) (r :: S).
Distinct n =>
pattern n l -> pattern n r -> UnifyNameBinders pattern n l r
forall (pattern :: S -> S -> *) (n :: S) (l :: S) (r :: S).
(UnifiablePattern pattern, Distinct n) =>
pattern n l -> pattern n r -> UnifyNameBinders pattern n l r
unifyPatterns pattern n l
l (pattern n' l' -> pattern n Any
forall a b. a -> b
unsafeCoerce pattern n' l'
r) of
SameNameBinders{} -> Bool
True
UnifyNameBinders pattern n l Any
_ -> Bool
False
class Sinkable (e :: S -> Type) where
sinkabilityProof
:: (Name n -> Name l)
-> e n
-> e l
default sinkabilityProof
:: (GenericK e, GSinkableK (RepK e)) => (Name n -> Name l) -> e n -> e l
sinkabilityProof Name n -> Name l
rename = RepK e (l ':&&: 'LoT0) -> e l
RepK e (l ':&&: 'LoT0) -> e :@@: (l ':&&: 'LoT0)
forall k (f :: k) (x :: LoT k). GenericK f => RepK f x -> f :@@: x
forall (x :: LoT (S -> *)). RepK e x -> e :@@: x
toK (RepK e (l ':&&: 'LoT0) -> e l)
-> (e n -> RepK e (l ':&&: 'LoT0)) -> e n -> e l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name n -> Name l)
-> RepK e (n ':&&: 'LoT0) -> RepK e (l ':&&: 'LoT0)
forall (f :: LoT (S -> *) -> *) (n :: S) (n' :: S).
GSinkableK f =>
(Name n -> Name n') -> f (n ':&&: 'LoT0) -> f (n' ':&&: 'LoT0)
gsinkabilityProof1 Name n -> Name l
rename (RepK e (n ':&&: 'LoT0) -> RepK e (l ':&&: 'LoT0))
-> (e n -> RepK e (n ':&&: 'LoT0)) -> e n -> RepK e (l ':&&: 'LoT0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e n -> RepK e (n ':&&: 'LoT0)
(e :@@: (n ':&&: 'LoT0)) -> RepK e (n ':&&: 'LoT0)
forall k (f :: k) (x :: LoT k).
GenericK f =>
(f :@@: x) -> RepK f x
forall (x :: LoT (S -> *)). (e :@@: x) -> RepK e x
fromK
instance Sinkable Name where
sinkabilityProof :: forall (n :: S) (l :: S). (Name n -> Name l) -> Name n -> Name l
sinkabilityProof Name n -> Name l
rename = Name n -> Name l
rename
sink :: (Sinkable e, DExt n l) => e n -> e l
sink :: forall (e :: S -> *) (n :: S) (l :: S).
(Sinkable e, DExt n l) =>
e n -> e l
sink = e n -> e l
forall a b. a -> b
unsafeCoerce
extendRenaming
:: CoSinkable pattern
=> (Name n -> Name n')
-> pattern n l
-> (forall l'. (Name l -> Name l') -> pattern n' l' -> r )
-> r
extendRenaming :: forall (pattern :: S -> S -> *) (n :: S) (n' :: S) (l :: S) r.
CoSinkable pattern =>
(Name n -> Name n')
-> pattern n l
-> (forall (l' :: S). (Name l -> Name l') -> pattern n' l' -> r)
-> r
extendRenaming Name n -> Name n'
_ pattern n l
pattern forall (l' :: S). (Name l -> Name l') -> pattern n' l' -> r
cont =
(Name l -> Name Any) -> pattern n' Any -> r
forall (l' :: S). (Name l -> Name l') -> pattern n' l' -> r
cont Name l -> Name Any
forall a b. a -> b
unsafeCoerce (pattern n l -> pattern n' Any
forall a b. a -> b
unsafeCoerce pattern n l
pattern)
extendNameBinderRenaming
:: CoSinkable pattern
=> (NameBinder i n -> NameBinder i n')
-> pattern n l
-> (forall l'. (NameBinder n' l -> NameBinder n' l') -> pattern n' l' -> r )
-> r
extendNameBinderRenaming :: forall (pattern :: S -> S -> *) (i :: S) (n :: S) (n' :: S)
(l :: S) r.
CoSinkable pattern =>
(NameBinder i n -> NameBinder i n')
-> pattern n l
-> (forall (l' :: S).
(NameBinder n' l -> NameBinder n' l') -> pattern n' l' -> r)
-> r
extendNameBinderRenaming NameBinder i n -> NameBinder i n'
_ pattern n l
pattern forall (l' :: S).
(NameBinder n' l -> NameBinder n' l') -> pattern n' l' -> r
cont =
(NameBinder n' l -> NameBinder n' Any) -> pattern n' Any -> r
forall (l' :: S).
(NameBinder n' l -> NameBinder n' l') -> pattern n' l' -> r
cont NameBinder n' l -> NameBinder n' Any
forall a b. a -> b
unsafeCoerce (pattern n l -> pattern n' Any
forall a b. a -> b
unsafeCoerce pattern n l
pattern)
composeNameBinderRenamings
:: (NameBinder n i -> NameBinder n i')
-> (NameBinder i' l -> NameBinder i' l')
-> (NameBinder n l -> NameBinder n l')
composeNameBinderRenamings :: forall (n :: S) (i :: S) (i' :: S) (l :: S) (l' :: S).
(NameBinder n i -> NameBinder n i')
-> (NameBinder i' l -> NameBinder i' l')
-> NameBinder n l
-> NameBinder n l'
composeNameBinderRenamings = ((Any -> Any) -> (Any -> Any) -> Any -> Any)
-> (NameBinder n i -> NameBinder n i')
-> (NameBinder i' l -> NameBinder i' l')
-> NameBinder n l
-> NameBinder n l'
forall a b. a -> b
unsafeCoerce (((Any -> Any) -> (Any -> Any) -> Any -> Any)
-> (Any -> Any) -> (Any -> Any) -> Any -> Any
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Any -> Any) -> (Any -> Any) -> Any -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.))
fromNameBinderRenaming :: (NameBinder n l -> NameBinder n l') -> Name l -> Name l'
fromNameBinderRenaming :: forall (n :: S) (l :: S) (l' :: S).
(NameBinder n l -> NameBinder n l') -> Name l -> Name l'
fromNameBinderRenaming = (NameBinder n l -> NameBinder n l') -> Name l -> Name l'
forall a b. Coercible a b => a -> b
coerce
extendRenamingNameBinder
:: (Name n -> Name n')
-> NameBinder n l
-> (forall l'. (Name l -> Name l') -> NameBinder n' l' -> r )
-> r
extendRenamingNameBinder :: forall (n :: S) (n' :: S) (l :: S) r.
(Name n -> Name n')
-> NameBinder n l
-> (forall (l' :: S). (Name l -> Name l') -> NameBinder n' l' -> r)
-> r
extendRenamingNameBinder Name n -> Name n'
_ (UnsafeNameBinder Name l
name) forall (l' :: S). (Name l -> Name l') -> NameBinder n' l' -> r
cont =
(Name l -> Name l) -> NameBinder n' l -> r
forall (l' :: S). (Name l -> Name l') -> NameBinder n' l' -> r
cont Name l -> Name l
forall a b. a -> b
unsafeCoerce (Name l -> NameBinder n' l
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder Name l
name)
class CoSinkable (pattern :: S -> S -> Type) where
coSinkabilityProof
:: (Name n -> Name n')
-> pattern n l
-> (forall l'. (Name l -> Name l') -> pattern n' l' -> r)
-> r
default coSinkabilityProof
:: (GenericK pattern, GSinkableK (RepK pattern))
=> (Name n -> Name n')
-> pattern n l
-> (forall l'. (Name l -> Name l') -> pattern n' l' -> r)
-> r
coSinkabilityProof Name n -> Name n'
rename pattern n l
p forall (l' :: S). (Name l -> Name l') -> pattern n' l' -> r
cont = (Name n -> Name n')
-> RepK pattern (n ':&&: (l ':&&: 'LoT0))
-> (forall {l' :: S}.
(Name l -> Name l')
-> RepK pattern (n' ':&&: (l' ':&&: 'LoT0)) -> r)
-> r
forall (f :: LoT (S -> S -> *) -> *) (n :: S) (n' :: S) (l :: S) r.
GSinkableK f =>
(Name n -> Name n')
-> f (n ':&&: (l ':&&: 'LoT0))
-> (forall (l' :: S).
(Name l -> Name l') -> f (n' ':&&: (l' ':&&: 'LoT0)) -> r)
-> r
gsinkabilityProof2 Name n -> Name n'
rename (forall k (f :: k) (x :: LoT k).
GenericK f =>
(f :@@: x) -> RepK f x
fromK @_ @pattern pattern n l
pattern :@@: (n ':&&: (l ':&&: 'LoT0))
p) ((forall {l' :: S}.
(Name l -> Name l')
-> RepK pattern (n' ':&&: (l' ':&&: 'LoT0)) -> r)
-> r)
-> (forall {l' :: S}.
(Name l -> Name l')
-> RepK pattern (n' ':&&: (l' ':&&: 'LoT0)) -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \Name l -> Name l'
rename' RepK pattern (n' ':&&: (l' ':&&: 'LoT0))
p' ->
(Name l -> Name l') -> pattern n' l' -> r
forall (l' :: S). (Name l -> Name l') -> pattern n' l' -> r
cont Name l -> Name l'
rename' (forall k (f :: k) (x :: LoT k). GenericK f => RepK f x -> f :@@: x
toK @_ @pattern RepK pattern (n' ':&&: (l' ':&&: 'LoT0))
p')
withPattern
:: Distinct o
=> (forall x y z r'. Distinct z => Scope z -> NameBinder x y -> (forall z'. DExt z z' => f x y z z' -> NameBinder z z' -> r') -> r')
-> (forall x z z'. DExt z z' => f x x z z')
-> (forall x y y' z z' z''. (DExt z z', DExt z' z'') => f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall o'. DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
default withPattern
:: (Distinct o, GenericK pattern, GValidNameBinders pattern (RepK pattern), GHasNameBinders (RepK pattern))
=> (forall x y z r'. Distinct z => Scope z -> NameBinder x y -> (forall z'. DExt z z' => f x y z z' -> NameBinder z z' -> r') -> r')
-> (forall x z z'. DExt z z' => f x x z z')
-> (forall x y y' z z' z''. (DExt z z', DExt z' z'') => f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall o'. DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern = (forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
forall (pattern :: S -> S -> *) (f :: S -> S -> S -> S -> *)
(o :: S) (n :: S) (l :: S) r.
(Distinct o, GenericK pattern,
GValidNameBinders pattern (RepK pattern),
GHasNameBinders (RepK pattern)) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
gunsafeWithPatternViaHasNameBinders
newtype WithNameBinderList r n l (o :: S) (o' :: S) = WithNameBinderList (NameBinderList l r -> NameBinderList n r)
idWithNameBinderList :: DExt o o' => WithNameBinderList r n n o o'
idWithNameBinderList :: forall (o :: S) (o' :: S) (r :: S) (n :: S).
DExt o o' =>
WithNameBinderList r n n o o'
idWithNameBinderList = (NameBinderList n r -> NameBinderList n r)
-> WithNameBinderList r n n o o'
forall (r :: S) (n :: S) (l :: S) (o :: S) (o' :: S).
(NameBinderList l r -> NameBinderList n r)
-> WithNameBinderList r n l o o'
WithNameBinderList NameBinderList n r -> NameBinderList n r
forall a. a -> a
id
compWithNameBinderList
:: (DExt o o', DExt o' o'')
=> WithNameBinderList r n i o o'
-> WithNameBinderList r i l o' o''
-> WithNameBinderList r n l o o''
compWithNameBinderList :: forall (o :: S) (o' :: S) (o'' :: S) (r :: S) (n :: S) (i :: S)
(l :: S).
(DExt o o', DExt o' o'') =>
WithNameBinderList r n i o o'
-> WithNameBinderList r i l o' o''
-> WithNameBinderList r n l o o''
compWithNameBinderList (WithNameBinderList NameBinderList i r -> NameBinderList n r
f) (WithNameBinderList NameBinderList l r -> NameBinderList i r
g) =
(NameBinderList l r -> NameBinderList n r)
-> WithNameBinderList r n l o o''
forall (r :: S) (n :: S) (l :: S) (o :: S) (o' :: S).
(NameBinderList l r -> NameBinderList n r)
-> WithNameBinderList r n l o o'
WithNameBinderList (NameBinderList i r -> NameBinderList n r
f (NameBinderList i r -> NameBinderList n r)
-> (NameBinderList l r -> NameBinderList i r)
-> NameBinderList l r
-> NameBinderList n r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameBinderList l r -> NameBinderList i r
g)
nameBinderListOf :: (CoSinkable binder) => binder n l -> NameBinderList n l
nameBinderListOf :: forall (binder :: S -> S -> *) (n :: S) (l :: S).
CoSinkable binder =>
binder n l -> NameBinderList n l
nameBinderListOf binder n l
pat = (forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
WithNameBinderList l x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
WithNameBinderList l x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
WithNameBinderList l x y z z'
-> WithNameBinderList l y y' z' z''
-> WithNameBinderList l x y' z z'')
-> Scope 'VoidS
-> binder n l
-> (forall (o' :: S).
DExt 'VoidS o' =>
WithNameBinderList l n l 'VoidS o'
-> binder 'VoidS o' -> NameBinderList n l)
-> NameBinderList n l
forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> binder n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> binder o o' -> r)
-> r
forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern
(\Scope z
_scope' NameBinder x y
binder forall (z' :: S).
DExt z z' =>
WithNameBinderList l x y z z' -> NameBinder z z' -> r'
k ->
NameBinder x y -> (DExt z Any => NameBinder z Any -> r') -> r'
forall (n :: S) (l :: S) (n' :: S) (l' :: S) r.
NameBinder n l -> (DExt n' l' => NameBinder n' l' -> r) -> r
unsafeAssertFresh NameBinder x y
binder ((DExt z Any => NameBinder z Any -> r') -> r')
-> (DExt z Any => NameBinder z Any -> r') -> r'
forall a b. (a -> b) -> a -> b
$ \NameBinder z Any
binder' ->
WithNameBinderList l x y z Any -> NameBinder z Any -> r'
forall (z' :: S).
DExt z z' =>
WithNameBinderList l x y z z' -> NameBinder z z' -> r'
k ((NameBinderList y l -> NameBinderList x l)
-> WithNameBinderList l x y z Any
forall (r :: S) (n :: S) (l :: S) (o :: S) (o' :: S).
(NameBinderList l r -> NameBinderList n r)
-> WithNameBinderList r n l o o'
WithNameBinderList (NameBinder x y -> NameBinderList y l -> NameBinderList x l
forall (n :: S) (k :: S) (l :: S).
NameBinder n k -> NameBinderList k l -> NameBinderList n l
NameBinderListCons NameBinder x y
binder)) NameBinder z Any
binder')
WithNameBinderList l x x z z'
forall (x :: S) (z :: S) (z' :: S).
DExt z z' =>
WithNameBinderList l x x z z'
forall (o :: S) (o' :: S) (r :: S) (n :: S).
DExt o o' =>
WithNameBinderList r n n o o'
idWithNameBinderList
WithNameBinderList l x y z z'
-> WithNameBinderList l y y' z' z''
-> WithNameBinderList l x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
WithNameBinderList l x y z z'
-> WithNameBinderList l y y' z' z''
-> WithNameBinderList l x y' z z''
forall (o :: S) (o' :: S) (o'' :: S) (r :: S) (n :: S) (i :: S)
(l :: S).
(DExt o o', DExt o' o'') =>
WithNameBinderList r n i o o'
-> WithNameBinderList r i l o' o''
-> WithNameBinderList r n l o o''
compWithNameBinderList
Scope 'VoidS
emptyScope
binder n l
pat
(\(WithNameBinderList NameBinderList l l -> NameBinderList n l
f) binder 'VoidS o'
_ -> NameBinderList l l -> NameBinderList n l
f NameBinderList l l
forall (n :: S). NameBinderList n n
NameBinderListEmpty)
instance CoSinkable NameBinder where
coSinkabilityProof :: forall (n :: S) (n' :: S) (l :: S) r.
(Name n -> Name n')
-> NameBinder n l
-> (forall (l' :: S). (Name l -> Name l') -> NameBinder n' l' -> r)
-> r
coSinkabilityProof Name n -> Name n'
_rename (UnsafeNameBinder Name l
name) forall (l' :: S). (Name l -> Name l') -> NameBinder n' l' -> r
cont =
(Name l -> Name l) -> NameBinder n' l -> r
forall (l' :: S). (Name l -> Name l') -> NameBinder n' l' -> r
cont Name l -> Name l
forall a b. a -> b
unsafeCoerce (Name l -> NameBinder n' l
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder Name l
name)
withPattern :: forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> NameBinder n l
-> (forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinder o o' -> r)
-> r
withPattern forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
f forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
_ forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
_ = Scope o
-> NameBinder n l
-> (forall (z' :: S).
DExt o z' =>
f n l o z' -> NameBinder o z' -> r)
-> r
forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
f
newtype Substitution (e :: S -> Type) (i :: S) (o :: S) =
UnsafeSubstitution (IntMap (e o))
lookupSubst :: InjectName e => Substitution e i o -> Name i -> e o
lookupSubst :: forall (e :: S -> *) (i :: S) (o :: S).
InjectName e =>
Substitution e i o -> Name i -> e o
lookupSubst (UnsafeSubstitution IntMap (e o)
env) (UnsafeName RawName
name) =
case RawName -> IntMap (e o) -> Maybe (e o)
forall a. RawName -> IntMap a -> Maybe a
IntMap.lookup RawName
name IntMap (e o)
env of
Just e o
ex -> e o
ex
Maybe (e o)
Nothing -> Name o -> e o
forall (n :: S). Name n -> e n
forall (e :: S -> *) (n :: S). InjectName e => Name n -> e n
injectName (RawName -> Name o
forall (n :: S). RawName -> Name n
UnsafeName RawName
name)
identitySubst
:: InjectName e => Substitution e i i
identitySubst :: forall (e :: S -> *) (i :: S). InjectName e => Substitution e i i
identitySubst = IntMap (e i) -> Substitution e i i
forall (e :: S -> *) (i :: S) (o :: S).
IntMap (e o) -> Substitution e i o
UnsafeSubstitution IntMap (e i)
forall a. IntMap a
IntMap.empty
voidSubst :: Substitution e VoidS n
voidSubst :: forall (e :: S -> *) (n :: S). Substitution e 'VoidS n
voidSubst = IntMap (e n) -> Substitution e 'VoidS n
forall (e :: S -> *) (i :: S) (o :: S).
IntMap (e o) -> Substitution e i o
UnsafeSubstitution IntMap (e n)
forall a. IntMap a
IntMap.empty
addSubst
:: Substitution e i o
-> NameBinder i i'
-> e o
-> Substitution e i' o
addSubst :: forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
Substitution e i o -> NameBinder i i' -> e o -> Substitution e i' o
addSubst (UnsafeSubstitution IntMap (e o)
env) (UnsafeNameBinder (UnsafeName RawName
name)) e o
ex
= IntMap (e o) -> Substitution e i' o
forall (e :: S -> *) (i :: S) (o :: S).
IntMap (e o) -> Substitution e i o
UnsafeSubstitution (RawName -> e o -> IntMap (e o) -> IntMap (e o)
forall a. RawName -> a -> IntMap a -> IntMap a
IntMap.insert RawName
name e o
ex IntMap (e o)
env)
addSubstPattern
:: CoSinkable binder
=> Substitution e i o
-> binder i i'
-> [e o]
-> Substitution e i' o
addSubstPattern :: forall (binder :: S -> S -> *) (e :: S -> *) (i :: S) (o :: S)
(i' :: S).
CoSinkable binder =>
Substitution e i o -> binder i i' -> [e o] -> Substitution e i' o
addSubstPattern Substitution e i o
subst binder i i'
pat = Substitution e i o
-> NameBinderList i i' -> [e o] -> Substitution e i' o
forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
Substitution e i o
-> NameBinderList i i' -> [e o] -> Substitution e i' o
addSubstList Substitution e i o
subst (binder i i' -> NameBinderList i i'
forall (binder :: S -> S -> *) (n :: S) (l :: S).
CoSinkable binder =>
binder n l -> NameBinderList n l
nameBinderListOf binder i i'
pat)
addSubstList
:: Substitution e i o
-> NameBinderList i i'
-> [e o]
-> Substitution e i' o
addSubstList :: forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
Substitution e i o
-> NameBinderList i i' -> [e o] -> Substitution e i' o
addSubstList Substitution e i o
subst NameBinderList i i'
NameBinderListEmpty [e o]
_ = Substitution e i o
Substitution e i' o
subst
addSubstList Substitution e i o
subst (NameBinderListCons NameBinder i i
binder NameBinderList i i'
binders) (e o
x:[e o]
xs) =
Substitution e i o
-> NameBinderList i i' -> [e o] -> Substitution e i' o
forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
Substitution e i o
-> NameBinderList i i' -> [e o] -> Substitution e i' o
addSubstList (Substitution e i o -> NameBinder i i -> e o -> Substitution e i o
forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
Substitution e i o -> NameBinder i i' -> e o -> Substitution e i' o
addSubst Substitution e i o
subst NameBinder i i
binder e o
x) NameBinderList i i'
binders [e o]
xs
addSubstList Substitution e i o
_ NameBinderList i i'
_ [] = String -> Substitution e i' o
forall a. HasCallStack => String -> a
error String
"cannot add a binder to Substitution since the value list does not have enough elements"
addRename :: InjectName e => Substitution e i o -> NameBinder i i' -> Name o -> Substitution e i' o
addRename :: forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
InjectName e =>
Substitution e i o
-> NameBinder i i' -> Name o -> Substitution e i' o
addRename s :: Substitution e i o
s@(UnsafeSubstitution IntMap (e o)
env) b :: NameBinder i i'
b@(UnsafeNameBinder (UnsafeName RawName
name1)) n :: Name o
n@(UnsafeName RawName
name2)
| RawName
name1 RawName -> RawName -> Bool
forall a. Eq a => a -> a -> Bool
== RawName
name2 = IntMap (e o) -> Substitution e i' o
forall (e :: S -> *) (i :: S) (o :: S).
IntMap (e o) -> Substitution e i o
UnsafeSubstitution (RawName -> IntMap (e o) -> IntMap (e o)
forall a. RawName -> IntMap a -> IntMap a
IntMap.delete RawName
name1 IntMap (e o)
env)
| Bool
otherwise = Substitution e i o -> NameBinder i i' -> e o -> Substitution e i' o
forall (e :: S -> *) (i :: S) (o :: S) (i' :: S).
Substitution e i o -> NameBinder i i' -> e o -> Substitution e i' o
addSubst Substitution e i o
s NameBinder i i'
b (Name o -> e o
forall (n :: S). Name n -> e n
forall (e :: S -> *) (n :: S). InjectName e => Name n -> e n
injectName Name o
n)
instance (Sinkable e) => Sinkable (Substitution e i) where
sinkabilityProof :: forall (n :: S) (l :: S).
(Name n -> Name l) -> Substitution e i n -> Substitution e i l
sinkabilityProof Name n -> Name l
rename (UnsafeSubstitution IntMap (e n)
env) =
IntMap (e l) -> Substitution e i l
forall (e :: S -> *) (i :: S) (o :: S).
IntMap (e o) -> Substitution e i o
UnsafeSubstitution ((e n -> e l) -> IntMap (e n) -> IntMap (e l)
forall a b. (a -> b) -> IntMap a -> IntMap b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Name n -> Name l) -> e n -> e l
forall (n :: S) (l :: S). (Name n -> Name l) -> e n -> e l
forall (e :: S -> *) (n :: S) (l :: S).
Sinkable e =>
(Name n -> Name l) -> e n -> e l
sinkabilityProof Name n -> Name l
rename) IntMap (e n)
env)
newtype NameMap (n :: S) a = NameMap { forall (n :: S) a. NameMap n a -> IntMap a
getNameMap :: IntMap a } deriving ((forall a b. (a -> b) -> NameMap n a -> NameMap n b)
-> (forall a b. a -> NameMap n b -> NameMap n a)
-> Functor (NameMap n)
forall a b. a -> NameMap n b -> NameMap n a
forall a b. (a -> b) -> NameMap n a -> NameMap n b
forall (n :: S) a b. a -> NameMap n b -> NameMap n a
forall (n :: S) a b. (a -> b) -> NameMap n a -> NameMap n b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (n :: S) a b. (a -> b) -> NameMap n a -> NameMap n b
fmap :: forall a b. (a -> b) -> NameMap n a -> NameMap n b
$c<$ :: forall (n :: S) a b. a -> NameMap n b -> NameMap n a
<$ :: forall a b. a -> NameMap n b -> NameMap n a
Functor, (forall m. Monoid m => NameMap n m -> m)
-> (forall m a. Monoid m => (a -> m) -> NameMap n a -> m)
-> (forall m a. Monoid m => (a -> m) -> NameMap n a -> m)
-> (forall a b. (a -> b -> b) -> b -> NameMap n a -> b)
-> (forall a b. (a -> b -> b) -> b -> NameMap n a -> b)
-> (forall b a. (b -> a -> b) -> b -> NameMap n a -> b)
-> (forall b a. (b -> a -> b) -> b -> NameMap n a -> b)
-> (forall a. (a -> a -> a) -> NameMap n a -> a)
-> (forall a. (a -> a -> a) -> NameMap n a -> a)
-> (forall a. NameMap n a -> [a])
-> (forall a. NameMap n a -> Bool)
-> (forall a. NameMap n a -> RawName)
-> (forall a. Eq a => a -> NameMap n a -> Bool)
-> (forall a. Ord a => NameMap n a -> a)
-> (forall a. Ord a => NameMap n a -> a)
-> (forall a. Num a => NameMap n a -> a)
-> (forall a. Num a => NameMap n a -> a)
-> Foldable (NameMap n)
forall a. Eq a => a -> NameMap n a -> Bool
forall a. Num a => NameMap n a -> a
forall a. Ord a => NameMap n a -> a
forall m. Monoid m => NameMap n m -> m
forall a. NameMap n a -> Bool
forall a. NameMap n a -> RawName
forall a. NameMap n a -> [a]
forall a. (a -> a -> a) -> NameMap n a -> a
forall m a. Monoid m => (a -> m) -> NameMap n a -> m
forall b a. (b -> a -> b) -> b -> NameMap n a -> b
forall a b. (a -> b -> b) -> b -> NameMap n a -> b
forall (n :: S) a. Eq a => a -> NameMap n a -> Bool
forall (n :: S) a. Num a => NameMap n a -> a
forall (n :: S) a. Ord a => NameMap n a -> a
forall (n :: S) m. Monoid m => NameMap n m -> m
forall (n :: S) a. NameMap n a -> Bool
forall (n :: S) a. NameMap n a -> RawName
forall (n :: S) a. NameMap n a -> [a]
forall (n :: S) a. (a -> a -> a) -> NameMap n a -> a
forall (n :: S) m a. Monoid m => (a -> m) -> NameMap n a -> m
forall (n :: S) b a. (b -> a -> b) -> b -> NameMap n a -> b
forall (n :: S) a b. (a -> b -> b) -> b -> NameMap n a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> RawName)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall (n :: S) m. Monoid m => NameMap n m -> m
fold :: forall m. Monoid m => NameMap n m -> m
$cfoldMap :: forall (n :: S) m a. Monoid m => (a -> m) -> NameMap n a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> NameMap n a -> m
$cfoldMap' :: forall (n :: S) m a. Monoid m => (a -> m) -> NameMap n a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> NameMap n a -> m
$cfoldr :: forall (n :: S) a b. (a -> b -> b) -> b -> NameMap n a -> b
foldr :: forall a b. (a -> b -> b) -> b -> NameMap n a -> b
$cfoldr' :: forall (n :: S) a b. (a -> b -> b) -> b -> NameMap n a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> NameMap n a -> b
$cfoldl :: forall (n :: S) b a. (b -> a -> b) -> b -> NameMap n a -> b
foldl :: forall b a. (b -> a -> b) -> b -> NameMap n a -> b
$cfoldl' :: forall (n :: S) b a. (b -> a -> b) -> b -> NameMap n a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> NameMap n a -> b
$cfoldr1 :: forall (n :: S) a. (a -> a -> a) -> NameMap n a -> a
foldr1 :: forall a. (a -> a -> a) -> NameMap n a -> a
$cfoldl1 :: forall (n :: S) a. (a -> a -> a) -> NameMap n a -> a
foldl1 :: forall a. (a -> a -> a) -> NameMap n a -> a
$ctoList :: forall (n :: S) a. NameMap n a -> [a]
toList :: forall a. NameMap n a -> [a]
$cnull :: forall (n :: S) a. NameMap n a -> Bool
null :: forall a. NameMap n a -> Bool
$clength :: forall (n :: S) a. NameMap n a -> RawName
length :: forall a. NameMap n a -> RawName
$celem :: forall (n :: S) a. Eq a => a -> NameMap n a -> Bool
elem :: forall a. Eq a => a -> NameMap n a -> Bool
$cmaximum :: forall (n :: S) a. Ord a => NameMap n a -> a
maximum :: forall a. Ord a => NameMap n a -> a
$cminimum :: forall (n :: S) a. Ord a => NameMap n a -> a
minimum :: forall a. Ord a => NameMap n a -> a
$csum :: forall (n :: S) a. Num a => NameMap n a -> a
sum :: forall a. Num a => NameMap n a -> a
$cproduct :: forall (n :: S) a. Num a => NameMap n a -> a
product :: forall a. Num a => NameMap n a -> a
Foldable, Functor (NameMap n)
Foldable (NameMap n)
(Functor (NameMap n), Foldable (NameMap n)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NameMap n a -> f (NameMap n b))
-> (forall (f :: * -> *) a.
Applicative f =>
NameMap n (f a) -> f (NameMap n a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NameMap n a -> m (NameMap n b))
-> (forall (m :: * -> *) a.
Monad m =>
NameMap n (m a) -> m (NameMap n a))
-> Traversable (NameMap n)
forall (n :: S). Functor (NameMap n)
forall (n :: S). Foldable (NameMap n)
forall (n :: S) (m :: * -> *) a.
Monad m =>
NameMap n (m a) -> m (NameMap n a)
forall (n :: S) (f :: * -> *) a.
Applicative f =>
NameMap n (f a) -> f (NameMap n a)
forall (n :: S) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NameMap n a -> m (NameMap n b)
forall (n :: S) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NameMap n a -> f (NameMap n b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
NameMap n (m a) -> m (NameMap n a)
forall (f :: * -> *) a.
Applicative f =>
NameMap n (f a) -> f (NameMap n a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NameMap n a -> m (NameMap n b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NameMap n a -> f (NameMap n b)
$ctraverse :: forall (n :: S) (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NameMap n a -> f (NameMap n b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NameMap n a -> f (NameMap n b)
$csequenceA :: forall (n :: S) (f :: * -> *) a.
Applicative f =>
NameMap n (f a) -> f (NameMap n a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
NameMap n (f a) -> f (NameMap n a)
$cmapM :: forall (n :: S) (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NameMap n a -> m (NameMap n b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> NameMap n a -> m (NameMap n b)
$csequence :: forall (n :: S) (m :: * -> *) a.
Monad m =>
NameMap n (m a) -> m (NameMap n a)
sequence :: forall (m :: * -> *) a.
Monad m =>
NameMap n (m a) -> m (NameMap n a)
Traversable)
emptyNameMap :: NameMap VoidS a
emptyNameMap :: forall a. NameMap 'VoidS a
emptyNameMap = IntMap a -> NameMap 'VoidS a
forall (n :: S) a. IntMap a -> NameMap n a
NameMap IntMap a
forall a. IntMap a
IntMap.empty
nameMapToSubstitution :: NameMap i (e o) -> Substitution e i o
nameMapToSubstitution :: forall (i :: S) (e :: S -> *) (o :: S).
NameMap i (e o) -> Substitution e i o
nameMapToSubstitution (NameMap IntMap (e o)
m) = (IntMap (e o) -> Substitution e i o
forall (e :: S -> *) (i :: S) (o :: S).
IntMap (e o) -> Substitution e i o
UnsafeSubstitution IntMap (e o)
m)
nameMapToScope :: NameMap n a -> Scope n
nameMapToScope :: forall (n :: S) a. NameMap n a -> Scope n
nameMapToScope (NameMap IntMap a
m) = RawScope -> Scope n
forall (n :: S). RawScope -> Scope n
UnsafeScope (IntMap a -> RawScope
forall a. IntMap a -> RawScope
IntMap.keysSet IntMap a
m)
addNameBinders :: CoSinkable binder => binder n l -> [a] -> NameMap n a -> NameMap l a
addNameBinders :: forall (binder :: S -> S -> *) (n :: S) (l :: S) a.
CoSinkable binder =>
binder n l -> [a] -> NameMap n a -> NameMap l a
addNameBinders binder n l
pat = NameBinderList n l -> [a] -> NameMap n a -> NameMap l a
forall (n :: S) (l :: S) a.
NameBinderList n l -> [a] -> NameMap n a -> NameMap l a
addNameBinderList (binder n l -> NameBinderList n l
forall (binder :: S -> S -> *) (n :: S) (l :: S).
CoSinkable binder =>
binder n l -> NameBinderList n l
nameBinderListOf binder n l
pat)
addNameBinderList :: NameBinderList n l -> [a] -> NameMap n a -> NameMap l a
addNameBinderList :: forall (n :: S) (l :: S) a.
NameBinderList n l -> [a] -> NameMap n a -> NameMap l a
addNameBinderList NameBinderList n l
NameBinderListEmpty [a]
_ = NameMap n a -> NameMap n a
NameMap n a -> NameMap l a
forall a. a -> a
id
addNameBinderList (NameBinderListCons NameBinder n i
binder NameBinderList i l
binders) (a
x:[a]
xs) =
NameBinderList i l -> [a] -> NameMap i a -> NameMap l a
forall (n :: S) (l :: S) a.
NameBinderList n l -> [a] -> NameMap n a -> NameMap l a
addNameBinderList NameBinderList i l
binders [a]
xs (NameMap i a -> NameMap l a)
-> (NameMap n a -> NameMap i a) -> NameMap n a -> NameMap l a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameBinder n i -> a -> NameMap n a -> NameMap i a
forall (n :: S) (l :: S) a.
NameBinder n l -> a -> NameMap n a -> NameMap l a
addNameBinder NameBinder n i
binder a
x
addNameBinderList NameBinderList n l
_ [] = String -> NameMap n a -> NameMap l a
forall a. HasCallStack => String -> a
error String
"cannot add a binder to NameMap since the value list does not have enough elements"
lookupName :: Name n -> NameMap n a -> a
lookupName :: forall (n :: S) a. Name n -> NameMap n a -> a
lookupName Name n
name (NameMap IntMap a
m) =
case RawName -> IntMap a -> Maybe a
forall a. RawName -> IntMap a -> Maybe a
IntMap.lookup (Name n -> RawName
forall (l :: S). Name l -> RawName
nameId Name n
name) IntMap a
m of
Maybe a
Nothing -> String -> a
forall a. HasCallStack => String -> a
error String
"impossible: unknown name in a NameMap"
Just a
x -> a
x
addNameBinder :: NameBinder n l -> a -> NameMap n a -> NameMap l a
addNameBinder :: forall (n :: S) (l :: S) a.
NameBinder n l -> a -> NameMap n a -> NameMap l a
addNameBinder NameBinder n l
name a
x (NameMap IntMap a
m) = IntMap a -> NameMap l a
forall (n :: S) a. IntMap a -> NameMap n a
NameMap (RawName -> a -> IntMap a -> IntMap a
forall a. RawName -> a -> IntMap a -> IntMap a
IntMap.insert (Name l -> RawName
forall (l :: S). Name l -> RawName
nameId (NameBinder n l -> Name l
forall (n :: S) (l :: S). NameBinder n l -> Name l
nameOf NameBinder n l
name)) a
x IntMap a
m)
type Id = Int
type RawName = Id
type RawScope = IntSet
rawFreshName :: RawScope -> RawName
rawFreshName :: RawScope -> RawName
rawFreshName RawScope
scope | RawScope -> Bool
IntSet.null RawScope
scope = RawName
0
| Bool
otherwise = RawScope -> RawName
IntSet.findMax RawScope
scope RawName -> RawName -> RawName
forall a. Num a => a -> a -> a
+ RawName
1
rawMember :: RawName -> RawScope -> Bool
rawMember :: RawName -> RawScope -> Bool
rawMember = RawName -> RawScope -> Bool
IntSet.member
class ExtEndo (n :: S)
class (ExtEndo n => ExtEndo l ) => Ext (n :: S) (l :: S)
instance ( ExtEndo n => ExtEndo l ) => Ext n l
class Distinct (n :: S)
instance Distinct VoidS
type DExt n l = (Distinct l, Ext n l)
class InjectName (e :: S -> Type) where
injectName :: Name n -> e n
data RenamingsK (as :: LoT k) (bs :: LoT k) where
RNil :: RenamingsK LoT0 LoT0
RCons :: (Name a -> Name b) -> RenamingsK as bs -> RenamingsK (a :&&: as) (b :&&: bs)
RSkip :: RenamingsK as bs -> RenamingsK (k :&&: as) (k :&&: bs)
class SinkableK (f :: S -> k) where
sinkabilityProofK
:: forall as bs r.
RenamingsK as bs
-> f :@@: as
-> (forall cs. RenamingsK as cs -> f :@@: cs -> r)
-> r
default sinkabilityProofK :: forall as bs r.
(GenericK f, GSinkableK (RepK f))
=> RenamingsK as bs
-> f :@@: as
-> (forall cs. RenamingsK as cs -> f :@@: cs -> r)
-> r
sinkabilityProofK RenamingsK as bs
rename f :@@: as
e forall (cs :: LoT (S -> k)). RenamingsK as cs -> (f :@@: cs) -> r
cont =
RenamingsK as bs
-> RepK f as
-> (forall {cs :: LoT (S -> k)}.
RenamingsK as cs -> RepK f cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT (S -> k)) (bs :: LoT (S -> k)) r.
RenamingsK as bs
-> RepK f as
-> (forall (cs :: LoT (S -> k)).
RenamingsK as cs -> RepK f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
rename (forall k (f :: k) (x :: LoT k).
GenericK f =>
(f :@@: x) -> RepK f x
fromK @_ @f f :@@: as
e) ((forall {cs :: LoT (S -> k)}. RenamingsK as cs -> RepK f cs -> r)
-> r)
-> (forall {cs :: LoT (S -> k)}.
RenamingsK as cs -> RepK f cs -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
rename' RepK f cs
e' ->
RenamingsK as cs -> (f :@@: cs) -> r
forall (cs :: LoT (S -> k)). RenamingsK as cs -> (f :@@: cs) -> r
cont RenamingsK as cs
rename' (forall k (f :: k) (x :: LoT k). GenericK f => RepK f x -> f :@@: x
toK @_ @f RepK f cs
e')
sinkK :: GSinkableK f => RenamingsK xs as -> RenamingsK xs bs -> f :@@: as -> f :@@: bs
sinkK :: forall {k} (f :: LoT k -> *) (xs :: LoT (LoT k -> *))
(as :: LoT (LoT k -> *)) (bs :: LoT (LoT k -> *)).
GSinkableK f =>
RenamingsK xs as -> RenamingsK xs bs -> (f :@@: as) -> f :@@: bs
sinkK RenamingsK xs as
_ RenamingsK xs bs
_ = f (HeadLoT as) -> f (HeadLoT bs)
(f :@@: as) -> f :@@: bs
forall a b. a -> b
unsafeCoerce
instance SinkableK Name where
sinkabilityProofK :: forall (as :: LoT (S -> *)) (bs :: LoT (S -> *)) r.
RenamingsK as bs
-> (Name :@@: as)
-> (forall (cs :: LoT (S -> *)).
RenamingsK as cs -> (Name :@@: cs) -> r)
-> r
sinkabilityProofK renameK :: RenamingsK as bs
renameK@(RCons Name a -> Name b
rename RenamingsK as bs
RNil) Name :@@: as
name forall (cs :: LoT (S -> *)).
RenamingsK as cs -> (Name :@@: cs) -> r
cont = RenamingsK as bs -> (Name :@@: bs) -> r
forall (cs :: LoT (S -> *)).
RenamingsK as cs -> (Name :@@: cs) -> r
cont RenamingsK as bs
renameK (Name a -> Name b
rename Name :@@: as
Name a
name)
instance SinkableK NameBinder where
sinkabilityProofK :: forall (as :: LoT (S -> S -> *)) (bs :: LoT (S -> S -> *)) r.
RenamingsK as bs
-> (NameBinder :@@: as)
-> (forall (cs :: LoT (S -> S -> *)).
RenamingsK as cs -> (NameBinder :@@: cs) -> r)
-> r
sinkabilityProofK (RCons Name a -> Name b
_ RenamingsK as bs
RNil) (UnsafeNameBinder Name (HeadLoT 'LoT0)
name) forall (cs :: LoT (S -> S -> *)).
RenamingsK as cs -> (NameBinder :@@: cs) -> r
cont =
RenamingsK as (Any ':&&: 'LoT0)
-> (NameBinder :@@: (Any ':&&: 'LoT0)) -> r
forall (cs :: LoT (S -> S -> *)).
RenamingsK as cs -> (NameBinder :@@: cs) -> r
cont ((Name a -> Name Any)
-> RenamingsK 'LoT0 'LoT0
-> RenamingsK (a ':&&: 'LoT0) (Any ':&&: 'LoT0)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name a -> Name Any
forall a b. a -> b
unsafeCoerce RenamingsK 'LoT0 'LoT0
RenamingsK 'LoT0 'LoT0
RNil) (Name (HeadLoT 'LoT0) -> NameBinder Any (HeadLoT 'LoT0)
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder Name (HeadLoT 'LoT0)
name)
instance SinkableK NameBinders where
sinkabilityProofK :: forall (as :: LoT (S -> S -> *)) (bs :: LoT (S -> S -> *)) r.
RenamingsK as bs
-> (NameBinders :@@: as)
-> (forall (cs :: LoT (S -> S -> *)).
RenamingsK as cs -> (NameBinders :@@: cs) -> r)
-> r
sinkabilityProofK (RCons Name a -> Name b
_ RenamingsK as bs
RNil) (UnsafeNameBinders RawScope
s) forall (cs :: LoT (S -> S -> *)).
RenamingsK as cs -> (NameBinders :@@: cs) -> r
cont =
RenamingsK as (Any ':&&: 'LoT0)
-> (NameBinders :@@: (Any ':&&: 'LoT0)) -> r
forall (cs :: LoT (S -> S -> *)).
RenamingsK as cs -> (NameBinders :@@: cs) -> r
cont ((Name a -> Name Any)
-> RenamingsK 'LoT0 'LoT0
-> RenamingsK (a ':&&: 'LoT0) (Any ':&&: 'LoT0)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name a -> Name Any
forall a b. a -> b
unsafeCoerce RenamingsK 'LoT0 'LoT0
RenamingsK 'LoT0 'LoT0
RNil) (RawScope -> NameBinders Any (HeadLoT 'LoT0)
forall (n :: S) (l :: S). RawScope -> NameBinders n l
UnsafeNameBinders RawScope
s)
instance GenericK NameBinderList where
type RepK NameBinderList = ((Var0 :~~: Var1) :=>: U1) :+: Exists S
(Field (NameBinder :$: Var1 :@: Var0) :*: Field (NameBinderList :$: Var0 :@: Var2))
toK :: forall (x :: LoT (S -> S -> *)).
RepK NameBinderList x -> NameBinderList :@@: x
toK (L1 (SuchThat U1 x
U1)) = NameBinderList :@@: x
NameBinderList (HeadLoT x) (HeadLoT x)
forall (n :: S). NameBinderList n n
NameBinderListEmpty
toK (R1 (Exists (Field Interpret ((NameBinder :$: Var1) ':@: Var0) (t ':&&: x)
x :*: Field Interpret ((NameBinderList :$: Var0) ':@: Var2) (t ':&&: x)
xs))) = NameBinder (HeadLoT x) t
-> NameBinderList t (HeadLoT (TailLoT x))
-> NameBinderList (HeadLoT x) (HeadLoT (TailLoT x))
forall (n :: S) (k :: S) (l :: S).
NameBinder n k -> NameBinderList k l -> NameBinderList n l
NameBinderListCons Interpret ((NameBinder :$: Var1) ':@: Var0) (t ':&&: x)
NameBinder (HeadLoT x) t
x Interpret ((NameBinderList :$: Var0) ':@: Var2) (t ':&&: x)
NameBinderList t (HeadLoT (TailLoT x))
xs
fromK :: forall (x :: LoT (S -> S -> *)).
(NameBinderList :@@: x) -> RepK NameBinderList x
fromK NameBinderList :@@: x
NameBinderList (HeadLoT x) (HeadLoT (TailLoT x))
NameBinderListEmpty = (:=>:) (Var0 :~~: Var1) U1 x
-> (:+:)
((Var0 :~~: Var1) :=>: U1)
(Exists
S
(Field ((NameBinder :$: Var1) ':@: Var0)
:*: Field ((NameBinderList :$: Var0) ':@: Var2)))
x
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (U1 x -> (:=>:) (Var0 :~~: Var1) U1 x
forall {d} (c :: Atom d Constraint) (x :: LoT d) (f :: LoT d -> *).
Interpret c x =>
f x -> (:=>:) c f x
SuchThat U1 x
forall k (p :: k). U1 p
U1)
fromK (NameBinderListCons NameBinder (HeadLoT x) i
x NameBinderList i (HeadLoT (TailLoT x))
xs) = Exists
S
(Field ((NameBinder :$: Var1) ':@: Var0)
:*: Field ((NameBinderList :$: Var0) ':@: Var2))
x
-> (:+:)
((Var0 :~~: Var1) :=>: U1)
(Exists
S
(Field ((NameBinder :$: Var1) ':@: Var0)
:*: Field ((NameBinderList :$: Var0) ':@: Var2)))
x
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 ((:*:)
(Field ((NameBinder :$: Var1) ':@: Var0))
(Field ((NameBinderList :$: Var0) ':@: Var2))
(i ':&&: x)
-> Exists
S
(Field ((NameBinder :$: Var1) ':@: Var0)
:*: Field ((NameBinderList :$: Var0) ':@: Var2))
x
forall k (t :: k) d (f :: LoT (k -> d) -> *) (x :: LoT d).
f (t ':&&: x) -> Exists k f x
Exists (Interpret ((NameBinder :$: Var1) ':@: Var0) (i ':&&: x)
-> Field ((NameBinder :$: Var1) ':@: Var0) (i ':&&: x)
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field Interpret ((NameBinder :$: Var1) ':@: Var0) (i ':&&: x)
NameBinder (HeadLoT x) i
x Field ((NameBinder :$: Var1) ':@: Var0) (i ':&&: x)
-> Field ((NameBinderList :$: Var0) ':@: Var2) (i ':&&: x)
-> (:*:)
(Field ((NameBinder :$: Var1) ':@: Var0))
(Field ((NameBinderList :$: Var0) ':@: Var2))
(i ':&&: x)
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: Interpret ((NameBinderList :$: Var0) ':@: Var2) (i ':&&: x)
-> Field ((NameBinderList :$: Var0) ':@: Var2) (i ':&&: x)
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field Interpret ((NameBinderList :$: Var0) ':@: Var2) (i ':&&: x)
NameBinderList i (HeadLoT (TailLoT x))
xs))
instance GenericK V2 where
type RepK V2 = V1
toK :: forall (x :: LoT (S -> S -> *)). RepK V2 x -> V2 :@@: x
toK RepK V2 x
_v1 = String -> V2 (HeadLoT x) (HeadLoT (TailLoT x))
forall a. HasCallStack => String -> a
error String
"absurd: Generics.Kind.V1"
fromK :: forall (x :: LoT (S -> S -> *)). (V2 :@@: x) -> RepK V2 x
fromK = (V2 :@@: x) -> RepK V2 x
V2 (HeadLoT x) (HeadLoT (TailLoT x)) -> V1 x
forall (n :: S) (l :: S) a. V2 n l -> a
absurd2
instance GenericK U2 where
type RepK U2 = ((Var0 :~~: Var1) :=>: U1)
toK :: forall (x :: LoT (S -> S -> *)). RepK U2 x -> U2 :@@: x
toK (SuchThat U1 x
U1) = U2 :@@: x
U2 (HeadLoT x) (HeadLoT x)
forall (n :: S). U2 n n
U2
fromK :: forall (x :: LoT (S -> S -> *)). (U2 :@@: x) -> RepK U2 x
fromK U2 :@@: x
U2 (HeadLoT x) (HeadLoT (TailLoT x))
U2 = U1 x -> (:=>:) (Var0 :~~: Var1) U1 x
forall {d} (c :: Atom d Constraint) (x :: LoT d) (f :: LoT d -> *).
Interpret c x =>
f x -> (:=>:) c f x
SuchThat U1 x
forall k (p :: k). U1 p
U1
instance SinkableK NameBinderList
instance SinkableK V2
instance SinkableK U2
sinkabilityProof1 :: SinkableK f => (Name n -> Name n') -> f n -> f n'
sinkabilityProof1 :: forall (f :: S -> *) (n :: S) (n' :: S).
SinkableK f =>
(Name n -> Name n') -> f n -> f n'
sinkabilityProof1 Name n -> Name n'
rename f n
e = RenamingsK (n ':&&: 'LoT0) (n' ':&&: 'LoT0)
-> (f :@@: (n ':&&: 'LoT0))
-> (forall {cs :: LoT (S -> *)}.
RenamingsK (n ':&&: 'LoT0) cs -> (f :@@: cs) -> f n')
-> f n'
forall k (f :: S -> k) (as :: LoT (S -> k)) (bs :: LoT (S -> k)) r.
SinkableK f =>
RenamingsK as bs
-> (f :@@: as)
-> (forall (cs :: LoT (S -> k)).
RenamingsK as cs -> (f :@@: cs) -> r)
-> r
forall (as :: LoT (S -> *)) (bs :: LoT (S -> *)) r.
RenamingsK as bs
-> (f :@@: as)
-> (forall (cs :: LoT (S -> *)).
RenamingsK as cs -> (f :@@: cs) -> r)
-> r
sinkabilityProofK ((Name n -> Name n')
-> RenamingsK 'LoT0 'LoT0
-> RenamingsK (n ':&&: 'LoT0) (n' ':&&: 'LoT0)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name n -> Name n'
rename RenamingsK 'LoT0 'LoT0
RNil) f n
f :@@: (n ':&&: 'LoT0)
e ((forall {cs :: LoT (S -> *)}.
RenamingsK (n ':&&: 'LoT0) cs -> (f :@@: cs) -> f n')
-> f n')
-> (forall {cs :: LoT (S -> *)}.
RenamingsK (n ':&&: 'LoT0) cs -> (f :@@: cs) -> f n')
-> f n'
forall a b. (a -> b) -> a -> b
$ \RenamingsK (n ':&&: 'LoT0) cs
_ f :@@: cs
e' -> f (HeadLoT cs) -> f n'
forall a b. a -> b
unsafeCoerce f (HeadLoT cs)
f :@@: cs
e'
gsinkabilityProof1 :: GSinkableK f => (Name n -> Name n') -> f (n :&&: LoT0) -> f (n' :&&: LoT0)
gsinkabilityProof1 :: forall (f :: LoT (S -> *) -> *) (n :: S) (n' :: S).
GSinkableK f =>
(Name n -> Name n') -> f (n ':&&: 'LoT0) -> f (n' ':&&: 'LoT0)
gsinkabilityProof1 Name n -> Name n'
rename f (n ':&&: 'LoT0)
e = RenamingsK (n ':&&: 'LoT0) (n' ':&&: 'LoT0)
-> f (n ':&&: 'LoT0)
-> (forall {cs :: LoT (S -> *)}.
RenamingsK (n ':&&: 'LoT0) cs -> f cs -> f (n' ':&&: 'LoT0))
-> f (n' ':&&: 'LoT0)
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT (S -> *)) (bs :: LoT (S -> *)) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT (S -> *)). RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK ((Name n -> Name n')
-> RenamingsK 'LoT0 'LoT0
-> RenamingsK (n ':&&: 'LoT0) (n' ':&&: 'LoT0)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name n -> Name n'
rename RenamingsK 'LoT0 'LoT0
RNil) f (n ':&&: 'LoT0)
e ((forall {cs :: LoT (S -> *)}.
RenamingsK (n ':&&: 'LoT0) cs -> f cs -> f (n' ':&&: 'LoT0))
-> f (n' ':&&: 'LoT0))
-> (forall {cs :: LoT (S -> *)}.
RenamingsK (n ':&&: 'LoT0) cs -> f cs -> f (n' ':&&: 'LoT0))
-> f (n' ':&&: 'LoT0)
forall a b. (a -> b) -> a -> b
$ \RenamingsK (n ':&&: 'LoT0) cs
_ f cs
e' -> f cs -> f (n' ':&&: 'LoT0)
forall a b. a -> b
unsafeCoerce f cs
e'
gsinkabilityProof2
:: forall f n n' l r. GSinkableK f
=> (Name n -> Name n') -> f (n :&&: l :&&: LoT0)
-> (forall l'. (Name l -> Name l') -> f (n' :&&: l' :&&: LoT0) -> r)
-> r
gsinkabilityProof2 :: forall (f :: LoT (S -> S -> *) -> *) (n :: S) (n' :: S) (l :: S) r.
GSinkableK f =>
(Name n -> Name n')
-> f (n ':&&: (l ':&&: 'LoT0))
-> (forall (l' :: S).
(Name l -> Name l') -> f (n' ':&&: (l' ':&&: 'LoT0)) -> r)
-> r
gsinkabilityProof2 Name n -> Name n'
rename f (n ':&&: (l ':&&: 'LoT0))
e forall (l' :: S).
(Name l -> Name l') -> f (n' ':&&: (l' ':&&: 'LoT0)) -> r
cont =
RenamingsK (n ':&&: (l ':&&: 'LoT0)) (n' ':&&: (l ':&&: 'LoT0))
-> f (n ':&&: (l ':&&: 'LoT0))
-> (forall {cs :: LoT (S -> S -> *)}.
RenamingsK (n ':&&: (l ':&&: 'LoT0)) cs -> f cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT (S -> S -> *)) (bs :: LoT (S -> S -> *)) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT (S -> S -> *)).
RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK ((Name n -> Name n')
-> RenamingsK (l ':&&: 'LoT0) (l ':&&: 'LoT0)
-> RenamingsK (n ':&&: (l ':&&: 'LoT0)) (n' ':&&: (l ':&&: 'LoT0))
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name n -> Name n'
rename ((Name l -> Name l)
-> RenamingsK 'LoT0 'LoT0
-> RenamingsK (l ':&&: 'LoT0) (l ':&&: 'LoT0)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name l -> Name l
forall a. a -> a
id RenamingsK 'LoT0 'LoT0
RNil)) f (n ':&&: (l ':&&: 'LoT0))
e ((forall {cs :: LoT (S -> S -> *)}.
RenamingsK (n ':&&: (l ':&&: 'LoT0)) cs -> f cs -> r)
-> r)
-> (forall {cs :: LoT (S -> S -> *)}.
RenamingsK (n ':&&: (l ':&&: 'LoT0)) cs -> f cs -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \case
RCons (Name n -> Name b
_ :: Name n -> Name n'') (RCons Name a -> Name b
rename' RenamingsK as bs
RNil) -> \f cs
e' ->
case (n' :~: n') -> n' :~: b
forall a b. a -> b
unsafeCoerce (n' :~: n'
forall {k} (a :: k). a :~: a
Type.Refl :: n' Type.:~: n') :: n' Type.:~: n'' of
n' :~: b
Type.Refl -> (Name l -> Name b) -> f (n' ':&&: (b ':&&: 'LoT0)) -> r
forall (l' :: S).
(Name l -> Name l') -> f (n' ':&&: (l' ':&&: 'LoT0)) -> r
cont Name l -> Name b
Name a -> Name b
rename' f cs
f (n' ':&&: (b ':&&: 'LoT0))
e'
gsinkabilityProofK' :: GSinkableK f => RenamingsK as bs -> f as -> f bs
gsinkabilityProofK' :: forall {k} (f :: LoT k -> *) (as :: LoT k) (bs :: LoT k).
GSinkableK f =>
RenamingsK as bs -> f as -> f bs
gsinkabilityProofK' RenamingsK as bs
renameK f as
e = RenamingsK as bs
-> f as
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> f bs)
-> f bs
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT k). RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
renameK f as
e ((forall {cs :: LoT k}. RenamingsK as cs -> f cs -> f bs) -> f bs)
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> f bs) -> f bs
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
_ f cs
e' -> f cs -> f bs
forall a b. a -> b
unsafeCoerce f cs
e'
class GSinkableK p where
gsinkabilityProofK
:: forall as bs r.
RenamingsK as bs
-> p as
-> (forall cs. RenamingsK as cs -> p cs -> r)
-> r
gsinkK :: GSinkableK f => RenamingsK xs as -> RenamingsK xs bs -> f as -> f bs
gsinkK :: forall {k} (f :: LoT k -> *) (xs :: LoT k) (as :: LoT k)
(bs :: LoT k).
GSinkableK f =>
RenamingsK xs as -> RenamingsK xs bs -> f as -> f bs
gsinkK RenamingsK xs as
_ RenamingsK xs bs
_ = f as -> f bs
forall a b. a -> b
unsafeCoerce
instance GSinkableK V1 where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> V1 as
-> (forall (cs :: LoT k). RenamingsK as cs -> V1 cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename V1 as
_v1 forall (cs :: LoT k). RenamingsK as cs -> V1 cs -> r
cont =
RenamingsK as bs -> V1 bs -> r
forall (cs :: LoT k). RenamingsK as cs -> V1 cs -> r
cont RenamingsK as bs
irename (String -> V1 bs
forall a. HasCallStack => String -> a
error String
"absurd: Generics.Kind.V1")
instance GSinkableK U1 where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> U1 as
-> (forall (cs :: LoT k). RenamingsK as cs -> U1 cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename U1 as
U1 forall (cs :: LoT k). RenamingsK as cs -> U1 cs -> r
cont =
RenamingsK as bs -> U1 bs -> r
forall (cs :: LoT k). RenamingsK as cs -> U1 cs -> r
cont RenamingsK as bs
irename U1 bs
forall k (p :: k). U1 p
U1
instance GSinkableK f => GSinkableK (M1 i c f) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> M1 i c f as
-> (forall (cs :: LoT k). RenamingsK as cs -> M1 i c f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (M1 f as
x) forall (cs :: LoT k). RenamingsK as cs -> M1 i c f cs -> r
cont =
RenamingsK as bs
-> f as
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT k). RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename f as
x ((forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r) -> r)
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r) -> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
irename' f cs
x' ->
RenamingsK as cs -> M1 i c f cs -> r
forall (cs :: LoT k). RenamingsK as cs -> M1 i c f cs -> r
cont RenamingsK as cs
irename' (f cs -> M1 i c f cs
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 f cs
x')
instance (GSinkableK f, GSinkableK g) => GSinkableK (f :+: g) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> (:+:) f g as
-> (forall (cs :: LoT k). RenamingsK as cs -> (:+:) f g cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (L1 f as
x) forall (cs :: LoT k). RenamingsK as cs -> (:+:) f g cs -> r
cont =
RenamingsK as bs
-> f as
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT k). RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename f as
x ((forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r) -> r)
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r) -> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
irename' f cs
x' ->
RenamingsK as cs -> (:+:) f g cs -> r
forall (cs :: LoT k). RenamingsK as cs -> (:+:) f g cs -> r
cont RenamingsK as cs
irename' (f cs -> (:+:) f g cs
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 f cs
x')
gsinkabilityProofK RenamingsK as bs
irename (R1 g as
x) forall (cs :: LoT k). RenamingsK as cs -> (:+:) f g cs -> r
cont =
RenamingsK as bs
-> g as
-> (forall {cs :: LoT k}. RenamingsK as cs -> g cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> g as
-> (forall (cs :: LoT k). RenamingsK as cs -> g cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename g as
x ((forall {cs :: LoT k}. RenamingsK as cs -> g cs -> r) -> r)
-> (forall {cs :: LoT k}. RenamingsK as cs -> g cs -> r) -> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
irename' g cs
x' ->
RenamingsK as cs -> (:+:) f g cs -> r
forall (cs :: LoT k). RenamingsK as cs -> (:+:) f g cs -> r
cont RenamingsK as cs
irename' (g cs -> (:+:) f g cs
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 g cs
x')
instance (GSinkableK f, GSinkableK g) => GSinkableK (f :*: g) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> (:*:) f g as
-> (forall (cs :: LoT k). RenamingsK as cs -> (:*:) f g cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (f as
x :*: g as
y) forall (cs :: LoT k). RenamingsK as cs -> (:*:) f g cs -> r
cont =
RenamingsK as bs
-> f as
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT k). RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename f as
x ((forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r) -> r)
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r) -> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
irename' f cs
x' ->
RenamingsK as cs
-> g as
-> (forall {cs :: LoT k}. RenamingsK as cs -> g cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> g as
-> (forall (cs :: LoT k). RenamingsK as cs -> g cs -> r)
-> r
gsinkabilityProofK RenamingsK as cs
irename' g as
y ((forall {cs :: LoT k}. RenamingsK as cs -> g cs -> r) -> r)
-> (forall {cs :: LoT k}. RenamingsK as cs -> g cs -> r) -> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
irename'' g cs
y' ->
RenamingsK as cs -> (:*:) f g cs -> r
forall (cs :: LoT k). RenamingsK as cs -> (:*:) f g cs -> r
cont RenamingsK as cs
irename'' (RenamingsK as cs -> RenamingsK as cs -> f cs -> f cs
forall {k} (f :: LoT k -> *) (xs :: LoT k) (as :: LoT k)
(bs :: LoT k).
GSinkableK f =>
RenamingsK xs as -> RenamingsK xs bs -> f as -> f bs
gsinkK RenamingsK as cs
irename' RenamingsK as cs
irename'' f cs
x' f cs -> g cs -> (:*:) f g cs
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g cs
y')
instance GSinkableK f => GSinkableK (Exists S f) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> Exists S f as
-> (forall (cs :: LoT k). RenamingsK as cs -> Exists S f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (Exists f (t ':&&: as)
x) forall (cs :: LoT k). RenamingsK as cs -> Exists S f cs -> r
cont =
RenamingsK (t ':&&: as) (t ':&&: bs)
-> f (t ':&&: as)
-> (forall {cs :: LoT (S -> k)}.
RenamingsK (t ':&&: as) cs -> f cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT (S -> k)) (bs :: LoT (S -> k)) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT (S -> k)). RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK ((Name t -> Name t)
-> RenamingsK as bs -> RenamingsK (t ':&&: as) (t ':&&: bs)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name t -> Name t
forall a. a -> a
id RenamingsK as bs
irename) f (t ':&&: as)
x ((forall {cs :: LoT (S -> k)}.
RenamingsK (t ':&&: as) cs -> f cs -> r)
-> r)
-> (forall {cs :: LoT (S -> k)}.
RenamingsK (t ':&&: as) cs -> f cs -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \case
RCons Name a -> Name b
_ RenamingsK as bs
irename' -> \f cs
x' ->
RenamingsK as bs -> Exists S f bs -> r
forall (cs :: LoT k). RenamingsK as cs -> Exists S f cs -> r
cont RenamingsK as bs
RenamingsK as bs
irename' (f (b ':&&: bs) -> Exists S f bs
forall k (t :: k) d (f :: LoT (k -> d) -> *) (x :: LoT d).
f (t ':&&: x) -> Exists k f x
Exists f cs
f (b ':&&: bs)
x')
instance {-# OVERLAPPABLE #-} GSinkableK f => GSinkableK (Exists k f) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> Exists k f as
-> (forall (cs :: LoT k). RenamingsK as cs -> Exists k f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (Exists f (t ':&&: as)
x) forall (cs :: LoT k). RenamingsK as cs -> Exists k f cs -> r
cont =
RenamingsK (t ':&&: as) (t ':&&: bs)
-> f (t ':&&: as)
-> (forall {cs :: LoT (k -> k)}.
RenamingsK (t ':&&: as) cs -> f cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT (k -> k)) (bs :: LoT (k -> k)) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT (k -> k)). RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK (RenamingsK as bs -> RenamingsK (t ':&&: as) (t ':&&: bs)
forall {k} {k1} (as :: LoT k) (bs :: LoT k) (k :: k1).
RenamingsK as bs -> RenamingsK (k ':&&: as) (k ':&&: bs)
RSkip RenamingsK as bs
irename) f (t ':&&: as)
x ((forall {cs :: LoT (k -> k)}.
RenamingsK (t ':&&: as) cs -> f cs -> r)
-> r)
-> (forall {cs :: LoT (k -> k)}.
RenamingsK (t ':&&: as) cs -> f cs -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \case
RSkip RenamingsK as bs
irename' -> \f cs
x' ->
RenamingsK as bs -> Exists k f bs -> r
forall (cs :: LoT k). RenamingsK as cs -> Exists k f cs -> r
cont RenamingsK as bs
RenamingsK as bs
irename' (f (t ':&&: bs) -> Exists k f bs
forall k (t :: k) d (f :: LoT (k -> d) -> *) (x :: LoT d).
f (t ':&&: x) -> Exists k f x
Exists f cs
f (t ':&&: bs)
x')
instance GSinkableK f => GSinkableK ((a :~~: b) :=>: f) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> (:=>:) (a :~~: b) f as
-> (forall (cs :: LoT k).
RenamingsK as cs -> (:=>:) (a :~~: b) f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (SuchThat f as
x) forall (cs :: LoT k).
RenamingsK as cs -> (:=>:) (a :~~: b) f cs -> r
cont =
RenamingsK as bs
-> f as
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r)
-> r
forall {k} (p :: LoT k -> *) (as :: LoT k) (bs :: LoT k) r.
GSinkableK p =>
RenamingsK as bs
-> p as
-> (forall (cs :: LoT k). RenamingsK as cs -> p cs -> r)
-> r
forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> f as
-> (forall (cs :: LoT k). RenamingsK as cs -> f cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename f as
x ((forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r) -> r)
-> (forall {cs :: LoT k}. RenamingsK as cs -> f cs -> r) -> r
forall a b. (a -> b) -> a -> b
$ \(RenamingsK as cs
irename' :: RenamingsK as cs) f cs
x' ->
case (Interpret a cs :~: Interpret a cs)
-> Interpret a cs :~: Interpret b cs
forall a b. a -> b
unsafeCoerce (Interpret a cs :~: Interpret a cs
Interpret a cs :~: Interpret a cs
forall {k} (a :: k). a :~: a
Type.Refl :: Interpret a cs Type.:~: Interpret a cs) :: Interpret a cs Type.:~: Interpret b cs of
Interpret a cs :~: Interpret b cs
Type.Refl -> RenamingsK as cs -> (:=>:) (a :~~: b) f cs -> r
forall (cs :: LoT k).
RenamingsK as cs -> (:=>:) (a :~~: b) f cs -> r
cont RenamingsK as cs
irename' (f cs -> (:=>:) (a :~~: b) f cs
forall {d} (c :: Atom d Constraint) (x :: LoT d) (f :: LoT d -> *).
Interpret c x =>
f x -> (:=>:) c f x
SuchThat f cs
x')
instance GSinkableK (Field (Kon a)) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> Field ('Kon a) as
-> (forall (cs :: LoT k).
RenamingsK as cs -> Field ('Kon a) cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (Field Interpret ('Kon a) as
x) forall (cs :: LoT k). RenamingsK as cs -> Field ('Kon a) cs -> r
cont =
RenamingsK as bs -> Field ('Kon a) bs -> r
forall (cs :: LoT k). RenamingsK as cs -> Field ('Kon a) cs -> r
cont RenamingsK as bs
irename (Interpret ('Kon a) bs -> Field ('Kon a) bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field Interpret ('Kon a) as
Interpret ('Kon a) bs
x)
instance GSinkableK (Field (Var a)) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> Field ('Var a) as
-> (forall (cs :: LoT k).
RenamingsK as cs -> Field ('Var a) cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (Field Interpret ('Var a) as
x) forall (cs :: LoT k). RenamingsK as cs -> Field ('Var a) cs -> r
cont =
RenamingsK as bs -> Field ('Var a) bs -> r
forall (cs :: LoT k). RenamingsK as cs -> Field ('Var a) cs -> r
cont RenamingsK as bs
irename (Interpret ('Var a) bs -> Field ('Var a) bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field (InterpretVar a as -> InterpretVar a bs
forall a b. a -> b
unsafeCoerce Interpret ('Var a) as
InterpretVar a as
x))
instance (SinkableK f, ExtractRenamingK i) => GSinkableK (Field (Kon f :@: Var i)) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> Field ('Kon f ':@: 'Var i) as
-> (forall (cs :: LoT k).
RenamingsK as cs -> Field ('Kon f ':@: 'Var i) cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (Field Interpret ('Kon f ':@: 'Var i) as
x) forall (cs :: LoT k).
RenamingsK as cs -> Field ('Kon f ':@: 'Var i) cs -> r
cont =
RenamingsK
(InterpretVar i as ':&&: 'LoT0) (InterpretVar i bs ':&&: 'LoT0)
-> (f :@@: (InterpretVar i as ':&&: 'LoT0))
-> (forall {cs :: LoT (S -> *)}.
RenamingsK (InterpretVar i as ':&&: 'LoT0) cs -> (f :@@: cs) -> r)
-> r
forall k (f :: S -> k) (as :: LoT (S -> k)) (bs :: LoT (S -> k)) r.
SinkableK f =>
RenamingsK as bs
-> (f :@@: as)
-> (forall (cs :: LoT (S -> k)).
RenamingsK as cs -> (f :@@: cs) -> r)
-> r
forall (as :: LoT (S -> *)) (bs :: LoT (S -> *)) r.
RenamingsK as bs
-> (f :@@: as)
-> (forall (cs :: LoT (S -> *)).
RenamingsK as cs -> (f :@@: cs) -> r)
-> r
sinkabilityProofK ((Name (InterpretVar i as) -> Name (InterpretVar i bs))
-> RenamingsK 'LoT0 'LoT0
-> RenamingsK
(InterpretVar i as ':&&: 'LoT0) (InterpretVar i bs ':&&: 'LoT0)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons (forall k (i :: TyVar k S) (as :: LoT k) (bs :: LoT k).
ExtractRenamingK i =>
RenamingsK as bs
-> Name (Interpret ('Var i) as) -> Name (Interpret ('Var i) bs)
extractRenamingK @_ @i RenamingsK as bs
irename) RenamingsK 'LoT0 'LoT0
RNil) f :@@: (InterpretVar i as ':&&: 'LoT0)
Interpret ('Kon f ':@: 'Var i) as
x ((forall {cs :: LoT (S -> *)}.
RenamingsK (InterpretVar i as ':&&: 'LoT0) cs -> (f :@@: cs) -> r)
-> r)
-> (forall {cs :: LoT (S -> *)}.
RenamingsK (InterpretVar i as ':&&: 'LoT0) cs -> (f :@@: cs) -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \case
RCons Name a -> Name b
rename' RenamingsK as bs
RNil -> \f :@@: cs
x' ->
RenamingsK as (PutBackLoT i b bs)
-> Field ('Kon f ':@: 'Var i) (PutBackLoT i b bs) -> r
forall (cs :: LoT k).
RenamingsK as cs -> Field ('Kon f ':@: 'Var i) cs -> r
cont (forall k (i :: TyVar k S) (c :: S) (as :: LoT k) (bs :: LoT k).
ExtractRenamingK i =>
(Name (Interpret ('Var i) as) -> Name c)
-> RenamingsK as bs -> RenamingsK as (PutBackLoT i c bs)
putBackRenamingK @_ @i Name a -> Name b
Name (Interpret ('Var i) as) -> Name b
rename' RenamingsK as bs
irename) (Interpret ('Kon f ':@: 'Var i) (PutBackLoT i b bs)
-> Field ('Kon f ':@: 'Var i) (PutBackLoT i b bs)
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field (f b -> f (InterpretVar i (PutBackLoT i b bs))
forall a b. a -> b
unsafeCoerce f b
f :@@: cs
x'))
instance SinkableK (f a) => GSinkableK (Field (Kon f :@: Kon a :@: Var0)) where
gsinkabilityProofK :: forall (as :: LoT (S -> xs)) (bs :: LoT (S -> xs)) r.
RenamingsK as bs
-> Field (('Kon f ':@: 'Kon a) ':@: Var0) as
-> (forall (cs :: LoT (S -> xs)).
RenamingsK as cs -> Field (('Kon f ':@: 'Kon a) ':@: Var0) cs -> r)
-> r
gsinkabilityProofK irename :: RenamingsK as bs
irename@(RCons Name a -> Name b
_ RenamingsK as bs
RNil) (Field Interpret (('Kon f ':@: 'Kon a) ':@: Var0) as
x) forall (cs :: LoT (S -> xs)).
RenamingsK as cs -> Field (('Kon f ':@: 'Kon a) ':@: Var0) cs -> r
cont =
RenamingsK as bs
-> (f a :@@: as)
-> (forall {cs :: LoT (S -> xs)}.
RenamingsK as cs -> (f a :@@: cs) -> r)
-> r
forall k (f :: S -> k) (as :: LoT (S -> k)) (bs :: LoT (S -> k)) r.
SinkableK f =>
RenamingsK as bs
-> (f :@@: as)
-> (forall (cs :: LoT (S -> k)).
RenamingsK as cs -> (f :@@: cs) -> r)
-> r
forall (as :: LoT (S -> xs)) (bs :: LoT (S -> xs)) r.
RenamingsK as bs
-> (f a :@@: as)
-> (forall (cs :: LoT (S -> xs)).
RenamingsK as cs -> (f a :@@: cs) -> r)
-> r
sinkabilityProofK RenamingsK as bs
irename f a :@@: as
Interpret (('Kon f ':@: 'Kon a) ':@: Var0) as
x ((forall {cs :: LoT (S -> xs)}.
RenamingsK as cs -> (f a :@@: cs) -> r)
-> r)
-> (forall {cs :: LoT (S -> xs)}.
RenamingsK as cs -> (f a :@@: cs) -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
rename' f a :@@: cs
x' ->
RenamingsK as cs -> Field (('Kon f ':@: 'Kon a) ':@: Var0) cs -> r
forall (cs :: LoT (S -> xs)).
RenamingsK as cs -> Field (('Kon f ':@: 'Kon a) ':@: Var0) cs -> r
cont RenamingsK as cs
rename' (Interpret (('Kon f ':@: 'Kon a) ':@: Var0) cs
-> Field (('Kon f ':@: 'Kon a) ':@: Var0) cs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field f a :@@: cs
Interpret (('Kon f ':@: 'Kon a) ':@: Var0) cs
x')
instance SinkableK (f a b) => GSinkableK (Field (Kon f :@: Kon a :@: Kon b :@: Var0)) where
gsinkabilityProofK :: forall (as :: LoT (S -> xs)) (bs :: LoT (S -> xs)) r.
RenamingsK as bs
-> Field ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) as
-> (forall (cs :: LoT (S -> xs)).
RenamingsK as cs
-> Field ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) cs -> r)
-> r
gsinkabilityProofK irename :: RenamingsK as bs
irename@(RCons Name a -> Name b
_ RenamingsK as bs
RNil) (Field Interpret ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) as
x) forall (cs :: LoT (S -> xs)).
RenamingsK as cs
-> Field ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) cs -> r
cont =
RenamingsK as bs
-> (f a b :@@: as)
-> (forall {cs :: LoT (S -> xs)}.
RenamingsK as cs -> (f a b :@@: cs) -> r)
-> r
forall k (f :: S -> k) (as :: LoT (S -> k)) (bs :: LoT (S -> k)) r.
SinkableK f =>
RenamingsK as bs
-> (f :@@: as)
-> (forall (cs :: LoT (S -> k)).
RenamingsK as cs -> (f :@@: cs) -> r)
-> r
forall (as :: LoT (S -> xs)) (bs :: LoT (S -> xs)) r.
RenamingsK as bs
-> (f a b :@@: as)
-> (forall (cs :: LoT (S -> xs)).
RenamingsK as cs -> (f a b :@@: cs) -> r)
-> r
sinkabilityProofK RenamingsK as bs
irename f a b :@@: as
Interpret ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) as
x ((forall {cs :: LoT (S -> xs)}.
RenamingsK as cs -> (f a b :@@: cs) -> r)
-> r)
-> (forall {cs :: LoT (S -> xs)}.
RenamingsK as cs -> (f a b :@@: cs) -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK as cs
rename' f a b :@@: cs
x' ->
RenamingsK as cs
-> Field ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) cs -> r
forall (cs :: LoT (S -> xs)).
RenamingsK as cs
-> Field ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) cs -> r
cont RenamingsK as cs
rename' (Interpret ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) cs
-> Field ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) cs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field f a b :@@: cs
Interpret ((('Kon f ':@: 'Kon a) ':@: 'Kon b) ':@: Var0) cs
x')
class (i :: TyVar k S) where
:: forall (as :: LoT k) (bs :: LoT k).
RenamingsK as bs -> Name (Interpret (Var i) as) -> Name (Interpret (Var i) bs)
putBackRenamingK :: forall c (as :: LoT k) (bs :: LoT k).
(Name (Interpret (Var i) as) -> Name c)
-> RenamingsK as bs
-> RenamingsK as (PutBackLoT i c bs)
instance ExtractRenamingK VZ where
extractRenamingK :: forall (as :: LoT (S -> xs)) (bs :: LoT (S -> xs)).
RenamingsK as bs
-> Name (Interpret ('Var 'VZ) as) -> Name (Interpret ('Var 'VZ) bs)
extractRenamingK (RCons Name a -> Name b
f RenamingsK as bs
_fs) = Name a -> Name b
Name (Interpret ('Var 'VZ) as) -> Name (Interpret ('Var 'VZ) bs)
f
putBackRenamingK :: forall (c :: S) (as :: LoT (S -> xs)) (bs :: LoT (S -> xs)).
(Name (Interpret ('Var 'VZ) as) -> Name c)
-> RenamingsK as bs -> RenamingsK as (PutBackLoT 'VZ c bs)
putBackRenamingK Name (Interpret ('Var 'VZ) as) -> Name c
f (RCons Name a -> Name b
_ RenamingsK as bs
gs) = (Name a -> Name c)
-> RenamingsK as bs -> RenamingsK (a ':&&: as) (c ':&&: bs)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name a -> Name c
Name (Interpret ('Var 'VZ) as) -> Name c
f RenamingsK as bs
RenamingsK as bs
gs
instance ExtractRenamingK x => ExtractRenamingK (VS x) where
extractRenamingK :: forall (as :: LoT (x -> xs)) (bs :: LoT (x -> xs)).
RenamingsK as bs
-> Name (Interpret ('Var ('VS x)) as)
-> Name (Interpret ('Var ('VS x)) bs)
extractRenamingK (RCons Name a -> Name b
_f RenamingsK as bs
fs) = forall k (i :: TyVar k S) (as :: LoT k) (bs :: LoT k).
ExtractRenamingK i =>
RenamingsK as bs
-> Name (Interpret ('Var i) as) -> Name (Interpret ('Var i) bs)
extractRenamingK @_ @x RenamingsK as bs
RenamingsK as bs
fs
putBackRenamingK :: forall (c :: S) (as :: LoT (x -> xs)) (bs :: LoT (x -> xs)).
(Name (Interpret ('Var ('VS x)) as) -> Name c)
-> RenamingsK as bs -> RenamingsK as (PutBackLoT ('VS x) c bs)
putBackRenamingK Name (Interpret ('Var ('VS x)) as) -> Name c
f (RCons Name a -> Name b
g RenamingsK as bs
gs) = (Name a -> Name b)
-> RenamingsK as (PutBackLoT x c bs)
-> RenamingsK (a ':&&: as) (b ':&&: PutBackLoT x c bs)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons Name a -> Name b
g (forall k (i :: TyVar k S) (c :: S) (as :: LoT k) (bs :: LoT k).
ExtractRenamingK i =>
(Name (Interpret ('Var i) as) -> Name c)
-> RenamingsK as bs -> RenamingsK as (PutBackLoT i c bs)
putBackRenamingK @_ @x Name (Interpret ('Var x) as) -> Name c
Name (Interpret ('Var ('VS x)) as) -> Name c
f RenamingsK as bs
RenamingsK as bs
gs)
extractTwoRenamingsK :: forall k (i :: TyVar k S) (j :: TyVar k S) (as :: LoT k) (bs :: LoT k).
(ExtractRenamingK i, ExtractRenamingK j)
=> RenamingsK as bs
-> RenamingsK
(Interpret (Var i) as :&&: Interpret (Var j) as :&&: LoT0)
(Interpret (Var i) bs :&&: Interpret (Var j) bs :&&: LoT0)
RenamingsK as bs
irename =
((Name (InterpretVar i as) -> Name (InterpretVar i bs))
-> RenamingsK
(InterpretVar j as ':&&: 'LoT0) (InterpretVar j bs ':&&: 'LoT0)
-> RenamingsK
(InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0))
(InterpretVar i bs ':&&: (InterpretVar j bs ':&&: 'LoT0))
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons (forall k (i :: TyVar k S) (as :: LoT k) (bs :: LoT k).
ExtractRenamingK i =>
RenamingsK as bs
-> Name (Interpret ('Var i) as) -> Name (Interpret ('Var i) bs)
extractRenamingK @_ @i RenamingsK as bs
irename) ((Name (InterpretVar j as) -> Name (InterpretVar j bs))
-> RenamingsK 'LoT0 'LoT0
-> RenamingsK
(InterpretVar j as ':&&: 'LoT0) (InterpretVar j bs ':&&: 'LoT0)
forall {k} (k1 :: S) (as :: S) (bs :: LoT k) (k :: LoT k).
(Name k1 -> Name as)
-> RenamingsK bs k -> RenamingsK (k1 ':&&: bs) (as ':&&: k)
RCons (forall k (i :: TyVar k S) (as :: LoT k) (bs :: LoT k).
ExtractRenamingK i =>
RenamingsK as bs
-> Name (Interpret ('Var i) as) -> Name (Interpret ('Var i) bs)
extractRenamingK @_ @j RenamingsK as bs
irename) RenamingsK 'LoT0 'LoT0
RNil))
putBackTwoRenamingsK :: forall k (i :: TyVar k S) (j :: TyVar k S) c1 c2 (as :: LoT k) (bs :: LoT k).
(ExtractRenamingK i, ExtractRenamingK j)
=> RenamingsK
(Interpret (Var i) as :&&: Interpret (Var j) as :&&: LoT0)
(c1 :&&: c2 :&&: LoT0)
-> RenamingsK as bs
-> RenamingsK as (PutBackLoT j c2 (PutBackLoT i c1 bs))
putBackTwoRenamingsK :: forall k (i :: TyVar k S) (j :: TyVar k S) (c1 :: S) (c2 :: S)
(as :: LoT k) (bs :: LoT k).
(ExtractRenamingK i, ExtractRenamingK j) =>
RenamingsK
(Interpret ('Var i) as ':&&: (Interpret ('Var j) as ':&&: 'LoT0))
(c1 ':&&: (c2 ':&&: 'LoT0))
-> RenamingsK as bs
-> RenamingsK as (PutBackLoT j c2 (PutBackLoT i c1 bs))
putBackTwoRenamingsK (RCons Name a -> Name b
f1 (RCons Name a -> Name b
f2 RenamingsK as bs
RNil)) RenamingsK as bs
rename
= forall k (i :: TyVar k S) (c :: S) (as :: LoT k) (bs :: LoT k).
ExtractRenamingK i =>
(Name (Interpret ('Var i) as) -> Name c)
-> RenamingsK as bs -> RenamingsK as (PutBackLoT i c bs)
putBackRenamingK @_ @j Name a -> Name b
Name (Interpret ('Var j) as) -> Name b
f2 (forall k (i :: TyVar k S) (c :: S) (as :: LoT k) (bs :: LoT k).
ExtractRenamingK i =>
(Name (Interpret ('Var i) as) -> Name c)
-> RenamingsK as bs -> RenamingsK as (PutBackLoT i c bs)
putBackRenamingK @_ @i Name a -> Name b
Name (Interpret ('Var i) as) -> Name b
f1 RenamingsK as bs
rename)
instance (SinkableK f, ExtractRenamingK i, ExtractRenamingK j) => GSinkableK (Field (Kon f :@: Var (i :: TyVar k S) :@: Var (j :: TyVar k S))) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> Field (('Kon f ':@: 'Var i) ':@: 'Var j) as
-> (forall (cs :: LoT k).
RenamingsK as cs
-> Field (('Kon f ':@: 'Var i) ':@: 'Var j) cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (Field Interpret (('Kon f ':@: 'Var i) ':@: 'Var j) as
x) forall (cs :: LoT k).
RenamingsK as cs
-> Field (('Kon f ':@: 'Var i) ':@: 'Var j) cs -> r
cont =
RenamingsK
(InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0))
(InterpretVar i bs ':&&: (InterpretVar j bs ':&&: 'LoT0))
-> (f
:@@: (InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0)))
-> (forall {cs :: LoT (S -> S -> *)}.
RenamingsK
(InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0)) cs
-> (f :@@: cs) -> r)
-> r
forall k (f :: S -> k) (as :: LoT (S -> k)) (bs :: LoT (S -> k)) r.
SinkableK f =>
RenamingsK as bs
-> (f :@@: as)
-> (forall (cs :: LoT (S -> k)).
RenamingsK as cs -> (f :@@: cs) -> r)
-> r
forall (as :: LoT (S -> S -> *)) (bs :: LoT (S -> S -> *)) r.
RenamingsK as bs
-> (f :@@: as)
-> (forall (cs :: LoT (S -> S -> *)).
RenamingsK as cs -> (f :@@: cs) -> r)
-> r
sinkabilityProofK (forall k (i :: TyVar k S) (j :: TyVar k S) (as :: LoT k)
(bs :: LoT k).
(ExtractRenamingK i, ExtractRenamingK j) =>
RenamingsK as bs
-> RenamingsK
(Interpret ('Var i) as ':&&: (Interpret ('Var j) as ':&&: 'LoT0))
(Interpret ('Var i) bs ':&&: (Interpret ('Var j) bs ':&&: 'LoT0))
extractTwoRenamingsK @_ @i @j RenamingsK as bs
irename) f :@@: (InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0))
Interpret (('Kon f ':@: 'Var i) ':@: 'Var j) as
x ((forall {cs :: LoT (S -> S -> *)}.
RenamingsK
(InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0)) cs
-> (f :@@: cs) -> r)
-> r)
-> (forall {cs :: LoT (S -> S -> *)}.
RenamingsK
(InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0)) cs
-> (f :@@: cs) -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \RenamingsK
(InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0)) cs
rename' f :@@: cs
x' ->
case RenamingsK
(InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0)) cs
rename' of
RCons Name a -> Name b
_ (RCons Name a -> Name b
_ RenamingsK as bs
RNil) ->
RenamingsK as (PutBackLoT j b (PutBackLoT i b bs))
-> Field
(('Kon f ':@: 'Var i) ':@: 'Var j)
(PutBackLoT j b (PutBackLoT i b bs))
-> r
forall (cs :: LoT k).
RenamingsK as cs
-> Field (('Kon f ':@: 'Var i) ':@: 'Var j) cs -> r
cont (forall k (i :: TyVar k S) (j :: TyVar k S) (c1 :: S) (c2 :: S)
(as :: LoT k) (bs :: LoT k).
(ExtractRenamingK i, ExtractRenamingK j) =>
RenamingsK
(Interpret ('Var i) as ':&&: (Interpret ('Var j) as ':&&: 'LoT0))
(c1 ':&&: (c2 ':&&: 'LoT0))
-> RenamingsK as bs
-> RenamingsK as (PutBackLoT j c2 (PutBackLoT i c1 bs))
putBackTwoRenamingsK @_ @i @j RenamingsK
(Interpret ('Var i) as ':&&: (Interpret ('Var j) as ':&&: 'LoT0))
(b ':&&: (b ':&&: 'LoT0))
RenamingsK
(InterpretVar i as ':&&: (InterpretVar j as ':&&: 'LoT0)) cs
rename' RenamingsK as bs
irename)
(Interpret
(('Kon f ':@: 'Var i) ':@: 'Var j)
(PutBackLoT j b (PutBackLoT i b bs))
-> Field
(('Kon f ':@: 'Var i) ':@: 'Var j)
(PutBackLoT j b (PutBackLoT i b bs))
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field (f b b
-> f (InterpretVar i (PutBackLoT j b (PutBackLoT i b bs)))
(InterpretVar j (PutBackLoT j b (PutBackLoT i b bs)))
forall a b. a -> b
unsafeCoerce f b b
f :@@: cs
x'))
instance (Functor f, GSinkableK (Field x)) => GSinkableK (Field (Kon f :@: x)) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> Field ('Kon f ':@: x) as
-> (forall (cs :: LoT k).
RenamingsK as cs -> Field ('Kon f ':@: x) cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (Field Interpret ('Kon f ':@: x) as
x) forall (cs :: LoT k).
RenamingsK as cs -> Field ('Kon f ':@: x) cs -> r
cont =
RenamingsK as bs -> Field ('Kon f ':@: x) bs -> r
forall (cs :: LoT k).
RenamingsK as cs -> Field ('Kon f ':@: x) cs -> r
cont RenamingsK as bs
irename (Interpret ('Kon f ':@: x) bs -> Field ('Kon f ':@: x) bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field ((Interpret x as -> Interpret x bs)
-> f (Interpret x as) -> f (Interpret x bs)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(Field x bs -> Interpret x bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Field t x -> Interpret t x
unField (Field x bs -> Interpret x bs)
-> (Interpret x as -> Field x bs)
-> Interpret x as
-> Interpret x bs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (f :: LoT k -> *) (as :: LoT k) (bs :: LoT k).
GSinkableK f =>
RenamingsK as bs -> f as -> f bs
forall (f :: LoT k -> *) (as :: LoT k) (bs :: LoT k).
GSinkableK f =>
RenamingsK as bs -> f as -> f bs
gsinkabilityProofK' @(Field x) RenamingsK as bs
irename (Field x as -> Field x bs)
-> (Interpret x as -> Field x as) -> Interpret x as -> Field x bs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Interpret x as -> Field x as
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field)
f (Interpret x as)
Interpret ('Kon f ':@: x) as
x))
instance (Bifunctor f, GSinkableK (Field x), GSinkableK (Field y)) => GSinkableK (Field (Kon f :@: x :@: y)) where
gsinkabilityProofK :: forall (as :: LoT k) (bs :: LoT k) r.
RenamingsK as bs
-> Field (('Kon f ':@: x) ':@: y) as
-> (forall (cs :: LoT k).
RenamingsK as cs -> Field (('Kon f ':@: x) ':@: y) cs -> r)
-> r
gsinkabilityProofK RenamingsK as bs
irename (Field Interpret (('Kon f ':@: x) ':@: y) as
x) forall (cs :: LoT k).
RenamingsK as cs -> Field (('Kon f ':@: x) ':@: y) cs -> r
cont =
RenamingsK as bs -> Field (('Kon f ':@: x) ':@: y) bs -> r
forall (cs :: LoT k).
RenamingsK as cs -> Field (('Kon f ':@: x) ':@: y) cs -> r
cont RenamingsK as bs
irename (Interpret (('Kon f ':@: x) ':@: y) bs
-> Field (('Kon f ':@: x) ':@: y) bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field ((Interpret x as -> Interpret x bs)
-> (Interpret y as -> Interpret y bs)
-> f (Interpret x as) (Interpret y as)
-> f (Interpret x bs) (Interpret y bs)
forall a b c d. (a -> b) -> (c -> d) -> f a c -> f b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap
(Field x bs -> Interpret x bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Field t x -> Interpret t x
unField (Field x bs -> Interpret x bs)
-> (Interpret x as -> Field x bs)
-> Interpret x as
-> Interpret x bs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (f :: LoT k -> *) (as :: LoT k) (bs :: LoT k).
GSinkableK f =>
RenamingsK as bs -> f as -> f bs
forall (f :: LoT k -> *) (as :: LoT k) (bs :: LoT k).
GSinkableK f =>
RenamingsK as bs -> f as -> f bs
gsinkabilityProofK' @(Field x) RenamingsK as bs
irename (Field x as -> Field x bs)
-> (Interpret x as -> Field x as) -> Interpret x as -> Field x bs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Interpret x as -> Field x as
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field)
(Field y bs -> Interpret y bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Field t x -> Interpret t x
unField (Field y bs -> Interpret y bs)
-> (Interpret y as -> Field y bs)
-> Interpret y as
-> Interpret y bs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (f :: LoT k -> *) (as :: LoT k) (bs :: LoT k).
GSinkableK f =>
RenamingsK as bs -> f as -> f bs
forall (f :: LoT k -> *) (as :: LoT k) (bs :: LoT k).
GSinkableK f =>
RenamingsK as bs -> f as -> f bs
gsinkabilityProofK' @(Field y) RenamingsK as bs
irename (Field y as -> Field y bs)
-> (Interpret y as -> Field y as) -> Interpret y as -> Field y bs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Interpret y as -> Field y as
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field)
f (Interpret x as) (Interpret y as)
Interpret (('Kon f ':@: x) ':@: y) as
x))
gunsafeWithPatternViaHasNameBinders
:: forall pattern f o n l r.
(Distinct o, GenericK pattern, GValidNameBinders pattern (RepK pattern), GHasNameBinders (RepK pattern))
=> (forall x y z r'. Distinct z => Scope z -> NameBinder x y -> (forall z'. DExt z z' => f x y z z' -> NameBinder z z' -> r') -> r')
-> (forall x z z'. DExt z z' => f x x z z')
-> (forall x y y' z z' z''. (DExt z z', DExt z' z'') => f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall o'. DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
gunsafeWithPatternViaHasNameBinders :: forall (pattern :: S -> S -> *) (f :: S -> S -> S -> S -> *)
(o :: S) (n :: S) (l :: S) r.
(Distinct o, GenericK pattern,
GValidNameBinders pattern (RepK pattern),
GHasNameBinders (RepK pattern)) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
gunsafeWithPatternViaHasNameBinders forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
withBinder forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
id_ forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
comp_ Scope o
scope pattern n l
pat forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r
cont =
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> NameBinders n l
-> (forall {o' :: S}.
DExt o o' =>
f n l o o' -> NameBinders o o' -> r)
-> r
forall (o :: S) (f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
Distinct o =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> NameBinders n l
-> (forall (o' :: S).
DExt o o' =>
f n l o o' -> NameBinders o o' -> r)
-> r
forall (pattern :: S -> S -> *) (o :: S)
(f :: S -> S -> S -> S -> *) (n :: S) (l :: S) r.
(CoSinkable pattern, Distinct o) =>
(forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r')
-> (forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z')
-> (forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S)
(z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z'')
-> Scope o
-> pattern n l
-> (forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r)
-> r
withPattern Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
forall (x :: S) (y :: S) (z :: S) r'.
Distinct z =>
Scope z
-> NameBinder x y
-> (forall (z' :: S).
DExt z z' =>
f x y z z' -> NameBinder z z' -> r')
-> r'
withBinder f x x z z'
forall (x :: S) (z :: S) (z' :: S). DExt z z' => f x x z z'
id_ f x y z z' -> f y y' z' z'' -> f x y' z z''
forall (x :: S) (y :: S) (y' :: S) (z :: S) (z' :: S) (z'' :: S).
(DExt z z', DExt z' z'') =>
f x y z z' -> f y y' z' z'' -> f x y' z z''
comp_ Scope o
scope (pattern n l -> NameBinders n l
forall (f :: S -> S -> *) (n :: S) (l :: S).
(GenericK f, GHasNameBinders (RepK f)) =>
f n l -> NameBinders n l
ggetNameBinders pattern n l
pat) ((forall {o' :: S}.
DExt o o' =>
f n l o o' -> NameBinders o o' -> r)
-> r)
-> (forall {o' :: S}.
DExt o o' =>
f n l o o' -> NameBinders o o' -> r)
-> r
forall a b. (a -> b) -> a -> b
$ \f n l o o'
result NameBinders o o'
binders ->
f n l o o' -> pattern o o' -> r
forall (o' :: S). DExt o o' => f n l o o' -> pattern o o' -> r
cont f n l o o'
result (pattern o Any -> NameBinders o o' -> pattern o o'
forall (f :: S -> S -> *) (n :: S) (l :: S) (l' :: S).
(GenericK f, GValidNameBinders f (RepK f),
GHasNameBinders (RepK f)) =>
f n l -> NameBinders n l' -> f n l'
gunsafeSetNameBinders (pattern n l -> pattern o Any
forall a b. a -> b
unsafeCoerce pattern n l
pat) NameBinders o o'
binders)
class HasNameBinders f where
getNameBinders :: f n l -> NameBinders n l
getNameBinders = RawScope -> NameBinders n l
forall (n :: S) (l :: S). RawScope -> NameBinders n l
UnsafeNameBinders (RawScope -> NameBinders n l)
-> (f n l -> RawScope) -> f n l -> NameBinders n l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [RawName] -> RawScope
IntSet.fromList ([RawName] -> RawScope)
-> (f n l -> [RawName]) -> f n l -> RawScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f n l -> [RawName]
forall (n :: S) (l :: S). f n l -> [RawName]
forall (f :: S -> S -> *) (n :: S) (l :: S).
HasNameBinders f =>
f n l -> [RawName]
getNameBindersRaw
unsafeSetNameBinders :: f n l -> NameBinders n l' -> f n l'
unsafeSetNameBinders f n l
e (UnsafeNameBinders RawScope
m) = (f n l', [RawName]) -> f n l'
forall a b. (a, b) -> a
fst (f n l -> [RawName] -> (f n l', [RawName])
forall (n :: S) (l :: S) (l' :: S).
f n l -> [RawName] -> (f n l', [RawName])
forall (f :: S -> S -> *) (n :: S) (l :: S) (l' :: S).
HasNameBinders f =>
f n l -> [RawName] -> (f n l', [RawName])
reallyUnsafeSetNameBindersRaw f n l
e (RawScope -> [RawName]
IntSet.toList RawScope
m))
getNameBindersRaw :: f n l -> [RawName]
default getNameBindersRaw :: forall n l. (GenericK f, GHasNameBinders (RepK f)) => f n l -> [RawName]
getNameBindersRaw = RepK f (n ':&&: (l ':&&: 'LoT0)) -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
forall (as :: LoT (S -> S -> *)). RepK f as -> [RawName]
ggetNameBindersRaw (RepK f (n ':&&: (l ':&&: 'LoT0)) -> [RawName])
-> (f n l -> RepK f (n ':&&: (l ':&&: 'LoT0)))
-> f n l
-> [RawName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k (f :: k) (x :: LoT k).
GenericK f =>
(f :@@: x) -> RepK f x
fromK @_ @f @(n :&&: l :&&: LoT0)
reallyUnsafeSetNameBindersRaw :: f n l -> [RawName] -> (f n l', [RawName])
default reallyUnsafeSetNameBindersRaw :: forall n l l'. (GenericK f, GValidNameBinders f (RepK f), GHasNameBinders (RepK f)) => f n l -> [RawName] -> (f n l', [RawName])
reallyUnsafeSetNameBindersRaw f n l
e [RawName]
names =
let (RepK f (n ':&&: (l' ':&&: 'LoT0))
e', [RawName]
names') = RepK f (n ':&&: (l ':&&: 'LoT0))
-> [RawName] -> (RepK f (n ':&&: (l' ':&&: 'LoT0)), [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
forall (as :: LoT (S -> S -> *)) (bs :: LoT (S -> S -> *)).
RepK f as -> [RawName] -> (RepK f bs, [RawName])
greallyUnsafeSetNameBindersRaw (forall k (f :: k) (x :: LoT k).
GenericK f =>
(f :@@: x) -> RepK f x
fromK @_ @f @(n :&&: l :&&: LoT0) f n l
f :@@: (n ':&&: (l ':&&: 'LoT0))
e) [RawName]
names
in (forall k (f :: k) (x :: LoT k). GenericK f => RepK f x -> f :@@: x
toK @_ @f @(n :&&: l' :&&: LoT0) RepK f (n ':&&: (l' ':&&: 'LoT0))
e', [RawName]
names')
instance HasNameBinders NameBinder where
getNameBindersRaw :: forall (n :: S) (l :: S). NameBinder n l -> [RawName]
getNameBindersRaw (UnsafeNameBinder (UnsafeName RawName
name)) = [RawName
name]
reallyUnsafeSetNameBindersRaw :: forall (n :: S) (l :: S) (l' :: S).
NameBinder n l -> [RawName] -> (NameBinder n l', [RawName])
reallyUnsafeSetNameBindersRaw NameBinder n l
_ (RawName
name:[RawName]
names) = (Name l' -> NameBinder n l'
forall (n :: S) (l :: S). Name l -> NameBinder n l
UnsafeNameBinder (RawName -> Name l'
forall (n :: S). RawName -> Name n
UnsafeName RawName
name), [RawName]
names)
instance HasNameBinders NameBinderList
ggetNameBinders :: forall f n l. (GenericK f, GHasNameBinders (RepK f)) => f n l -> NameBinders n l
ggetNameBinders :: forall (f :: S -> S -> *) (n :: S) (l :: S).
(GenericK f, GHasNameBinders (RepK f)) =>
f n l -> NameBinders n l
ggetNameBinders = RawScope -> NameBinders n l
forall (n :: S) (l :: S). RawScope -> NameBinders n l
UnsafeNameBinders (RawScope -> NameBinders n l)
-> (f n l -> RawScope) -> f n l -> NameBinders n l
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [RawName] -> RawScope
IntSet.fromList ([RawName] -> RawScope)
-> (f n l -> [RawName]) -> f n l -> RawScope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RepK f (n ':&&: (l ':&&: 'LoT0)) -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
forall (as :: LoT (S -> S -> *)). RepK f as -> [RawName]
ggetNameBindersRaw (RepK f (n ':&&: (l ':&&: 'LoT0)) -> [RawName])
-> (f n l -> RepK f (n ':&&: (l ':&&: 'LoT0)))
-> f n l
-> [RawName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k (f :: k) (x :: LoT k).
GenericK f =>
(f :@@: x) -> RepK f x
fromK @_ @f @(n :&&: l :&&: LoT0)
gunsafeSetNameBinders :: forall f n l l'. (GenericK f, GValidNameBinders f (RepK f), GHasNameBinders (RepK f)) => f n l -> NameBinders n l' -> f n l'
gunsafeSetNameBinders :: forall (f :: S -> S -> *) (n :: S) (l :: S) (l' :: S).
(GenericK f, GValidNameBinders f (RepK f),
GHasNameBinders (RepK f)) =>
f n l -> NameBinders n l' -> f n l'
gunsafeSetNameBinders f n l
e (UnsafeNameBinders RawScope
m) = forall k (f :: k) (x :: LoT k). GenericK f => RepK f x -> f :@@: x
toK @_ @f @(n :&&: l' :&&: LoT0) (RepK f (n ':&&: (l' ':&&: 'LoT0))
-> f :@@: (n ':&&: (l' ':&&: 'LoT0)))
-> RepK f (n ':&&: (l' ':&&: 'LoT0))
-> f :@@: (n ':&&: (l' ':&&: 'LoT0))
forall a b. (a -> b) -> a -> b
$
(RepK f (n ':&&: (l' ':&&: 'LoT0)), [RawName])
-> RepK f (n ':&&: (l' ':&&: 'LoT0))
forall a b. (a, b) -> a
fst (RepK f (n ':&&: (l ':&&: 'LoT0))
-> [RawName] -> (RepK f (n ':&&: (l' ':&&: 'LoT0)), [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
forall (as :: LoT (S -> S -> *)) (bs :: LoT (S -> S -> *)).
RepK f as -> [RawName] -> (RepK f bs, [RawName])
greallyUnsafeSetNameBindersRaw (forall k (f :: k) (x :: LoT k).
GenericK f =>
(f :@@: x) -> RepK f x
fromK @_ @f @(n :&&: l :&&: LoT0) f n l
f :@@: (n ':&&: (l ':&&: 'LoT0))
e) (RawScope -> [RawName]
IntSet.toList RawScope
m))
class GHasNameBinders f where
ggetNameBindersRaw :: f as -> [RawName]
greallyUnsafeSetNameBindersRaw :: f as -> [RawName] -> (f bs, [RawName])
instance GHasNameBinders V1 where
ggetNameBindersRaw :: forall (as :: k). V1 as -> [RawName]
ggetNameBindersRaw V1 as
_ = String -> [RawName]
forall a. HasCallStack => String -> a
error String
"absurd: Generics.Kind.V1"
greallyUnsafeSetNameBindersRaw :: forall (as :: k) (bs :: k).
V1 as -> [RawName] -> (V1 bs, [RawName])
greallyUnsafeSetNameBindersRaw V1 as
_ [RawName]
_ = String -> (V1 bs, [RawName])
forall a. HasCallStack => String -> a
error String
"absurd: Generics.Kind.V1"
instance GHasNameBinders U1 where
ggetNameBindersRaw :: forall (as :: k). U1 as -> [RawName]
ggetNameBindersRaw U1 as
U1 = []
greallyUnsafeSetNameBindersRaw :: forall (as :: k) (bs :: k).
U1 as -> [RawName] -> (U1 bs, [RawName])
greallyUnsafeSetNameBindersRaw U1 as
U1 [RawName]
names = (U1 bs
forall k (p :: k). U1 p
U1, [RawName]
names)
instance (GHasNameBinders f, GHasNameBinders g) => GHasNameBinders (f :+: g) where
ggetNameBindersRaw :: forall (as :: k). (:+:) f g as -> [RawName]
ggetNameBindersRaw (L1 f as
x) = f as -> [RawName]
forall (as :: k). f as -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
ggetNameBindersRaw f as
x
ggetNameBindersRaw (R1 g as
x) = g as -> [RawName]
forall (as :: k). g as -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
ggetNameBindersRaw g as
x
greallyUnsafeSetNameBindersRaw :: forall (as :: k) (bs :: k).
(:+:) f g as -> [RawName] -> ((:+:) f g bs, [RawName])
greallyUnsafeSetNameBindersRaw (L1 f as
x) [RawName]
names = (f bs -> (:+:) f g bs)
-> (f bs, [RawName]) -> ((:+:) f g bs, [RawName])
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first f bs -> (:+:) f g bs
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (f as -> [RawName] -> (f bs, [RawName])
forall (as :: k) (bs :: k). f as -> [RawName] -> (f bs, [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
greallyUnsafeSetNameBindersRaw f as
x [RawName]
names)
greallyUnsafeSetNameBindersRaw (R1 g as
x) [RawName]
names = (g bs -> (:+:) f g bs)
-> (g bs, [RawName]) -> ((:+:) f g bs, [RawName])
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first g bs -> (:+:) f g bs
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (g as -> [RawName] -> (g bs, [RawName])
forall (as :: k) (bs :: k). g as -> [RawName] -> (g bs, [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
greallyUnsafeSetNameBindersRaw g as
x [RawName]
names)
instance (GHasNameBinders f, GHasNameBinders g) => GHasNameBinders (f :*: g) where
ggetNameBindersRaw :: forall (as :: k). (:*:) f g as -> [RawName]
ggetNameBindersRaw (f as
x :*: g as
y) = f as -> [RawName]
forall (as :: k). f as -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
ggetNameBindersRaw f as
x [RawName] -> [RawName] -> [RawName]
forall a. Semigroup a => a -> a -> a
<> g as -> [RawName]
forall (as :: k). g as -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
ggetNameBindersRaw g as
y
greallyUnsafeSetNameBindersRaw :: forall (as :: k) (bs :: k).
(:*:) f g as -> [RawName] -> ((:*:) f g bs, [RawName])
greallyUnsafeSetNameBindersRaw (f as
x :*: g as
y) [RawName]
names =
let (f bs
x', [RawName]
names') = f as -> [RawName] -> (f bs, [RawName])
forall (as :: k) (bs :: k). f as -> [RawName] -> (f bs, [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
greallyUnsafeSetNameBindersRaw f as
x [RawName]
names
(g bs
y', [RawName]
names'') = g as -> [RawName] -> (g bs, [RawName])
forall (as :: k) (bs :: k). g as -> [RawName] -> (g bs, [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
greallyUnsafeSetNameBindersRaw g as
y [RawName]
names'
in (f bs
x' f bs -> g bs -> (:*:) f g bs
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g bs
y', [RawName]
names'')
instance GHasNameBinders f => GHasNameBinders (M1 i c f) where
ggetNameBindersRaw :: forall (as :: k). M1 i c f as -> [RawName]
ggetNameBindersRaw (M1 f as
x) = f as -> [RawName]
forall (as :: k). f as -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
ggetNameBindersRaw f as
x
greallyUnsafeSetNameBindersRaw :: forall (as :: k) (bs :: k).
M1 i c f as -> [RawName] -> (M1 i c f bs, [RawName])
greallyUnsafeSetNameBindersRaw (M1 f as
x) [RawName]
names =
let (f bs
x', [RawName]
names') = f as -> [RawName] -> (f bs, [RawName])
forall (as :: k) (bs :: k). f as -> [RawName] -> (f bs, [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
greallyUnsafeSetNameBindersRaw f as
x [RawName]
names
in (f bs -> M1 i c f bs
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 f bs
x', [RawName]
names')
instance GHasNameBinders f => GHasNameBinders (Var i :~~: Var j :=>: f) where
ggetNameBindersRaw :: forall (as :: LoT d). (:=>:) ('Var i :~~: 'Var j) f as -> [RawName]
ggetNameBindersRaw (SuchThat f as
x) = f as -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
forall (as :: LoT d). f as -> [RawName]
ggetNameBindersRaw f as
x
greallyUnsafeSetNameBindersRaw :: forall as bs. (Var i :~~: Var j :=>: f) as -> [RawName] -> ((Var i :~~: Var j :=>: f) bs, [RawName])
greallyUnsafeSetNameBindersRaw :: forall (as :: LoT d) (bs :: LoT d).
(:=>:) ('Var i :~~: 'Var j) f as
-> [RawName] -> ((:=>:) ('Var i :~~: 'Var j) f bs, [RawName])
greallyUnsafeSetNameBindersRaw (SuchThat f as
x) [RawName]
names =
case (InterpretVar i bs :~: InterpretVar i bs)
-> InterpretVar i bs :~: InterpretVar j bs
forall a b. a -> b
unsafeCoerce (Interpret ('Var i) bs :~: Interpret ('Var i) bs
InterpretVar i bs :~: InterpretVar i bs
forall {k} (a :: k). a :~: a
Type.Refl :: Interpret (Var i) bs Type.:~: Interpret (Var i) bs) :: Interpret (Var i) bs Type.:~: Interpret (Var j) bs of
Interpret ('Var i) bs :~: Interpret ('Var j) bs
Type.Refl ->
let (f bs
x', [RawName]
names') = f as -> [RawName] -> (f bs, [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
forall (as :: LoT d) (bs :: LoT d).
f as -> [RawName] -> (f bs, [RawName])
greallyUnsafeSetNameBindersRaw f as
x [RawName]
names
in (f bs -> (:=>:) ('Var i :~~: 'Var j) f bs
forall {d} (c :: Atom d Constraint) (x :: LoT d) (f :: LoT d -> *).
Interpret c x =>
f x -> (:=>:) c f x
SuchThat f bs
x', [RawName]
names')
instance GHasNameBinders f => GHasNameBinders (Exists k f) where
ggetNameBindersRaw :: forall (as :: LoT d). Exists k f as -> [RawName]
ggetNameBindersRaw (Exists f (t ':&&: as)
x) = f (t ':&&: as) -> [RawName]
forall {k} (f :: k -> *) (as :: k).
GHasNameBinders f =>
f as -> [RawName]
forall (as :: LoT (k -> d)). f as -> [RawName]
ggetNameBindersRaw f (t ':&&: as)
x
greallyUnsafeSetNameBindersRaw :: forall (as :: LoT d) (bs :: LoT d).
Exists k f as -> [RawName] -> (Exists k f bs, [RawName])
greallyUnsafeSetNameBindersRaw (Exists f (t ':&&: as)
x) [RawName]
names =
let (f (Any ':&&: bs)
x', [RawName]
names') = f (t ':&&: as) -> [RawName] -> (f (Any ':&&: bs), [RawName])
forall {k} (f :: k -> *) (as :: k) (bs :: k).
GHasNameBinders f =>
f as -> [RawName] -> (f bs, [RawName])
forall (as :: LoT (k -> d)) (bs :: LoT (k -> d)).
f as -> [RawName] -> (f bs, [RawName])
greallyUnsafeSetNameBindersRaw f (t ':&&: as)
x [RawName]
names
in (f (Any ':&&: bs) -> Exists k f bs
forall k (t :: k) d (f :: LoT (k -> d) -> *) (x :: LoT d).
f (t ':&&: x) -> Exists k f x
Exists f (Any ':&&: bs)
x', [RawName]
names')
instance GHasNameBinders (Field (Kon a)) where
ggetNameBindersRaw :: forall (as :: LoT d). Field ('Kon a) as -> [RawName]
ggetNameBindersRaw (Field Interpret ('Kon a) as
_x) = []
greallyUnsafeSetNameBindersRaw :: forall (as :: LoT d) (bs :: LoT d).
Field ('Kon a) as -> [RawName] -> (Field ('Kon a) bs, [RawName])
greallyUnsafeSetNameBindersRaw (Field Interpret ('Kon a) as
x) [RawName]
names = (Interpret ('Kon a) bs -> Field ('Kon a) bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field Interpret ('Kon a) as
Interpret ('Kon a) bs
x, [RawName]
names)
instance GHasNameBinders (Field (Var x)) where
ggetNameBindersRaw :: forall (as :: LoT d). Field ('Var x) as -> [RawName]
ggetNameBindersRaw (Field Interpret ('Var x) as
_x) = []
greallyUnsafeSetNameBindersRaw :: forall (as :: LoT d) (bs :: LoT d).
Field ('Var x) as -> [RawName] -> (Field ('Var x) bs, [RawName])
greallyUnsafeSetNameBindersRaw (Field Interpret ('Var x) as
x) [RawName]
names = (Interpret ('Var x) bs -> Field ('Var x) bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field (InterpretVar x as -> InterpretVar x bs
forall a b. a -> b
unsafeCoerce Interpret ('Var x) as
InterpretVar x as
x), [RawName]
names)
instance GHasNameBinders (Field (Kon f :@: Var i)) where
ggetNameBindersRaw :: forall (as :: LoT d). Field ('Kon f ':@: 'Var i) as -> [RawName]
ggetNameBindersRaw (Field Interpret ('Kon f ':@: 'Var i) as
_x) = []
greallyUnsafeSetNameBindersRaw :: forall (as :: LoT d) (bs :: LoT d).
Field ('Kon f ':@: 'Var i) as
-> [RawName] -> (Field ('Kon f ':@: 'Var i) bs, [RawName])
greallyUnsafeSetNameBindersRaw (Field Interpret ('Kon f ':@: 'Var i) as
x) [RawName]
names = (Interpret ('Kon f ':@: 'Var i) bs -> Field ('Kon f ':@: 'Var i) bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field (f (InterpretVar i as) -> f (InterpretVar i bs)
forall a b. a -> b
unsafeCoerce f (InterpretVar i as)
Interpret ('Kon f ':@: 'Var i) as
x), [RawName]
names)
instance HasNameBinders f => GHasNameBinders (Field (Kon f :@: Var i :@: Var j)) where
ggetNameBindersRaw :: forall (as :: LoT d).
Field (('Kon f ':@: 'Var i) ':@: 'Var j) as -> [RawName]
ggetNameBindersRaw (Field Interpret (('Kon f ':@: 'Var i) ':@: 'Var j) as
x) = f (InterpretVar i as) (InterpretVar j as) -> [RawName]
forall (n :: S) (l :: S). f n l -> [RawName]
forall (f :: S -> S -> *) (n :: S) (l :: S).
HasNameBinders f =>
f n l -> [RawName]
getNameBindersRaw f (InterpretVar i as) (InterpretVar j as)
Interpret (('Kon f ':@: 'Var i) ':@: 'Var j) as
x
greallyUnsafeSetNameBindersRaw :: forall (as :: LoT d) (bs :: LoT d).
Field (('Kon f ':@: 'Var i) ':@: 'Var j) as
-> [RawName]
-> (Field (('Kon f ':@: 'Var i) ':@: 'Var j) bs, [RawName])
greallyUnsafeSetNameBindersRaw (Field Interpret (('Kon f ':@: 'Var i) ':@: 'Var j) as
x) [RawName]
names =
let (f (InterpretVar i as) Any
x', [RawName]
names') = f (InterpretVar i as) (InterpretVar j as)
-> [RawName] -> (f (InterpretVar i as) Any, [RawName])
forall (n :: S) (l :: S) (l' :: S).
f n l -> [RawName] -> (f n l', [RawName])
forall (f :: S -> S -> *) (n :: S) (l :: S) (l' :: S).
HasNameBinders f =>
f n l -> [RawName] -> (f n l', [RawName])
reallyUnsafeSetNameBindersRaw f (InterpretVar i as) (InterpretVar j as)
Interpret (('Kon f ':@: 'Var i) ':@: 'Var j) as
x [RawName]
names
in (Interpret (('Kon f ':@: 'Var i) ':@: 'Var j) bs
-> Field (('Kon f ':@: 'Var i) ':@: 'Var j) bs
forall {d} (t :: Atom d (*)) (x :: LoT d).
Interpret t x -> Field t x
Field (f (InterpretVar i as) Any
-> f (InterpretVar i bs) (InterpretVar j bs)
forall a b. a -> b
unsafeCoerce f (InterpretVar i as) Any
x'), [RawName]
names')