clash-prelude-0.10.4: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2013-2015, University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellSafe
LanguageHaskell2010

CLaSH.Prelude.Moore

Contents

Description

Whereas the output of a Mealy machine depends on current transition, the output of a Moore machine depends on the previous state.

Moore machines are strictly less expressive, but may impose laxer timing requirements.

Synopsis

Moore machine synchronised to the system clock

moore Source

Arguments

:: (s -> i -> s)

Transfer function in moore machine form: state -> input -> newstate

-> (s -> o)

Output function in moore machine form: state -> output

-> s

Initial state

-> Signal i -> Signal o

Synchronous sequential function with input and output matching that of the moore machine

Create a synchronous function from a combinational function describing a moore machine

mac :: Int        -- Current state
    -> (Int,Int)  -- Input
    -> Int        -- Updated state
mac s (x,y) = x * y + s

topEntity :: Signal (Int, Int) -> Signal Int
topEntity = moore mac id 0
>>> simulate topEntity [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14...

Synchronous sequential functions can be composed just like their combinational counterpart:

dualMac :: (Signal Int, Signal Int)
        -> (Signal Int, Signal Int)
        -> Signal Int
dualMac (a,b) (x,y) = s1 + s2
  where
    s1 = moore mac id 0 (bundle (a,x))
    s2 = moore mac id 0 (bundle (b,y))

mooreB Source

Arguments

:: (Bundle i, Bundle o) 
=> (s -> i -> s)

Transfer function in moore machine form: state -> input -> newstate

-> (s -> o)

Output function in moore machine form: state -> output

-> s

Initial state

-> Unbundled i -> Unbundled o

Synchronous sequential function with input and output matching that of the moore machine

A version of moore that does automatic Bundleing

Given a functions t and o of types:

t :: Int -> (Bool, Int) -> Int
o :: Int -> (Int, Bool)

When we want to make compositions of t and o in g using moore, we have to write:

g a b c = (b1,b2,i2)
  where
    (i1,b1) = unbundle (moore t o 0 (bundle (a,b)))
    (i2,b2) = unbundle (moore t o 3 (bundle (i1,c)))

Using mooreB however we can write:

g a b c = (b1,b2,i2)
  where
    (i1,b1) = mooreB t o 0 (a,b)
    (i2,b2) = mooreB t o 3 (i1,c)

Moore machine synchronised to an arbitrary clock

moore' Source

Arguments

:: SClock clk

Clock to synchronize to

-> (s -> i -> s)

Transfer function in moore machine form: state -> input -> newstate

-> (s -> o)

Output function in moore machine form: state -> output

-> s

Initial state

-> Signal' clk i -> Signal' clk o

Synchronous sequential function with input and output matching that of the moore machine

Create a synchronous function from a combinational function describing a moore machine

mac :: Int        -- Current state
    -> (Int,Int)  -- Input
    -> (Int,Int)  -- Updated state
mac s (x,y) = x * y + s

type ClkA = Clk "A" 100

clkA :: SClock ClkA
clkA = sclock

topEntity :: Signal' ClkA (Int, Int) -> Signal' ClkA Int
topEntity = moore' clkA mac id 0
>>> simulate topEntity [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14...

Synchronous sequential functions can be composed just like their combinational counterpart:

dualMac :: (Signal' clkA Int, Signal' clkA Int)
        -> (Signal' clkA Int, Signal' clkA Int)
        -> Signal' clkA Int
dualMac (a,b) (x,y) = s1 + s2
  where
    s1 = moore' clkA mac id 0 (bundle' clkA (a,x))
    s2 = moore' clkA mac id 0 (bundle' clkA (b,y))

mooreB' Source

Arguments

:: (Bundle i, Bundle o) 
=> SClock clk 
-> (s -> i -> s)

Transfer function in moore machine form: state -> input -> newstate

-> (s -> o)

Output function in moore machine form: state -> output

-> s

Initial state

-> Unbundled' clk i -> Unbundled' clk o

Synchronous sequential function with input and output matching that of the moore machine

A version of moore' that does automatic Bundleing

Given a functions t and o of types:

t :: Int -> (Bool, Int) -> Int
o :: Int -> (Int, Bool)

When we want to make compositions of t and o in g using moore', we have to write:

g clk a b c = (b1,b2,i2)
  where
    (i1,b1) = unbundle' clk (moore' clk t o 0 (bundle' clk (a,b)))
    (i2,b2) = unbundle' clk (moore' clk t o 3 (bundle' clk (i1,c)))

Using mooreB' however we can write:

g clk a b c = (b1,b2,i2)
  where
    (i1,b1) = mooreB' clk t o 0 (a,b)
    (i2,b2) = mooreB' clk to 3 (i1,c)