|
1 | | -{-# LANGUAGE Safe #-} |
2 | | - |
3 | | -{-# LANGUAGE TypeFamilies #-} |
| 1 | +{-# LANGUAGE FlexibleInstances #-} |
| 2 | +{-# LANGUAGE MultiParamTypeClasses #-} |
| 3 | +{-# LANGUAGE Safe #-} |
| 4 | +{-# LANGUAGE TypeFamilies #-} |
| 5 | +-- The following warning is disabled due to a necessary instance of Projectable |
| 6 | +-- defined in this module. |
| 7 | +{-# OPTIONS_GHC -fno-warn-orphans #-} |
4 | 8 |
|
5 | 9 | -- | Combinators to deal with streams carrying arrays. |
6 | 10 | module Copilot.Language.Operators.Array |
7 | 11 | ( (.!!) |
| 12 | + , (!) |
| 13 | + , (!!) |
| 14 | + , (=:) |
| 15 | + , (=$) |
8 | 16 | ) where |
9 | 17 |
|
10 | | -import Copilot.Core ( Typed |
11 | | - , Op2 (Index) |
12 | | - , typeOf |
13 | | - , Array |
14 | | - ) |
15 | | -import Copilot.Language.Stream (Stream (..)) |
| 18 | +import Copilot.Core (Array, Op2 (Index), |
| 19 | + Op3 (UpdateArray), Typed, typeOf) |
| 20 | +import Copilot.Language.Operators.Projection (Projectable(..)) |
| 21 | +import Copilot.Language.Stream (Stream (..)) |
| 22 | + |
| 23 | +import Data.Word (Word32) |
| 24 | +import GHC.TypeLits (KnownNat) |
| 25 | +import Prelude hiding ((!!)) |
16 | 26 |
|
17 | | -import Data.Word (Word32) |
18 | | -import GHC.TypeLits (KnownNat) |
| 27 | +-- | Create a stream that carries an element of an array in another stream. |
| 28 | +-- |
| 29 | +-- This function implements a projection of the element of an array at a given |
| 30 | +-- position, over time. For example, if @s@ is a stream of type @Stream (Array |
| 31 | +-- '5 Word8)@, then @s ! 3@ has type @Stream Word8@ and contains the 3rd |
| 32 | +-- element (starting from zero) of the arrays in @s@ at any point in time. |
| 33 | +(!) :: (KnownNat n, Typed t) |
| 34 | + => Stream (Array n t) -> Stream Word32 -> Stream t |
| 35 | +arr ! n = Op2 (Index typeOf) arr n |
19 | 36 |
|
20 | 37 | -- | Create a stream that carries an element of an array in another stream. |
21 | 38 | -- |
22 | 39 | -- This function implements a projection of the element of an array at a given |
23 | 40 | -- position, over time. For example, if @s@ is a stream of type @Stream (Array |
24 | 41 | -- '5 Word8)@, then @s .!! 3@ has type @Stream Word8@ and contains the 3rd |
25 | 42 | -- element (starting from zero) of the arrays in @s@ at any point in time. |
| 43 | +{-# DEPRECATED (.!!) "This function is deprecated in Copilot 4. Use (!)." #-} |
26 | 44 | (.!!) :: ( KnownNat n |
27 | 45 | , Typed t |
28 | 46 | ) => Stream (Array n t) -> Stream Word32 -> Stream t |
29 | | -arr .!! n = Op2 (Index typeOf) arr n |
| 47 | +(.!!) = (!) |
| 48 | + |
| 49 | +-- | Pair a stream with an element accessor, without applying it to obtain the |
| 50 | +-- value of the element. |
| 51 | +-- |
| 52 | +-- This function is needed to refer to an element accessor when the goal is to |
| 53 | +-- update the element value, not just to read it. |
| 54 | +(!!) :: Stream (Array n t) |
| 55 | + -> Stream Word32 |
| 56 | + -> Projection (Array n t) (Stream Word32) t |
| 57 | +(!!) = ProjectionA |
| 58 | + |
| 59 | +-- | Update a stream of arrays. |
| 60 | + |
| 61 | +-- This is an orphan instance; we suppress the warning that GHC would |
| 62 | +-- normally produce with a GHC option at the top. |
| 63 | +instance (KnownNat n, Typed t) => Projectable (Array n t) (Stream Word32) t where |
| 64 | + |
| 65 | + -- | A projection of an element of a stream of arrays. |
| 66 | + data Projection (Array n t) (Stream Word32) t = |
| 67 | + ProjectionA (Stream (Array n t)) (Stream Word32) |
| 68 | + |
| 69 | + -- | Create a stream where an element of an array has been updated with |
| 70 | + -- values from another stream. |
| 71 | + -- |
| 72 | + -- For example, if an array has two elements of type @Int32@, and @s@ is a |
| 73 | + -- stream of such array type (@Stream (Array 2 Int32)@), and $v0$ is a stream |
| 74 | + -- of type @Int32@, then @s !! 0 =: v0@ has type @Stream (Array 2 Int32)@ and |
| 75 | + -- contains arrays where the value of the first element of each array is that |
| 76 | + -- of @v0@ at each point in time, and the value of the second element in the |
| 77 | + -- array is the same it had in @s@. |
| 78 | + (=:) (ProjectionA s ix) v = Op3 (UpdateArray typeOf) s ix v |
| 79 | + |
| 80 | + -- | Create a stream where an element of an array has been updated by |
| 81 | + -- applying a stream function to it. |
| 82 | + -- |
| 83 | + -- For example, if an array has two elements of type @Int32@, and @s@ is a |
| 84 | + -- stream of such array type (@Stream (Array 2 Int32)@), and $f$ is function |
| 85 | + -- of type @Stream Int32 -> Stream Int32@, then @s !! 0 =$ f@ has type |
| 86 | + -- @Stream (Array 2 Int32)@ and contains arrays where the value of the first |
| 87 | + -- element of each array is that of @f (s ! 0)@ at each point in time, and |
| 88 | + -- the value of the second element in the array is the same it had in @s@. |
| 89 | + (=$) (ProjectionA s ix) op = Op3 (UpdateArray typeOf) s ix (op (s ! ix)) |
0 commit comments