{-|
Copyright   :  (C) 2019, Myrtle Software Ltd,
License     :  BSD2 (see the file LICENSE)
Maintainer  :  Christiaan Baaij <christiaan.baaij@gmail.com>

Synchronizer circuits for safe clock domain crossings
-}

{-# LANGUAGE TypeFamilies #-}

module Clash.Prelude.Synchronizer
  ( -- * Bit-synchronizers
    dualFlipFlopSynchronizer
    -- * Word-synchronizers
  , asyncFIFOSynchronizer
  ) where

import qualified Clash.Explicit.Synchronizer as E
import           Clash.Promoted.Nat          (SNat)
import           Clash.Signal
  (HiddenClockResetEnable, HiddenClock, Signal, hasClock, hasReset, hasEnable)
import           Clash.XException            (NFDataX)
import           GHC.TypeLits                (type (<=))

-- | Synchronizer based on two sequentially connected flip-flops.
--
--  * __NB__: This synchronizer can be used for __bit__-synchronization.
--
--  * __NB__: Although this synchronizer does reduce metastability, it does
--  not guarantee the proper synchronization of a whole __word__. For
--  example, given that the output is sampled twice as fast as the input is
--  running, and we have two samples in the input stream that look like:
--
--      @[0111,1000]@
--
--      But the circuit driving the input stream has a longer propagation delay
--      on __msb__ compared to the __lsb__s. What can happen is an output stream
--      that looks like this:
--
--      @[0111,0111,0000,1000]@
--
--      Where the level-change of the __msb__ was not captured, but the level
--      change of the __lsb__s were.
--
--      If you want to have /safe/ __word__-synchronization use
--      'asyncFIFOSynchronizer'.
dualFlipFlopSynchronizer
  :: ( NFDataX a
     , HiddenClock dom1
     , HiddenClockResetEnable dom2
     )
  => a
  -- ^ Initial value of the two synchronization registers
  -> Signal dom1 a
  -- ^ Incoming data
  -> Signal dom2 a
  -- ^ Outgoing, synchronized, data
dualFlipFlopSynchronizer :: a -> Signal dom1 a -> Signal dom2 a
dualFlipFlopSynchronizer =
  Clock dom1
-> Clock dom2
-> Reset dom2
-> Enable dom2
-> a
-> Signal dom1 a
-> Signal dom2 a
forall a (dom1 :: Domain) (dom2 :: Domain).
(NFDataX a, KnownDomain dom1, KnownDomain dom2) =>
Clock dom1
-> Clock dom2
-> Reset dom2
-> Enable dom2
-> a
-> Signal dom1 a
-> Signal dom2 a
E.dualFlipFlopSynchronizer Clock dom1
forall (dom :: Domain). HiddenClock dom => Clock dom
hasClock Clock dom2
forall (dom :: Domain). HiddenClock dom => Clock dom
hasClock Reset dom2
forall (dom :: Domain). HiddenReset dom => Reset dom
hasReset Enable dom2
forall (dom :: Domain). HiddenEnable dom => Enable dom
hasEnable

-- | Synchronizer implemented as a FIFO around an asynchronous RAM. Based on the
-- design described in "Clash.Tutorial#multiclock", which is itself based on the
-- design described in <http://www.sunburst-design.com/papers/CummingsSNUG2002SJ_FIFO1.pdf>.
--
-- __NB__: This synchronizer can be used for __word__-synchronization.
asyncFIFOSynchronizer
  :: ( HiddenClockResetEnable rdom
     , HiddenClockResetEnable wdom
     , 2 <= addrSize
     , NFDataX a )
  => SNat addrSize
  -- ^ Size of the internally used addresses, the  FIFO contains @2^addrSize@
  -- elements.
  -> Signal rdom Bool
  -- ^ Read request
  -> Signal wdom (Maybe a)
  -- ^ Element to insert
  -> (Signal rdom a, Signal rdom Bool, Signal wdom Bool)
  -- ^ (Oldest element in the FIFO, @empty@ flag, @full@ flag)
asyncFIFOSynchronizer :: SNat addrSize
-> Signal rdom Bool
-> Signal wdom (Maybe a)
-> (Signal rdom a, Signal rdom Bool, Signal wdom Bool)
asyncFIFOSynchronizer SNat addrSize
addrSize =
  SNat addrSize
-> Clock wdom
-> Clock rdom
-> Reset wdom
-> Reset rdom
-> Enable wdom
-> Enable rdom
-> Signal rdom Bool
-> Signal wdom (Maybe a)
-> (Signal rdom a, Signal rdom Bool, Signal wdom Bool)
forall (wdom :: Domain) (rdom :: Domain) (addrSize :: Nat) a.
(KnownDomain wdom, KnownDomain rdom, 2 <= addrSize, NFDataX a) =>
SNat addrSize
-> Clock wdom
-> Clock rdom
-> Reset wdom
-> Reset rdom
-> Enable wdom
-> Enable rdom
-> Signal rdom Bool
-> Signal wdom (Maybe a)
-> (Signal rdom a, Signal rdom Bool, Signal wdom Bool)
E.asyncFIFOSynchronizer
    SNat addrSize
addrSize
    Clock wdom
forall (dom :: Domain). HiddenClock dom => Clock dom
hasClock  -- wdom
    Clock rdom
forall (dom :: Domain). HiddenClock dom => Clock dom
hasClock  -- rdom
    Reset wdom
forall (dom :: Domain). HiddenReset dom => Reset dom
hasReset  -- wdom
    Reset rdom
forall (dom :: Domain). HiddenReset dom => Reset dom
hasReset  -- rdom
    Enable wdom
forall (dom :: Domain). HiddenEnable dom => Enable dom
hasEnable  -- wdom
    Enable rdom
forall (dom :: Domain). HiddenEnable dom => Enable dom
hasEnable  -- rdom