Copyright | (C) 2013-2016 University of Twente 2017 Myrtle Software Ltd Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
Extensions |
|
Clash.Explicit.Prelude.Safe
Contents
Description
This is the Safe API only of Clash.Explicit.Prelude
This module defines the explicitly clocked counterparts of the functions defined in Clash.Prelude. Take a look at Clash.Signal.Explicit to see how you can make multi-clock designs.
Synopsis
- mealy :: Clock dom gated -> Reset dom synchronous -> (s -> i -> (s, o)) -> s -> Signal dom i -> Signal dom o
- mealyB :: (Bundle i, Bundle o) => Clock dom gated -> Reset dom synchronous -> (s -> i -> (s, o)) -> s -> Unbundled dom i -> Unbundled dom o
- moore :: Clock domain gated -> Reset domain synchronous -> (s -> i -> s) -> (s -> o) -> s -> Signal domain i -> Signal domain o
- mooreB :: (Bundle i, Bundle o) => Clock domain gated -> Reset domain synchronous -> (s -> i -> s) -> (s -> o) -> s -> Unbundled domain i -> Unbundled domain o
- registerB :: Bundle a => Clock domain gated -> Reset domain synchronous -> a -> Unbundled domain a -> Unbundled domain a
- dualFlipFlopSynchronizer :: Clock domain1 gated1 -> Clock domain2 gated2 -> Reset domain2 synchronous -> a -> Signal domain1 a -> Signal domain2 a
- asyncFIFOSynchronizer :: 2 <= addrSize => SNat addrSize -> Clock wdomain wgated -> Clock rdomain rgated -> Reset wdomain synchronous -> Reset rdomain synchronous -> Signal rdomain Bool -> Signal wdomain (Maybe a) -> (Signal rdomain a, Signal rdomain Bool, Signal wdomain Bool)
- asyncRom :: (KnownNat n, Enum addr) => Vec n a -> addr -> a
- asyncRomPow2 :: KnownNat n => Vec (2 ^ n) a -> Unsigned n -> a
- rom :: (KnownNat n, Enum addr) => Clock domain gated -> Vec n a -> Signal domain addr -> Signal domain a
- romPow2 :: KnownNat n => Clock domain gated -> Vec (2 ^ n) a -> Signal domain (Unsigned n) -> Signal domain a
- asyncRam :: (Enum addr, HasCallStack) => Clock wdom wgated -> Clock rdom rgated -> SNat n -> Signal rdom addr -> Signal wdom (Maybe (addr, a)) -> Signal rdom a
- asyncRamPow2 :: forall wdom rdom wgated rgated n a. (KnownNat n, HasCallStack) => Clock wdom wgated -> Clock rdom rgated -> Signal rdom (Unsigned n) -> Signal wdom (Maybe (Unsigned n, a)) -> Signal rdom a
- blockRam :: HasCallStack => Enum addr => Clock dom gated -> Vec n a -> Signal dom addr -> Signal dom (Maybe (addr, a)) -> Signal dom a
- blockRamPow2 :: (KnownNat n, HasCallStack) => Clock dom gated -> Vec (2 ^ n) a -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, a)) -> Signal dom a
- readNew :: Eq addr => Reset domain synchronous -> Clock domain gated -> (Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a) -> Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
- isRising :: (Bounded a, Eq a) => Clock domain gated -> Reset domain synchronous -> a -> Signal domain a -> Signal domain Bool
- isFalling :: (Bounded a, Eq a) => Clock domain gated -> Reset domain synchronous -> a -> Signal domain a -> Signal domain Bool
- riseEvery :: forall domain gated synchronous n. Clock domain gated -> Reset domain synchronous -> SNat n -> Signal domain Bool
- oscillate :: forall domain gated synchronous n. Clock domain gated -> Reset domain synchronous -> Bool -> SNat n -> Signal domain Bool
- module Clash.Explicit.Signal
- module Clash.Explicit.Signal.Delayed
- module Clash.Prelude.DataFlow
- module Clash.Sized.BitVector
- module Clash.Prelude.BitIndex
- module Clash.Prelude.BitReduction
- module Clash.Sized.Signed
- module Clash.Sized.Unsigned
- module Clash.Sized.Index
- module Clash.Sized.Fixed
- module Clash.Sized.Vector
- module Clash.Sized.RTree
- module Clash.Annotations.TopEntity
- module GHC.TypeLits
- module GHC.TypeLits.Extra
- module Clash.Promoted.Nat
- module Clash.Promoted.Nat.Literals
- module Clash.Promoted.Nat.TH
- module Clash.Promoted.Symbol
- module Clash.Class.BitPack
- module Clash.Class.Num
- module Clash.Class.Resize
- module Control.Applicative
- module Data.Bits
- module Clash.XException
- undefined :: HasCallStack => a
- module Clash.NamedTypes
- seq :: a -> b -> b
- filter :: (a -> Bool) -> [a] -> [a]
- print :: Show a => a -> IO ()
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- otherwise :: Bool
- ($) :: (a -> b) -> a -> b
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- class Bounded a where
- class Enum a where
- class Eq a where
- class Fractional a => Floating a where
- class Num a => Fractional a where
- class (Real a, Enum a) => Integral a where
- class Applicative m => Monad (m :: * -> *) where
- class Functor (f :: * -> *) where
- class Num a where
- class Eq a => Ord a where
- class Read a where
- class (Num a, Ord a) => Real a where
- class (RealFrac a, Floating a) => RealFloat a where
- class (Real a, Fractional a) => RealFrac a where
- class Show a where
- class Functor f => Applicative (f :: * -> *) where
- class Foldable (t :: * -> *) where
- class (Functor t, Foldable t) => Traversable (t :: * -> *) where
- class Semigroup a where
- class Semigroup a => Monoid a where
- data Bool
- data Char
- data Double
- data Float
- data Int
- data Integer
- data Maybe a
- data Ordering
- type Rational = Ratio Integer
- data IO a
- data Word
- data Either a b
- type String = [Char]
- id :: a -> a
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- readIO :: Read a => String -> IO a
- readLn :: Read a => IO a
- appendFile :: FilePath -> String -> IO ()
- writeFile :: FilePath -> String -> IO ()
- readFile :: FilePath -> IO String
- interact :: (String -> String) -> IO ()
- getContents :: IO String
- getLine :: IO String
- getChar :: IO Char
- putStrLn :: String -> IO ()
- putStr :: String -> IO ()
- putChar :: Char -> IO ()
- ioError :: IOError -> IO a
- type FilePath = String
- userError :: String -> IOError
- type IOError = IOException
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- or :: Foldable t => t Bool -> Bool
- and :: Foldable t => t Bool -> Bool
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- unwords :: [String] -> String
- words :: String -> [String]
- unlines :: [String] -> String
- lines :: String -> [String]
- read :: Read a => String -> a
- reads :: Read a => ReadS a
- lex :: ReadS String
- readParen :: Bool -> ReadS a -> ReadS a
- type ReadS a = String -> [(a, String)]
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- lcm :: Integral a => a -> a -> a
- gcd :: Integral a => a -> a -> a
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- (^) :: (Num a, Integral b) => a -> b -> a
- odd :: Integral a => a -> Bool
- even :: Integral a => a -> Bool
- showParen :: Bool -> ShowS -> ShowS
- showString :: String -> ShowS
- showChar :: Char -> ShowS
- shows :: Show a => a -> ShowS
- type ShowS = String -> String
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- break :: (a -> Bool) -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- dropWhile :: (a -> Bool) -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- cycle :: [a] -> [a]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- maybe :: b -> (a -> b) -> Maybe a -> b
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- subtract :: Num a => a -> a -> a
- asTypeOf :: a -> a -> a
- until :: (a -> Bool) -> (a -> a) -> a -> a
- ($!) :: (a -> b) -> a -> b
- flip :: (a -> b -> c) -> b -> a -> c
- (.) :: (b -> c) -> (a -> b) -> a -> c
- const :: a -> b -> a
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- errorWithoutStackTrace :: [Char] -> a
- error :: HasCallStack => [Char] -> a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
Creating synchronous sequential circuits
Arguments
:: Clock dom gated |
|
-> Reset dom synchronous | |
-> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> Signal dom i -> Signal dom o | Synchronous sequential function with input and output matching that of the mealy machine |
Create a synchronous function from a combinational function describing a mealy machine
import qualified Data.List as L macT :: Int -- Current state -> (Int,Int) -- Input -> (Int,Int) -- (Updated state, output) macT s (x,y) = (s',s) where s' = x * y + s mac ::Clock
domain Source ->Reset
domain Asynchronous ->Signal
domain (Int, Int) ->Signal
domain Int mac clk rst =mealy
clk rst macT 0
>>>
simulate (mac systemClockGen systemResetGen) [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14... ...
Synchronous sequential functions can be composed just like their combinational counterpart:
dualMac ::Clock
domain gated ->Reset
domain synchronous -> (Signal
domain Int,Signal
domain Int) -> (Signal
domain Int,Signal
domain Int) ->Signal
domain Int dualMac clk rst (a,b) (x,y) = s1 + s2 where s1 =mealy
clk rst mac 0 (bundle
(a,x)) s2 =mealy
clk rst mac 0 (bundle
(b,y))
Arguments
:: (Bundle i, Bundle o) | |
=> Clock dom gated | |
-> Reset dom synchronous | |
-> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> Unbundled dom i -> Unbundled dom o | Synchronous sequential function with input and output matching that of the mealy machine |
A version of mealy
that does automatic Bundle
ing
Given a function f
of type:
f :: Int -> (Bool,Int) -> (Int,(Int,Bool))
When we want to make compositions of f
in g
using mealy'
, we have to
write:
g clk rst a b c = (b1,b2,i2) where (i1,b1) =unbundle
(mealy clk rst f 0 (bundle
(a,b))) (i2,b2) =unbundle
(mealy clk rst f 3 (bundle
(i1,c)))
Using mealyB'
however we can write:
g clk rst a b c = (b1,b2,i2) where (i1,b1) =mealyB
clk rst f 0 (a,b) (i2,b2) =mealyB
clk rst f 3 (i1,c)
Arguments
:: Clock domain gated |
|
-> Reset domain synchronous | |
-> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> Signal domain i -> Signal domain 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
macT :: Int -- Current state -> (Int,Int) -- Input -> (Int,Int) -- Updated state macT s (x,y) = x * y + s mac ::Clock
mac Source ->Reset
mac Asynchronous ->Signal
mac (Int, Int) ->Signal
mac Int mac clk rst =moore
clk rst macT id 0
>>>
simulate (mac systemClockGen systemResetGen) [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14... ...
Synchronous sequential functions can be composed just like their combinational counterpart:
dualMac :: Clock domain gated -> Reset domain synchronous -> (Signal
domain Int,Signal
domain Int) -> (Signal
domain Int,Signal
domain Int) ->Signal
domain Int dualMac clk rst (a,b) (x,y) = s1 + s2 where s1 =moore
clk rst mac id 0 (bundle
(a,x)) s2 =moore
clk rst mac id 0 (bundle
(b,y))
Arguments
:: (Bundle i, Bundle o) | |
=> Clock domain gated | |
-> Reset domain synchronous | |
-> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> Unbundled domain i -> Unbundled domain o | Synchronous sequential function with input and output matching that of the moore machine |
A version of moore
that does automatic Bundle
ing
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 rst a b c = (b1,b2,i2) where (i1,b1) =unbundle
(moore clk rst t o 0 (bundle
(a,b))) (i2,b2) =unbundle
(moore clk rst t o 3 (bundle
(i1,c)))
Using mooreB'
however we can write:
g clk rst a b c = (b1,b2,i2) where (i1,b1) =mooreB
clk rst t o 0 (a,b) (i2,b2) =mooreB
clk rst t o 3 (i1,c)
registerB :: Bundle a => Clock domain gated -> Reset domain synchronous -> a -> Unbundled domain a -> Unbundled domain a Source #
Create a register
function for product-type like signals (e.g.
(
)Signal
a, Signal
b)
rP :: Clock domain gated -> Reset domain synchronous -> (Signal
domain Int,Signal
domain Int) -> (Signal
domain Int,Signal
domain Int) rP clk rst =registerB
clk rst (8,8)
>>>
simulateB (rP systemClockGen systemResetGen) [(1,1),(2,2),(3,3)] :: [(Int,Int)]
[(8,8),(1,1),(2,2),(3,3)... ...
Synchronizer circuits for safe clock domain crossing
dualFlipFlopSynchronizer Source #
Arguments
:: Clock domain1 gated1 |
|
-> Clock domain2 gated2 |
|
-> Reset domain2 synchronous |
|
-> a | Initial value of the two synchronisation registers |
-> Signal domain1 a | Incoming data |
-> Signal domain2 a | Outgoing, synchronised, data |
Synchroniser based on two sequentially connected flip-flops.
- NB: This synchroniser can be used for bit-synchronization.
NB: Although this synchroniser does reduce metastability, it does not guarantee the proper synchronisation 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 lsbs. 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 lsbs were.
If you want to have safe word-synchronisation use
asyncFIFOSynchronizer
.
asyncFIFOSynchronizer Source #
Arguments
:: 2 <= addrSize | |
=> SNat addrSize | Size of the internally used addresses, the FIFO contains |
-> Clock wdomain wgated |
|
-> Clock rdomain rgated |
|
-> Reset wdomain synchronous | |
-> Reset rdomain synchronous | |
-> Signal rdomain Bool | Read request |
-> Signal wdomain (Maybe a) | Element to insert |
-> (Signal rdomain a, Signal rdomain Bool, Signal wdomain Bool) | (Oldest element in the FIFO, |
Synchroniser implemented as a FIFO around an asynchronous RAM. Based on the design described in Clash.Tutorial, which is itself based on the design described in http://www.sunburst-design.com/papers/CummingsSNUG2002SJ_FIFO1.pdf.
NB: This synchroniser can be used for word-synchronization.
ROMs
Arguments
:: (KnownNat n, Enum addr) | |
=> Vec n a | ROM content NB: must be a constant |
-> addr | Read address |
-> a | The value of the ROM at address |
An asynchronous/combinational ROM with space for n
elements
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
Arguments
:: KnownNat n | |
=> Vec (2 ^ n) a | ROM content NB: must be a constant |
-> Unsigned n | Read address |
-> a | The value of the ROM at address |
An asynchronous/combinational ROM with space for 2^n
elements
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
Arguments
:: (KnownNat n, Enum addr) | |
=> Clock domain gated |
|
-> Vec n a | ROM content NB: must be a constant |
-> Signal domain addr | Read address |
-> Signal domain a | The value of the ROM at address |
A ROM with a synchronous read port, with space for n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Explicit.BlockRam for ideas on how to use ROMs and RAMs
Arguments
:: KnownNat n | |
=> Clock domain gated |
|
-> Vec (2 ^ n) a | ROM content NB: must be a constant |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain a | The value of the ROM at address |
A ROM with a synchronous read port, with space for 2^n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Explicit.BlockRam for ideas on how to use ROMs and RAMs
RAM primitives with a combinational read port
Arguments
:: (Enum addr, HasCallStack) | |
=> Clock wdom wgated |
|
-> Clock rdom rgated |
|
-> SNat n | Size |
-> Signal rdom addr | Read address |
-> Signal wdom (Maybe (addr, a)) | (write address |
-> Signal rdom a | Value of the |
Create a RAM with space for n
elements
- NB: Initial content of the RAM is
undefined
Additional helpful information:
- See Clash.Explicit.BlockRam for more information on how to use a RAM.
Arguments
:: (KnownNat n, HasCallStack) | |
=> Clock wdom wgated |
|
-> Clock rdom rgated |
|
-> Signal rdom (Unsigned n) | Read address |
-> Signal wdom (Maybe (Unsigned n, a)) | (write address |
-> Signal rdom a | Value of the |
Create a RAM with space for 2^n
elements
- NB: Initial content of the RAM is
undefined
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a RAM.
BlockRAM primitives
Arguments
:: HasCallStack | |
=> Enum addr | |
=> Clock dom gated |
|
-> Vec n a | Initial content of the BRAM, also determines the size, NB: MUST be a constant. |
-> Signal dom addr | Read address |
-> Signal dom (Maybe (addr, a)) | (write address |
-> Signal dom a | Value of the |
Create a blockRAM with space for n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
bram40 ::Clock
domain gated ->Signal
domain (Unsigned
6) ->Signal
domain (Maybe (Unsigned
6,Bit
)) ->Signal
domainBit
bram40 clk =blockRam
clk (replicate
d40 1)
Additional helpful information:
- See Clash.Explicit.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew
for obtaining write-before-read semantics like this:
.readNew
clk rst (blockRam
clk inits) rd wrM
Arguments
:: (KnownNat n, HasCallStack) | |
=> Clock dom gated |
|
-> Vec (2 ^ n) a | Initial content of the BRAM, also
determines the size, NB: MUST be a constant. |
-> Signal dom (Unsigned n) | Read address |
-> Signal dom (Maybe (Unsigned n, a)) | (Write address |
-> Signal dom a | Value of the |
Create a blockRAM with space for 2^n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is
undefined
bram32 ::Signal
domain (Unsigned
5) ->Signal
domain (Maybe (Unsigned
5,Bit
)) ->Signal
domainBit
bram32 clk =blockRamPow2
clk (replicate
d32 1)
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew
for obtaining write-before-read semantics like this:
.readNew
clk rst (blockRamPow2
clk inits) rd wrM
BlockRAM read/write conflict resolution
Arguments
:: Eq addr | |
=> Reset domain synchronous | |
-> Clock domain gated | |
-> (Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a) | The |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, a)) | (Write address |
-> Signal domain a | Value of the |
Create read-after-write blockRAM from a read-before-write one
Utility functions
riseEvery :: forall domain gated synchronous n. Clock domain gated -> Reset domain synchronous -> SNat n -> Signal domain Bool Source #
oscillate :: forall domain gated synchronous n. Clock domain gated -> Reset domain synchronous -> Bool -> SNat n -> Signal domain Bool Source #
Oscillate a
for a given number of cycles, given the starting state.Bool
Exported modules
Synchronous signals
module Clash.Explicit.Signal
DataFlow interface
module Clash.Prelude.DataFlow
Datatypes
Bit vectors
module Clash.Sized.BitVector
module Clash.Prelude.BitIndex
module Clash.Prelude.BitReduction
Arbitrary-width numbers
module Clash.Sized.Signed
module Clash.Sized.Unsigned
module Clash.Sized.Index
Fixed point numbers
module Clash.Sized.Fixed
Fixed size vectors
module Clash.Sized.Vector
Perfect depth trees
module Clash.Sized.RTree
Annotations
module Clash.Annotations.TopEntity
Type-level natural numbers
module GHC.TypeLits
module GHC.TypeLits.Extra
module Clash.Promoted.Nat
module Clash.Promoted.Nat.Literals
module Clash.Promoted.Nat.TH
Type-level strings
module Clash.Promoted.Symbol
Type classes
Clash
module Clash.Class.BitPack
module Clash.Class.Num
module Clash.Class.Resize
Other
module Control.Applicative
module Data.Bits
Exceptions
module Clash.XException
undefined :: HasCallStack => a Source #
Named types
module Clash.NamedTypes
Haskell Prelude
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression seq a b
does
not guarantee that a
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
filter :: (a -> Bool) -> [a] -> [a] #
filter
, applied to a predicate and a list, returns the list of
those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
print :: Show a => a -> IO () #
The print
function outputs a value of any printable type to the
standard output device.
Printable types are those that are instances of class Show
; print
converts values to strings for output using the show
operation and
adds a newline.
For example, a program to print the first 20 integers and their powers of 2 could be written as:
main = print ([(n, 2^n) | n <- [0..19]])
($) :: (a -> b) -> a -> b infixr 0 #
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.zipWith
($
) fs xs
fromIntegral :: (Integral a, Num b) => a -> b #
general coercion from integral types
realToFrac :: (Real a, Fractional b) => a -> b #
general coercion to fractional types
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Instances
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
Methods
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
.
enumFromThen :: a -> a -> [a] #
Used in Haskell's translation of [n,n'..]
.
enumFromTo :: a -> a -> [a] #
Used in Haskell's translation of [n..m]
.
enumFromThenTo :: a -> a -> a -> [a] #
Used in Haskell's translation of [n,n'..m]
.
Instances
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
Instances
class Fractional a => Floating a where #
Trigonometric and hyperbolic functions and related functions.
Minimal complete definition
pi, exp, log, sin, cos, asin, acos, atan, sinh, cosh, asinh, acosh, atanh