clash-lib-1.7.0: Clash: a functional hardware description language - As a library
Copyright(C) 2022 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Backend.Verilog.Time

Description

Utilities and definitions to deal with Verilog's time unit. These definitions are here mostly to deal with varying `timescale defintions, see:

https://www.chipverify.com/verilog/verilog-timescale

Synopsis

Documentation

data Unit Source #

Verilog time units

Constructors

Fs 
Ps 
Ns 
Us 
Ms 
S 

Instances

Instances details
Bounded Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Enum Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

succ :: Unit -> Unit #

pred :: Unit -> Unit #

toEnum :: Int -> Unit #

fromEnum :: Unit -> Int #

enumFrom :: Unit -> [Unit] #

enumFromThen :: Unit -> Unit -> [Unit] #

enumFromTo :: Unit -> Unit -> [Unit] #

enumFromThenTo :: Unit -> Unit -> Unit -> [Unit] #

Eq Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

(==) :: Unit -> Unit -> Bool #

(/=) :: Unit -> Unit -> Bool #

Ord Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

(>=) :: Unit -> Unit -> Bool #

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

Show Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

Generic Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Associated Types

type Rep Unit :: Type -> Type #

Methods

from :: Unit -> Rep Unit x #

to :: Rep Unit x -> Unit #

Hashable Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

hashWithSalt :: Int -> Unit -> Int #

hash :: Unit -> Int #

NFData Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

rnf :: Unit -> () #

type Rep Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

type Rep Unit = D1 ('MetaData "Unit" "Clash.Backend.Verilog.Time" "clash-lib-1.7.0-inplace" 'False) ((C1 ('MetaCons "Fs" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ps" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ns" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Us" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ms" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "S" 'PrefixI 'False) (U1 :: Type -> Type))))
type TryDomain t Unit Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

type TryDomain t Unit = 'NotFound

data Period Source #

Verilog time period. A combination of a length and a unit.

Constructors

Period Word64 Unit 

Instances

Instances details
Eq Period Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

(==) :: Period -> Period -> Bool #

(/=) :: Period -> Period -> Bool #

Show Period Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Generic Period Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Associated Types

type Rep Period :: Type -> Type #

Methods

from :: Period -> Rep Period x #

to :: Rep Period x -> Period #

Hashable Period Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

hashWithSalt :: Int -> Period -> Int #

hash :: Period -> Int #

NFData Period Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

rnf :: Period -> () #

type Rep Period Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

type Rep Period = D1 ('MetaData "Period" "Clash.Backend.Verilog.Time" "clash-lib-1.7.0-inplace" 'False) (C1 ('MetaCons "Period" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Unit)))

data Scale Source #

Verilog timescale. Influences simulation precision.

Constructors

Scale 

Fields

  • step :: Period

    Time step in wait statements, e.g. `#1`.

  • precision :: Period

    Simulator precision - all units will get rounded to this period.

Instances

Instances details
Eq Scale Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

(==) :: Scale -> Scale -> Bool #

(/=) :: Scale -> Scale -> Bool #

Show Scale Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

showsPrec :: Int -> Scale -> ShowS #

show :: Scale -> String #

showList :: [Scale] -> ShowS #

Generic Scale Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Associated Types

type Rep Scale :: Type -> Type #

Methods

from :: Scale -> Rep Scale x #

to :: Rep Scale x -> Scale #

Hashable Scale Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

hashWithSalt :: Int -> Scale -> Int #

hash :: Scale -> Int #

NFData Scale Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

Methods

rnf :: Scale -> () #

type Rep Scale Source # 
Instance details

Defined in Clash.Backend.Verilog.Time

type Rep Scale = D1 ('MetaData "Scale" "Clash.Backend.Verilog.Time" "clash-lib-1.7.0-inplace" 'False) (C1 ('MetaCons "Scale" 'PrefixI 'True) (S1 ('MetaSel ('Just "step") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Period) :*: S1 ('MetaSel ('Just "precision") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Period)))

scaleToString :: Scale -> String Source #

Pretty print Scale to Verilog `timescale

>>> scaleToString (Scale (Period 100 Ps) (Period 10 Fs))
"`timescale 100ps/10fs"

periodToString :: Period -> String Source #

Convert Unit to Verilog time unit

>>> periodToString (Period 100 Fs)
"100fs"

unitToString :: Unit -> String Source #

Convert Unit to Verilog time unit

>>> unitToString Ms
"ms"

parseUnit :: String -> Maybe Unit Source #

Parse string representing a Verilog time unit to Unit.

>>> parseUnit "ms"
Just Ms
>>> parseUnit "xs"
Nothing

parsePeriod :: String -> Maybe Period Source #

Parse a Verilog

>>> parsePeriod "100ms"
Just (Period 100 Ms)
>>> parsePeriod "100xs"
Nothing
>>> parsePeriod "100"
Nothing
>>> parsePeriod "ms"
Nothing

convertUnit :: Unit -> Period -> Word64 Source #

Convert a period to a specific time unit. Will always output a minimum of 1, even if the given Period is already of the right Unit.

>>> convertUnit Ps (Period 100 Ps)
100
>>> convertUnit Fs (Period 100 Ps)
100000
>>> convertUnit Ns (Period 100 Ps)
1
>>> convertUnit Ms (Period 0 Ms)
1