rebind ifThenElse

This commit is contained in:
rnhmjoj 2016-11-28 21:13:32 +01:00
parent be168245c9
commit f0b2422711
No known key found for this signature in database
GPG Key ID: 362BB82B7E496B7C
2 changed files with 21 additions and 4 deletions

View File

@ -13,13 +13,13 @@ cabal-version: >=1.10
library library
exposed-modules: Relation.Equality, Data.TypeClass, exposed-modules: Relation.Equality, Data.TypeClass,
Data.Bool, Data.Nat, Data.Integer Data.Bool, Data.Nat, Data.Fin, Data.Integer
Data.Function, Data.Vec Data.Function, Data.Vec
other-extensions: GADTs, DataKinds, TypeFamilies, TypeOperators, other-extensions: GADTs, DataKinds, TypeFamilies, TypeOperators,
StandaloneDeriving, ScopedTypeVariables, StandaloneDeriving, ScopedTypeVariables,
UndecidableInstances, NoImplicitPrelude, UndecidableInstances, NoImplicitPrelude,
TemplateHaskell, QuasiQuotes, PolyKinds, TemplateHaskell, QuasiQuotes, PolyKinds,
UnicodeSyntax UnicodeSyntax, RebindableSyntax
build-depends: base ==4.*, singletons, integer-gmp build-depends: base ==4.*, singletons, integer-gmp, ghc-prim
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010

View File

@ -9,16 +9,23 @@
{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
{-# LANGUAGE UnicodeSyntax #-} {-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE RebindableSyntax #-}
-- | Defines the boolean type and logical operators -- | Defines the boolean type and logical operators
module Data.Bool where module Data.Bool where
import Data.Kind (Type) import Data.Kind (Type)
import Data.TypeClass (Eq, Enum, Show) import Data.TypeClass (Eq(..), Enum, Show)
import GHC.Types (Bool(..))
import Data.Singletons.TH import Data.Singletons.TH
import Data.Singletons.Prelude.Enum import Data.Singletons.Prelude.Enum
class IfThenElse b where
ifThenElse b -> a -> a -> a
singletons [d| singletons [d|
-- | Boolean Type -- | Boolean Type
@ -49,3 +56,13 @@ singletons [d|
|] |]
-- | Values equality
() Eq a a a 𝔹
x y = case x == y of
True T
False F
instance IfThenElse 𝔹 where
ifThenElse T x y = x
ifThenElse F x y = y