1 module CLasH.VHDL.Constants where
4 import qualified Language.VHDL.AST as AST
6 -- | A list of all builtin functions. Partly duplicates the name table
7 -- in VHDL.Generate, but we can't use that map everywhere due to
8 -- circular dependencie.
9 builtinIds = [ exId, replaceId, headId, lastId, tailId, initId, takeId, dropId
10 , selId, plusgtId, ltplusId, plusplusId, mapId, zipWithId, foldlId
11 , foldrId, zipId, unzipId, shiftlId, shiftrId, rotlId, rotrId
12 , concatId, reverseId, iteratenId, iterateId, generatenId, generateId
13 , emptyId, singletonId, copynId, copyId, lengthTId, nullId
14 , hwxorId, hwandId, hworId, hwnotId, equalityId, inEqualityId, ltId
15 , lteqId, gtId, gteqId, boolOrId, boolAndId, plusId, timesId
16 , negateId, minusId, fromSizedWordId, fromIntegerId, resizeWordId
17 , resizeIntId, sizedIntId, smallIntegerId, fstId, sndId, blockRAMId
18 , splitId, minimumId, fromRangedWordId
24 -- | reset and clock signal identifiers in String form
25 resetStr, clockStr :: String
29 -- | reset and clock signal identifiers in basic AST.VHDLId form
30 resetId, clockId :: AST.VHDLId
31 resetId = AST.unsafeVHDLBasicId resetStr
32 clockId = AST.unsafeVHDLBasicId clockStr
34 integerId :: AST.VHDLId
35 integerId = AST.unsafeVHDLBasicId "integer"
37 -- | \"types\" identifier
39 typesId = AST.unsafeVHDLBasicId "types"
43 workId = AST.unsafeVHDLBasicId "work"
47 stdId = AST.unsafeVHDLBasicId "std"
50 -- | textio identifier
51 textioId :: AST.VHDLId
52 textioId = AST.unsafeVHDLBasicId "textio"
54 -- | range attribute identifier
56 rangeId = AST.unsafeVHDLBasicId "range"
59 -- | high attribute identifier
61 highId = AST.unsafeVHDLBasicId "high"
63 -- | range attribute identifier
65 imageId = AST.unsafeVHDLBasicId "image"
67 -- | event attribute identifie
69 eventId = AST.unsafeVHDLBasicId "event"
72 -- | default function identifier
73 defaultId :: AST.VHDLId
74 defaultId = AST.unsafeVHDLBasicId "default"
76 -- FSVec function identifiers
78 -- | ex (operator ! in original Haskell source) function identifier
82 -- | sel (function select in original Haskell source) function identifier
87 -- | ltplus (function (<+) in original Haskell source) function identifier
92 -- | plusplus (function (++) in original Haskell source) function identifier
97 -- | empty function identifier
101 -- | plusgt (function (+>) in original Haskell source) function identifier
105 -- | singleton function identifier
106 singletonId :: String
107 singletonId = "singleton"
109 -- | length function identifier
114 -- | isnull (function null in original Haskell source) function identifier
119 -- | replace function identifier
121 replaceId = "replace"
124 -- | head function identifier
129 -- | last function identifier
134 -- | init function identifier
139 -- | tail function identifier
143 -- | minimum ftp function identifier
145 minimumId = "minimum"
147 -- | take function identifier
152 -- | drop function identifier
156 -- | shiftl function identifier
160 -- | shiftr function identifier
164 -- | rotl function identifier
168 -- | reverse function identifier
172 -- | concatenate the vectors in a vector
176 -- | reverse function identifier
178 reverseId = "reverse"
180 -- | iterate function identifier
182 iterateId = "iterate"
184 -- | iteraten function identifier
186 iteratenId = "iteraten"
188 -- | iterate function identifier
190 generateId = "generate"
192 -- | iteraten function identifier
193 generatenId :: String
194 generatenId = "generaten"
196 -- | copy function identifier
200 -- | copyn function identifier
204 -- | map function identifier
208 -- | zipwith function identifier
210 zipWithId = "zipWith"
212 -- | foldl function identifier
216 -- | foldr function identifier
220 -- | zip function identifier
224 -- | unzip function identifier
228 -- | hwxor function identifier
232 -- | hwor function identifier
236 -- | hwnot function identifier
240 -- | hwand function identifier
245 lengthTId = "lengthT"
256 -- Equality Operations
260 inEqualityId :: String
284 -- Numeric Operations
286 -- | plus operation identifier
290 -- | times operation identifier
294 -- | negate operation identifier
298 -- | minus operation identifier
302 -- | convert sizedword to ranged
303 fromSizedWordId :: String
304 fromSizedWordId = "fromSizedWord"
306 fromRangedWordId :: String
307 fromRangedWordId = "fromRangedWord"
309 toIntegerId :: String
310 toIntegerId = "to_integer"
312 fromIntegerId :: String
313 fromIntegerId = "fromInteger"
316 toSignedId = "to_signed"
318 toUnsignedId :: String
319 toUnsignedId = "to_unsigned"
324 resizeWordId :: String
325 resizeWordId = "resizeWord"
327 resizeIntId :: String
328 resizeIntId = "resizeInt"
330 smallIntegerId :: String
331 smallIntegerId = "smallInteger"
334 sizedIntId = "SizedInt"
340 blockRAMId = "blockRAM"
342 -- | output file identifier (from std.textio)
343 showIdString :: String
344 showIdString = "show"
347 showId = AST.unsafeVHDLExtId showIdString
349 -- | write function identifier (from std.textio)
350 writeId :: AST.VHDLId
351 writeId = AST.unsafeVHDLBasicId "write"
353 -- | output file identifier (from std.textio)
354 outputId :: AST.VHDLId
355 outputId = AST.unsafeVHDLBasicId "output"
361 -- | The Bit type mark
362 bitTM :: AST.TypeMark
363 bitTM = AST.unsafeVHDLBasicId "Bit"
365 -- | Stardard logic type mark
366 std_logicTM :: AST.TypeMark
367 std_logicTM = AST.unsafeVHDLBasicId "std_logic"
369 -- | boolean type mark
370 booleanTM :: AST.TypeMark
371 booleanTM = AST.unsafeVHDLBasicId "boolean"
373 -- | fsvec_index AST. TypeMark
374 tfvec_indexTM :: AST.TypeMark
375 tfvec_indexTM = AST.unsafeVHDLBasicId "tfvec_index"
377 -- | natural AST. TypeMark
378 naturalTM :: AST.TypeMark
379 naturalTM = AST.unsafeVHDLBasicId "natural"
381 -- | integer TypeMark
382 integerTM :: AST.TypeMark
383 integerTM = AST.unsafeVHDLBasicId "integer"
386 signedTM :: AST.TypeMark
387 signedTM = AST.unsafeVHDLBasicId "signed"
389 -- | unsigned TypeMark
390 unsignedTM :: AST.TypeMark
391 unsignedTM = AST.unsafeVHDLBasicId "unsigned"
394 stringTM :: AST.TypeMark
395 stringTM = AST.unsafeVHDLBasicId "string"
397 -- | tup VHDLName suffix
398 tupVHDLSuffix :: AST.VHDLId -> AST.Suffix
399 tupVHDLSuffix id = AST.SSimple id