This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
import Data.Generics(Data,Typeable) | |
import Prelude(Show,Read,Eq) | |
data Bit=T | F | |
deriving (Show,Read,Eq,Data,Typeable) | |
nand :: (Bit, Bit) -> Bit | |
nand (T,T)=F | |
nand _=T | |
not :: Bit -> Bit | |
not a=nand(a,T) |
Then I moved on to the other gates. It was interesting to think about boolean logic without Or, for example, after years of only reasoning in terms of And Or and Not. But at some stage I thought "why am I doing this by hand?". I remembered a thread about a new genetic programming library on an Haskell group. Surely generating the gates would be simple enough?
So I got genprog from hackage, and adapted the example for my needs. I started with a very simple system to determine the implementation of Not:
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses #-} | |
module Gen where | |
import GenProg | |
import Data.Generics | |
import Control.Monad | |
import Control.Monad.Random | |
import Logic | |
data E=Nand E E | |
| Const Bit | |
| Param | |
deriving (Show,Eq,Data,Typeable) | |
eval :: E -> Bit -> Bit | |
eval (Nand e1 e2) p=nand (eval e1 p,eval e2 p) | |
eval (Const b) _=b | |
eval Param p=p | |
notFitness :: E -> Double | |
notFitness e=let | |
resF=eval e F | |
resT=eval e T | |
in if resF==T && resT==F | |
then ((realToFrac $ nodes e)*100) | |
else 100000000 | |
instance GenProg (Rand StdGen) E where | |
terminal = do | |
r<-getRandomR (0,2) | |
return $ [Const T,Const F,Param] !! r | |
nonterminal = liftM2 Nand terminal terminal | |
run=let | |
params = defaultEvolParams { fitness = notFitness } | |
g = mkStdGen 0 | |
in cachedBest $ evalRand (evolve params) g |
And of course, the result came quickly enough: not a=nand(a,a). No need for a Const at all! Evolution has beaten me! (OK, I'm only a not-so-intelligent designer, I suppose...)
Now, I'm going to see if this approach can take me all the way to the arithmetic unit...
3 comments:
It seems both work:
not a = nand (a,a)
nand (F,F) = T -- not F
nand (T,T) = F -- not T
not a = nand (a,T)
nand (F,T) = T -- not F
nand (T,T) = F -- not T
It works because in the truth table for nand:
a b NAND
F F T *
F T T *
T F T
T T F
Both starred methods work to get not F.
Oh I know that both works, I had tested my version before I started genprog, I was just amused that genprog found a version arguably simpler than mine (no need for constant expressions).
I think that trying to evolve a whole ALU straight off the bat is a little excessive.
How about a half adder, and then a full adder?
If my memory serves me correctly, a half adder does need Not, And, and Or, so it'd have to evolve those before it could get any further in the same way that a human would, or it might evolve it straight away. I'd be interested in the results.
Haskell is a decent choice. Once you've got your understanding of hardware down, Haskell's pattern matching and abstract data types make producing assemblers, interpreters and compilers rather easy as compared to some other languages.
Best of luck!
Post a Comment