Skip to content

Commit

Permalink
Use Data.Map.Map instead of association list
Browse files Browse the repository at this point in the history
  • Loading branch information
bagl committed Jul 19, 2015
1 parent 96b2957 commit 067d009
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 7 deletions.
1 change: 1 addition & 0 deletions pv-uKanren.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -20,5 +20,6 @@ library
-- other-modules:
-- other-extensions:
build-depends: base >=4.6 && <4.7
, containers
hs-source-dirs: src
default-language: Haskell2010
14 changes: 7 additions & 7 deletions src/UKanren.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
{-# LANGUAGE TupleSections #-}

module UKanren where

import Control.Monad (mzero)
import qualified Data.Map as M
import Data.Monoid ((<>))

data Term = Var Index
| Atom String
| Pair Term Term
deriving (Eq)
deriving (Eq, Ord)

instance Show Term where
show t = case t of
Expand All @@ -19,7 +19,7 @@ instance Show Term where
type Index = Int
type Stream = [State]
type State = (Subs, Index)
type Subs = [(Term, Term)]
type Subs = M.Map Term Term
type Goal = State -> Stream

var :: Index -> Term
Expand All @@ -29,14 +29,14 @@ emptyStream :: Stream
emptyStream = []

emptyState :: State
emptyState = ([], 0)
emptyState = (M.empty, 0)

walk :: Term -> Subs -> Term
walk v@Var{} subs = maybe v (`walk` subs) $ lookup v subs
walk t _ = t
walk v@Var{} s = maybe v (`walk` s) $ M.lookup v s
walk t _ = t

extend :: Term -> Term -> Subs -> Subs
extend v a s = (v, a) : s
extend = M.insert

(===) :: Term -> Term -> Goal
(===) u v (s, c) = case unify u v s of
Expand Down

0 comments on commit 067d009

Please sign in to comment.