summaryrefslogtreecommitdiff
path: root/src/Library/TermNet.hs
blob: 16b54468f969db7d1fbe4feed4b58f8e69fc706f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
module Library.TermNet(
    TermNet,

    empty,
    getLeafList,
    getBranchList,

    genThm,
    termToTermString,
    thmToTermString,

    addThm,
    addThmFromNode,
    matchThm
    ) where



import Data.Maybe
import Data.List
import qualified Data.Set as Set
import Data.Graph.Inductive.Graph( Node )
import qualified Data.Graph.Inductive.Graph as Graph
import Library.ProofGraph
import Library.WriteProof
import Library.Object
import Library.Theorem
import Library.Term
import Library.Parse
import Library.Semantic
import Library.Stack( Stack, at, (<:>) )
import qualified Library.Stack as Stack



data TermNet = Leaf [(Theorem, Node)] | Branch [(String, TermNet)]
    deriving (Eq, Show)



empty :: TermNet
empty = Branch []



isLeaf :: TermNet -> Bool
isLeaf (Leaf _) = True
isLeaf _ = False



isBranch :: TermNet -> Bool
isBranch (Branch _) = True
isBranch _ = False



getLeafList :: TermNet -> Maybe [(Theorem, Node)]
getLeafList net =
    case net of
        Leaf list -> Just list
        Branch list -> Nothing



getBranchList :: TermNet -> Maybe [(String, TermNet)]
getBranchList net =
    case net of 
        Leaf list -> Nothing
        Branch list -> Just list



genThm :: PGraph -> Node -> Theorem
genThm graph node =
    let gen g n num = 
            let edge = filter (\x -> (fst . thd3 $ x) == num) (Graph.out g n)
                node = (snd3 . head $ edge)
                listing = write g node
            in fromJust (((\(a,_,_,_) -> a) . fromJust $ (eval listing)) `at` 0)

        hypList = map (fromJust . objTerm) (fromJust . objList $ (gen graph node 2))
        con = fromJust . objTerm $ (gen graph node 1)

    in Theorem (Set.fromList hypList) con



termToTermString :: Term -> [String]
termToTermString term =
    case term of
        (TConst _ _) ->
            ["const"]

        (TApp func arg) ->
            ["app"] ++ (termToTermString func) ++ (termToTermString arg)

        (TAbs var body) ->
            ["abs", "var"] ++ (termToTermString body)

        (TVar var) ->
            ["var"]



thmToTermString :: Theorem -> [String]
thmToTermString theorem =
    let hypList = Set.toList (thmHyp theorem)
        f soFar hyp = soFar ++ ["hyp"] ++ (termToTermString hyp)
    in (foldl' f [] hypList) ++ ["con"] ++ (termToTermString . thmCon $ theorem)



addThm :: TermNet -> Theorem -> Node -> TermNet
addThm net theorem node =
    addThmImp net (theorem,node) (thmToTermString theorem)



addThmFromNode :: TermNet -> PGraph -> Node -> TermNet
addThmFromNode net graph node =
    let theorem = genThm graph node
    in addThmImp net (theorem,node) (thmToTermString theorem)



addThmImp :: TermNet -> (Theorem,Node) -> [String] -> TermNet
addThmImp (Branch branchList) item (x:[]) =
    let (sameKey, rest) = partition (\(y,z) -> y == x && isLeaf z) branchList
    in if (sameKey == [])
       then let leaf' = Leaf [item]
            in Branch ((x,leaf'):rest)
       else let leaf = snd . head $ sameKey
                leafList = fromJust . getLeafList $ leaf
            in if (item `elem` leafList)
               then Branch branchList
               else let leaf' = Leaf (item:leafList)
                    in Branch ((x,leaf'):rest)

addThmImp (Branch branchList) item (x:xs) =
    let (sameKey, rest) = partition (\(y,z) -> y == x) branchList
    in if (sameKey == [])
       then let net' = addThmImp empty item xs
            in Branch ((x,net'):rest)
       else let nextStepDown = snd . head $ sameKey
                net' = addThmImp nextStepDown item xs
            in Branch ((x,net'):rest)



matchThm :: TermNet -> Theorem -> [(Theorem,Node)]
matchThm net theorem =
    let hyp = Set.toList (thmHyp theorem)
        con = thmCon theorem
        (curPrefix, curTerm) = if (hyp == [])
                               then ("con", con)
                               else ("hyp", head hyp)

        r = do a <- matchImp curPrefix net
               let b = matchTermImp curTerm a
                   (branches, leaves) = partition (\x -> isBranch x) b

               c <- if (hyp == [])
                    then getLeafList (foldl' unify (Leaf []) leaves)
                    else let theorem' = Theorem (Set.fromList (tail hyp)) con
                         in return (matchThm (foldl' unify empty branches) theorem')
               return c

    in if (isNothing r) then [] else fromJust r



matchImp :: String -> TermNet -> Maybe TermNet
matchImp key net =
    do list <- getBranchList net
       let result = filter (\(x,y) -> x == key) list
       r <- if (result == []) then Nothing else Just (snd . head $ result)
       return r



matchTermImp :: Term -> TermNet -> [TermNet]
matchTermImp term net =
    let list = getBranchList net
        var = matchImp "var" net
        result =
            case term of
                (TConst c ty) -> 
                    do a <- matchImp "const" net
                       return [a]

                (TApp f x) ->
                    do a <- matchImp "app" net
                       let b = matchTermImp f a
                       return (concat (map (matchTermImp x) b))

                (TAbs v x) ->
                    do a <- matchImp "abs" net
                       b <- matchImp "var" a
                       return (matchTermImp x b)

                (TVar v) -> Nothing --don't need to do anything because variables are already taken care of

        var' = if (isNothing var) then [] else [fromJust var]
        result' = if (isNothing result) then [] else fromJust result

    in var' ++ result'



unify :: TermNet -> TermNet -> TermNet
unify (Branch a) (Branch b) = Branch (a ++ b)
unify (Leaf a) (Leaf b) = Leaf (a ++ b)