Derive Show for a bunch of types.
[matthijs/master-project/cλash.git] / FlattenTypes.hs
1 module FlattenTypes where
2
3 import qualified Maybe
4 import Data.Traversable
5 import qualified Data.Foldable as Foldable
6 import qualified Control.Monad.State as State
7
8 import CoreSyn
9 import qualified Type
10
11 import HsValueMap
12 import CoreShow
13
14 -- | A signal identifier
15 type SignalId = Int
16
17 -- | A map of a Haskell value to signal ids
18 type SignalMap = HsValueMap SignalId
19
20 -- | A state identifier
21 type StateId = Int
22
23 -- | How is a given (single) value in a function's type (ie, argument or
24 --   return value) used?
25 data HsValueUse = 
26   Port           -- ^ Use it as a port (input or output)
27   | State StateId -- ^ Use it as state (input or output). The int is used to
28                  --   match input state to output state.
29   | HighOrder {  -- ^ Use it as a high order function input
30     hoName :: String,  -- ^ Which function is passed in?
31     hoArgs :: [HsUseMap]   -- ^ Which arguments are already applied? This
32                          -- ^ map should only contain Port and other
33                          --   HighOrder values. 
34   }
35   deriving (Show, Eq, Ord)
36
37 -- | Is this HsValueUse a state use?
38 isStateUse :: HsValueUse -> Bool
39 isStateUse (State _) = True
40 isStateUse _         = False
41
42 -- | A map from a Haskell value to the use of each single value
43 type HsUseMap = HsValueMap HsValueUse
44
45 -- | Builds a HsUseMap with the same structure has the given HsValueMap in
46 --   which all the Single elements are marked as State, with increasing state
47 --   numbers.
48 useAsState :: HsValueMap a -> HsUseMap
49 useAsState map =
50   map'
51   where
52     -- Traverse the existing map, resulting in a function that maps an initial
53     -- state number to the final state number and the new map
54     PassState f = traverse asState map
55     -- Run this function to get the new map
56     (_, map')   = f 0
57     -- This function maps each element to a State with a unique number, by
58     -- incrementing the state count.
59     asState x   = PassState (\s -> (s+1, State s))
60
61 -- | Builds a HsUseMap with the same structure has the given HsValueMap in
62 --   which all the Single elements are marked as Port.
63 useAsPort :: HsValueMap a -> HsUseMap
64 useAsPort map = fmap (\x -> Port) map
65
66 -- | A Haskell function with a specific signature. The signature defines what
67 --   use the arguments and return value of the function get.
68 data HsFunction = HsFunction {
69   hsFuncName :: String,
70   hsFuncArgs :: [HsUseMap],
71   hsFuncRes  :: HsUseMap
72 } deriving (Show, Eq, Ord)
73
74 hasState :: HsFunction -> Bool
75 hasState hsfunc = 
76   any (Foldable.any isStateUse) (hsFuncArgs hsfunc)
77   || Foldable.any isStateUse (hsFuncRes hsfunc)
78
79 -- | Something that defines a signal
80 data SigDef =
81   -- | A flattened function application
82   FApp {
83     appFunc :: HsFunction,
84     appArgs :: [SignalMap],
85     appRes  :: SignalMap
86   }
87   -- | A conditional signal definition
88   | CondDef {
89     cond    :: SignalId,
90     high    :: SignalId,
91     low     :: SignalId,
92     condRes :: SignalId
93   }
94   -- | Unconditional signal definition
95   | UncondDef {
96     defSrc :: Either SignalId SignalExpr,
97     defDst :: SignalId
98   } deriving (Show, Eq)
99
100 -- | Is the given SigDef a FApp?
101 is_FApp :: SigDef -> Bool
102 is_FApp d = case d of  
103   (FApp _ _ _) -> True
104   _ -> False
105
106 -- | Which signals are used by the given SigDef?
107 sigDefUses :: SigDef -> [SignalId]
108 sigDefUses (UncondDef (Left id) _) = [id]
109 sigDefUses (UncondDef (Right expr) _) = sigExprUses expr
110 sigDefUses (CondDef cond true false _) = [cond, true, false]
111 sigDefUses (FApp _ args _) = concat $ map Foldable.toList args
112
113 -- | An expression on signals
114 data SignalExpr = 
115   EqLit SignalId String -- ^ Is the given signal equal to the given (VHDL) literal
116   | Literal String -- ^ A literal value
117   | Eq SignalId SignalId -- ^ A comparison between to signals
118   deriving (Show, Eq)
119
120 -- | Which signals are used by the given SignalExpr?
121 sigExprUses :: SignalExpr -> [SignalId]
122 sigExprUses (EqLit id _) = [id]
123 sigExprUses (Literal _) = []
124 sigExprUses (Eq a b) = [a, b]
125
126 -- Returns the function used by the given SigDef, if any
127 usedHsFunc :: SigDef -> Maybe HsFunction
128 usedHsFunc (FApp hsfunc _ _) = Just hsfunc
129 usedHsFunc _ = Nothing
130
131 -- | How is a given signal used in the resulting VHDL?
132 data SigUse = 
133   SigPortIn          -- | Use as an input port
134   | SigPortOut       -- | Use as an input port
135   | SigInternal      -- | Use as an internal signal
136   | SigStateOld StateId  -- | Use as the current internal state
137   | SigStateNew StateId  -- | Use as the new internal state
138   | SigSubState      -- | Do not use, state variable is used in a subcircuit
139   deriving (Show)
140
141 -- | Is this a port signal use?
142 isPortSigUse :: SigUse -> Bool
143 isPortSigUse SigPortIn = True
144 isPortSigUse SigPortOut = True
145 isPortSigUse _ = False
146
147 -- | Is this a state signal use? Returns false for substate.
148 isStateSigUse :: SigUse -> Bool
149 isStateSigUse (SigStateOld _) = True
150 isStateSigUse (SigStateNew _) = True
151 isStateSigUse _ = False
152
153 -- | Is this an internal signal use?
154 isInternalSigUse :: SigUse -> Bool
155 isInternalSigUse SigInternal = True
156 isInternalSigUse _ = False
157
158 oldStateId :: SigUse -> Maybe StateId
159 oldStateId (SigStateOld id) = Just id
160 oldStateId _ = Nothing
161
162 newStateId :: SigUse -> Maybe StateId
163 newStateId (SigStateNew id) = Just id
164 newStateId _ = Nothing
165
166 -- | Information on a signal definition
167 data SignalInfo = SignalInfo {
168   sigName :: Maybe String,
169   sigUse  :: SigUse,
170   sigTy   :: Type.Type,
171   nameHints :: [String]
172 } deriving (Show)
173
174 -- | A flattened function
175 data FlatFunction = FlatFunction {
176   flat_args   :: [SignalMap],
177   flat_res    :: SignalMap,
178   flat_defs   :: [SigDef],
179   flat_sigs   :: [(SignalId, SignalInfo)]
180 } deriving (Show)
181
182 -- | Lookup a given signal id in a signal map, and return the associated
183 --   SignalInfo. Errors out if the signal was not found.
184 signalInfo :: [(SignalId, SignalInfo)] -> SignalId -> SignalInfo
185 signalInfo sigs id = Maybe.fromJust $ lookup id sigs
186
187 -- | A list of binds in effect at a particular point of evaluation
188 type BindMap = [(
189   CoreBndr,            -- ^ The bind name
190   BindValue            -- ^ The value bound to it
191   )]
192
193 type BindValue =
194   Either               -- ^ The bind value which is either
195     (SignalMap)
196                        -- ^ a signal
197     (
198       HsValueUse,      -- ^ or a HighOrder function
199       [SignalId]       -- ^ With these signals already applied to it
200     )
201
202 -- | The state during the flattening of a single function
203 type FlattenState = State.State ([SigDef], [(SignalId, SignalInfo)], SignalId)
204
205 -- | Add an application to the current FlattenState
206 addDef :: SigDef -> FlattenState ()
207 addDef d = do
208   (defs, sigs, n) <- State.get
209   State.put (d:defs, sigs, n)
210
211 -- | Generates a new signal id, which is unique within the current flattening.
212 genSignalId :: SigUse -> Type.Type -> FlattenState SignalId 
213 genSignalId use ty = do
214   (defs, sigs, n) <- State.get
215   -- Generate a new numbered but unnamed signal
216   let s = (n, SignalInfo Nothing use ty [])
217   State.put (defs, s:sigs, n+1)
218   return n
219
220 -- | Add a name hint to the given signal
221 addNameHint :: String -> SignalId -> FlattenState ()
222 addNameHint hint id = do
223   info <- getSignalInfo id
224   let hints = nameHints info
225   if hint `elem` hints
226     then do
227       return ()
228     else do
229       let hints' = (hint:hints)
230       setSignalInfo id (info {nameHints = hints'})
231
232 -- | Returns the SignalInfo for the given signal. Errors if the signal is not
233 --   known in the session.
234 getSignalInfo :: SignalId -> FlattenState SignalInfo
235 getSignalInfo id = do
236   (defs, sigs, n) <- State.get
237   return $ signalInfo sigs id
238
239 setSignalInfo :: SignalId -> SignalInfo -> FlattenState ()
240 setSignalInfo id' info' = do
241   (defs, sigs, n) <- State.get
242   let sigs' = map (\(id, info) -> (id, if id == id' then info' else info)) sigs
243   State.put (defs, sigs', n)
244
245 -- vim: set ts=8 sw=2 sts=2 expandtab: