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

Copyright(C) 2013-2016 University of Twente
2016 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellUnsafe
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • TypeFamilies
  • DataKinds
  • DeriveDataTypeable
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • MagicHash
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • TypeApplications

Clash.Sized.Internal.Index

Contents

Description

 
Synopsis

Datatypes

newtype Index (n :: Nat) Source #

Arbitrary-bounded unsigned integer represented by ceil(log_2(n)) bits.

Given an upper bound n, an Index n number has a range of: [0 .. n-1]

>>> maxBound :: Index 8
7
>>> minBound :: Index 8
0
>>> read (show (maxBound :: Index 8)) :: Index 8
7
>>> 1 + 2 :: Index 8
3
>>> 2 + 6 :: Index 8
*** Exception: Clash.Sized.Index: result 8 is out of bounds: [0..7]
...
>>> 1 - 3 :: Index 8
*** Exception: Clash.Sized.Index: result -2 is out of bounds: [0..7]
...
>>> 2 * 3 :: Index 8
6
>>> 2 * 4 :: Index 8
*** Exception: Clash.Sized.Index: result 8 is out of bounds: [0..7]
...

Constructors

I

The constructor, I, and the field, unsafeToInteger, are not synthesisable.

Instances
Resize Index Source # 
Instance details

Methods

resize :: (KnownNat a, KnownNat b) => Index a -> Index b Source #

extend :: (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

zeroExtend :: (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

signExtend :: (KnownNat a, KnownNat b) => Index a -> Index (b + a) Source #

truncateB :: KnownNat a => Index (a + b) -> Index a Source #

KnownNat n => Bounded (Index n) Source # 
Instance details

Methods

minBound :: Index n #

maxBound :: Index n #

KnownNat n => Enum (Index n) Source #

The functions: enumFrom, enumFromThen, enumFromTo, and enumFromThenTo, are not synthesisable.

Instance details

Methods

succ :: Index n -> Index n #

pred :: Index n -> Index n #

toEnum :: Int -> Index n #

fromEnum :: Index n -> Int #

enumFrom :: Index n -> [Index n] #

enumFromThen :: Index n -> Index n -> [Index n] #

enumFromTo :: Index n -> Index n -> [Index n] #

enumFromThenTo :: Index n -> Index n -> Index n -> [Index n] #

Eq (Index n) Source # 
Instance details

Methods

(==) :: Index n -> Index n -> Bool #

(/=) :: Index n -> Index n -> Bool #

KnownNat n => Integral (Index n) Source # 
Instance details

Methods

quot :: Index n -> Index n -> Index n #

rem :: Index n -> Index n -> Index n #

div :: Index n -> Index n -> Index n #

mod :: Index n -> Index n -> Index n #

quotRem :: Index n -> Index n -> (Index n, Index n) #

divMod :: Index n -> Index n -> (Index n, Index n) #

toInteger :: Index n -> Integer #

KnownNat n => Data (Index n) Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Index n -> c (Index n) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Index n) #

toConstr :: Index n -> Constr #

dataTypeOf :: Index n -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Index n)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Index n)) #

gmapT :: (forall b. Data b => b -> b) -> Index n -> Index n #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Index n -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Index n -> r #

gmapQ :: (forall d. Data d => d -> u) -> Index n -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Index n -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Index n -> m (Index n) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Index n -> m (Index n) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Index n -> m (Index n) #

KnownNat n => Num (Index n) Source #

Operators report an error on overflow and underflow

Instance details

Methods

(+) :: Index n -> Index n -> Index n #

(-) :: Index n -> Index n -> Index n #

(*) :: Index n -> Index n -> Index n #

negate :: Index n -> Index n #

abs :: Index n -> Index n #

signum :: Index n -> Index n #

fromInteger :: Integer -> Index n #

Ord (Index n) Source # 
Instance details

Methods

compare :: Index n -> Index n -> Ordering #

(<) :: Index n -> Index n -> Bool #

(<=) :: Index n -> Index n -> Bool #

(>) :: Index n -> Index n -> Bool #

