-
-
Save rightfold/9a92bc22e709645ed1a61a3ebb484e8b to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE GADTs, TypeOperators, ScopedTypeVariables #-} | |
import Data.Eq.Type | |
import Unsafe.Coerce | |
data Expr e a where | |
Sum :: Expr [x] Int -> Expr [x] Int | |
-- | This is almost ADT, x is existetial. | |
data Expr' e a where | |
Sum' :: [x] := e -> Int := a -> Expr' e a -> Expr' e a | |
fromExpr :: Expr e a -> Expr' e a | |
fromExpr (Sum e) = Sum' refl refl (fromExpr e) | |
toExpr :: forall e a. Expr' e a -> Expr e a | |
toExpr (Sum' proofE proofA e) = coerceBack $ Sum (coerceFwd $ toExpr e) | |
where | |
coerceBack = coerce (lift2' proofE proofA) | |
coerceFwd = coerce (lift2' (symm proofE) (symm proofA)) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment