Skip to content

Commit

Permalink
Trying to use HOAS for the monadic part of the surface language
Browse files Browse the repository at this point in the history
Ignore-this: 4df5c7d57202bcbcb29dfe022ea93115

darcs-hash:20090805112529-6295e-9956a02536a87cb650a901b1a09534c52f09e674.gz
  • Loading branch information
mchakravarty committed Aug 5, 2009
1 parent 74c4593 commit cf2646b
Show file tree
Hide file tree
Showing 2 changed files with 155 additions and 69 deletions.
43 changes: 17 additions & 26 deletions Data/Array/Accelerate/AST.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GADTs, EmptyDataDecls, DeriveDataTypeable #-}

-- |Embedded array processing language: accelerate AST with de Bruijn indices
--
Expand Down Expand Up @@ -67,7 +67,7 @@ module Data.Array.Accelerate.AST (
Arr(..), Sca, Vec,

-- * Monadic array computations
Program, Comp(..), CompResult(..),
Program, Comp(..),

-- * Expressions
Fun(..), Exp(..), PrimConst(..), PrimFun(..)
Expand Down Expand Up @@ -95,8 +95,8 @@ data Idx env t where
SuccIdx :: Idx env t -> Idx (env, s) t


-- Internal arrays
-- ---------------
-- Internal arrays (using representation types)
-- --------------------------------------------

-- |Array representation inside collective computations; this is only to track
-- the array, not to represent it's value.
Expand All @@ -105,10 +105,13 @@ data Idx env t where
-- use type-indexed de Bruijn indices for array variables at the moment and
-- hence need to cast in the interpreter.
--
data Arr dim e where
data Arr dim e {- where
Arr :: (IxRepr dim, ArrayElem e, Typeable dim, Typeable e)
=> TupleType e -> Int -> Arr dim e

=> TupleType e -> Int -> Arr dim e -}
-- FIXME: Do we ever construct values of this type? If not, the problem is
-- that the restrictions imposed by the classes are not effective either.
deriving Typeable

-- |Scalar results (both elementary scalars and tuples of scalars) are being
-- represented as 0-dimensional singleton arrays
--
Expand All @@ -125,22 +128,6 @@ type Vec a = Arr DIM1Repr a
-- Abstract syntax of array computations
--

-- |Possible results of collective array computations are tuples of
-- multi-dimensional arrays
--
class CompResult r where
strings :: r -> [String]

instance CompResult () where
strings _ = []

instance CompResult (Arr dim e) where
strings (Arr _ i) = ['a':show i]

instance (CompResult r1, CompResult r2) => CompResult (r1, r2) where
strings (r1, r2) = strings r1 ++ strings r2


-- |Programs are closed array computations.
--
type Program a = Comp () a
Expand All @@ -153,9 +140,9 @@ type Program a = Comp () a
-- code, when only one of the two values is needed.
--
-- * Scalar functions and expressions embedded in well-formed array
-- computations cannot contain free scalar variable indices. They cannot be
-- bound in array computations, and hence, cannot appear in any well-formed
-- program.
-- computations cannot contain free scalar variable indices. The latter
-- cannot be bound in array computations, and hence, cannot appear in any
-- well-formed program.
--
data Comp env a where

Expand Down Expand Up @@ -258,6 +245,10 @@ data Comp env a where
-> Fun env (dim' -> dim) -- ^permutation function
-> Idx env (Arr dim e) -- ^source array
-> Comp env (Arr dim' e)


-- Embedded expressions
-- --------------------

-- |Function abstraction
--
Expand Down

0 comments on commit cf2646b

Please sign in to comment.