Skip to content

Commit

Permalink
start on predicate simplifier
Browse files Browse the repository at this point in the history
  • Loading branch information
raehik committed Oct 10, 2024
1 parent a1df4c1 commit 08c7d63
Show file tree
Hide file tree
Showing 12 changed files with 223 additions and 111 deletions.
4 changes: 2 additions & 2 deletions .github/workflows/nix.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,8 @@ jobs:
ghc: [ghc98, ghc910]
runs-on: ubuntu-latest
permissions:
id-token: "write"
contents: "read"
id-token: write # ? requested by magic-nix-cache
contents: read # ? requested by magic-nix-cache
steps:
- uses: actions/checkout@v4
- uses: DeterminateSystems/nix-installer-action@main
Expand Down
13 changes: 13 additions & 0 deletions TODO.md
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,19 @@
the predicate nicely and slots the value in!
* hrmmmmm idk exactly how it'll look. maybe leave till later.

## Consider stop using `Ordering` for relational operators
I have an inkling that this is Bad. It makes type-level usage (widening) harder.

## Normalization and minimization
Alas, it looks like I fell upon an intractable problem. Which is annoying,
because I want to do things like combine relational predicates, which appears
less relevant to the problem of Boolean expression minimization.

I simply can't figure out what to do here. I can continue to write internals and
hope that some limited, heuristic algorithm pops out.

Ack, turns out polykinding is getting in the way as well!

## Predicates
* `All ps`, `And` a list of predicates? My errors work for it. Seems fun.

Expand Down
3 changes: 1 addition & 2 deletions rerefined.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -40,15 +40,14 @@ library
Rerefined.Predicate.Logical.Iff
Rerefined.Predicate.Logical.Nand
Rerefined.Predicate.Logical.Nor
Rerefined.Predicate.Logical.Normalize
Rerefined.Predicate.Logical.Not
Rerefined.Predicate.Logical.Or
Rerefined.Predicate.Logical.Xor
Rerefined.Predicate.Normalize
Rerefined.Predicate.Relational
Rerefined.Predicate.Relational.Internal
Rerefined.Predicate.Relational.Length
Rerefined.Predicate.Relational.Value
Rerefined.Predicate.Simplify
Rerefined.Predicate.Succeed
Rerefined.Predicate.Via
Rerefined.Predicates
Expand Down
10 changes: 0 additions & 10 deletions src/Rerefined/Predicate/Logical/Normalize.hs

This file was deleted.

12 changes: 0 additions & 12 deletions src/Rerefined/Predicate/Normalize.hs

This file was deleted.

