summaryrefslogtreecommitdiff
path: root/SC/Defs.hs
diff options
context:
space:
mode:
authorTom Smeding <tom@tomsmeding.com>2021-09-25 21:45:43 +0200
committerTom Smeding <tom@tomsmeding.com>2021-09-25 21:46:10 +0200
commit57e5bbbbab0d5315c6bba497447ff9bf2487e995 (patch)
treee505ed9ff97f8822824c5b8d1d7615f5c86f1d65 /SC/Defs.hs
parent070772f008bcb5edb63f3f2c2c5f10c4eb9cb008 (diff)
Lots of stuff; can compile simple single-generate program
Diffstat (limited to 'SC/Defs.hs')
-rw-r--r--SC/Defs.hs33
1 files changed, 20 insertions, 13 deletions
diff --git a/SC/Defs.hs b/SC/Defs.hs
index fac4e33..0ecf9cd 100644
--- a/SC/Defs.hs
+++ b/SC/Defs.hs
@@ -1,11 +1,13 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE StandaloneDeriving #-}
module SC.Defs where
import Data.Array.Accelerate.AST.Idx
import Data.Array.Accelerate.Representation.Array
import Data.Array.Accelerate.Representation.Shape
import Data.Array.Accelerate.Type
+import Data.Either (lefts, rights)
import qualified Language.C as C
import Language.C (Name(..))
@@ -68,39 +70,44 @@ data TypedAName = TypedAName C.Type Name
data TupANames t where
ANPair :: TupANames a -> TupANames b -> TupANames (a, b)
- ANArray :: ShNames sh -> ITup TypedAName t -> TupANames (Array sh t)
+ ANArray :: ShNames sh -> ANames t -> TupANames (Array sh t)
ANIgnore :: TupANames a
-- Shape names and data array names
tupanamesList :: TupANames t -> ([TypedName], [TypedAName])
-tupanamesList (ANPair a b) =
- let (shn1, an1) = tupanamesList a
- (shn2, an2) = tupanamesList b
- in (shn1 ++ shn2, an1 ++ an2)
-tupanamesList (ANArray shn ns) = (shnamesList shn, itupList ns)
-tupanamesList ANIgnore = ([], [])
+tupanamesList an = let l = tupanamesList' an in (lefts l, rights l)
+
+tupanamesList' :: TupANames t -> [Either TypedName TypedAName]
+tupanamesList' (ANPair a b) = tupanamesList' a ++ tupanamesList' b
+tupanamesList' (ANArray shn ns) =
+ map Left (shnamesList shn) ++ map Right (itupList ns)
+tupanamesList' ANIgnore = []
data ShNames sh where
ShZ :: ShNames ()
- ShS :: Name -> ShNames sh -> ShNames (sh, Int)
+ ShS :: ShNames sh -> Name -> ShNames (sh, Int)
+deriving instance Show (ShNames sh)
shnamesList :: ShNames sh -> [TypedName]
-shnamesList ShZ = []
-shnamesList (ShS n shns) = TypedName (C.TInt C.B64) n : shnamesList shns
+shnamesList = reverse . go
+ where
+ go :: ShNames sh -> [TypedName]
+ go ShZ = []
+ go (ShS shns n) = TypedName (C.TInt C.B64) n : go shns
makeShNames :: ShapeR sh -> ITup TypedName sh -> ShNames sh
makeShNames ShapeRz ITupIgnore = ShZ
makeShNames (ShapeRsnoc sht) (ITupPair ns (ITupSingle (TypedName _ n))) =
- ShS n (makeShNames sht ns)
+ ShS (makeShNames sht ns) n
makeShNames _ _ = error "wat"
fromShNames :: ShNames sh -> ITup TypedName sh
fromShNames ShZ = ITupIgnore
-fromShNames (ShS n ns) = ITupPair (fromShNames ns) (ITupSingle (TypedName (C.TInt C.B64) n))
+fromShNames (ShS ns n) = ITupPair (fromShNames ns) (ITupSingle (TypedName (C.TInt C.B64) n))
shNamesShape :: ShNames sh -> ShapeR sh
shNamesShape ShZ = ShapeRz
-shNamesShape (ShS _ ns) = ShapeRsnoc (shNamesShape ns)
+shNamesShape (ShS ns _) = ShapeRsnoc (shNamesShape ns)
-- GENERATING VARIABLE NAMES