-- | 
-- Module: Clocks
-- Description: Clocks based on a base period and phase
-- Copyright: (c) 2011 National Institute of Aerospace / Galois, Inc.
--
-- This library generates new clocks based on a base period and phase.
--
-- = Example Usage
-- 
-- Also see @Examples/ClockExamples.hs@ in the
-- <https://github.com/leepike/Copilot/tree/master/Examples Copilot repository>.
--
-- @
--     'clk' ( 'period' 3 ) ( 'phase' 1 )
-- @
--
-- is equivalent to a stream of values like:
--
-- @
--     cycle [False, True, False]
-- @
--
-- that generates a stream of values
--
-- @
--     False True False False True False False True False ...
--     0     1    2     3     4    5     6     7    8
-- @
--
-- That is true every 3 ticks (the period) starting on the 1st tick (the phase).

{-# LANGUAGE NoImplicitPrelude #-}

module Copilot.Library.Clocks
  ( clk, clk1, period, phase ) where

import Prelude ()
import qualified Prelude as P
import Copilot.Language

data ( Integral a ) => Period a = Period a
data ( Integral a ) => Phase  a = Phase  a

-- | Constructor for a 'Period'. Note that period must be greater than 0.
period :: ( Integral a ) => a -> Period a
period :: a -> Period a
period = a -> Period a
forall a. a -> Period a
Period

-- | Constructor for a 'Phase'. Note that phase must be greater than or equal
-- to 0, and must be less than the period.
phase :: ( Integral a ) => a -> Phase a
phase :: a -> Phase a
phase  = a -> Phase a
forall a. a -> Phase a
Phase

-- | Generate a clock that counts every @n@ ticks, starting at tick @m@, by
-- using an array of size @n@.
clk :: ( Integral a ) =>
       Period a       -- ^ Period @n@ of clock
       -> Phase a     -- ^ Phase @m@ of clock
       -> Stream Bool -- ^ Clock signal - 'True' on clock ticks, 'False' otherwise
clk :: Period a -> Phase a -> Stream Bool
clk ( Period period' :: a
period' ) ( Phase phase' :: a
phase' ) = Stream Bool
clk'
  where clk' :: Stream Bool
clk' = if a
period' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
P.< 1 then
                   String -> Stream Bool
forall a. String -> a
badUsage ( "clk: clock period must be 1 or greater" )
               else if a
phase' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
P.< 0 then
                        String -> Stream Bool
forall a. String -> a
badUsage ( "clk: clock phase must be 0 or greater" )
                    else if a
phase' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
P.>= a
period' then
                             String -> Stream Bool
forall a. String -> a
badUsage ( "clk: clock phase must be less than period")
                         else Int -> Bool -> [Bool]
forall a. Int -> a -> [a]
replicate ( a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
phase' ) Bool
False
                              [Bool] -> [Bool] -> [Bool]
forall a. [a] -> [a] -> [a]
P.++ Bool
True Bool -> [Bool] -> [Bool]
forall a. a -> [a] -> [a]
: Int -> Bool -> [Bool]
forall a. Int -> a -> [a]
replicate
                                   ( a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
                                     (a -> Int) -> a -> Int
forall a b. (a -> b) -> a -> b
$ a
period' a -> a -> a
forall a. Num a => a -> a -> a
P.- a
phase' a -> a -> a
forall a. Num a => a -> a -> a
P.- 1 ) Bool
False
                                   [Bool] -> Stream Bool -> Stream Bool
forall a. Typed a => [a] -> Stream a -> Stream a
++ Stream Bool
clk'


-- | This follows the same convention as 'clk', but uses a counter variable of
-- integral type /a/ rather than an array.
clk1 :: ( Integral a, Typed a ) =>
        Period a       -- ^ Period @n@ of clock
        -> Phase a     -- ^ Phase @m@ of clock
        -> Stream Bool -- ^ Clock signal - 'True' on clock ticks, 'False' otherwise
clk1 :: Period a -> Phase a -> Stream Bool
clk1 ( Period period' :: a
period' ) ( Phase phase' :: a
phase' ) =
    if a
period' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
P.< 1 then
        String -> Stream Bool
forall a. String -> a
badUsage ( "clk1: clock period must be 1 or greater" )
    else if a
phase' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
P.< 0 then
             String -> Stream Bool
forall a. String -> a
badUsage ( "clk1: clock phase must be 0 or greater" )
         else if a
phase' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
P.>= a
period' then
                  String -> Stream Bool
forall a. String -> a
badUsage ( "clk1: clock phase must be less than period")
              else
                  let counter :: Stream a
counter = [ Integer -> a
forall a. Num a => Integer -> a
P.fromInteger 0 ]
                                [a] -> Stream a -> Stream a
forall a. Typed a => [a] -> Stream a -> Stream a
++ Stream Bool -> Stream a -> Stream a -> Stream a
forall a.
Typed a =>
Stream Bool -> Stream a -> Stream a -> Stream a
mux ( Stream a
counter Stream a -> Stream a -> Stream Bool
forall a. (Eq a, Typed a) => Stream a -> Stream a -> Stream Bool
/= ( a -> Stream a
forall a. Typed a => a -> Stream a
constant (a -> Stream a) -> a -> Stream a
forall a b. (a -> b) -> a -> b
$ 
                                                        a
period' a -> a -> a
forall a. Num a => a -> a -> a
P.- 1 ) )
                                       ( Stream a
counter Stream a -> Stream a -> Stream a
forall a. Num a => a -> a -> a
P.+ 1 )
                                       ( 0 )
                  in Stream a
counter Stream a -> Stream a -> Stream Bool
forall a. (Eq a, Typed a) => Stream a -> Stream a -> Stream Bool
== a -> Stream a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
phase'