4 changes: 2 additions & 2 deletions src/Rerefined/Predicate/Relational.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
module Rerefined.Predicate.Relational
( CompareValue
( RelOp(..)
, CompareValue
, Sign(..)
, CompareLength
, LTE, GTE
) where

import Rerefined.Predicate.Relational.Internal
Expand Down
114 changes: 40 additions & 74 deletions src/Rerefined/Predicate/Relational/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,111 +1,77 @@
{-# LANGUAGE AllowAmbiguousTypes #-} -- for ReifyRelOp
{-# LANGUAGE UndecidableInstances #-} -- for WidenRelOp

{- | Relational operator definitions.
Haskell base exports the type 'Ordering', which is an enum that states the
result of comparing two 'Ord's. We can utilize this to define /relational
operators/:
* 'LT', 'EQ' and 'GT' already map to relational operators.
* The others can be defined by combining the above with 'Or'. e.g. @'LT' ``Or``
'EQ'@ -> "less than or equal" ('<=')
What's the point? We save on definitions, and get to reuse well-known data types
which most users will have intuition for. We do have to contest with
commutativity, but this is an extremely minor concern which can only come up if
you don't use the provided type synonyms, or do lots of type-level predicate
manipulation. And we provide those swapped-order instances anyway!
-}
-- | Relational operator definitions.

module Rerefined.Predicate.Relational.Internal where

import Rerefined.Predicate.Logical.Or
import GHC.TypeNats
import Data.Type.Ord ( OrdCond )
import GHC.TypeLits ( Symbol )

import Data.Kind ( Type )

type LTE = LT `Or` EQ

-- | "not equal to" is equivalent to "strictly less than or greater than". We
-- could use 'Rerefined.Predicate.Logical.Not.Not', but sticking with just
-- 'Or' keeps the internals simple.
type NEQ = LT `Or` GT
{- | Relational operator.
type GTE = GT `Or` EQ
Constructor order is arbitrary due to @NEQ@, which obstructs ordering in a
meaningful way.
-- | Reify a relational operator type tag.
--
-- Permitted operators are @Ordering@ constructors 'LT', 'EQ' and 'GT'; and
-- combinations of these using 'Or'.
class ReifyRelOp op where
Note that these operators may be defined by combining 'Ordering's in certain
ways: for example @'LT' OR 'EQ'@ could be @LTE@, @'LT' OR 'GT'@ could be @NEQ@.
This is convenient for user intuition, permitting the use of e.g. 'LT' as a
relational operator directly. However, it complicates type-level work, as now we
can't restrict relational operators to a given kind, and we have to handle
non-standard orderings like @'GT' OR 'LT'@.
-}
data RelOp
= RelOpLT -- ^ @<@ less than
| RelOpLTE -- ^ @<=@ less than or equal to
| RelOpEQ -- ^ @==@ equal to
| RelOpNEQ -- ^ @/=@ less than or greater than (also not equal to)
| RelOpGTE -- ^ @>=@ equal to or greater than
| RelOpGT -- ^ @>@ greater than

-- | Reify a 'RelOp'.
class ReifyRelOp (op :: RelOp) where
-- | Pretty @op@.
type ShowRelOp op :: Symbol

-- | The term-level relational operator that @op@ describes.
-- | The term-level relational operator that @op :: 'RelOp'@ describes.
reifyRelOp :: forall a. Ord a => a -> a -> Bool

instance ReifyRelOp LT where
type ShowRelOp LT = "<"
instance ReifyRelOp RelOpLT where
type ShowRelOp RelOpLT = "<"
reifyRelOp = (<)

instance ReifyRelOp LTE where
type ShowRelOp LTE = "<="
instance ReifyRelOp RelOpLTE where
type ShowRelOp RelOpLTE = "<="
reifyRelOp = (<=)

-- | Hidden instance. You won't see this if you use the type synonyms.
deriving via LTE instance ReifyRelOp (EQ `Or` LT)

instance ReifyRelOp EQ where
type ShowRelOp EQ = "=="
instance ReifyRelOp RelOpEQ where
type ShowRelOp RelOpEQ = "=="
reifyRelOp = (==)

instance ReifyRelOp NEQ where
type ShowRelOp NEQ = "/="
instance ReifyRelOp RelOpNEQ where
type ShowRelOp RelOpNEQ = "/="
reifyRelOp = (/=)

-- | Hidden instance. You won't see this if you use the type synonyms.
deriving via NEQ instance ReifyRelOp (GT `Or` LT)

instance ReifyRelOp GTE where
type ShowRelOp GTE = ">="
instance ReifyRelOp RelOpGTE where
type ShowRelOp RelOpGTE = ">="
reifyRelOp = (>=)

-- | Hidden instance. You won't see this if you use the type synonyms.
deriving via GTE instance ReifyRelOp (EQ `Or` GT)

instance ReifyRelOp GT where
type ShowRelOp GT = ">"
instance ReifyRelOp RelOpGT where
type ShowRelOp RelOpGT = ">"
reifyRelOp = (>)

-- | Can we widen the given 'RelOp' on the given 'Natural' from @n@ to @m@?
type WidenRelOp :: k -> Natural -> Natural -> Bool
type WidenRelOp :: RelOp -> Natural -> Natural -> Bool
type family WidenRelOp op n m where
-- @n == m@? no problem
WidenRelOp op n n = True

-- I'd love to simplify this, but 'CmpNat' is opaque.
WidenRelOp LT n m = OrdCond (CmpNat n m) True True False
WidenRelOp LTE n m = OrdCond (CmpNat n m) True True False
WidenRelOp GTE n m = OrdCond (CmpNat n m) False True True
WidenRelOp GT n m = OrdCond (CmpNat n m) False True True

-- | swapped LTE, lower down in equation list because less common
WidenRelOp (EQ `Or` LT) n m =
OrdCond (CmpNat n m) True True False

-- | swapped GTE, lower down in equation list because less common
WidenRelOp (EQ `Or` GT) n m =
OrdCond (CmpNat n m) False True True
WidenRelOp RelOpLT n m = OrdCond (CmpNat n m) True True False
WidenRelOp RelOpLTE n m = OrdCond (CmpNat n m) True True False
WidenRelOp RelOpGTE n m = OrdCond (CmpNat n m) False True True
WidenRelOp RelOpGT n m = OrdCond (CmpNat n m) False True True

-- can't widen (==) or (/=)
WidenRelOp _ _ _ = False

-- this gets clumsier due to kinding clashes (k vs. Ordering)
type NormalizeOrRelOp :: Type -> Type
type family NormalizeOrRelOp op where
NormalizeOrRelOp (EQ `Or` LT) = LTE
NormalizeOrRelOp (GT `Or` LT) = NEQ
NormalizeOrRelOp (EQ `Or` GT) = GTE
WidenRelOp op n m = False
2 changes: 1 addition & 1 deletion src/Rerefined/Predicate/Relational/Length.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ import TypeLevelShow.Natural
import Data.Text.Builder.Linear qualified as TBL

-- | Compare length to a type-level 'Natural' using the given 'RelOp'.
data CompareLength op (n :: Natural)
data CompareLength (op :: RelOp) (n :: Natural)

-- | Precedence of 4 (matching base relational operators e.g. '>=').
instance Predicate (CompareLength op n) where
Expand Down
2 changes: 1 addition & 1 deletion src/Rerefined/Predicate/Relational/Value.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import TypeLevelShow.Natural
import GHC.TypeLits ( Symbol )

-- | Compare value to a type-level 'Natural' using the given 'RelOp'.
data CompareValue op (sign :: Sign) (n :: Natural)
data CompareValue (op :: RelOp) (sign :: Sign) (n :: Natural)

-- | Precedence of 4 (matching base relational operators e.g. '>=').
instance Predicate (CompareValue op sign n) where
Expand Down
Loading

0 comments on commit 08c7d63

Please sign in to comment.