nice readme, rename M to MIU system

This commit is contained in:
hi 2025-08-12 05:21:15 +00:00
parent b28263fdc3
commit e46bcf6ddc
3 changed files with 50 additions and 14 deletions

View file

@ -6,6 +6,7 @@ instance Show a => Show (ConcatShowList a) where
show (ConcatShowList xs) = concat $ map show xs show (ConcatShowList xs) = concat $ map show xs
-- Formal language (/grammar/production system/whatever) -- Formal language (/grammar/production system/whatever)
-- https://en.wikipedia.org/wiki/Post_canonical_system
class (Eq symbol, Show symbol) => Language symbol where class (Eq symbol, Show symbol) => Language symbol where
isWellFormed :: [symbol] -> Bool isWellFormed :: [symbol] -> Bool

View file

@ -3,17 +3,17 @@ module Logic.Language.Impl.M where
import Logic.Language (Language(..), ConcatShowList(..)) import Logic.Language (Language(..), ConcatShowList(..))
import Logic.Language.Derivation (Derivation(..)) import Logic.Language.Derivation (Derivation(..))
-- The language M -- The MIU system
-- (from "Gödel, Escher, Bach: An Eternal Golden Braid" by Douglas Hofstadter) -- (from "Gödel, Escher, Bach: An Eternal Golden Braid" by Douglas Hofstadter)
data AlphaM data AlphaMIU
= M = M
| I | I
| U | U
deriving (Eq, Show) deriving (Eq, Show)
type StringM = [AlphaM] type StringMIU = [AlphaMIU]
instance Language AlphaM where instance Language AlphaMIU where
isWellFormed (M:_) = True isWellFormed (M:_) = True
isWellFormed _ = False isWellFormed _ = False
@ -26,19 +26,19 @@ instance Language AlphaM where
] ]
-- RULE I: If you possess a string whose last letter is I, you can add on a U at the end. -- RULE I: If you possess a string whose last letter is I, you can add on a U at the end.
mRule1 :: StringM -> [StringM] mRule1 :: StringMIU -> [StringMIU]
mRule1 [I] = [[I, U]] mRule1 [I] = [[I, U]]
mRule1 (x:xs) = (x:) <$> mRule1 xs mRule1 (x:xs) = (x:) <$> mRule1 xs
mRule1 _ = [] mRule1 _ = []
-- RULE II: Suppose you have Mx. Then you may add Mxx to your collection. -- RULE II: Suppose you have Mx. Then you may add Mxx to your collection.
mRule2 :: StringM -> [StringM] mRule2 :: StringMIU -> [StringMIU]
mRule2 string@(M:xs) = [string ++ xs] mRule2 string@(M:xs) = [string ++ xs]
mRule2 _ = [] mRule2 _ = []
-- RULE III: If III occurs in one of the strings in your collection, you may -- RULE III: If III occurs in one of the strings in your collection, you may
-- make a new string with U in place of III. -- make a new string with U in place of III.
mRule3 :: StringM -> [StringM] mRule3 :: StringMIU -> [StringMIU]
mRule3 string@(M:xs) = (M:) <$> aux xs mRule3 string@(M:xs) = (M:) <$> aux xs
where where
aux (x@I:xs@(I:I:xs')) = (U:xs'):((x:) <$> aux xs) aux (x@I:xs@(I:I:xs')) = (U:xs'):((x:) <$> aux xs)
@ -47,7 +47,7 @@ mRule3 string@(M:xs) = (M:) <$> aux xs
mRule3 _ = [] mRule3 _ = []
-- RULE IV: If UU occurs inside one of your strings, you can drop it. -- RULE IV: If UU occurs inside one of your strings, you can drop it.
mRule4 :: StringM -> [StringM] mRule4 :: StringMIU -> [StringMIU]
mRule4 string@(M:xs) = (M:) <$> aux xs mRule4 string@(M:xs) = (M:) <$> aux xs
where where
aux (x@U:xs@(U:xs')) = xs':((x:) <$> aux xs) aux (x@U:xs@(U:xs')) = xs':((x:) <$> aux xs)
@ -56,13 +56,13 @@ mRule4 string@(M:xs) = (M:) <$> aux xs
mRule4 _ = [] mRule4 _ = []
{- {-
ghci> map ConcatShowList infer0 :: [ConcatShowList AlphaM] ghci> map ConcatShowList infer0 :: [ConcatShowList AlphaMIU]
[MI] [MI]
ghci> map ConcatShowList $ concat $ map ($ [M, I, I, I, I, U, U, I]) infer1 ghci> map ConcatShowList $ concat $ map ($ [M, I, I, I, I, U, U, I]) infer1
[MIIIIUUIU,MIIIIUUIIIIIUUI,MUIUUI,MIUUUI,MIIIII] [MIIIIUUIU,MIIIIUUIIIIIUUI,MUIUUI,MIUUUI,MIIIII]
-} -}
deriveMIIUII :: Derivation AlphaM deriveMIIUII :: Derivation AlphaMIU
deriveMIIUII = deriveMIIUII =
Infer1 3 0 $ Infer1 3 0 $
Infer1 2 2 $ Infer1 2 2 $

View file

@ -1,18 +1,53 @@
Statement logic !!! # statement logic !!!
# Compile it things you can do with this:
### general things
- parse string -> statement
- parse L (the formal language) string -> statement
- serialize a statement to plaintext, LaTeX, L (the formal language)
### semantic things (statements have meaning I guess)
- evaluate statements
- from a statement generate a LaTeX truth table
- match/replace patterns in statements (e.g. logical laws)
- verify logical-law equivalence of statements (TODO)
- find logical-law equivalence of statements with breadth-first search
### syntactic things (statements are strings of symbols)
- implement formal languages (symbols, axioms schemas, and inference rules):
<https://en.wikipedia.org/wiki/Post_canonical_system>
- verify derivations in formal languages
### formal languages implemented
- the MIU system (from "Gödel, Escher, Bach")
- L
## Requirements
a haskell compiler e.g. GHC
## Compile it
```sh ```sh
make make
``` ```
# Usage or look in `Makefile`
## Usage
only this has been implemented in the main function:
```sh ```sh
echo '((p->q)<->(!q->!p))' | ./logic echo '((p->q)<->(!q->!p))' | ./logic
``` ```
## Output ### Output
``` ```
Iff (Implies (Atom "p") (Atom "q")) (Implies (Not (Atom "q")) (Not (Atom "p"))) Iff (Implies (Atom "p") (Atom "q")) (Implies (Not (Atom "q")) (Not (Atom "p")))