module Hackage.Security.Util.TypedEmbedded (
(:=:)(Refl)
, TypeOf
, Unify(..)
, Typed(..)
, AsType(..)
) where
import MyPrelude
data a :=: b where
Refl :: a :=: a
type family TypeOf (f :: * -> *) :: * -> *
class Unify f where
unify :: f typ -> f typ' -> Maybe (typ :=: typ')
class Unify (TypeOf f) => Typed f where
typeOf :: f typ -> TypeOf f typ
class AsType f where
asType :: f typ -> TypeOf f typ' -> Maybe (f typ')
default asType :: Typed f => f typ -> TypeOf f typ' -> Maybe (f typ')
asType f typ
x TypeOf f typ'
typ = case forall (f :: * -> *) typ typ'.
Unify f =>
f typ -> f typ' -> Maybe (typ :=: typ')
unify (forall (f :: * -> *) typ. Typed f => f typ -> TypeOf f typ
typeOf f typ
x) TypeOf f typ'
typ of
Just typ :=: typ'
Refl -> forall a. a -> Maybe a
Just f typ
x
Maybe (typ :=: typ')
Nothing -> forall a. Maybe a
Nothing