Last active
July 19, 2016 12:59
-
-
Save cblp/f5676184374e357fae787e11057526f5 to your computer and use it in GitHub Desktop.
"propositions as types" is cool!
This file contains hidden or 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
module Logic.Deduction where | |
modusPonens :: (a -> b) -> a -> b | |
modusPonens = id | |
transitivity :: (b -> c) -> (a -> b) -> a -> c | |
transitivity = (.) | |
cons1 :: (a -> c) -> (b -> c) -> Either a b -> c | |
cons1 f _ (Left x) = f x | |
cons1 _ g (Right y) = g y | |
cons2 :: (a -> c) -> (b -> d) -> Either a b -> Either c d | |
cons2 f _ (Left x) = Left (f x) | |
cons2 _ g (Right y) = Right (g y) |
This file contains hidden or 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 DataKinds #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE PolyKinds #-} | |
{-# LANGUAGE TypeOperators #-} | |
module Logic.LessThan where | |
import Data.Kind (Type) | |
import GHC.TypeLits (type (+), Nat) | |
data (x :: Nat) < (y :: Nat) where | |
LessBy1 :: x < (x + 1) | |
LessByN :: x < y -> x < (y + 1) | |
class Transitive (t :: x -> x -> Type) where | |
transitive :: t a b -> t b c -> t a c | |
instance Transitive (<) where | |
transitive ab LessBy1 = LessByN ab | |
transitive ab (LessByN bcm1) = LessByN (transitive ab bcm1) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment