Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Copilot.Language.Stream
Description
Abstract syntax for streams and operators.
Synopsis
- data Stream :: * -> * where
- Append :: Typed a => [a] -> Maybe (Stream Bool) -> Stream a -> Stream a
- Const :: Typed a => a -> Stream a
- Drop :: Typed a => Int -> Stream a -> Stream a
- Extern :: Typed a => String -> Maybe [a] -> Stream a
- Local :: (Typed a, Typed b) => Stream a -> (Stream a -> Stream b) -> Stream b
- Var :: Typed a => String -> Stream a
- Op1 :: (Typed a, Typed b) => Op1 a b -> Stream a -> Stream b
- Op2 :: (Typed a, Typed b, Typed c) => Op2 a b c -> Stream a -> Stream b -> Stream c
- Op3 :: (Typed a, Typed b, Typed c, Typed d) => Op3 a b c d -> Stream a -> Stream b -> Stream c -> Stream d
- Label :: Typed a => String -> Stream a -> Stream a
- ceiling :: (Typed a, RealFrac a) => Stream a -> Stream a
- floor :: (Typed a, RealFrac a) => Stream a -> Stream a
- atan2 :: (Typed a, RealFloat a) => Stream a -> Stream a -> Stream a
Documentation
data Stream :: * -> * where Source #
A stream in Copilot is an infinite succession of values of the same type.
Streams can be built using simple primities (e.g., Const
), by applying
step-wise (e.g., Op1
) or temporal transformations (e.g., Append
, Drop
)
to streams, or by combining existing streams to form new streams (e.g.,
Op2
, Op3
).
Constructors
Append :: Typed a => [a] -> Maybe (Stream Bool) -> Stream a -> Stream a | |
Const :: Typed a => a -> Stream a | |
Drop :: Typed a => Int -> Stream a -> Stream a | |
Extern :: Typed a => String -> Maybe [a] -> Stream a | |
Local :: (Typed a, Typed b) => Stream a -> (Stream a -> Stream b) -> Stream b | |
Var :: Typed a => String -> Stream a | |
Op1 :: (Typed a, Typed b) => Op1 a b -> Stream a -> Stream b | |
Op2 :: (Typed a, Typed b, Typed c) => Op2 a b c -> Stream a -> Stream b -> Stream c | |
Op3 :: (Typed a, Typed b, Typed c, Typed d) => Op3 a b c d -> Stream a -> Stream b -> Stream c -> Stream d | |
Label :: Typed a => String -> Stream a -> Stream a |
Instances
(Typed a, Bits a) => Bits (Stream a) Source # | Instance of the Only the methods |
Defined in Copilot.Language.Operators.BitWise Methods (.&.) :: Stream a -> Stream a -> Stream a # (.|.) :: Stream a -> Stream a -> Stream a # xor :: Stream a -> Stream a -> Stream a # complement :: Stream a -> Stream a # shift :: Stream a -> Int -> Stream a # rotate :: Stream a -> Int -> Stream a # setBit :: Stream a -> Int -> Stream a # clearBit :: Stream a -> Int -> Stream a # complementBit :: Stream a -> Int -> Stream a # testBit :: Stream a -> Int -> Bool # bitSizeMaybe :: Stream a -> Maybe Int # isSigned :: Stream a -> Bool # shiftL :: Stream a -> Int -> Stream a # unsafeShiftL :: Stream a -> Int -> Stream a # shiftR :: Stream a -> Int -> Stream a # unsafeShiftR :: Stream a -> Int -> Stream a # rotateL :: Stream a -> Int -> Stream a # | |
(Typed a, Eq a, Floating a) => Floating (Stream a) Source # | Streams carrying floating point numbers are instances of |
Defined in Copilot.Language.Stream Methods sqrt :: Stream a -> Stream a # (**) :: Stream a -> Stream a -> Stream a # logBase :: Stream a -> Stream a -> Stream a # asin :: Stream a -> Stream a # acos :: Stream a -> Stream a # atan :: Stream a -> Stream a # sinh :: Stream a -> Stream a # cosh :: Stream a -> Stream a # tanh :: Stream a -> Stream a # asinh :: Stream a -> Stream a # acosh :: Stream a -> Stream a # atanh :: Stream a -> Stream a # log1p :: Stream a -> Stream a # expm1 :: Stream a -> Stream a # | |
(Typed a, Eq a, Num a) => Num (Stream a) Source # | Streams carrying numbers are instances of |
(Typed a, Eq a, Fractional a) => Fractional (Stream a) Source # | Streams carrying fractional numbers are instances of |
Show (Stream a) Source # | |
Eq (Stream a) Source # | |
(KnownNat n, Typed t) => Projectable (Array n t) (Stream Word32) t Source # | Update a stream of arrays. |
Defined in Copilot.Language.Operators.Array | |
data Projection (Array n t) (Stream Word32) t Source # | |
Defined in Copilot.Language.Operators.Array |
ceiling :: (Typed a, RealFrac a) => Stream a -> Stream a Source #
Point-wise application of ceiling
to a stream.
Unlike the Haskell variant of this function, this variant takes and returns two streams of the same type. Use a casting function to convert the result to an intergral type of your choice.
Note that the result can be too big (or, if negative, too small) for that
type (see the man page of ceil
for details), so you must check that the
value fits in the desired integral type before casting it.
This definition clashes with one in RealFrac
in Haskell's Prelude,
re-exported from Language.Copilot
, so you need to import this module
qualified to use this function.
floor :: (Typed a, RealFrac a) => Stream a -> Stream a Source #
Point-wise application of floor
to a stream.
Unlike the Haskell variant of this function, this variant takes and returns two streams of the same type. Use a casting function to convert the result to an intergral type of your choice.
Note that the result can be too big (or, if negative, too small) for that
type (see the man page of floor
for details), so you must check that the
value fits in the desired integral type before casting it.
This definition clashes with one in RealFrac
in Haskell's Prelude,
re-exported from Language.Copilot
, so you need to import this module
qualified to use this function.
atan2 :: (Typed a, RealFloat a) => Stream a -> Stream a -> Stream a Source #
Point-wise application of atan2
to the values of two streams.
For each pair of real floating-point samples x
and y
, one from each
stream, atan2
computes the angle of the vector from (0, 0)
to the point
(x, y)
.
This definition clashes with one in RealFloat
in Haskell's Prelude,
re-exported from Language.Copilot
, so you need to import this module
qualified to use this function.