(>=) :: Index n -> Index n -> Bool #

max :: Index n -> Index n -> Index n #

min :: Index n -> Index n -> Index n #

KnownNat n => Read (Index n) Source #

None of the Read class' methods are synthesisable.

Instance details
KnownNat n => Real (Index n) Source # 
Instance details

Methods

toRational :: Index n -> Rational #

Show (Index n) Source # 
Instance details

Methods

showsPrec :: Int -> Index n -> ShowS #

show :: Index n -> String #

showList :: [Index n] -> ShowS #

KnownNat n => Lift (Index n) Source # 
Instance details

Methods

lift :: Index n -> Q Exp #

KnownNat n => Arbitrary (Index n) Source # 
Instance details

Methods

arbitrary :: Gen (Index n) #

shrink :: Index n -> [Index n] #

KnownNat n => CoArbitrary (Index n) Source # 
Instance details

Methods

coarbitrary :: Index n -> Gen b -> Gen b #

KnownNat n => Default (Index n) Source # 
Instance details

Methods

def :: Index n #

NFData (Index n) Source # 
Instance details

Methods

rnf :: Index n -> () #

(KnownNat n, 1 <= n) => SaturatingNum (Index n) Source # 
Instance details
ShowX (Index n) Source # 
Instance details
KnownNat n => BitPack (Index n) Source # 
Instance details

Associated Types

type BitSize (Index n) :: Nat Source #

Bundle (Index n) Source # 
Instance details

Associated Types

type Unbundled domain (Index n) = (res :: *) Source #

Methods

bundle :: Unbundled domain (Index n) -> Signal domain (Index n) Source #

unbundle :: Signal domain (Index n) -> Unbundled domain (Index n) Source #

ExtendingNum (Index m) (Index n) Source # 
Instance details

Associated Types

type AResult (Index m) (Index n) :: * Source #

type MResult (Index m) (Index n) :: * Source #

Methods

plus :: Index m -> Index n -> AResult (Index m) (Index n) Source #

minus :: Index m -> Index n -> AResult (Index m) (Index n) Source #

times :: Index m -> Index n -> MResult (Index m) (Index n) Source #

type Unbundled domain (Index n) Source # 
Instance details
type Unbundled domain (Index n) = Signal domain (Index n)
type BitSize (Index n) Source # 
Instance details
type BitSize (Index n) = CLog 2 n
type AResult (Index m) (Index n) Source # 
Instance details
type AResult (Index m) (Index n) = Index ((m + n) - 1)
type MResult (Index m) (Index n) Source # 
Instance details
type MResult (Index m) (Index n) = Index (((m - 1) * (n - 1)) + 1)

Construction

fromSNat :: (KnownNat m, CmpNat n m ~ LT) => SNat n -> Index m Source #

Safely convert an SNat value to an Index

Type classes

BitConvert

Eq

eq# :: Index n -> Index n -> Bool Source #

neq# :: Index n -> Index n -> Bool Source #

Ord

lt# :: Index n -> Index n -> Bool Source #

ge# :: Index n -> Index n -> Bool Source #

gt# :: Index n -> Index n -> Bool Source #

le# :: Index n -> Index n -> Bool Source #

Enum (not synthesisable)

enumFromTo# :: Index n -> Index n -> [Index n] Source #

enumFromThenTo# :: Index n -> Index n -> Index n -> [Index n] Source #

Bounded

Num

(+#) :: KnownNat n => Index n -> Index n -> Index n Source #

(-#) :: KnownNat n => Index n -> Index n -> Index n Source #

(*#) :: KnownNat n => Index n -> Index n -> Index n Source #

ExtendingNum

plus# :: Index m -> Index n -> Index ((m + n) - 1) Source #

minus# :: Index m -> Index n -> Index ((m + n) - 1) Source #

times# :: Index m -> Index n -> Index (((m - 1) * (n - 1)) + 1) Source #

Integral

quot# :: Index n -> Index n -> Index n Source #

rem# :: Index n -> Index n -> Index n Source #

Resize