Skip to content

Instantly share code, notes, and snippets.

@gallais
Created February 15, 2017 12:34
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save gallais/df9f598e576caadf1321275cacf996f7 to your computer and use it in GitHub Desktop.
Save gallais/df9f598e576caadf1321275cacf996f7 to your computer and use it in GitHub Desktop.
Getting a type-level ITE to fire
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Ite where
import Data.Proxy
import GHC.TypeLits
import Data.Type.Equality
import Data.Singletons.Prelude
ifThenElse :: forall (a :: Nat) (b :: Nat) x l r.
(KnownNat a, KnownNat b, x ~ If (a==b) l r) =>
Proxy a -> Proxy b -> Either (x :~: l) (x :~: r)
ifThenElse pa pb = case (sing :: Sing a) %:== (sing :: Sing b) of
STrue -> Left Refl
SFalse -> Right Refl
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment