{-# LANGUAGE FlexibleInstances, TypeFamilies #-}
module Futhark.Representation.AST.RetType
(
IsBodyType (..)
, bodyTypeValues
, IsRetType (..)
, retTypeValues
, expectedTypes
)
where
import qualified Data.Map.Strict as M
import Futhark.Representation.AST.Syntax.Core
import Futhark.Representation.AST.Attributes.Types
class (Show rt, Eq rt, Ord rt, ExtTyped rt) => IsBodyType rt where
primBodyType :: PrimType -> rt
bodyTypeValues :: IsBodyType rt => [rt] -> [ExtType]
bodyTypeValues = map extTypeOf
instance IsBodyType ExtType where
primBodyType = Prim
class (Show rt, Eq rt, Ord rt, DeclExtTyped rt) => IsRetType rt where
primRetType :: PrimType -> rt
applyRetType :: Typed attr =>
[rt]
-> [Param attr]
-> [(SubExp, Type)]
-> Maybe [rt]
retTypeValues :: IsRetType rt => [rt] -> [DeclExtType]
retTypeValues = map declExtTypeOf
expectedTypes :: Typed t => [VName] -> [t] -> [SubExp] -> [Type]
expectedTypes shapes value_ts args = map (correctDims . typeOf) value_ts
where parammap :: M.Map VName SubExp
parammap = M.fromList $ zip shapes args
correctDims t =
t `setArrayShape`
Shape (map correctDim $ shapeDims $ arrayShape t)
correctDim (Constant v) = Constant v
correctDim (Var v)
| Just se <- M.lookup v parammap = se
| otherwise = Var v
instance IsRetType DeclExtType where
primRetType = Prim
applyRetType extret params args =
if length args == length params &&
and (zipWith subtypeOf argtypes $
expectedTypes (map paramName params) params $ map fst args)
then Just $ map correctExtDims extret
else Nothing
where argtypes = map snd args
parammap :: M.Map VName SubExp
parammap = M.fromList $ zip (map paramName params) (map fst args)
correctExtDims t =
t `setArrayShape`
Shape (map correctExtDim $ shapeDims $ arrayShape t)
correctExtDim (Ext i) = Ext i
correctExtDim (Free d) = Free $ correctDim d
correctDim (Constant v) = Constant v
correctDim (Var v)
| Just se <- M.lookup v parammap = se
| otherwise = Var v