Simulating Digital Circuits --------------------------- > module Circuits where > import List (zipWith4) The first line above defines the name of this module. The second line imports the function zipWith4 from the List library. Static Boolean Values --------------------- As discussed in class, we could represent Boolean values using Haskell's Bool type, which consists of the values True and False, but instead I will define our own data type, which I will call Bit: > data Bit = Zero | One > deriving (Eq,Show) So a Bit is either a Zero or a One. Bit is the name of the type, and Zero and One are the only elements of that type. They are called "constructors". The second line above automatically "derives" methods for comparing Bits for equality, and for "showing" their values. For example: Zero == Zero returns the Boolean value True show Zero returns the string "Zero" Using this simple data type we can define the basic Boolean logic gates, as follows: > notB :: Bit -> Bit > notB Zero = One > notB One = Zero > andB, orB, nandB, norB, xorB :: Bit -> Bit -> Bit > andB One One = One > andB x y = Zero > orB Zero Zero = Zero > orB x y = One > nandB x y = notB (andB x y) > norB x y = notB (orB x y) SOLUTION: > xorB One Zero = One > xorB Zero One = One > xorB x y = Zero > halfAddB :: Bit -> Bit -> (Bit,Bit) > halfAddB x y = (andB x y, xorB x y) > addB :: Bit -> Bit -> Bit -> (Bit,Bit) > addB cin x y = let (cout1,s1) = halfAddB cin x > (cout2,s2) = halfAddB s1 y > in (orB cout1 cout2, s2) Exercise 1.1: Fill in the definition of xorB above. Then load this module into GHCi and test a few of the functions by typing a few expressions into the GHCi prompt, such as: *Circuits> nandB One Zero to see how results are returned. Also try typing: *Circuits> :t nandB One Zero which tells you the type of an expression. What happens when you ask for the type of "nandB" and "nandB One"? Exercise 1.2: Using the building blocks above, define a 2-bit adder, called "add2B", whose type is: add2B :: Bit -> Bit -> Bit -> Bit -> Bit -> (Bit,Bit,Bit) SOLUTION: > add2B :: Bit -> Bit -> Bit -> Bit -> Bit -> (Bit,Bit,Bit) > add2B cin x1 x0 y1 y0 = > let (cout1,s1) = addB cin x0 y0 > (cout2,s2) = addB cout1 x1 y1 > in (cout2,s2,s1) Test your definition on a few example inputs. > t_1 = add2B Zero Zero One Zero One -- 1+1 = 2 > t_2 = add2B One One One One One -- 3+3+1 = 7 Exercise 1.3: Define a "demultiplexer" as described in Probem 4 in Chapter 13 of the Omnibus. Its name and type should be: demuxB :: Bit -> Bit -> (Bit,Bit) SOLUTION: In designing the demux, one must decide what the value of the unselected output should be -- I will use Zero. The solution is then very simple: > demuxB :: Bit -> Bit -> (Bit,Bit) > demuxB d s = (andB d s, andB d (notB s)) Dynamic Boolean Values -- i.e. Signals -------------------------------------- Functions such as andB, orB, notB, etc. take one or two Boolean values as input, and yield one or two Boolean values as output. What we would like to do instead is have these functions simulate logic gates that take time-varying signals as input and yield time-varying signals as output. We can simulate time-varying signals using STREAMS of Boolean values, which we will represent using a Haskell LIST, i.e. [Bit]. For convenience, we will define a type synonym for this: > type Sig = [Bit] For example, a "clock" signal can be represented as [Zero, One, Zero, One, ...] ad infinitim. Indeed we can define this signal recursively as: > clock :: Sig > clock = Zero : One : clock You should convince yourself that this yields the infinite sequence mentioned above. Here's a different (slower) clock: > slowClock :: Sig > slowClock = Zero : Zero : One : slowClock Similarly, the constant "zero" and "one" signals can be represented as: > zero, one :: Sig > zero = Zero : zero > one = One : one The "infinite" nature of the Sig domain is not a concern with respect to program termination, because Haskell's "lazy evaluation" semantics will only generate that portion of the signal that we are interested in. Exercise 1.4: Load this module into GHCi. Then type "zero", "one", or "clock" at the GHCi prompt. The output will not terminate! Type Ctrl-C to terminate the computation manually. Then type "take 100 clock" and see what happens. SOLUTION: Here is the result of the latter: *Circuits> take 100 clock [Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,On e,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,O ne,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero, One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero ,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One,Zer o,One,Zero,One,Zero,One,Zero,One,Zero,One,Zero,One] Moving on to logic gates, our new "not" gate should have type: > notS :: Sig -> Sig and is easily defined as: > notS (x:xs) = notB x : notS xs Note that I do not include an equation for the empty list, because the intention is that all of these functions operate on conceptually INFINITE streams of values, such as "clock", "zero", and "one" above. The binary logic gates will all have the following type: andS, orS, nandS, norS, xorS :: Sig -> Sig -> Sig and are easily defined as: andS (x:xs) (y:ys) = andB x y : andS xs ys orS (x:xs) (y:ys) = orB x y : orS xs ys nandS (x:xs) (y:ys) = nandB x y : nandS xs ys norS (x:xs) (y:ys) = norB x y : norS xs ys xorS (x:xs) (y:ys) = xorB x y : xorS xs ys However, to make things slightly easier, we can capture this pattern of recursion using a higher-order function: > lift2 :: (a->b->c) -> [a] -> [b] -> [c] > lift2 op (x:xs) (y:ys) = op x y : lift2 op xs ys and then rewrite the above definitions as: > andS, orS, nandS, norS, xorS :: Sig -> Sig -> Sig > andS = lift2 andB > orS = lift2 orB > nandS = lift2 nandB > norS = lift2 norB > xorS = lift2 xorB Note the use of a polymorphic type for lift2, but once used with andB, orB, etc. the type variables a, b, and c all get instantiated to Bit. Exercise 1.5: Try typing things like the following at the GHCi prompt: take 20 (xorS clock slowClock) take 20 (andS clock slowClock) etc. SOLUTION: *Circuits> take 20 (xorS clock slowClock) [Zero,One,One,One,Zero,Zero,Zero,One,One,One,Zero,Zero,Zero,One,One,One,Zero,Zer o,Zero,One] *Circuits> take 20 (andS clock slowClock) [Zero,Zero,Zero,Zero,Zero,One,Zero,Zero,Zero,Zero,Zero,One,Zero,Zero,Zero,Zero,Z ero,One,Zero,Zero] Using this same trick, we can "lift" more complex combinational circuits, such as the half adder, full adder, etc. However, there is one problem: the result type of halfAdd, for example, is (Bit,Bit), so the result of "lift2 halfAdd" is [(Bit,Bit)] (thanks to polymorphism). But if we are to use this result as input to other functions, we need to turn this list of pairs into a pair of lists! No problem, let's define a function trans to do this for us: > trans2 :: [(Bit,Bit)] -> (Sig,Sig) > trans2 ((b1,b2):bps) = let (bs1,bs2) = trans2 bps > in (b1:bs1,b2:bs2) Exercise 1.6: Define a function lift3 of type: lift3 :: (a->b->c->d) -> [a] -> [b] -> [c] -> [d] Then use it and trans2 to lift addB to a function addS of type: addS :: Sig -> Sig -> Sig -> (Sig,Sig) > addS = undefined > lift3 = undefined Here is some code that will help in testing your program: > halve :: Sig -> Sig > halve (x:xs) = x : x : halve xs > > halfClock = halve clock > quarterClock = halve halfClock > > take2 n (xs1,xs2) = (take n xs1, take n xs2) > > test = take2 8 (addS quarterClock halfClock clock) The idea here is to use clock, halfClock, and quarterClock to generate all eight combinations of three inputs to addS. Once you've written your solution, just type "test" to see the result. A proper output should look like this (with slight reformatting): Main> test ([Zero,Zero,Zero,One,Zero,One,One,One], [Zero,One,One,Zero,One,Zero,Zero,One]) The first set of results is the carry, and the second set is the sum. You should verify that your program generates this result. A "D" Flip-Flop --------------- Here is a one-bit D flip-flop: > dff :: Sig -> Sig -> Sig > dff dat clk = > let out = Zero : orS (andS dat clk) > (andS out (notS clk)) > in out As explained in class, this is not a direct encoding of the "nor gates with feedback", because that would lead to non-termination. Instead, I am explicitly introducing a delay, in this case by setting the initial value of the flip-flop's output to Zero (0). From then on, the output is either whatever is on the input if the clock is One, or whatever was last on the output if the clock is Zero. The easiest way to understand this code is to draw a "stream diagram" (see Chapter 14 in SOE). But if you don't understand it fully, don't worry -- you won't have to create anything like it, and all we will do below is use dff to build larger circuits -- starting with a four-bit register. From Single Bits to Four Bits ----------------------------- In what follows, we will mostly be working with 4-bit values. So let's define another type signature for this: > type Sig4 = (Sig, Sig, Sig, Sig) Here is a four-bit register: > reg4 :: Sig4 -> Sig -> Sig4 > reg4 ~(d3,d2,d1,d0) clk = > (dff d3 clk, > dff d2 clk, > dff d1 clk, > dff d0 clk) The tilde on the tuple argument to reg4 is to ensure that the pattern is matched "lazily", but you can otherwise ignore it. Here is a one-bit stream-based multiplexer (and thus it doesn't have to be "lifted" since it is built using gates that are already lifted): > muxS :: Sig -> Sig -> Sig -> Sig > muxS as bs sel = orS (andS as sel) > (andS bs (notS sel)) Exercise 2.1: Define a four-bit multiplexer: mux4 :: Sig4 -> Sig4 -> Sig -> Sig4 Note that mux4 is to muxS as what reg4 is to dff. > mux4 = undefined To create a 4-bit adder, we can cascade 1-bit adders (i.e. full adders) as described in class, but it is different from the above because we have to connect the carry-out from one to the carry-in of the next. Here is a 2-bit version, assuming a type Sig2: > type Sig2 = (Sig, Sig) > > add2 :: Sig2 -> Sig2 -> Sig -> (Sig,Sig2) > add2 (a1,a0) (b1,b0) cin = > let (c0,s0) = addS a0 b0 cin > (c1,s1) = addS a1 b1 c0 > in (c1,(s1,s0)) Exercise 2.2: Define a 4-bit adder: add4 :: Sig4 -> Sig4 -> Sig -> (Sig,Sig4) using add2 as a guide. > add4 = undefined Example: A 4-bit Counter ------------------------ Here is a four-bit counter, first in diagram form: one4 _ \ / | (carry-in) zero -- add4 | | | clk -- reg4 | |____| | V Since reg4 starts out at zero, this circuit should count: 0000, 0001, 0010, 0011, ..., 1110, 1111, and then back to 0000, etc. Here's the Haskell code: > counter :: Sig -> Sig4 > counter clk = let out = reg4 s clk > (c,s) = add4 one4 out zero > in out > > one4 = (zero,zero,zero,one) Using the convenient "interp" function (defined at the very end of this file, but don't worry about how it works), which converts a Sig4 value into a sequence of integers, we can look at the output of the counter like this: > testCount = take 40 (interp (counter clock)) Here is the output in GHCi: Circuits> testCount [0,0,1,1,2,2,3,3,4,4,5,5,6,6,7,7,8,8,9,9,10,10, 11,11,12,12,13,13,14,14,15,15,0,0,1,1,2,2,3,3] Note that the output changes every other time-step, because each clock cycle takes two time-steps (one for Zero, the other for One). The Big Machine --------------- Finally, our "Big Machine" (nicknamed "BM") looks like this as a circuit: b ________ \ / | a mux4-- sel | \ | | add4 | | | clk -- reg4 | |___________| | V Exercise 2.3: Define a function bm: bm :: Sig4 -> Sig4 -> Sig -> Sig -> Sig4 that takes Sig4 values for inputs a and b, and Sig values for inputs clk and sel, and returns a Sig4 value as the result. > bm = undefined Exercise 2.4: Define the necessary a, b, and select signals to compute 3a+b. Be sure to show a running example of your code. For example, if a=3 and b=4, the successive results should be 0, 7, 10, and 13 (remember that 15 is the maximum) or in binary: 0000 0111 1010 1101. (I don't care what the values are after that). The Interpreter --------------- This function turns a Sig4 value into a stream of integers: > interp :: Sig4 -> [Int] > interp (a3,a2,a1,a0) = > zipWith4 (\a b c d -> a+b+c+d) > (map (foo 1) a0) (map (foo 2) a1) > (map (foo 4) a2) (map (foo 8) a3) > where foo n b = if b==One then n else 0 For example, interp ([Zero,One, Zero...], [One, One, One... ], [One, Zero,Zero...], {Zero,One, Zero...]) yields [6,13,4,...]