module Language.Futhark.Prop
(
Intrinsic (..),
intrinsics,
intrinsicVar,
isBuiltin,
isBuiltinLoc,
maxIntrinsicTag,
namesToPrimTypes,
qualName,
qualify,
primValueType,
leadingOperator,
progImports,
decImports,
progModuleTypes,
identifierReference,
prettyStacktrace,
progHoles,
defaultEntryPoint,
paramName,
anySize,
typeOf,
valBindTypeScheme,
valBindBound,
funType,
stripExp,
similarExps,
patIdents,
patNames,
patternMap,
patternType,
patternStructType,
patternParam,
patternOrderZero,
uniqueness,
unique,
diet,
arrayRank,
arrayShape,
orderZero,
unfoldFunType,
foldFunType,
typeVars,
isAccType,
peelArray,
stripArray,
arrayOf,
arrayOfWithAliases,
toStructural,
toStruct,
toRes,
toParam,
resToParam,
paramToRes,
toResRet,
setUniqueness,
noSizes,
traverseDims,
DimPos (..),
tupleRecord,
isTupleRecord,
areTupleFields,
tupleFields,
tupleFieldNames,
sortFields,
sortConstrs,
isTypeParam,
isSizeParam,
matchDims,
UncheckedType,
UncheckedTypeExp,
UncheckedIdent,
UncheckedDimIndex,
UncheckedSlice,
UncheckedExp,
UncheckedModExp,
UncheckedModTypeExp,
UncheckedTypeParam,
UncheckedPat,
UncheckedValBind,
UncheckedTypeBind,
UncheckedModTypeBind,
UncheckedModBind,
UncheckedDec,
UncheckedSpec,
UncheckedProg,
UncheckedCase,
Ident,
DimIndex,
Slice,
AppExp,
Exp,
Pat,
ModExp,
ModParam,
ModTypeExp,
ModBind,
ModTypeBind,
ValBind,
Dec,
Spec,
Prog,
TypeBind,
StructTypeArg,
ScalarType,
TypeParam,
Case,
)
where
import Control.Monad
import Control.Monad.State
import Data.Bifunctor
import Data.Bitraversable (bitraverse)
import Data.Char
import Data.Foldable
import Data.List (genericLength, isPrefixOf, sortOn)
import Data.List.NonEmpty qualified as NE
import Data.Loc (Loc (..), posFile)
import Data.Map.Strict qualified as M
import Data.Maybe
import Data.Ord
import Data.Set qualified as S
import Futhark.Util (maxinum)
import Futhark.Util.Pretty
import Language.Futhark.Primitive qualified as Primitive
import Language.Futhark.Syntax
import Language.Futhark.Traversals
import Language.Futhark.Tuple
import System.FilePath (takeDirectory)
defaultEntryPoint :: Name
defaultEntryPoint :: Name
defaultEntryPoint = FilePath -> Name
nameFromString FilePath
"main"
arrayRank :: TypeBase dim as -> Int
arrayRank :: forall dim as. TypeBase dim as -> Int
arrayRank = Shape dim -> Int
forall dim. Shape dim -> Int
shapeRank (Shape dim -> Int)
-> (TypeBase dim as -> Shape dim) -> TypeBase dim as -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeBase dim as -> Shape dim
forall dim as. TypeBase dim as -> Shape dim
arrayShape
arrayShape :: TypeBase dim as -> Shape dim
arrayShape :: forall dim as. TypeBase dim as -> Shape dim
arrayShape (Array as
_ Shape dim
ds ScalarTypeBase dim NoUniqueness
_) = Shape dim
ds
arrayShape TypeBase dim as
_ = Shape dim
forall a. Monoid a => a
mempty
noSizes :: TypeBase Size as -> TypeBase () as
noSizes :: forall as. TypeBase (ExpBase Info VName) as -> TypeBase () as
noSizes = (ExpBase Info VName -> ())
-> TypeBase (ExpBase Info VName) as -> TypeBase () as
forall a b c. (a -> b) -> TypeBase a c -> TypeBase b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ((ExpBase Info VName -> ())
-> TypeBase (ExpBase Info VName) as -> TypeBase () as)
-> (ExpBase Info VName -> ())
-> TypeBase (ExpBase Info VName) as
-> TypeBase () as
forall a b. (a -> b) -> a -> b
$ () -> ExpBase Info VName -> ()
forall a b. a -> b -> a
const ()
data DimPos
=
PosImmediate
|
PosParam
|
PosReturn
deriving (DimPos -> DimPos -> Bool
(DimPos -> DimPos -> Bool)
-> (DimPos -> DimPos -> Bool) -> Eq DimPos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DimPos -> DimPos -> Bool
== :: DimPos -> DimPos -> Bool
$c/= :: DimPos -> DimPos -> Bool
/= :: DimPos -> DimPos -> Bool
Eq, Eq DimPos
Eq DimPos =>
(DimPos -> DimPos -> Ordering)
-> (DimPos -> DimPos -> Bool)
-> (DimPos -> DimPos -> Bool)
-> (DimPos -> DimPos -> Bool)
-> (DimPos -> DimPos -> Bool)
-> (DimPos -> DimPos -> DimPos)
-> (DimPos -> DimPos -> DimPos)
-> Ord DimPos
DimPos -> DimPos -> Bool
DimPos -> DimPos -> Ordering
DimPos -> DimPos -> DimPos
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DimPos -> DimPos -> Ordering
compare :: DimPos -> DimPos -> Ordering
$c< :: DimPos -> DimPos -> Bool
< :: DimPos -> DimPos -> Bool
$c<= :: DimPos -> DimPos -> Bool
<= :: DimPos -> DimPos -> Bool
$c> :: DimPos -> DimPos -> Bool
> :: DimPos -> DimPos -> Bool
$c>= :: DimPos -> DimPos -> Bool
>= :: DimPos -> DimPos -> Bool
$cmax :: DimPos -> DimPos -> DimPos
max :: DimPos -> DimPos -> DimPos
$cmin :: DimPos -> DimPos -> DimPos
min :: DimPos -> DimPos -> DimPos
Ord, Int -> DimPos -> ShowS
[DimPos] -> ShowS
DimPos -> FilePath
(Int -> DimPos -> ShowS)
-> (DimPos -> FilePath) -> ([DimPos] -> ShowS) -> Show DimPos
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DimPos -> ShowS
showsPrec :: Int -> DimPos -> ShowS
$cshow :: DimPos -> FilePath
show :: DimPos -> FilePath
$cshowList :: [DimPos] -> ShowS
showList :: [DimPos] -> ShowS
Show)
traverseDims ::
forall f fdim tdim als.
(Applicative f) =>
(S.Set VName -> DimPos -> fdim -> f tdim) ->
TypeBase fdim als ->
f (TypeBase tdim als)
traverseDims :: forall (f :: * -> *) fdim tdim als.
Applicative f =>
(Set VName -> DimPos -> fdim -> f tdim)
-> TypeBase fdim als -> f (TypeBase tdim als)
traverseDims Set VName -> DimPos -> fdim -> f tdim
f = Set VName -> DimPos -> TypeBase fdim als -> f (TypeBase tdim als)
forall als'.
Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
go Set VName
forall a. Monoid a => a
mempty DimPos
PosImmediate
where
go ::
forall als'.
S.Set VName ->
DimPos ->
TypeBase fdim als' ->
f (TypeBase tdim als')
go :: forall als'.
Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
go Set VName
bound DimPos
b t :: TypeBase fdim als'
t@Array {} =
(fdim -> f tdim)
-> (als' -> f als') -> TypeBase fdim als' -> f (TypeBase tdim als')
forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> TypeBase a b -> f (TypeBase c d)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse (Set VName -> DimPos -> fdim -> f tdim
f Set VName
bound DimPos
b) als' -> f als'
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TypeBase fdim als'
t
go Set VName
bound DimPos
b (Scalar (Record Map Name (TypeBase fdim als')
fields)) =
ScalarTypeBase tdim als' -> TypeBase tdim als'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase tdim als' -> TypeBase tdim als')
-> (Map Name (TypeBase tdim als') -> ScalarTypeBase tdim als')
-> Map Name (TypeBase tdim als')
-> TypeBase tdim als'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Name (TypeBase tdim als') -> ScalarTypeBase tdim als'
forall dim u. Map Name (TypeBase dim u) -> ScalarTypeBase dim u
Record (Map Name (TypeBase tdim als') -> TypeBase tdim als')
-> f (Map Name (TypeBase tdim als')) -> f (TypeBase tdim als')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TypeBase fdim als' -> f (TypeBase tdim als'))
-> Map Name (TypeBase fdim als')
-> f (Map Name (TypeBase tdim als'))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map Name a -> f (Map Name b)
traverse (Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
forall als'.
Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
go Set VName
bound DimPos
b) Map Name (TypeBase fdim als')
fields
go Set VName
bound DimPos
b (Scalar (TypeVar als'
as QualName VName
tn [TypeArg fdim]
targs)) =
ScalarTypeBase tdim als' -> TypeBase tdim als'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase tdim als' -> TypeBase tdim als')
-> f (ScalarTypeBase tdim als') -> f (TypeBase tdim als')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (als'
-> QualName VName -> [TypeArg tdim] -> ScalarTypeBase tdim als'
forall dim u.
u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
TypeVar als'
as QualName VName
tn ([TypeArg tdim] -> ScalarTypeBase tdim als')
-> f [TypeArg tdim] -> f (ScalarTypeBase tdim als')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TypeArg fdim -> f (TypeArg tdim))
-> [TypeArg fdim] -> f [TypeArg tdim]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (QualName VName
-> Set VName -> DimPos -> TypeArg fdim -> f (TypeArg tdim)
onTypeArg QualName VName
tn Set VName
bound DimPos
b) [TypeArg fdim]
targs)
go Set VName
bound DimPos
b (Scalar (Sum Map Name [TypeBase fdim als']
cs)) =
ScalarTypeBase tdim als' -> TypeBase tdim als'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase tdim als' -> TypeBase tdim als')
-> (Map Name [TypeBase tdim als'] -> ScalarTypeBase tdim als')
-> Map Name [TypeBase tdim als']
-> TypeBase tdim als'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Name [TypeBase tdim als'] -> ScalarTypeBase tdim als'
forall dim u. Map Name [TypeBase dim u] -> ScalarTypeBase dim u
Sum (Map Name [TypeBase tdim als'] -> TypeBase tdim als')
-> f (Map Name [TypeBase tdim als']) -> f (TypeBase tdim als')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([TypeBase fdim als'] -> f [TypeBase tdim als'])
-> Map Name [TypeBase fdim als']
-> f (Map Name [TypeBase tdim als'])
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map Name a -> f (Map Name b)
traverse ((TypeBase fdim als' -> f (TypeBase tdim als'))
-> [TypeBase fdim als'] -> f [TypeBase tdim als']
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
forall als'.
Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
go Set VName
bound DimPos
b)) Map Name [TypeBase fdim als']
cs
go Set VName
_ DimPos
_ (Scalar (Prim PrimType
t)) =
TypeBase tdim als' -> f (TypeBase tdim als')
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TypeBase tdim als' -> f (TypeBase tdim als'))
-> TypeBase tdim als' -> f (TypeBase tdim als')
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase tdim als' -> TypeBase tdim als'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase tdim als' -> TypeBase tdim als')
-> ScalarTypeBase tdim als' -> TypeBase tdim als'
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase tdim als'
forall dim u. PrimType -> ScalarTypeBase dim u
Prim PrimType
t
go Set VName
bound DimPos
_ (Scalar (Arrow als'
als PName
p Diet
u TypeBase fdim NoUniqueness
t1 (RetType [VName]
dims TypeBase fdim Uniqueness
t2))) =
ScalarTypeBase tdim als' -> TypeBase tdim als'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase tdim als' -> TypeBase tdim als')
-> f (ScalarTypeBase tdim als') -> f (TypeBase tdim als')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (als'
-> PName
-> Diet
-> TypeBase tdim NoUniqueness
-> RetTypeBase tdim Uniqueness
-> ScalarTypeBase tdim als'
forall dim u.
u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
Arrow als'
als PName
p Diet
u (TypeBase tdim NoUniqueness
-> RetTypeBase tdim Uniqueness -> ScalarTypeBase tdim als')
-> f (TypeBase tdim NoUniqueness)
-> f (RetTypeBase tdim Uniqueness -> ScalarTypeBase tdim als')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set VName
-> DimPos
-> TypeBase fdim NoUniqueness
-> f (TypeBase tdim NoUniqueness)
forall als'.
Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
go Set VName
bound' DimPos
PosParam TypeBase fdim NoUniqueness
t1 f (RetTypeBase tdim Uniqueness -> ScalarTypeBase tdim als')
-> f (RetTypeBase tdim Uniqueness) -> f (ScalarTypeBase tdim als')
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([VName] -> TypeBase tdim Uniqueness -> RetTypeBase tdim Uniqueness
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [VName]
dims (TypeBase tdim Uniqueness -> RetTypeBase tdim Uniqueness)
-> f (TypeBase tdim Uniqueness) -> f (RetTypeBase tdim Uniqueness)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set VName
-> DimPos
-> TypeBase fdim Uniqueness
-> f (TypeBase tdim Uniqueness)
forall als'.
Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
go Set VName
bound' DimPos
PosReturn TypeBase fdim Uniqueness
t2))
where
bound' :: Set VName
bound' =
[VName] -> Set VName
forall a. Ord a => [a] -> Set a
S.fromList [VName]
dims
Set VName -> Set VName -> Set VName
forall a. Semigroup a => a -> a -> a
<> case PName
p of
Named VName
p' -> VName -> Set VName -> Set VName
forall a. Ord a => a -> Set a -> Set a
S.insert VName
p' Set VName
bound
PName
Unnamed -> Set VName
bound
onTypeArg :: QualName VName
-> Set VName -> DimPos -> TypeArg fdim -> f (TypeArg tdim)
onTypeArg QualName VName
_ Set VName
bound DimPos
b (TypeArgDim fdim
d) =
tdim -> TypeArg tdim
forall dim. dim -> TypeArg dim
TypeArgDim (tdim -> TypeArg tdim) -> f tdim -> f (TypeArg tdim)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set VName -> DimPos -> fdim -> f tdim
f Set VName
bound DimPos
b fdim
d
onTypeArg QualName VName
tn Set VName
bound DimPos
b (TypeArgType TypeBase fdim NoUniqueness
t) =
TypeBase tdim NoUniqueness -> TypeArg tdim
forall dim. TypeBase dim NoUniqueness -> TypeArg dim
TypeArgType (TypeBase tdim NoUniqueness -> TypeArg tdim)
-> f (TypeBase tdim NoUniqueness) -> f (TypeArg tdim)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set VName
-> DimPos
-> TypeBase fdim NoUniqueness
-> f (TypeBase tdim NoUniqueness)
forall als'.
Set VName -> DimPos -> TypeBase fdim als' -> f (TypeBase tdim als')
go Set VName
bound DimPos
b' TypeBase fdim NoUniqueness
t
where
b' :: DimPos
b' =
if QualName VName -> VName
forall vn. QualName vn -> vn
qualLeaf QualName VName
tn VName -> VName -> Bool
forall a. Eq a => a -> a -> Bool
== (VName, Intrinsic) -> VName
forall a b. (a, b) -> a
fst (VName, Intrinsic)
intrinsicAcc
then DimPos
b
else DimPos
PosParam
uniqueness :: TypeBase shape Uniqueness -> Uniqueness
uniqueness :: forall shape. TypeBase shape Uniqueness -> Uniqueness
uniqueness (Array Uniqueness
u Shape shape
_ ScalarTypeBase shape NoUniqueness
_) = Uniqueness
u
uniqueness (Scalar (TypeVar Uniqueness
u QualName VName
_ [TypeArg shape]
_)) = Uniqueness
u
uniqueness (Scalar (Sum Map Name [TypeBase shape Uniqueness]
ts))
| ([TypeBase shape Uniqueness] -> Bool)
-> Map Name [TypeBase shape Uniqueness] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((TypeBase shape Uniqueness -> Bool)
-> [TypeBase shape Uniqueness] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any TypeBase shape Uniqueness -> Bool
forall shape. TypeBase shape Uniqueness -> Bool
unique) Map Name [TypeBase shape Uniqueness]
ts = Uniqueness
Unique
uniqueness (Scalar (Record Map Name (TypeBase shape Uniqueness)
fs))
| (TypeBase shape Uniqueness -> Bool)
-> Map Name (TypeBase shape Uniqueness) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any TypeBase shape Uniqueness -> Bool
forall shape. TypeBase shape Uniqueness -> Bool
unique Map Name (TypeBase shape Uniqueness)
fs = Uniqueness
Unique
uniqueness TypeBase shape Uniqueness
_ = Uniqueness
Nonunique
unique :: TypeBase shape Uniqueness -> Bool
unique :: forall shape. TypeBase shape Uniqueness -> Bool
unique = (Uniqueness -> Uniqueness -> Bool
forall a. Eq a => a -> a -> Bool
== Uniqueness
Unique) (Uniqueness -> Bool)
-> (TypeBase shape Uniqueness -> Uniqueness)
-> TypeBase shape Uniqueness
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeBase shape Uniqueness -> Uniqueness
forall shape. TypeBase shape Uniqueness -> Uniqueness
uniqueness
diet :: TypeBase shape Diet -> Diet
diet :: forall shape. TypeBase shape Diet -> Diet
diet (Scalar (Record Map Name (TypeBase shape Diet)
ets)) = (Diet -> Diet -> Diet) -> Diet -> Map Name Diet -> Diet
forall b a. (b -> a -> b) -> b -> Map Name a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Diet -> Diet -> Diet
forall a. Ord a => a -> a -> a
max Diet
Observe (Map Name Diet -> Diet) -> Map Name Diet -> Diet
forall a b. (a -> b) -> a -> b
$ (TypeBase shape Diet -> Diet)
-> Map Name (TypeBase shape Diet) -> Map Name Diet
forall a b. (a -> b) -> Map Name a -> Map Name b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TypeBase shape Diet -> Diet
forall shape. TypeBase shape Diet -> Diet
diet Map Name (TypeBase shape Diet)
ets
diet (Scalar (Prim PrimType
_)) = Diet
Observe
diet (Scalar (Arrow {})) = Diet
Observe
diet (Array Diet
d Shape shape
_ ScalarTypeBase shape NoUniqueness
_) = Diet
d
diet (Scalar (TypeVar Diet
d QualName VName
_ [TypeArg shape]
_)) = Diet
d
diet (Scalar (Sum Map Name [TypeBase shape Diet]
cs)) = (Diet -> Diet -> Diet) -> Diet -> [Diet] -> Diet
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Diet -> Diet -> Diet
forall a. Ord a => a -> a -> a
max Diet
Observe ([Diet] -> Diet) -> [Diet] -> Diet
forall a b. (a -> b) -> a -> b
$ ([TypeBase shape Diet] -> [Diet])
-> Map Name [TypeBase shape Diet] -> [Diet]
forall m a. Monoid m => (a -> m) -> Map Name a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((TypeBase shape Diet -> Diet) -> [TypeBase shape Diet] -> [Diet]
forall a b. (a -> b) -> [a] -> [b]
map TypeBase shape Diet -> Diet
forall shape. TypeBase shape Diet -> Diet
diet) Map Name [TypeBase shape Diet]
cs
toStructural ::
TypeBase dim as ->
TypeBase () ()
toStructural :: forall dim as. TypeBase dim as -> TypeBase () ()
toStructural = (dim -> ()) -> (as -> ()) -> TypeBase dim as -> TypeBase () ()
forall a b c d.
(a -> b) -> (c -> d) -> TypeBase a c -> TypeBase b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (() -> dim -> ()
forall a b. a -> b -> a
const ()) (() -> as -> ()
forall a b. a -> b -> a
const ())
toStruct :: TypeBase dim u -> TypeBase dim NoUniqueness
toStruct :: forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct = (u -> NoUniqueness) -> TypeBase dim u -> TypeBase dim NoUniqueness
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (NoUniqueness -> u -> NoUniqueness
forall a b. a -> b -> a
const NoUniqueness
NoUniqueness)
toParam :: Diet -> TypeBase Size u -> ParamType
toParam :: forall u. Diet -> TypeBase (ExpBase Info VName) u -> ParamType
toParam Diet
d = (u -> Diet) -> TypeBase (ExpBase Info VName) u -> ParamType
forall a b.
(a -> b)
-> TypeBase (ExpBase Info VName) a
-> TypeBase (ExpBase Info VName) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Diet -> u -> Diet
forall a b. a -> b -> a
const Diet
d)
toRes :: Uniqueness -> TypeBase Size u -> ResType
toRes :: forall u. Uniqueness -> TypeBase (ExpBase Info VName) u -> ResType
toRes Uniqueness
u = (u -> Uniqueness) -> TypeBase (ExpBase Info VName) u -> ResType
forall a b.
(a -> b)
-> TypeBase (ExpBase Info VName) a
-> TypeBase (ExpBase Info VName) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Uniqueness -> u -> Uniqueness
forall a b. a -> b -> a
const Uniqueness
u)
toResRet :: Uniqueness -> RetTypeBase Size u -> ResRetType
toResRet :: forall u.
Uniqueness -> RetTypeBase (ExpBase Info VName) u -> ResRetType
toResRet Uniqueness
u = (u -> Uniqueness)
-> RetTypeBase (ExpBase Info VName) u -> ResRetType
forall b c a. (b -> c) -> RetTypeBase a b -> RetTypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Uniqueness -> u -> Uniqueness
forall a b. a -> b -> a
const Uniqueness
u)
resToParam :: ResType -> ParamType
resToParam :: ResType -> ParamType
resToParam = (Uniqueness -> Diet) -> ResType -> ParamType
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second Uniqueness -> Diet
f
where
f :: Uniqueness -> Diet
f Uniqueness
Unique = Diet
Consume
f Uniqueness
Nonunique = Diet
Observe
paramToRes :: ParamType -> ResType
paramToRes :: ParamType -> ResType
paramToRes = (Diet -> Uniqueness) -> ParamType -> ResType
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second Diet -> Uniqueness
f
where
f :: Diet -> Uniqueness
f Diet
Consume = Uniqueness
Unique
f Diet
Observe = Uniqueness
Nonunique
peelArray :: Int -> TypeBase dim u -> Maybe (TypeBase dim u)
peelArray :: forall dim u. Int -> TypeBase dim u -> Maybe (TypeBase dim u)
peelArray Int
n (Array u
u Shape dim
shape ScalarTypeBase dim NoUniqueness
t)
| Shape dim -> Int
forall dim. Shape dim -> Int
shapeRank Shape dim
shape Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
n =
TypeBase dim u -> Maybe (TypeBase dim u)
forall a. a -> Maybe a
Just (TypeBase dim u -> Maybe (TypeBase dim u))
-> TypeBase dim u -> Maybe (TypeBase dim u)
forall a b. (a -> b) -> a -> b
$ (NoUniqueness -> u) -> TypeBase dim NoUniqueness -> TypeBase dim u
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (u -> NoUniqueness -> u
forall a b. a -> b -> a
const u
u) (ScalarTypeBase dim NoUniqueness -> TypeBase dim NoUniqueness
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar ScalarTypeBase dim NoUniqueness
t)
| Bool
otherwise =
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array u
u (Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u)
-> Maybe (Shape dim)
-> Maybe (ScalarTypeBase dim NoUniqueness -> TypeBase dim u)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Shape dim -> Maybe (Shape dim)
forall dim. Int -> Shape dim -> Maybe (Shape dim)
stripDims Int
n Shape dim
shape Maybe (ScalarTypeBase dim NoUniqueness -> TypeBase dim u)
-> Maybe (ScalarTypeBase dim NoUniqueness)
-> Maybe (TypeBase dim u)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ScalarTypeBase dim NoUniqueness
-> Maybe (ScalarTypeBase dim NoUniqueness)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ScalarTypeBase dim NoUniqueness
t
peelArray Int
_ TypeBase dim u
_ = Maybe (TypeBase dim u)
forall a. Maybe a
Nothing
arrayOf ::
Shape dim ->
TypeBase dim NoUniqueness ->
TypeBase dim NoUniqueness
arrayOf :: forall dim.
Shape dim -> TypeBase dim NoUniqueness -> TypeBase dim NoUniqueness
arrayOf = NoUniqueness
-> Shape dim
-> TypeBase dim NoUniqueness
-> TypeBase dim NoUniqueness
forall u dim. u -> Shape dim -> TypeBase dim u -> TypeBase dim u
arrayOfWithAliases NoUniqueness
forall a. Monoid a => a
mempty
arrayOfWithAliases ::
u ->
Shape dim ->
TypeBase dim u ->
TypeBase dim u
arrayOfWithAliases :: forall u dim. u -> Shape dim -> TypeBase dim u -> TypeBase dim u
arrayOfWithAliases u
u Shape dim
shape2 (Array u
_ Shape dim
shape1 ScalarTypeBase dim NoUniqueness
et) =
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array u
u (Shape dim
shape2 Shape dim -> Shape dim -> Shape dim
forall a. Semigroup a => a -> a -> a
<> Shape dim
shape1) ScalarTypeBase dim NoUniqueness
et
arrayOfWithAliases u
u Shape dim
shape (Scalar ScalarTypeBase dim u
t) =
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array u
u Shape dim
shape ((u -> NoUniqueness)
-> ScalarTypeBase dim u -> ScalarTypeBase dim NoUniqueness
forall b c a. (b -> c) -> ScalarTypeBase a b -> ScalarTypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (NoUniqueness -> u -> NoUniqueness
forall a b. a -> b -> a
const NoUniqueness
forall a. Monoid a => a
mempty) ScalarTypeBase dim u
t)
stripArray :: Int -> TypeBase dim as -> TypeBase dim as
stripArray :: forall dim as. Int -> TypeBase dim as -> TypeBase dim as
stripArray Int
n (Array as
u Shape dim
shape ScalarTypeBase dim NoUniqueness
et)
| Just Shape dim
shape' <- Int -> Shape dim -> Maybe (Shape dim)
forall dim. Int -> Shape dim -> Maybe (Shape dim)
stripDims Int
n Shape dim
shape =
as
-> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim as
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array as
u Shape dim
shape' ScalarTypeBase dim NoUniqueness
et
| Bool
otherwise =
(NoUniqueness -> as)
-> TypeBase dim NoUniqueness -> TypeBase dim as
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (as -> NoUniqueness -> as
forall a b. a -> b -> a
const as
u) (ScalarTypeBase dim NoUniqueness -> TypeBase dim NoUniqueness
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar ScalarTypeBase dim NoUniqueness
et)
stripArray Int
_ TypeBase dim as
t = TypeBase dim as
t
tupleRecord :: [TypeBase dim as] -> ScalarTypeBase dim as
tupleRecord :: forall dim as. [TypeBase dim as] -> ScalarTypeBase dim as
tupleRecord = Map Name (TypeBase dim as) -> ScalarTypeBase dim as
forall dim u. Map Name (TypeBase dim u) -> ScalarTypeBase dim u
Record (Map Name (TypeBase dim as) -> ScalarTypeBase dim as)
-> ([TypeBase dim as] -> Map Name (TypeBase dim as))
-> [TypeBase dim as]
-> ScalarTypeBase dim as
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Name, TypeBase dim as)] -> Map Name (TypeBase dim as)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, TypeBase dim as)] -> Map Name (TypeBase dim as))
-> ([TypeBase dim as] -> [(Name, TypeBase dim as)])
-> [TypeBase dim as]
-> Map Name (TypeBase dim as)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Name] -> [TypeBase dim as] -> [(Name, TypeBase dim as)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
tupleFieldNames
isTupleRecord :: TypeBase dim as -> Maybe [TypeBase dim as]
isTupleRecord :: forall dim as. TypeBase dim as -> Maybe [TypeBase dim as]
isTupleRecord (Scalar (Record Map Name (TypeBase dim as)
fs)) = Map Name (TypeBase dim as) -> Maybe [TypeBase dim as]
forall a. Map Name a -> Maybe [a]
areTupleFields Map Name (TypeBase dim as)
fs
isTupleRecord TypeBase dim as
_ = Maybe [TypeBase dim as]
forall a. Maybe a
Nothing
sortConstrs :: M.Map Name a -> [(Name, a)]
sortConstrs :: forall a. Map Name a -> [(Name, a)]
sortConstrs Map Name a
cs = ((Name, a) -> Name) -> [(Name, a)] -> [(Name, a)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (Name, a) -> Name
forall a b. (a, b) -> a
fst ([(Name, a)] -> [(Name, a)]) -> [(Name, a)] -> [(Name, a)]
forall a b. (a -> b) -> a -> b
$ Map Name a -> [(Name, a)]
forall k a. Map k a -> [(k, a)]
M.toList Map Name a
cs
isTypeParam :: TypeParamBase vn -> Bool
isTypeParam :: forall vn. TypeParamBase vn -> Bool
isTypeParam TypeParamType {} = Bool
True
isTypeParam TypeParamDim {} = Bool
False
isSizeParam :: TypeParamBase vn -> Bool
isSizeParam :: forall vn. TypeParamBase vn -> Bool
isSizeParam = Bool -> Bool
not (Bool -> Bool)
-> (TypeParamBase vn -> Bool) -> TypeParamBase vn -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeParamBase vn -> Bool
forall vn. TypeParamBase vn -> Bool
isTypeParam
paramName :: PName -> Maybe VName
paramName :: PName -> Maybe VName
paramName (Named VName
v) = VName -> Maybe VName
forall a. a -> Maybe a
Just VName
v
paramName PName
Unnamed = Maybe VName
forall a. Maybe a
Nothing
anySize :: Size
anySize :: ExpBase Info VName
anySize =
[Word8] -> SrcLoc -> ExpBase Info VName
forall (f :: * -> *) vn. [Word8] -> SrcLoc -> ExpBase f vn
StringLit [Word8
65, Word8
78, Word8
89] SrcLoc
forall a. Monoid a => a
mempty
matchDims ::
forall as m d1 d2.
(Monoid as, Monad m) =>
([VName] -> d1 -> d2 -> m d1) ->
TypeBase d1 as ->
TypeBase d2 as ->
m (TypeBase d1 as)
matchDims :: forall as (m :: * -> *) d1 d2.
(Monoid as, Monad m) =>
([VName] -> d1 -> d2 -> m d1)
-> TypeBase d1 as -> TypeBase d2 as -> m (TypeBase d1 as)
matchDims [VName] -> d1 -> d2 -> m d1
onDims = [VName] -> TypeBase d1 as -> TypeBase d2 as -> m (TypeBase d1 as)
forall u'.
Monoid u' =>
[VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' [VName]
forall a. Monoid a => a
mempty
where
matchDims' ::
forall u'. (Monoid u') => [VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' :: forall u'.
Monoid u' =>
[VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' [VName]
bound TypeBase d1 u'
t1 TypeBase d2 u'
t2 =
case (TypeBase d1 u'
t1, TypeBase d2 u'
t2) of
(Array u'
u1 Shape d1
shape1 ScalarTypeBase d1 NoUniqueness
et1, Array u'
u2 Shape d2
shape2 ScalarTypeBase d2 NoUniqueness
et2) ->
u' -> Shape d1 -> TypeBase d1 u' -> TypeBase d1 u'
forall u dim. u -> Shape dim -> TypeBase dim u -> TypeBase dim u
arrayOfWithAliases u'
u1
(Shape d1 -> TypeBase d1 u' -> TypeBase d1 u')
-> m (Shape d1) -> m (TypeBase d1 u' -> TypeBase d1 u')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [VName] -> Shape d1 -> Shape d2 -> m (Shape d1)
onShapes [VName]
bound Shape d1
shape1 Shape d2
shape2
m (TypeBase d1 u' -> TypeBase d1 u')
-> m (TypeBase d1 u') -> m (TypeBase d1 u')
forall a b. m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
forall u'.
Monoid u' =>
[VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' [VName]
bound ((NoUniqueness -> u') -> TypeBase d1 NoUniqueness -> TypeBase d1 u'
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (u' -> NoUniqueness -> u'
forall a b. a -> b -> a
const u'
u2) (ScalarTypeBase d1 NoUniqueness -> TypeBase d1 NoUniqueness
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar ScalarTypeBase d1 NoUniqueness
et1)) ((NoUniqueness -> u') -> TypeBase d2 NoUniqueness -> TypeBase d2 u'
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (u' -> NoUniqueness -> u'
forall a b. a -> b -> a
const u'
u2) (ScalarTypeBase d2 NoUniqueness -> TypeBase d2 NoUniqueness
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar ScalarTypeBase d2 NoUniqueness
et2))
(Scalar (Record Map Name (TypeBase d1 u')
f1), Scalar (Record Map Name (TypeBase d2 u')
f2)) ->
ScalarTypeBase d1 u' -> TypeBase d1 u'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase d1 u' -> TypeBase d1 u')
-> (Map Name (TypeBase d1 u') -> ScalarTypeBase d1 u')
-> Map Name (TypeBase d1 u')
-> TypeBase d1 u'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Name (TypeBase d1 u') -> ScalarTypeBase d1 u'
forall dim u. Map Name (TypeBase dim u) -> ScalarTypeBase dim u
Record
(Map Name (TypeBase d1 u') -> TypeBase d1 u')
-> m (Map Name (TypeBase d1 u')) -> m (TypeBase d1 u')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((TypeBase d1 u', TypeBase d2 u') -> m (TypeBase d1 u'))
-> Map Name (TypeBase d1 u', TypeBase d2 u')
-> m (Map Name (TypeBase d1 u'))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map Name a -> f (Map Name b)
traverse ((TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u'))
-> (TypeBase d1 u', TypeBase d2 u') -> m (TypeBase d1 u')
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ([VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
forall u'.
Monoid u' =>
[VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' [VName]
bound)) ((TypeBase d1 u'
-> TypeBase d2 u' -> (TypeBase d1 u', TypeBase d2 u'))
-> Map Name (TypeBase d1 u')
-> Map Name (TypeBase d2 u')
-> Map Name (TypeBase d1 u', TypeBase d2 u')
forall k a b c.
Ord k =>
(a -> b -> c) -> Map k a -> Map k b -> Map k c
M.intersectionWith (,) Map Name (TypeBase d1 u')
f1 Map Name (TypeBase d2 u')
f2)
(Scalar (Sum Map Name [TypeBase d1 u']
cs1), Scalar (Sum Map Name [TypeBase d2 u']
cs2)) ->
ScalarTypeBase d1 u' -> TypeBase d1 u'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase d1 u' -> TypeBase d1 u')
-> (Map Name [TypeBase d1 u'] -> ScalarTypeBase d1 u')
-> Map Name [TypeBase d1 u']
-> TypeBase d1 u'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Name [TypeBase d1 u'] -> ScalarTypeBase d1 u'
forall dim u. Map Name [TypeBase dim u] -> ScalarTypeBase dim u
Sum
(Map Name [TypeBase d1 u'] -> TypeBase d1 u')
-> m (Map Name [TypeBase d1 u']) -> m (TypeBase d1 u')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([(TypeBase d1 u', TypeBase d2 u')] -> m [TypeBase d1 u'])
-> Map Name [(TypeBase d1 u', TypeBase d2 u')]
-> m (Map Name [TypeBase d1 u'])
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map Name a -> f (Map Name b)
traverse
(((TypeBase d1 u', TypeBase d2 u') -> m (TypeBase d1 u'))
-> [(TypeBase d1 u', TypeBase d2 u')] -> m [TypeBase d1 u']
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u'))
-> (TypeBase d1 u', TypeBase d2 u') -> m (TypeBase d1 u')
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ([VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
forall u'.
Monoid u' =>
[VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' [VName]
bound)))
(([TypeBase d1 u']
-> [TypeBase d2 u'] -> [(TypeBase d1 u', TypeBase d2 u')])
-> Map Name [TypeBase d1 u']
-> Map Name [TypeBase d2 u']
-> Map Name [(TypeBase d1 u', TypeBase d2 u')]
forall k a b c.
Ord k =>
(a -> b -> c) -> Map k a -> Map k b -> Map k c
M.intersectionWith [TypeBase d1 u']
-> [TypeBase d2 u'] -> [(TypeBase d1 u', TypeBase d2 u')]
forall a b. [a] -> [b] -> [(a, b)]
zip Map Name [TypeBase d1 u']
cs1 Map Name [TypeBase d2 u']
cs2)
( Scalar (Arrow u'
als1 PName
p1 Diet
d1 TypeBase d1 NoUniqueness
a1 (RetType [VName]
dims1 TypeBase d1 Uniqueness
b1)),
Scalar (Arrow u'
als2 PName
p2 Diet
_d2 TypeBase d2 NoUniqueness
a2 (RetType [VName]
dims2 TypeBase d2 Uniqueness
b2))
) ->
let bound' :: [VName]
bound' = (PName -> Maybe VName) -> [PName] -> [VName]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PName -> Maybe VName
paramName [PName
p1, PName
p2] [VName] -> [VName] -> [VName]
forall a. Semigroup a => a -> a -> a
<> [VName]
dims1 [VName] -> [VName] -> [VName]
forall a. Semigroup a => a -> a -> a
<> [VName]
dims2 [VName] -> [VName] -> [VName]
forall a. Semigroup a => a -> a -> a
<> [VName]
bound
in ScalarTypeBase d1 u' -> TypeBase d1 u'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar
(ScalarTypeBase d1 u' -> TypeBase d1 u')
-> m (ScalarTypeBase d1 u') -> m (TypeBase d1 u')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ( u'
-> PName
-> Diet
-> TypeBase d1 NoUniqueness
-> RetTypeBase d1 Uniqueness
-> ScalarTypeBase d1 u'
forall dim u.
u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
Arrow (u'
als1 u' -> u' -> u'
forall a. Semigroup a => a -> a -> a
<> u'
als2) PName
p1 Diet
d1
(TypeBase d1 NoUniqueness
-> RetTypeBase d1 Uniqueness -> ScalarTypeBase d1 u')
-> m (TypeBase d1 NoUniqueness)
-> m (RetTypeBase d1 Uniqueness -> ScalarTypeBase d1 u')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [VName]
-> TypeBase d1 NoUniqueness
-> TypeBase d2 NoUniqueness
-> m (TypeBase d1 NoUniqueness)
forall u'.
Monoid u' =>
[VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' [VName]
bound' TypeBase d1 NoUniqueness
a1 TypeBase d2 NoUniqueness
a2
m (RetTypeBase d1 Uniqueness -> ScalarTypeBase d1 u')
-> m (RetTypeBase d1 Uniqueness) -> m (ScalarTypeBase d1 u')
forall a b. m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([VName] -> TypeBase d1 Uniqueness -> RetTypeBase d1 Uniqueness
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [VName]
dims1 (TypeBase d1 Uniqueness -> RetTypeBase d1 Uniqueness)
-> m (TypeBase d1 Uniqueness) -> m (RetTypeBase d1 Uniqueness)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [VName]
-> TypeBase d1 Uniqueness
-> TypeBase d2 Uniqueness
-> m (TypeBase d1 Uniqueness)
forall u'.
Monoid u' =>
[VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' [VName]
bound' TypeBase d1 Uniqueness
b1 TypeBase d2 Uniqueness
b2)
)
( Scalar (TypeVar u'
als1 QualName VName
v [TypeArg d1]
targs1),
Scalar (TypeVar u'
als2 QualName VName
_ [TypeArg d2]
targs2)
) ->
ScalarTypeBase d1 u' -> TypeBase d1 u'
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase d1 u' -> TypeBase d1 u')
-> ([TypeArg d1] -> ScalarTypeBase d1 u')
-> [TypeArg d1]
-> TypeBase d1 u'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. u' -> QualName VName -> [TypeArg d1] -> ScalarTypeBase d1 u'
forall dim u.
u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
TypeVar (u'
als1 u' -> u' -> u'
forall a. Semigroup a => a -> a -> a
<> u'
als2) QualName VName
v
([TypeArg d1] -> TypeBase d1 u')
-> m [TypeArg d1] -> m (TypeBase d1 u')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TypeArg d1 -> TypeArg d2 -> m (TypeArg d1))
-> [TypeArg d1] -> [TypeArg d2] -> m [TypeArg d1]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM ([VName] -> TypeArg d1 -> TypeArg d2 -> m (TypeArg d1)
matchTypeArg [VName]
bound) [TypeArg d1]
targs1 [TypeArg d2]
targs2
(TypeBase d1 u', TypeBase d2 u')
_ -> TypeBase d1 u' -> m (TypeBase d1 u')
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TypeBase d1 u'
t1
matchTypeArg :: [VName] -> TypeArg d1 -> TypeArg d2 -> m (TypeArg d1)
matchTypeArg [VName]
bound (TypeArgType TypeBase d1 NoUniqueness
t1) (TypeArgType TypeBase d2 NoUniqueness
t2) =
TypeBase d1 NoUniqueness -> TypeArg d1
forall dim. TypeBase dim NoUniqueness -> TypeArg dim
TypeArgType (TypeBase d1 NoUniqueness -> TypeArg d1)
-> m (TypeBase d1 NoUniqueness) -> m (TypeArg d1)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [VName]
-> TypeBase d1 NoUniqueness
-> TypeBase d2 NoUniqueness
-> m (TypeBase d1 NoUniqueness)
forall u'.
Monoid u' =>
[VName] -> TypeBase d1 u' -> TypeBase d2 u' -> m (TypeBase d1 u')
matchDims' [VName]
bound TypeBase d1 NoUniqueness
t1 TypeBase d2 NoUniqueness
t2
matchTypeArg [VName]
bound (TypeArgDim d1
x) (TypeArgDim d2
y) =
d1 -> TypeArg d1
forall dim. dim -> TypeArg dim
TypeArgDim (d1 -> TypeArg d1) -> m d1 -> m (TypeArg d1)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [VName] -> d1 -> d2 -> m d1
onDims [VName]
bound d1
x d2
y
matchTypeArg [VName]
_ TypeArg d1
a TypeArg d2
_ = TypeArg d1 -> m (TypeArg d1)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TypeArg d1
a
onShapes :: [VName] -> Shape d1 -> Shape d2 -> m (Shape d1)
onShapes [VName]
bound Shape d1
shape1 Shape d2
shape2 =
[d1] -> Shape d1
forall dim. [dim] -> Shape dim
Shape ([d1] -> Shape d1) -> m [d1] -> m (Shape d1)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (d1 -> d2 -> m d1) -> [d1] -> [d2] -> m [d1]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM ([VName] -> d1 -> d2 -> m d1
onDims [VName]
bound) (Shape d1 -> [d1]
forall dim. Shape dim -> [dim]
shapeDims Shape d1
shape1) (Shape d2 -> [d2]
forall dim. Shape dim -> [dim]
shapeDims Shape d2
shape2)
setUniqueness :: TypeBase dim u1 -> u2 -> TypeBase dim u2
setUniqueness :: forall dim u1 u2. TypeBase dim u1 -> u2 -> TypeBase dim u2
setUniqueness TypeBase dim u1
t u2
u = (u1 -> u2) -> TypeBase dim u1 -> TypeBase dim u2
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (u2 -> u1 -> u2
forall a b. a -> b -> a
const u2
u) TypeBase dim u1
t
intValueType :: IntValue -> IntType
intValueType :: IntValue -> IntType
intValueType Int8Value {} = IntType
Int8
intValueType Int16Value {} = IntType
Int16
intValueType Int32Value {} = IntType
Int32
intValueType Int64Value {} = IntType
Int64
floatValueType :: FloatValue -> FloatType
floatValueType :: FloatValue -> FloatType
floatValueType Float16Value {} = FloatType
Float16
floatValueType Float32Value {} = FloatType
Float32
floatValueType Float64Value {} = FloatType
Float64
primValueType :: PrimValue -> PrimType
primValueType :: PrimValue -> PrimType
primValueType (SignedValue IntValue
v) = IntType -> PrimType
Signed (IntType -> PrimType) -> IntType -> PrimType
forall a b. (a -> b) -> a -> b
$ IntValue -> IntType
intValueType IntValue
v
primValueType (UnsignedValue IntValue
v) = IntType -> PrimType
Unsigned (IntType -> PrimType) -> IntType -> PrimType
forall a b. (a -> b) -> a -> b
$ IntValue -> IntType
intValueType IntValue
v
primValueType (FloatValue FloatValue
v) = FloatType -> PrimType
FloatType (FloatType -> PrimType) -> FloatType -> PrimType
forall a b. (a -> b) -> a -> b
$ FloatValue -> FloatType
floatValueType FloatValue
v
primValueType BoolValue {} = PrimType
Bool
typeOf :: ExpBase Info VName -> StructType
typeOf :: ExpBase Info VName -> StructType
typeOf (Literal PrimValue
val SrcLoc
_) = ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall a b. (a -> b) -> a -> b
$ PrimValue -> PrimType
primValueType PrimValue
val
typeOf (IntLit Integer
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (FloatLit Double
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (Parens ExpBase Info VName
e SrcLoc
_) = ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e
typeOf (QualParens (QualName VName, SrcLoc)
_ ExpBase Info VName
e SrcLoc
_) = ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e
typeOf (TupLit [ExpBase Info VName]
es SrcLoc
_) = ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ [StructType] -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim as. [TypeBase dim as] -> ScalarTypeBase dim as
tupleRecord ([StructType] -> ScalarTypeBase (ExpBase Info VName) NoUniqueness)
-> [StructType] -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall a b. (a -> b) -> a -> b
$ (ExpBase Info VName -> StructType)
-> [ExpBase Info VName] -> [StructType]
forall a b. (a -> b) -> [a] -> [b]
map ExpBase Info VName -> StructType
typeOf [ExpBase Info VName]
es
typeOf (RecordLit [FieldBase Info VName]
fs SrcLoc
_) =
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ Map Name StructType
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u. Map Name (TypeBase dim u) -> ScalarTypeBase dim u
Record (Map Name StructType
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness)
-> Map Name StructType
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall a b. (a -> b) -> a -> b
$ [(Name, StructType)] -> Map Name StructType
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, StructType)] -> Map Name StructType)
-> [(Name, StructType)] -> Map Name StructType
forall a b. (a -> b) -> a -> b
$ (FieldBase Info VName -> (Name, StructType))
-> [FieldBase Info VName] -> [(Name, StructType)]
forall a b. (a -> b) -> [a] -> [b]
map FieldBase Info VName -> (Name, StructType)
record [FieldBase Info VName]
fs
where
record :: FieldBase Info VName -> (Name, StructType)
record (RecordFieldExplicit Name
name ExpBase Info VName
e SrcLoc
_) = (Name
name, ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e)
record (RecordFieldImplicit VName
name (Info StructType
t) SrcLoc
_) = (VName -> Name
baseName VName
name, StructType
t)
typeOf (ArrayLit [ExpBase Info VName]
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (StringLit [Word8]
vs SrcLoc
loc) =
NoUniqueness
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> StructType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array
NoUniqueness
forall a. Monoid a => a
mempty
([ExpBase Info VName] -> Shape (ExpBase Info VName)
forall dim. [dim] -> Shape dim
Shape [Integer -> SrcLoc -> ExpBase Info VName
sizeFromInteger ([Word8] -> Integer
forall i a. Num i => [a] -> i
genericLength [Word8]
vs) SrcLoc
loc])
(PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (IntType -> PrimType
Unsigned IntType
Int8))
typeOf (Project Name
_ ExpBase Info VName
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (Var QualName VName
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (Hole (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (Ascript ExpBase Info VName
e TypeExp Info VName
_ SrcLoc
_) = ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e
typeOf (Coerce ExpBase Info VName
_ TypeExp Info VName
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (Negate ExpBase Info VName
e SrcLoc
_) = ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e
typeOf (Not ExpBase Info VName
e SrcLoc
_) = ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e
typeOf (Update ExpBase Info VName
e SliceBase Info VName
_ ExpBase Info VName
_ SrcLoc
_) = ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e
typeOf (RecordUpdate ExpBase Info VName
_ [Name]
_ ExpBase Info VName
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (Assert ExpBase Info VName
_ ExpBase Info VName
e Info Text
_ SrcLoc
_) = ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e
typeOf (Lambda [PatBase Info VName ParamType]
params ExpBase Info VName
_ Maybe (TypeExp Info VName)
_ (Info ResRetType
t) SrcLoc
_) = [PatBase Info VName ParamType] -> ResRetType -> StructType
funType [PatBase Info VName ParamType]
params ResRetType
t
typeOf (OpSection QualName VName
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (OpSectionLeft QualName VName
_ Info StructType
_ ExpBase Info VName
_ (Info (PName, ParamType, Maybe VName)
_, Info (PName
pn, ParamType
pt2)) (Info ResRetType
ret, Info [VName]
_) SrcLoc
_) =
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ NoUniqueness
-> PName
-> Diet
-> StructType
-> ResRetType
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u.
u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
Arrow NoUniqueness
forall a. Monoid a => a
mempty PName
pn (ParamType -> Diet
forall shape. TypeBase shape Diet -> Diet
diet ParamType
pt2) (ParamType -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct ParamType
pt2) ResRetType
ret
typeOf (OpSectionRight QualName VName
_ Info StructType
_ ExpBase Info VName
_ (Info (PName
pn, ParamType
pt1), Info (PName, ParamType, Maybe VName)
_) (Info ResRetType
ret) SrcLoc
_) =
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ NoUniqueness
-> PName
-> Diet
-> StructType
-> ResRetType
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u.
u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
Arrow NoUniqueness
forall a. Monoid a => a
mempty PName
pn (ParamType -> Diet
forall shape. TypeBase shape Diet -> Diet
diet ParamType
pt1) (ParamType -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct ParamType
pt1) ResRetType
ret
typeOf (ProjectSection [Name]
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (IndexSection SliceBase Info VName
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (Constr Name
_ [ExpBase Info VName]
_ (Info StructType
t) SrcLoc
_) = StructType
t
typeOf (Attr AttrInfo VName
_ ExpBase Info VName
e SrcLoc
_) = ExpBase Info VName -> StructType
typeOf ExpBase Info VName
e
typeOf (AppExp AppExpBase Info VName
_ (Info AppRes
res)) = AppRes -> StructType
appResType AppRes
res
funType :: [Pat ParamType] -> ResRetType -> StructType
funType :: [PatBase Info VName ParamType] -> ResRetType -> StructType
funType [PatBase Info VName ParamType]
params ResRetType
ret =
let RetType [VName]
_ ResType
t = (PatBase Info VName ParamType -> ResRetType -> ResRetType)
-> ResRetType -> [PatBase Info VName ParamType] -> ResRetType
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((PName, Diet, StructType) -> ResRetType -> ResRetType
forall {dim}.
(PName, Diet, TypeBase dim NoUniqueness)
-> RetTypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
arrow ((PName, Diet, StructType) -> ResRetType -> ResRetType)
-> (PatBase Info VName ParamType -> (PName, Diet, StructType))
-> PatBase Info VName ParamType
-> ResRetType
-> ResRetType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PatBase Info VName ParamType -> (PName, Diet, StructType)
patternParam) ResRetType
ret [PatBase Info VName ParamType]
params
in ResType -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct ResType
t
where
arrow :: (PName, Diet, TypeBase dim NoUniqueness)
-> RetTypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
arrow (PName
xp, Diet
d, TypeBase dim NoUniqueness
xt) RetTypeBase dim Uniqueness
yt =
[VName] -> TypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [] (TypeBase dim Uniqueness -> RetTypeBase dim Uniqueness)
-> TypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase dim Uniqueness -> TypeBase dim Uniqueness
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase dim Uniqueness -> TypeBase dim Uniqueness)
-> ScalarTypeBase dim Uniqueness -> TypeBase dim Uniqueness
forall a b. (a -> b) -> a -> b
$ Uniqueness
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim Uniqueness
forall dim u.
u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
Arrow Uniqueness
Nonunique PName
xp Diet
d TypeBase dim NoUniqueness
xt RetTypeBase dim Uniqueness
yt
foldFunType :: [ParamType] -> ResRetType -> StructType
foldFunType :: [ParamType] -> ResRetType -> StructType
foldFunType [ParamType]
ps ResRetType
ret =
let RetType [VName]
_ ResType
t = (ParamType -> ResRetType -> ResRetType)
-> ResRetType -> [ParamType] -> ResRetType
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ParamType -> ResRetType -> ResRetType
forall {dim}.
TypeBase dim Diet
-> RetTypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
arrow ResRetType
ret [ParamType]
ps
in ResType -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct ResType
t
where
arrow :: TypeBase dim Diet
-> RetTypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
arrow TypeBase dim Diet
t1 RetTypeBase dim Uniqueness
t2 =
[VName] -> TypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [] (TypeBase dim Uniqueness -> RetTypeBase dim Uniqueness)
-> TypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase dim Uniqueness -> TypeBase dim Uniqueness
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase dim Uniqueness -> TypeBase dim Uniqueness)
-> ScalarTypeBase dim Uniqueness -> TypeBase dim Uniqueness
forall a b. (a -> b) -> a -> b
$ Uniqueness
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim Uniqueness
forall dim u.
u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
Arrow Uniqueness
Nonunique PName
Unnamed (TypeBase dim Diet -> Diet
forall shape. TypeBase shape Diet -> Diet
diet TypeBase dim Diet
t1) (TypeBase dim Diet -> TypeBase dim NoUniqueness
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct TypeBase dim Diet
t1) RetTypeBase dim Uniqueness
t2
unfoldFunType :: TypeBase dim as -> ([TypeBase dim Diet], TypeBase dim NoUniqueness)
unfoldFunType :: forall dim as.
TypeBase dim as -> ([TypeBase dim Diet], TypeBase dim NoUniqueness)
unfoldFunType (Scalar (Arrow as
_ PName
_ Diet
d TypeBase dim NoUniqueness
t1 (RetType [VName]
_ TypeBase dim Uniqueness
t2))) =
let ([TypeBase dim Diet]
ps, TypeBase dim NoUniqueness
r) = TypeBase dim Uniqueness
-> ([TypeBase dim Diet], TypeBase dim NoUniqueness)
forall dim as.
TypeBase dim as -> ([TypeBase dim Diet], TypeBase dim NoUniqueness)
unfoldFunType TypeBase dim Uniqueness
t2
in ((NoUniqueness -> Diet)
-> TypeBase dim NoUniqueness -> TypeBase dim Diet
forall b c a. (b -> c) -> TypeBase a b -> TypeBase a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Diet -> NoUniqueness -> Diet
forall a b. a -> b -> a
const Diet
d) TypeBase dim NoUniqueness
t1 TypeBase dim Diet -> [TypeBase dim Diet] -> [TypeBase dim Diet]
forall a. a -> [a] -> [a]
: [TypeBase dim Diet]
ps, TypeBase dim NoUniqueness
r)
unfoldFunType TypeBase dim as
t = ([], TypeBase dim as -> TypeBase dim NoUniqueness
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct TypeBase dim as
t)
valBindTypeScheme :: ValBindBase Info VName -> ([TypeParamBase VName], StructType)
valBindTypeScheme :: ValBindBase Info VName -> ([TypeParamBase VName], StructType)
valBindTypeScheme ValBindBase Info VName
vb =
( ValBindBase Info VName -> [TypeParamBase VName]
forall (f :: * -> *) vn. ValBindBase f vn -> [TypeParamBase vn]
valBindTypeParams ValBindBase Info VName
vb,
[PatBase Info VName ParamType] -> ResRetType -> StructType
funType (ValBindBase Info VName -> [PatBase Info VName ParamType]
forall (f :: * -> *) vn.
ValBindBase f vn -> [PatBase f vn ParamType]
valBindParams ValBindBase Info VName
vb) (Info ResRetType -> ResRetType
forall a. Info a -> a
unInfo (ValBindBase Info VName -> Info ResRetType
forall (f :: * -> *) vn. ValBindBase f vn -> f ResRetType
valBindRetType ValBindBase Info VName
vb))
)
valBindBound :: ValBindBase Info VName -> [VName]
valBindBound :: ValBindBase Info VName -> [VName]
valBindBound ValBindBase Info VName
vb =
ValBindBase Info VName -> VName
forall (f :: * -> *) vn. ValBindBase f vn -> vn
valBindName ValBindBase Info VName
vb
VName -> [VName] -> [VName]
forall a. a -> [a] -> [a]
: case ValBindBase Info VName -> [PatBase Info VName ParamType]
forall (f :: * -> *) vn.
ValBindBase f vn -> [PatBase f vn ParamType]
valBindParams ValBindBase Info VName
vb of
[] -> ResRetType -> [VName]
forall dim as. RetTypeBase dim as -> [VName]
retDims (Info ResRetType -> ResRetType
forall a. Info a -> a
unInfo (ValBindBase Info VName -> Info ResRetType
forall (f :: * -> *) vn. ValBindBase f vn -> f ResRetType
valBindRetType ValBindBase Info VName
vb))
[PatBase Info VName ParamType]
_ -> []
typeVars :: TypeBase dim as -> S.Set VName
typeVars :: forall dim as. TypeBase dim as -> Set VName
typeVars TypeBase dim as
t =
case TypeBase dim as
t of
Scalar Prim {} -> Set VName
forall a. Monoid a => a
mempty
Scalar (TypeVar as
_ QualName VName
tn [TypeArg dim]
targs) ->
[Set VName] -> Set VName
forall a. Monoid a => [a] -> a
mconcat ([Set VName] -> Set VName) -> [Set VName] -> Set VName
forall a b. (a -> b) -> a -> b
$ VName -> Set VName
forall a. a -> Set a
S.singleton (QualName VName -> VName
forall vn. QualName vn -> vn
qualLeaf QualName VName
tn) Set VName -> [Set VName] -> [Set VName]
forall a. a -> [a] -> [a]
: (TypeArg dim -> Set VName) -> [TypeArg dim] -> [Set VName]
forall a b. (a -> b) -> [a] -> [b]
map TypeArg dim -> Set VName
forall {dim}. TypeArg dim -> Set VName
typeArgFree [TypeArg dim]
targs
Scalar (Arrow as
_ PName
_ Diet
_ TypeBase dim NoUniqueness
t1 (RetType [VName]
_ TypeBase dim Uniqueness
t2)) -> TypeBase dim NoUniqueness -> Set VName
forall dim as. TypeBase dim as -> Set VName
typeVars TypeBase dim NoUniqueness
t1 Set VName -> Set VName -> Set VName
forall a. Semigroup a => a -> a -> a
<> TypeBase dim Uniqueness -> Set VName
forall dim as. TypeBase dim as -> Set VName
typeVars TypeBase dim Uniqueness
t2
Scalar (Record Map Name (TypeBase dim as)
fields) -> (TypeBase dim as -> Set VName)
-> Map Name (TypeBase dim as) -> Set VName
forall m a. Monoid m => (a -> m) -> Map Name a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TypeBase dim as -> Set VName
forall dim as. TypeBase dim as -> Set VName
typeVars Map Name (TypeBase dim as)
fields
Scalar (Sum Map Name [TypeBase dim as]
cs) -> [Set VName] -> Set VName
forall a. Monoid a => [a] -> a
mconcat ([Set VName] -> Set VName) -> [Set VName] -> Set VName
forall a b. (a -> b) -> a -> b
$ (([TypeBase dim as] -> [Set VName])
-> Map Name [TypeBase dim as] -> [Set VName]
forall m a. Monoid m => (a -> m) -> Map Name a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (([TypeBase dim as] -> [Set VName])
-> Map Name [TypeBase dim as] -> [Set VName])
-> ((TypeBase dim as -> Set VName)
-> [TypeBase dim as] -> [Set VName])
-> (TypeBase dim as -> Set VName)
-> Map Name [TypeBase dim as]
-> [Set VName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TypeBase dim as -> Set VName) -> [TypeBase dim as] -> [Set VName]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) TypeBase dim as -> Set VName
forall dim as. TypeBase dim as -> Set VName
typeVars Map Name [TypeBase dim as]
cs
Array as
_ Shape dim
_ ScalarTypeBase dim NoUniqueness
rt -> TypeBase dim NoUniqueness -> Set VName
forall dim as. TypeBase dim as -> Set VName
typeVars (TypeBase dim NoUniqueness -> Set VName)
-> TypeBase dim NoUniqueness -> Set VName
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase dim NoUniqueness -> TypeBase dim NoUniqueness
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar ScalarTypeBase dim NoUniqueness
rt
where
typeArgFree :: TypeArg dim -> Set VName
typeArgFree (TypeArgType TypeBase dim NoUniqueness
ta) = TypeBase dim NoUniqueness -> Set VName
forall dim as. TypeBase dim as -> Set VName
typeVars TypeBase dim NoUniqueness
ta
typeArgFree TypeArgDim {} = Set VName
forall a. Monoid a => a
mempty
orderZero :: TypeBase dim as -> Bool
orderZero :: forall dim as. TypeBase dim as -> Bool
orderZero Array {} = Bool
True
orderZero (Scalar (Prim PrimType
_)) = Bool
True
orderZero (Scalar (Record Map Name (TypeBase dim as)
fs)) = (TypeBase dim as -> Bool) -> [TypeBase dim as] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all TypeBase dim as -> Bool
forall dim as. TypeBase dim as -> Bool
orderZero ([TypeBase dim as] -> Bool) -> [TypeBase dim as] -> Bool
forall a b. (a -> b) -> a -> b
$ Map Name (TypeBase dim as) -> [TypeBase dim as]
forall k a. Map k a -> [a]
M.elems Map Name (TypeBase dim as)
fs
orderZero (Scalar TypeVar {}) = Bool
True
orderZero (Scalar Arrow {}) = Bool
False
orderZero (Scalar (Sum Map Name [TypeBase dim as]
cs)) = ([TypeBase dim as] -> Bool) -> Map Name [TypeBase dim as] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((TypeBase dim as -> Bool) -> [TypeBase dim as] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all TypeBase dim as -> Bool
forall dim as. TypeBase dim as -> Bool
orderZero) Map Name [TypeBase dim as]
cs
patternOrderZero :: Pat (TypeBase d u) -> Bool
patternOrderZero :: forall d u. Pat (TypeBase d u) -> Bool
patternOrderZero = TypeBase d u -> Bool
forall dim as. TypeBase dim as -> Bool
orderZero (TypeBase d u -> Bool)
-> (Pat (TypeBase d u) -> TypeBase d u)
-> Pat (TypeBase d u)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pat (TypeBase d u) -> TypeBase d u
forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType
patIdents :: Pat t -> [Ident t]
patIdents :: forall t. Pat t -> [Ident t]
patIdents (Id VName
v Info t
t SrcLoc
loc) = [VName -> Info t -> SrcLoc -> Ident t
forall {k} (f :: k -> *) vn (t :: k).
vn -> f t -> SrcLoc -> IdentBase f vn t
Ident VName
v Info t
t SrcLoc
loc]
patIdents (PatParens PatBase Info VName t
p SrcLoc
_) = PatBase Info VName t -> [Ident t]
forall t. Pat t -> [Ident t]
patIdents PatBase Info VName t
p
patIdents (TuplePat [PatBase Info VName t]
pats SrcLoc
_) = (PatBase Info VName t -> [Ident t])
-> [PatBase Info VName t] -> [Ident t]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap PatBase Info VName t -> [Ident t]
forall t. Pat t -> [Ident t]
patIdents [PatBase Info VName t]
pats
patIdents (RecordPat [(Name, PatBase Info VName t)]
fs SrcLoc
_) = ((Name, PatBase Info VName t) -> [Ident t])
-> [(Name, PatBase Info VName t)] -> [Ident t]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (PatBase Info VName t -> [Ident t]
forall t. Pat t -> [Ident t]
patIdents (PatBase Info VName t -> [Ident t])
-> ((Name, PatBase Info VName t) -> PatBase Info VName t)
-> (Name, PatBase Info VName t)
-> [Ident t]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, PatBase Info VName t) -> PatBase Info VName t
forall a b. (a, b) -> b
snd) [(Name, PatBase Info VName t)]
fs
patIdents Wildcard {} = [Ident t]
forall a. Monoid a => a
mempty
patIdents (PatAscription PatBase Info VName t
p TypeExp Info VName
_ SrcLoc
_) = PatBase Info VName t -> [Ident t]
forall t. Pat t -> [Ident t]
patIdents PatBase Info VName t
p
patIdents PatLit {} = [Ident t]
forall a. Monoid a => a
mempty
patIdents (PatConstr Name
_ Info t
_ [PatBase Info VName t]
ps SrcLoc
_) = (PatBase Info VName t -> [Ident t])
-> [PatBase Info VName t] -> [Ident t]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap PatBase Info VName t -> [Ident t]
forall t. Pat t -> [Ident t]
patIdents [PatBase Info VName t]
ps
patIdents (PatAttr AttrInfo VName
_ PatBase Info VName t
p SrcLoc
_) = PatBase Info VName t -> [Ident t]
forall t. Pat t -> [Ident t]
patIdents PatBase Info VName t
p
patNames :: Pat t -> [VName]
patNames :: forall t. Pat t -> [VName]
patNames = ((VName, t) -> VName) -> [(VName, t)] -> [VName]
forall a b. (a -> b) -> [a] -> [b]
map (VName, t) -> VName
forall a b. (a, b) -> a
fst ([(VName, t)] -> [VName])
-> (Pat t -> [(VName, t)]) -> Pat t -> [VName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pat t -> [(VName, t)]
forall t. Pat t -> [(VName, t)]
patternMap
patternMap :: Pat t -> [(VName, t)]
patternMap :: forall t. Pat t -> [(VName, t)]
patternMap = (IdentBase Info VName t -> (VName, t))
-> [IdentBase Info VName t] -> [(VName, t)]
forall a b. (a -> b) -> [a] -> [b]
map IdentBase Info VName t -> (VName, t)
forall {a} {b}. IdentBase Info a b -> (a, b)
f ([IdentBase Info VName t] -> [(VName, t)])
-> (Pat t -> [IdentBase Info VName t]) -> Pat t -> [(VName, t)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pat t -> [IdentBase Info VName t]
forall t. Pat t -> [Ident t]
patIdents
where
f :: IdentBase Info a b -> (a, b)
f (Ident a
v (Info b
t) SrcLoc
_) = (a
v, b
t)
patternType :: Pat (TypeBase d u) -> TypeBase d u
patternType :: forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType (Wildcard (Info TypeBase d u
t) SrcLoc
_) = TypeBase d u
t
patternType (PatParens PatBase Info VName (TypeBase d u)
p SrcLoc
_) = PatBase Info VName (TypeBase d u) -> TypeBase d u
forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType PatBase Info VName (TypeBase d u)
p
patternType (Id VName
_ (Info TypeBase d u
t) SrcLoc
_) = TypeBase d u
t
patternType (TuplePat [PatBase Info VName (TypeBase d u)]
pats SrcLoc
_) = ScalarTypeBase d u -> TypeBase d u
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase d u -> TypeBase d u)
-> ScalarTypeBase d u -> TypeBase d u
forall a b. (a -> b) -> a -> b
$ [TypeBase d u] -> ScalarTypeBase d u
forall dim as. [TypeBase dim as] -> ScalarTypeBase dim as
tupleRecord ([TypeBase d u] -> ScalarTypeBase d u)
-> [TypeBase d u] -> ScalarTypeBase d u
forall a b. (a -> b) -> a -> b
$ (PatBase Info VName (TypeBase d u) -> TypeBase d u)
-> [PatBase Info VName (TypeBase d u)] -> [TypeBase d u]
forall a b. (a -> b) -> [a] -> [b]
map PatBase Info VName (TypeBase d u) -> TypeBase d u
forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType [PatBase Info VName (TypeBase d u)]
pats
patternType (RecordPat [(Name, PatBase Info VName (TypeBase d u))]
fs SrcLoc
_) = ScalarTypeBase d u -> TypeBase d u
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase d u -> TypeBase d u)
-> ScalarTypeBase d u -> TypeBase d u
forall a b. (a -> b) -> a -> b
$ Map Name (TypeBase d u) -> ScalarTypeBase d u
forall dim u. Map Name (TypeBase dim u) -> ScalarTypeBase dim u
Record (Map Name (TypeBase d u) -> ScalarTypeBase d u)
-> Map Name (TypeBase d u) -> ScalarTypeBase d u
forall a b. (a -> b) -> a -> b
$ PatBase Info VName (TypeBase d u) -> TypeBase d u
forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType (PatBase Info VName (TypeBase d u) -> TypeBase d u)
-> Map Name (PatBase Info VName (TypeBase d u))
-> Map Name (TypeBase d u)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Name, PatBase Info VName (TypeBase d u))]
-> Map Name (PatBase Info VName (TypeBase d u))
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(Name, PatBase Info VName (TypeBase d u))]
fs
patternType (PatAscription PatBase Info VName (TypeBase d u)
p TypeExp Info VName
_ SrcLoc
_) = PatBase Info VName (TypeBase d u) -> TypeBase d u
forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType PatBase Info VName (TypeBase d u)
p
patternType (PatLit PatLit
_ (Info TypeBase d u
t) SrcLoc
_) = TypeBase d u
t
patternType (PatConstr Name
_ (Info TypeBase d u
t) [PatBase Info VName (TypeBase d u)]
_ SrcLoc
_) = TypeBase d u
t
patternType (PatAttr AttrInfo VName
_ PatBase Info VName (TypeBase d u)
p SrcLoc
_) = PatBase Info VName (TypeBase d u) -> TypeBase d u
forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType PatBase Info VName (TypeBase d u)
p
patternStructType :: Pat (TypeBase Size u) -> StructType
patternStructType :: forall u. Pat (TypeBase (ExpBase Info VName) u) -> StructType
patternStructType = TypeBase (ExpBase Info VName) u -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct (TypeBase (ExpBase Info VName) u -> StructType)
-> (Pat (TypeBase (ExpBase Info VName) u)
-> TypeBase (ExpBase Info VName) u)
-> Pat (TypeBase (ExpBase Info VName) u)
-> StructType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pat (TypeBase (ExpBase Info VName) u)
-> TypeBase (ExpBase Info VName) u
forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType
patternParam :: Pat ParamType -> (PName, Diet, StructType)
patternParam :: PatBase Info VName ParamType -> (PName, Diet, StructType)
patternParam (PatParens PatBase Info VName ParamType
p SrcLoc
_) =
PatBase Info VName ParamType -> (PName, Diet, StructType)
patternParam PatBase Info VName ParamType
p
patternParam (PatAttr AttrInfo VName
_ PatBase Info VName ParamType
p SrcLoc
_) =
PatBase Info VName ParamType -> (PName, Diet, StructType)
patternParam PatBase Info VName ParamType
p
patternParam (PatAscription (Id VName
v (Info ParamType
t) SrcLoc
_) TypeExp Info VName
_ SrcLoc
_) =
(VName -> PName
Named VName
v, ParamType -> Diet
forall shape. TypeBase shape Diet -> Diet
diet ParamType
t, ParamType -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct ParamType
t)
patternParam (Id VName
v (Info ParamType
t) SrcLoc
_) =
(VName -> PName
Named VName
v, ParamType -> Diet
forall shape. TypeBase shape Diet -> Diet
diet ParamType
t, ParamType -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct ParamType
t)
patternParam PatBase Info VName ParamType
p =
(PName
Unnamed, ParamType -> Diet
forall shape. TypeBase shape Diet -> Diet
diet ParamType
p_t, ParamType -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct ParamType
p_t)
where
p_t :: ParamType
p_t = PatBase Info VName ParamType -> ParamType
forall d u. Pat (TypeBase d u) -> TypeBase d u
patternType PatBase Info VName ParamType
p
namesToPrimTypes :: M.Map Name PrimType
namesToPrimTypes :: Map Name PrimType
namesToPrimTypes =
[(Name, PrimType)] -> Map Name PrimType
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (FilePath -> Name
nameFromString (FilePath -> Name) -> FilePath -> Name
forall a b. (a -> b) -> a -> b
$ PrimType -> FilePath
forall a. Pretty a => a -> FilePath
prettyString PrimType
t, PrimType
t)
| PrimType
t <-
PrimType
Bool
PrimType -> [PrimType] -> [PrimType]
forall a. a -> [a] -> [a]
: (IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
Signed [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ (IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
Unsigned [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ (FloatType -> PrimType) -> [FloatType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> PrimType
FloatType [FloatType
forall a. Bounded a => a
minBound .. FloatType
forall a. Bounded a => a
maxBound]
]
data Intrinsic
= IntrinsicMonoFun [PrimType] PrimType
| IntrinsicOverloadedFun [PrimType] [Maybe PrimType] (Maybe PrimType)
| IntrinsicPolyFun [TypeParamBase VName] [ParamType] (RetTypeBase Size Uniqueness)
| IntrinsicType Liftedness [TypeParamBase VName] StructType
| IntrinsicEquality
intrinsicAcc :: (VName, Intrinsic)
intrinsicAcc :: (VName, Intrinsic)
intrinsicAcc =
( VName
acc_v,
Liftedness -> [TypeParamBase VName] -> StructType -> Intrinsic
IntrinsicType Liftedness
SizeLifted [Liftedness -> VName -> SrcLoc -> TypeParamBase VName
forall vn. Liftedness -> vn -> SrcLoc -> TypeParamBase vn
TypeParamType Liftedness
Unlifted VName
t_v SrcLoc
forall a. Monoid a => a
mempty] (StructType -> Intrinsic) -> StructType -> Intrinsic
forall a b. (a -> b) -> a -> b
$
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$
NoUniqueness
-> QualName VName
-> [TypeArg (ExpBase Info VName)]
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u.
u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
TypeVar NoUniqueness
forall a. Monoid a => a
mempty (VName -> QualName VName
forall v. v -> QualName v
qualName VName
acc_v) [TypeArg (ExpBase Info VName)
forall {dim}. TypeArg dim
arg]
)
where
acc_v :: VName
acc_v = Name -> Int -> VName
VName Name
"acc" Int
10
t_v :: VName
t_v = Name -> Int -> VName
VName Name
"t" Int
11
arg :: TypeArg dim
arg = TypeBase dim NoUniqueness -> TypeArg dim
forall dim. TypeBase dim NoUniqueness -> TypeArg dim
TypeArgType (TypeBase dim NoUniqueness -> TypeArg dim)
-> TypeBase dim NoUniqueness -> TypeArg dim
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase dim NoUniqueness -> TypeBase dim NoUniqueness
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness
-> QualName VName
-> [TypeArg dim]
-> ScalarTypeBase dim NoUniqueness
forall dim u.
u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
TypeVar NoUniqueness
forall a. Monoid a => a
mempty (VName -> QualName VName
forall v. v -> QualName v
qualName VName
t_v) [])
isAccType :: TypeBase d u -> Maybe (TypeBase d NoUniqueness)
isAccType :: forall d u. TypeBase d u -> Maybe (TypeBase d NoUniqueness)
isAccType (Scalar (TypeVar u
_ (QualName [] VName
v) [TypeArgType TypeBase d NoUniqueness
t]))
| VName
v VName -> VName -> Bool
forall a. Eq a => a -> a -> Bool
== (VName, Intrinsic) -> VName
forall a b. (a, b) -> a
fst (VName, Intrinsic)
intrinsicAcc =
TypeBase d NoUniqueness -> Maybe (TypeBase d NoUniqueness)
forall a. a -> Maybe a
Just TypeBase d NoUniqueness
t
isAccType TypeBase d u
_ = Maybe (TypeBase d NoUniqueness)
forall a. Maybe a
Nothing
intrinsicVar :: Name -> VName
intrinsicVar :: Name -> VName
intrinsicVar Name
v =
VName -> Maybe VName -> VName
forall a. a -> Maybe a -> a
fromMaybe VName
forall {a}. a
bad (Maybe VName -> VName) -> Maybe VName -> VName
forall a b. (a -> b) -> a -> b
$ (VName -> Bool) -> [VName] -> Maybe VName
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((Name
v ==) (Name -> Bool) -> (VName -> Name) -> VName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VName -> Name
baseName) ([VName] -> Maybe VName) -> [VName] -> Maybe VName
forall a b. (a -> b) -> a -> b
$ Map VName Intrinsic -> [VName]
forall k a. Map k a -> [k]
M.keys Map VName Intrinsic
intrinsics
where
bad :: a
bad = FilePath -> a
forall a. HasCallStack => FilePath -> a
error (FilePath -> a) -> FilePath -> a
forall a b. (a -> b) -> a -> b
$ FilePath
"findBuiltin: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Name -> FilePath
nameToString Name
v
mkBinOp :: Name -> StructType -> Exp -> Exp -> Exp
mkBinOp :: Name
-> StructType
-> ExpBase Info VName
-> ExpBase Info VName
-> ExpBase Info VName
mkBinOp Name
op StructType
t ExpBase Info VName
x ExpBase Info VName
y =
AppExpBase Info VName -> Info AppRes -> ExpBase Info VName
forall (f :: * -> *) vn.
AppExpBase f vn -> f AppRes -> ExpBase f vn
AppExp
( (QualName VName, SrcLoc)
-> Info StructType
-> (ExpBase Info VName, Info (Maybe VName))
-> (ExpBase Info VName, Info (Maybe VName))
-> SrcLoc
-> AppExpBase Info VName
forall (f :: * -> *) vn.
(QualName vn, SrcLoc)
-> f StructType
-> (ExpBase f vn, f (Maybe VName))
-> (ExpBase f vn, f (Maybe VName))
-> SrcLoc
-> AppExpBase f vn
BinOp
(VName -> QualName VName
forall v. v -> QualName v
qualName (Name -> VName
intrinsicVar Name
op), SrcLoc
forall a. Monoid a => a
mempty)
(StructType -> Info StructType
forall a. a -> Info a
Info StructType
t)
(ExpBase Info VName
x, Maybe VName -> Info (Maybe VName)
forall a. a -> Info a
Info Maybe VName
forall a. Maybe a
Nothing)
(ExpBase Info VName
y, Maybe VName -> Info (Maybe VName)
forall a. a -> Info a
Info Maybe VName
forall a. Maybe a
Nothing)
SrcLoc
forall a. Monoid a => a
mempty
)
(AppRes -> Info AppRes
forall a. a -> Info a
Info (AppRes -> Info AppRes) -> AppRes -> Info AppRes
forall a b. (a -> b) -> a -> b
$ StructType -> [VName] -> AppRes
AppRes StructType
t [])
mkAdd, mkMul :: Exp -> Exp -> Exp
mkAdd :: ExpBase Info VName -> ExpBase Info VName -> ExpBase Info VName
mkAdd = Name
-> StructType
-> ExpBase Info VName
-> ExpBase Info VName
-> ExpBase Info VName
mkBinOp Name
"+" (StructType
-> ExpBase Info VName -> ExpBase Info VName -> ExpBase Info VName)
-> StructType
-> ExpBase Info VName
-> ExpBase Info VName
-> ExpBase Info VName
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64
mkMul :: ExpBase Info VName -> ExpBase Info VName -> ExpBase Info VName
mkMul = Name
-> StructType
-> ExpBase Info VName
-> ExpBase Info VName
-> ExpBase Info VName
mkBinOp Name
"*" (StructType
-> ExpBase Info VName -> ExpBase Info VName -> ExpBase Info VName)
-> StructType
-> ExpBase Info VName
-> ExpBase Info VName
-> ExpBase Info VName
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64
intrinsics :: M.Map VName Intrinsic
intrinsics :: Map VName Intrinsic
intrinsics =
([(VName, Intrinsic)] -> Map VName Intrinsic
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(VName, Intrinsic)
intrinsicAcc] <>) (Map VName Intrinsic -> Map VName Intrinsic)
-> Map VName Intrinsic -> Map VName Intrinsic
forall a b. (a -> b) -> a -> b
$
[(VName, Intrinsic)] -> Map VName Intrinsic
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(VName, Intrinsic)] -> Map VName Intrinsic)
-> [(VName, Intrinsic)] -> Map VName Intrinsic
forall a b. (a -> b) -> a -> b
$
[(VName, Intrinsic)]
primOp
[(VName, Intrinsic)]
-> [(VName, Intrinsic)] -> [(VName, Intrinsic)]
forall a. [a] -> [a] -> [a]
++ (Int -> (FilePath, Intrinsic) -> (VName, Intrinsic))
-> [Int] -> [(FilePath, Intrinsic)] -> [(VName, Intrinsic)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
Int -> (FilePath, Intrinsic) -> (VName, Intrinsic)
forall {b}. Int -> (FilePath, b) -> (VName, b)
namify
[Int
intrinsicStart ..]
( [ ( FilePath
"manifest",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a]
[ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
forall a. Monoid a => a
mempty]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar
(ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
forall a. Monoid a => a
mempty
),
( FilePath
"flatten",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m]
[Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n, VName
m]) (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ResType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array
Uniqueness
Nonunique
([ExpBase Info VName] -> Shape (ExpBase Info VName)
forall dim. [dim] -> Shape dim
Shape [VName -> ExpBase Info VName
size VName
n ExpBase Info VName -> ExpBase Info VName -> ExpBase Info VName
`mkMul` VName -> ExpBase Info VName
size VName
m])
(NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty)
),
( FilePath
"unflatten",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m]
[ ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64,
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64,
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([ExpBase Info VName] -> Shape (ExpBase Info VName)
forall dim. [dim] -> Shape dim
Shape [VName -> ExpBase Info VName
size VName
n ExpBase Info VName -> ExpBase Info VName -> ExpBase Info VName
`mkMul` VName -> ExpBase Info VName
size VName
m]) (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ResType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Uniqueness
Nonunique ([VName] -> Shape (ExpBase Info VName)
shape [VName
n, VName
m]) (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty)
),
( FilePath
"concat",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n],
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [ExpBase Info VName] -> Shape (ExpBase Info VName)
forall dim. [dim] -> Shape dim
Shape [VName -> ExpBase Info VName
size VName
n ExpBase Info VName -> ExpBase Info VName -> ExpBase Info VName
`mkAdd` VName -> ExpBase Info VName
size VName
m]
),
( FilePath
"transpose",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m]
[Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n, VName
m]]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Nonunique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m, VName
n]
),
( FilePath
"scatter",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_l]
[ Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Consume ([VName] -> Shape (ExpBase Info VName)
shape [VName
n]) (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty,
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
l]) (PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
l]) (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ResType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Uniqueness
Unique ([VName] -> Shape (ExpBase Info VName)
shape [VName
n]) (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty)
),
( FilePath
"scatter_2d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m, TypeParamBase VName
sp_l]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n, VName
m],
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
l]) (Int -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {dim} {u}. Int -> ScalarTypeBase dim u
tupInt64 Int
2),
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
l]) (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n, VName
m]
),
( FilePath
"scatter_3d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m, TypeParamBase VName
sp_k, TypeParamBase VName
sp_l]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n, VName
m, VName
k],
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
l]) (Int -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {dim} {u}. Int -> ScalarTypeBase dim u
tupInt64 Int
3),
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
l]) (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> ParamType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n, VName
m, VName
k]
),
( FilePath
"zip",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
tp_b, TypeParamBase VName
sp_n]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n]),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_b Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n])
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness
-> StructType
-> StructType
-> Shape (ExpBase Info VName)
-> ResType
forall {u} {dim}.
u
-> TypeBase dim NoUniqueness
-> TypeBase dim NoUniqueness
-> Shape dim
-> TypeBase dim u
tuple_array Uniqueness
Unique (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b NoUniqueness
forall a. Monoid a => a
mempty)
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
),
( FilePath
"unzip",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
tp_b, TypeParamBase VName
sp_n]
[Diet
-> StructType
-> StructType
-> Shape (ExpBase Info VName)
-> ParamType
forall {u} {dim}.
u
-> TypeBase dim NoUniqueness
-> TypeBase dim NoUniqueness
-> Shape dim
-> TypeBase dim u
tuple_array Diet
Observe (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b NoUniqueness
forall a. Monoid a => a
mempty) (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [] (ResType -> ResRetType)
-> ([(Name, ResType)] -> ResType)
-> [(Name, ResType)]
-> ResRetType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ([(Name, ResType)]
-> ScalarTypeBase (ExpBase Info VName) Uniqueness)
-> [(Name, ResType)]
-> ResType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Name ResType -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall dim u. Map Name (TypeBase dim u) -> ScalarTypeBase dim u
Record (Map Name ResType
-> ScalarTypeBase (ExpBase Info VName) Uniqueness)
-> ([(Name, ResType)] -> Map Name ResType)
-> [(Name, ResType)]
-> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Name, ResType)] -> Map Name ResType
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
([(Name, ResType)] -> ResRetType)
-> [(Name, ResType)] -> ResRetType
forall a b. (a -> b) -> a -> b
$ [Name] -> [ResType] -> [(Name, ResType)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
tupleFieldNames [Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique (Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n], Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_b Uniqueness
Unique (Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]]
),
( FilePath
"hist_1d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m]
[ ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64,
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m],
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Nonunique)),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe,
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n]) (Int -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {dim} {u}. Int -> ScalarTypeBase dim u
tupInt64 Int
1),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n])
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m]
),
( FilePath
"hist_2d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m, TypeParamBase VName
sp_k]
[ ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64,
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m, VName
k],
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Nonunique)),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe,
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n]) (Int -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {dim} {u}. Int -> ScalarTypeBase dim u
tupInt64 Int
2),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n])
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m, VName
k]
),
( FilePath
"hist_3d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_m, TypeParamBase VName
sp_k, TypeParamBase VName
sp_l]
[ ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64,
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m, VName
k, VName
l],
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Nonunique)),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe,
Diet
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ParamType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n]) (Int -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {dim} {u}. Int -> ScalarTypeBase dim u
tupInt64 Int
3),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe ([VName] -> Shape (ExpBase Info VName)
shape [VName
n])
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m, VName
k, VName
l]
),
( FilePath
"map",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
tp_b, TypeParamBase VName
sp_n]
[ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b Uniqueness
Nonunique),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_b Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
),
( FilePath
"reduce",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n]
[ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Nonunique)),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe,
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Unique)
),
( FilePath
"reduce_comm",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n]
[ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Nonunique)),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe,
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [] (ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Unique))
),
( FilePath
"scan",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n]
[ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Nonunique)),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe,
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [] (Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique (Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n])
),
( FilePath
"partition",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n]
[ ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int32),
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Uniqueness)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
]
( [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [VName
k] (ResType -> ResRetType)
-> (ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness
-> ResRetType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResRetType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResRetType
forall a b. (a -> b) -> a -> b
$
[ResType] -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall dim as. [TypeBase dim as] -> ScalarTypeBase dim as
tupleRecord
[ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique (Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n],
Uniqueness
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> ResType
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array Uniqueness
Unique ([VName] -> Shape (ExpBase Info VName)
shape [VName
k]) (PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64)
]
)
),
( FilePath
"acc_write",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
sp_k, TypeParamBase VName
tp_a]
[ ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> StructType -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}.
u -> TypeBase dim NoUniqueness -> ScalarTypeBase dim u
accType Diet
Consume (StructType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> StructType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> StructType
forall {u}. u -> TypeBase (ExpBase Info VName) u
array_ka NoUniqueness
forall a. Monoid a => a
mempty,
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar
(ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall a b. (a -> b) -> a -> b
$ Uniqueness
-> StructType -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}.
u -> TypeBase dim NoUniqueness -> ScalarTypeBase dim u
accType Uniqueness
Unique (NoUniqueness -> StructType
forall {u}. u -> TypeBase (ExpBase Info VName) u
array_ka NoUniqueness
forall a. Monoid a => a
mempty)
),
( FilePath
"scatter_stream",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
tp_b, TypeParamBase VName
sp_k, TypeParamBase VName
sp_n]
[ Diet -> ParamType
forall {u}. u -> TypeBase (ExpBase Info VName) u
array_ka Diet
Consume,
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness
-> StructType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}.
u -> TypeBase dim NoUniqueness -> ScalarTypeBase dim u
accType NoUniqueness
forall a. Monoid a => a
mempty (NoUniqueness -> StructType
forall {u}. u -> TypeBase (ExpBase Info VName) u
array_ka NoUniqueness
forall a. Monoid a => a
mempty))
StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`carr` ( ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b NoUniqueness
forall a. Monoid a => a
mempty)
StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness
-> StructType -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}.
u -> TypeBase dim NoUniqueness -> ScalarTypeBase dim u
accType Uniqueness
Nonunique (StructType -> ScalarTypeBase (ExpBase Info VName) Uniqueness)
-> StructType -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> Shape (ExpBase Info VName) -> StructType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a NoUniqueness
forall a. Monoid a => a
mempty (Shape (ExpBase Info VName) -> StructType)
-> Shape (ExpBase Info VName) -> StructType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
k])
),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_b Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> ResType
forall {u}. u -> TypeBase (ExpBase Info VName) u
array_ka Uniqueness
Unique
),
( FilePath
"hist_stream",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
tp_b, TypeParamBase VName
sp_k, TypeParamBase VName
sp_n]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
k],
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Nonunique)),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Diet -> ParamType)
-> ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall a b. (a -> b) -> a -> b
$ Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe,
ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness
-> StructType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}.
u -> TypeBase dim NoUniqueness -> ScalarTypeBase dim u
accType NoUniqueness
forall a. Monoid a => a
mempty (StructType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness)
-> StructType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> StructType
forall {u}. u -> TypeBase (ExpBase Info VName) u
array_ka NoUniqueness
forall a. Monoid a => a
mempty)
StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`carr` ( ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b NoUniqueness
forall a. Monoid a => a
mempty)
StructType -> ResType -> ResType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness
-> StructType -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}.
u -> TypeBase dim NoUniqueness -> ScalarTypeBase dim u
accType Uniqueness
Nonunique (StructType -> ScalarTypeBase (ExpBase Info VName) Uniqueness)
-> StructType -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> Shape (ExpBase Info VName) -> StructType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a NoUniqueness
forall a. Monoid a => a
mempty (Shape (ExpBase Info VName) -> StructType)
-> Shape (ExpBase Info VName) -> StructType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
k])
),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_b Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
k]
),
( FilePath
"jvp2",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
tp_b]
[ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b Uniqueness
Nonunique),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe)
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar
(ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall a b. (a -> b) -> a -> b
$ [ResType] -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall dim as. [TypeBase dim as] -> ScalarTypeBase dim as
tupleRecord [ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b Uniqueness
Nonunique, ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b Uniqueness
Nonunique]
),
( FilePath
"vjp2",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
tp_b]
[ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty) StructType -> ResType -> ParamType
forall {u} {dim}.
Monoid u =>
TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
`arr` ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b Uniqueness
Nonunique),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Diet
Observe),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (Diet -> ScalarTypeBase (ExpBase Info VName) Diet
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b Diet
Observe)
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar
(ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall a b. (a -> b) -> a -> b
$ [ResType] -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall dim as. [TypeBase dim as] -> ScalarTypeBase dim as
tupleRecord [ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b Uniqueness
Nonunique, ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType)
-> ScalarTypeBase (ExpBase Info VName) Uniqueness -> ResType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> ScalarTypeBase (ExpBase Info VName) Uniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a Uniqueness
Nonunique]
)
]
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++
[ ( FilePath
"flat_index_2d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n],
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64)
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [VName
m, VName
k]
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Nonunique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m, VName
k]
),
( FilePath
"flat_update_2d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_k, TypeParamBase VName
sp_l]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n],
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
k, VName
l]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
),
( FilePath
"flat_index_3d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n],
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64)
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [VName
m, VName
k, VName
l]
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Nonunique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m, VName
k, VName
l]
),
( FilePath
"flat_update_3d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_k, TypeParamBase VName
sp_l, TypeParamBase VName
sp_p]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n],
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
k, VName
l, VName
p]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
),
( FilePath
"flat_index_4d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n],
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64)
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [VName
m, VName
k, VName
l, VName
p]
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Nonunique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
m, VName
k, VName
l, VName
p]
),
( FilePath
"flat_update_4d",
[TypeParamBase VName] -> [ParamType] -> ResRetType -> Intrinsic
IntrinsicPolyFun
[TypeParamBase VName
tp_a, TypeParamBase VName
sp_n, TypeParamBase VName
sp_k, TypeParamBase VName
sp_l, TypeParamBase VName
sp_p, TypeParamBase VName
sp_q]
[ Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Consume (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n],
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
ScalarTypeBase (ExpBase Info VName) Diet -> ParamType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase (ExpBase Info VName) Diet)
-> PrimType -> ScalarTypeBase (ExpBase Info VName) Diet
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64),
Diet -> Shape (ExpBase Info VName) -> ParamType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Diet
Observe (Shape (ExpBase Info VName) -> ParamType)
-> Shape (ExpBase Info VName) -> ParamType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
k, VName
l, VName
p, VName
q]
]
(ResRetType -> Intrinsic) -> ResRetType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ [VName] -> ResType -> ResRetType
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType []
(ResType -> ResRetType) -> ResType -> ResRetType
forall a b. (a -> b) -> a -> b
$ Uniqueness -> Shape (ExpBase Info VName) -> ResType
forall {u} {dim}. u -> Shape dim -> TypeBase dim u
array_a Uniqueness
Unique
(Shape (ExpBase Info VName) -> ResType)
-> Shape (ExpBase Info VName) -> ResType
forall a b. (a -> b) -> a -> b
$ [VName] -> Shape (ExpBase Info VName)
shape [VName
n]
)
]
)
where
primOp :: [(VName, Intrinsic)]
primOp =
(Int -> (FilePath, Intrinsic) -> (VName, Intrinsic))
-> [Int] -> [(FilePath, Intrinsic)] -> [(VName, Intrinsic)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> (FilePath, Intrinsic) -> (VName, Intrinsic)
forall {b}. Int -> (FilePath, b) -> (VName, b)
namify [Int
20 ..] ([(FilePath, Intrinsic)] -> [(VName, Intrinsic)])
-> [(FilePath, Intrinsic)] -> [(VName, Intrinsic)]
forall a b. (a -> b) -> a -> b
$
((FilePath, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
-> (FilePath, Intrinsic))
-> [(FilePath,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))]
-> [(FilePath, Intrinsic)]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath, ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))
-> (FilePath, Intrinsic)
forall {a} {c}. (a, ([PrimType], PrimType, c)) -> (a, Intrinsic)
primFun (Map FilePath ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)
-> [(FilePath,
([PrimType], PrimType, [PrimValue] -> Maybe PrimValue))]
forall k a. Map k a -> [(k, a)]
M.toList Map FilePath ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue)
Primitive.primFuns)
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++ (UnOp -> (FilePath, Intrinsic))
-> [UnOp] -> [(FilePath, Intrinsic)]
forall a b. (a -> b) -> [a] -> [b]
map UnOp -> (FilePath, Intrinsic)
unOpFun [UnOp]
Primitive.allUnOps
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++ (BinOp -> (FilePath, Intrinsic))
-> [BinOp] -> [(FilePath, Intrinsic)]
forall a b. (a -> b) -> [a] -> [b]
map BinOp -> (FilePath, Intrinsic)
binOpFun [BinOp]
Primitive.allBinOps
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++ (CmpOp -> (FilePath, Intrinsic))
-> [CmpOp] -> [(FilePath, Intrinsic)]
forall a b. (a -> b) -> [a] -> [b]
map CmpOp -> (FilePath, Intrinsic)
cmpOpFun [CmpOp]
Primitive.allCmpOps
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++ (ConvOp -> (FilePath, Intrinsic))
-> [ConvOp] -> [(FilePath, Intrinsic)]
forall a b. (a -> b) -> [a] -> [b]
map ConvOp -> (FilePath, Intrinsic)
convOpFun [ConvOp]
Primitive.allConvOps
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++ (IntType -> (FilePath, Intrinsic))
-> [IntType] -> [(FilePath, Intrinsic)]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> (FilePath, Intrinsic)
signFun [IntType]
Primitive.allIntTypes
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++ (IntType -> (FilePath, Intrinsic))
-> [IntType] -> [(FilePath, Intrinsic)]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> (FilePath, Intrinsic)
unsignFun [IntType]
Primitive.allIntTypes
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++ (PrimType -> (FilePath, Intrinsic))
-> [PrimType] -> [(FilePath, Intrinsic)]
forall a b. (a -> b) -> [a] -> [b]
map
PrimType -> (FilePath, Intrinsic)
intrinsicPrim
( (IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
Signed [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ (IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
Unsigned [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ (FloatType -> PrimType) -> [FloatType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> PrimType
FloatType [FloatType
forall a. Bounded a => a
minBound .. FloatType
forall a. Bounded a => a
maxBound]
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ [PrimType
Bool]
)
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++
[ ( FilePath
"!",
[PrimType] -> [Maybe PrimType] -> Maybe PrimType -> Intrinsic
IntrinsicOverloadedFun
( (IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
Signed [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ (IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
Unsigned [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ [PrimType
Bool]
)
[Maybe PrimType
forall a. Maybe a
Nothing]
Maybe PrimType
forall a. Maybe a
Nothing
)
]
[(FilePath, Intrinsic)]
-> [(FilePath, Intrinsic)] -> [(FilePath, Intrinsic)]
forall a. [a] -> [a] -> [a]
++
(BinOp -> Maybe (FilePath, Intrinsic))
-> [BinOp] -> [(FilePath, Intrinsic)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe BinOp -> Maybe (FilePath, Intrinsic)
mkIntrinsicBinOp [BinOp
forall a. Bounded a => a
minBound .. BinOp
forall a. Bounded a => a
maxBound]
intrinsicStart :: Int
intrinsicStart = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ VName -> Int
baseTag ((VName, Intrinsic) -> VName
forall a b. (a, b) -> a
fst ((VName, Intrinsic) -> VName) -> (VName, Intrinsic) -> VName
forall a b. (a -> b) -> a -> b
$ [(VName, Intrinsic)] -> (VName, Intrinsic)
forall a. HasCallStack => [a] -> a
last [(VName, Intrinsic)]
primOp)
[VName
a, VName
b, VName
n, VName
m, VName
k, VName
l, VName
p, VName
q] = (Name -> Int -> VName) -> [Name] -> [Int] -> [VName]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Name -> Int -> VName
VName ((FilePath -> Name) -> [FilePath] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Name
nameFromString [FilePath
"a", FilePath
"b", FilePath
"n", FilePath
"m", FilePath
"k", FilePath
"l", FilePath
"p", FilePath
"q"]) [Int
0 ..]
t_a :: u -> ScalarTypeBase dim u
t_a u
u = u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
forall dim u.
u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
TypeVar u
u (VName -> QualName VName
forall v. v -> QualName v
qualName VName
a) []
array_a :: u -> Shape dim -> TypeBase dim u
array_a u
u Shape dim
s = u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array u
u Shape dim
s (ScalarTypeBase dim NoUniqueness -> TypeBase dim u)
-> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase dim NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty
tp_a :: TypeParamBase VName
tp_a = Liftedness -> VName -> SrcLoc -> TypeParamBase VName
forall vn. Liftedness -> vn -> SrcLoc -> TypeParamBase vn
TypeParamType Liftedness
Unlifted VName
a SrcLoc
forall a. Monoid a => a
mempty
t_b :: u -> ScalarTypeBase dim u
t_b u
u = u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
forall dim u.
u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
TypeVar u
u (VName -> QualName VName
forall v. v -> QualName v
qualName VName
b) []
array_b :: u -> Shape dim -> TypeBase dim u
array_b u
u Shape dim
s = u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array u
u Shape dim
s (ScalarTypeBase dim NoUniqueness -> TypeBase dim u)
-> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase dim NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_b NoUniqueness
forall a. Monoid a => a
mempty
tp_b :: TypeParamBase VName
tp_b = Liftedness -> VName -> SrcLoc -> TypeParamBase VName
forall vn. Liftedness -> vn -> SrcLoc -> TypeParamBase vn
TypeParamType Liftedness
Unlifted VName
b SrcLoc
forall a. Monoid a => a
mempty
[TypeParamBase VName
sp_n, TypeParamBase VName
sp_m, TypeParamBase VName
sp_k, TypeParamBase VName
sp_l, TypeParamBase VName
sp_p, TypeParamBase VName
sp_q] = (VName -> TypeParamBase VName) -> [VName] -> [TypeParamBase VName]
forall a b. (a -> b) -> [a] -> [b]
map (VName -> SrcLoc -> TypeParamBase VName
forall vn. vn -> SrcLoc -> TypeParamBase vn
`TypeParamDim` SrcLoc
forall a. Monoid a => a
mempty) [VName
n, VName
m, VName
k, VName
l, VName
p, VName
q]
size :: VName -> ExpBase Info VName
size = (QualName VName -> SrcLoc -> ExpBase Info VName)
-> SrcLoc -> QualName VName -> ExpBase Info VName
forall a b c. (a -> b -> c) -> b -> a -> c
flip QualName VName -> SrcLoc -> ExpBase Info VName
sizeFromName SrcLoc
forall a. Monoid a => a
mempty (QualName VName -> ExpBase Info VName)
-> (VName -> QualName VName) -> VName -> ExpBase Info VName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VName -> QualName VName
forall v. v -> QualName v
qualName
shape :: [VName] -> Shape (ExpBase Info VName)
shape = [ExpBase Info VName] -> Shape (ExpBase Info VName)
forall dim. [dim] -> Shape dim
Shape ([ExpBase Info VName] -> Shape (ExpBase Info VName))
-> ([VName] -> [ExpBase Info VName])
-> [VName]
-> Shape (ExpBase Info VName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VName -> ExpBase Info VName) -> [VName] -> [ExpBase Info VName]
forall a b. (a -> b) -> [a] -> [b]
map VName -> ExpBase Info VName
size
tuple_array :: u
-> TypeBase dim NoUniqueness
-> TypeBase dim NoUniqueness
-> Shape dim
-> TypeBase dim u
tuple_array u
u TypeBase dim NoUniqueness
x TypeBase dim NoUniqueness
y Shape dim
s =
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array u
u Shape dim
s (Map Name (TypeBase dim NoUniqueness)
-> ScalarTypeBase dim NoUniqueness
forall dim u. Map Name (TypeBase dim u) -> ScalarTypeBase dim u
Record ([(Name, TypeBase dim NoUniqueness)]
-> Map Name (TypeBase dim NoUniqueness)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Name, TypeBase dim NoUniqueness)]
-> Map Name (TypeBase dim NoUniqueness))
-> [(Name, TypeBase dim NoUniqueness)]
-> Map Name (TypeBase dim NoUniqueness)
forall a b. (a -> b) -> a -> b
$ [Name]
-> [TypeBase dim NoUniqueness]
-> [(Name, TypeBase dim NoUniqueness)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
tupleFieldNames [TypeBase dim NoUniqueness
x, TypeBase dim NoUniqueness
y]))
arr :: TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
arr TypeBase dim NoUniqueness
x TypeBase dim Uniqueness
y = ScalarTypeBase dim u -> TypeBase dim u
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase dim u -> TypeBase dim u)
-> ScalarTypeBase dim u -> TypeBase dim u
forall a b. (a -> b) -> a -> b
$ u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
forall dim u.
u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
Arrow u
forall a. Monoid a => a
mempty PName
Unnamed Diet
Observe TypeBase dim NoUniqueness
x ([VName] -> TypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [] TypeBase dim Uniqueness
y)
carr :: TypeBase dim NoUniqueness
-> TypeBase dim Uniqueness -> TypeBase dim u
carr TypeBase dim NoUniqueness
x TypeBase dim Uniqueness
y = ScalarTypeBase dim u -> TypeBase dim u
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase dim u -> TypeBase dim u)
-> ScalarTypeBase dim u -> TypeBase dim u
forall a b. (a -> b) -> a -> b
$ u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
forall dim u.
u
-> PName
-> Diet
-> TypeBase dim NoUniqueness
-> RetTypeBase dim Uniqueness
-> ScalarTypeBase dim u
Arrow u
forall a. Monoid a => a
mempty PName
Unnamed Diet
Consume TypeBase dim NoUniqueness
x ([VName] -> TypeBase dim Uniqueness -> RetTypeBase dim Uniqueness
forall dim as. [VName] -> TypeBase dim as -> RetTypeBase dim as
RetType [] TypeBase dim Uniqueness
y)
array_ka :: u -> TypeBase (ExpBase Info VName) u
array_ka u
u = u
-> Shape (ExpBase Info VName)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> TypeBase (ExpBase Info VName) u
forall dim u.
u -> Shape dim -> ScalarTypeBase dim NoUniqueness -> TypeBase dim u
Array u
u ([ExpBase Info VName] -> Shape (ExpBase Info VName)
forall dim. [dim] -> Shape dim
Shape [QualName VName -> SrcLoc -> ExpBase Info VName
sizeFromName (VName -> QualName VName
forall v. v -> QualName v
qualName VName
k) SrcLoc
forall a. Monoid a => a
mempty]) (ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> TypeBase (ExpBase Info VName) u)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness
-> TypeBase (ExpBase Info VName) u
forall a b. (a -> b) -> a -> b
$ NoUniqueness -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall {u} {dim}. u -> ScalarTypeBase dim u
t_a NoUniqueness
forall a. Monoid a => a
mempty
accType :: u -> TypeBase dim NoUniqueness -> ScalarTypeBase dim u
accType u
u TypeBase dim NoUniqueness
t =
u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
forall dim u.
u -> QualName VName -> [TypeArg dim] -> ScalarTypeBase dim u
TypeVar u
u (VName -> QualName VName
forall v. v -> QualName v
qualName ((VName, Intrinsic) -> VName
forall a b. (a, b) -> a
fst (VName, Intrinsic)
intrinsicAcc)) [TypeBase dim NoUniqueness -> TypeArg dim
forall dim. TypeBase dim NoUniqueness -> TypeArg dim
TypeArgType TypeBase dim NoUniqueness
t]
namify :: Int -> (FilePath, b) -> (VName, b)
namify Int
i (FilePath
x, b
y) = (Name -> Int -> VName
VName (FilePath -> Name
nameFromString FilePath
x) Int
i, b
y)
primFun :: (a, ([PrimType], PrimType, c)) -> (a, Intrinsic)
primFun (a
name, ([PrimType]
ts, PrimType
t, c
_)) =
(a
name, [PrimType] -> PrimType -> Intrinsic
IntrinsicMonoFun ((PrimType -> PrimType) -> [PrimType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map PrimType -> PrimType
unPrim [PrimType]
ts) (PrimType -> Intrinsic) -> PrimType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ PrimType -> PrimType
unPrim PrimType
t)
unOpFun :: UnOp -> (FilePath, Intrinsic)
unOpFun UnOp
bop = (UnOp -> FilePath
forall a. Pretty a => a -> FilePath
prettyString UnOp
bop, [PrimType] -> PrimType -> Intrinsic
IntrinsicMonoFun [PrimType
t] PrimType
t)
where
t :: PrimType
t = PrimType -> PrimType
unPrim (PrimType -> PrimType) -> PrimType -> PrimType
forall a b. (a -> b) -> a -> b
$ UnOp -> PrimType
Primitive.unOpType UnOp
bop
binOpFun :: BinOp -> (FilePath, Intrinsic)
binOpFun BinOp
bop = (BinOp -> FilePath
forall a. Pretty a => a -> FilePath
prettyString BinOp
bop, [PrimType] -> PrimType -> Intrinsic
IntrinsicMonoFun [PrimType
t, PrimType
t] PrimType
t)
where
t :: PrimType
t = PrimType -> PrimType
unPrim (PrimType -> PrimType) -> PrimType -> PrimType
forall a b. (a -> b) -> a -> b
$ BinOp -> PrimType
Primitive.binOpType BinOp
bop
cmpOpFun :: CmpOp -> (FilePath, Intrinsic)
cmpOpFun CmpOp
bop = (CmpOp -> FilePath
forall a. Pretty a => a -> FilePath
prettyString CmpOp
bop, [PrimType] -> PrimType -> Intrinsic
IntrinsicMonoFun [PrimType
t, PrimType
t] PrimType
Bool)
where
t :: PrimType
t = PrimType -> PrimType
unPrim (PrimType -> PrimType) -> PrimType -> PrimType
forall a b. (a -> b) -> a -> b
$ CmpOp -> PrimType
Primitive.cmpOpType CmpOp
bop
convOpFun :: ConvOp -> (FilePath, Intrinsic)
convOpFun ConvOp
cop = (ConvOp -> FilePath
forall a. Pretty a => a -> FilePath
prettyString ConvOp
cop, [PrimType] -> PrimType -> Intrinsic
IntrinsicMonoFun [PrimType -> PrimType
unPrim PrimType
ft] (PrimType -> Intrinsic) -> PrimType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ PrimType -> PrimType
unPrim PrimType
tt)
where
(PrimType
ft, PrimType
tt) = ConvOp -> (PrimType, PrimType)
Primitive.convOpType ConvOp
cop
signFun :: IntType -> (FilePath, Intrinsic)
signFun IntType
t = (FilePath
"sign_" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ IntType -> FilePath
forall a. Pretty a => a -> FilePath
prettyString IntType
t, [PrimType] -> PrimType -> Intrinsic
IntrinsicMonoFun [IntType -> PrimType
Unsigned IntType
t] (PrimType -> Intrinsic) -> PrimType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
t)
unsignFun :: IntType -> (FilePath, Intrinsic)
unsignFun IntType
t = (FilePath
"unsign_" FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ IntType -> FilePath
forall a. Pretty a => a -> FilePath
prettyString IntType
t, [PrimType] -> PrimType -> Intrinsic
IntrinsicMonoFun [IntType -> PrimType
Signed IntType
t] (PrimType -> Intrinsic) -> PrimType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Unsigned IntType
t)
unPrim :: PrimType -> PrimType
unPrim (Primitive.IntType IntType
t) = IntType -> PrimType
Signed IntType
t
unPrim (Primitive.FloatType FloatType
t) = FloatType -> PrimType
FloatType FloatType
t
unPrim PrimType
Primitive.Bool = PrimType
Bool
unPrim PrimType
Primitive.Unit = PrimType
Bool
intrinsicPrim :: PrimType -> (FilePath, Intrinsic)
intrinsicPrim PrimType
t = (PrimType -> FilePath
forall a. Pretty a => a -> FilePath
prettyString PrimType
t, Liftedness -> [TypeParamBase VName] -> StructType -> Intrinsic
IntrinsicType Liftedness
Unlifted [] (StructType -> Intrinsic) -> StructType -> Intrinsic
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType)
-> ScalarTypeBase (ExpBase Info VName) NoUniqueness -> StructType
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase (ExpBase Info VName) NoUniqueness
forall dim u. PrimType -> ScalarTypeBase dim u
Prim PrimType
t)
anyIntType :: [PrimType]
anyIntType =
(IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
Signed [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ (IntType -> PrimType) -> [IntType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map IntType -> PrimType
Unsigned [IntType
forall a. Bounded a => a
minBound .. IntType
forall a. Bounded a => a
maxBound]
anyNumberType :: [PrimType]
anyNumberType =
[PrimType]
anyIntType
[PrimType] -> [PrimType] -> [PrimType]
forall a. [a] -> [a] -> [a]
++ (FloatType -> PrimType) -> [FloatType] -> [PrimType]
forall a b. (a -> b) -> [a] -> [b]
map FloatType -> PrimType
FloatType [FloatType
forall a. Bounded a => a
minBound .. FloatType
forall a. Bounded a => a
maxBound]
anyPrimType :: [PrimType]
anyPrimType = PrimType
Bool PrimType -> [PrimType] -> [PrimType]
forall a. a -> [a] -> [a]
: [PrimType]
anyNumberType
mkIntrinsicBinOp :: BinOp -> Maybe (String, Intrinsic)
mkIntrinsicBinOp :: BinOp -> Maybe (FilePath, Intrinsic)
mkIntrinsicBinOp BinOp
op = do
Intrinsic
op' <- BinOp -> Maybe Intrinsic
intrinsicBinOp BinOp
op
(FilePath, Intrinsic) -> Maybe (FilePath, Intrinsic)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BinOp -> FilePath
forall a. Pretty a => a -> FilePath
prettyString BinOp
op, Intrinsic
op')
binOp :: [PrimType] -> Maybe Intrinsic
binOp [PrimType]
ts = Intrinsic -> Maybe Intrinsic
forall a. a -> Maybe a
Just (Intrinsic -> Maybe Intrinsic) -> Intrinsic -> Maybe Intrinsic
forall a b. (a -> b) -> a -> b
$ [PrimType] -> [Maybe PrimType] -> Maybe PrimType -> Intrinsic
IntrinsicOverloadedFun [PrimType]
ts [Maybe PrimType
forall a. Maybe a
Nothing, Maybe PrimType
forall a. Maybe a
Nothing] Maybe PrimType
forall a. Maybe a
Nothing
ordering :: Maybe Intrinsic
ordering = Intrinsic -> Maybe Intrinsic
forall a. a -> Maybe a
Just (Intrinsic -> Maybe Intrinsic) -> Intrinsic -> Maybe Intrinsic
forall a b. (a -> b) -> a -> b
$ [PrimType] -> [Maybe PrimType] -> Maybe PrimType -> Intrinsic
IntrinsicOverloadedFun [PrimType]
anyPrimType [Maybe PrimType
forall a. Maybe a
Nothing, Maybe PrimType
forall a. Maybe a
Nothing] (PrimType -> Maybe PrimType
forall a. a -> Maybe a
Just PrimType
Bool)
intrinsicBinOp :: BinOp -> Maybe Intrinsic
intrinsicBinOp BinOp
Plus = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyNumberType
intrinsicBinOp BinOp
Minus = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyNumberType
intrinsicBinOp BinOp
Pow = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyNumberType
intrinsicBinOp BinOp
Times = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyNumberType
intrinsicBinOp BinOp
Divide = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyNumberType
intrinsicBinOp BinOp
Mod = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyNumberType
intrinsicBinOp BinOp
Quot = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyIntType
intrinsicBinOp BinOp
Rem = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyIntType
intrinsicBinOp BinOp
ShiftR = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyIntType
intrinsicBinOp BinOp
ShiftL = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyIntType
intrinsicBinOp BinOp
Band = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyIntType
intrinsicBinOp BinOp
Xor = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyIntType
intrinsicBinOp BinOp
Bor = [PrimType] -> Maybe Intrinsic
binOp [PrimType]
anyIntType
intrinsicBinOp BinOp
LogAnd = [PrimType] -> Maybe Intrinsic
binOp [PrimType
Bool]
intrinsicBinOp BinOp
LogOr = [PrimType] -> Maybe Intrinsic
binOp [PrimType
Bool]
intrinsicBinOp BinOp
Equal = Intrinsic -> Maybe Intrinsic
forall a. a -> Maybe a
Just Intrinsic
IntrinsicEquality
intrinsicBinOp BinOp
NotEqual = Intrinsic -> Maybe Intrinsic
forall a. a -> Maybe a
Just Intrinsic
IntrinsicEquality
intrinsicBinOp BinOp
Less = Maybe Intrinsic
ordering
intrinsicBinOp BinOp
Leq = Maybe Intrinsic
ordering
intrinsicBinOp BinOp
Greater = Maybe Intrinsic
ordering
intrinsicBinOp BinOp
Geq = Maybe Intrinsic
ordering
intrinsicBinOp BinOp
_ = Maybe Intrinsic
forall a. Maybe a
Nothing
tupInt64 :: Int -> ScalarTypeBase dim u
tupInt64 Int
1 =
PrimType -> ScalarTypeBase dim u
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase dim u)
-> PrimType -> ScalarTypeBase dim u
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64
tupInt64 Int
x =
[TypeBase dim u] -> ScalarTypeBase dim u
forall dim as. [TypeBase dim as] -> ScalarTypeBase dim as
tupleRecord ([TypeBase dim u] -> ScalarTypeBase dim u)
-> [TypeBase dim u] -> ScalarTypeBase dim u
forall a b. (a -> b) -> a -> b
$ Int -> TypeBase dim u -> [TypeBase dim u]
forall a. Int -> a -> [a]
replicate Int
x (TypeBase dim u -> [TypeBase dim u])
-> TypeBase dim u -> [TypeBase dim u]
forall a b. (a -> b) -> a -> b
$ ScalarTypeBase dim u -> TypeBase dim u
forall dim u. ScalarTypeBase dim u -> TypeBase dim u
Scalar (ScalarTypeBase dim u -> TypeBase dim u)
-> ScalarTypeBase dim u -> TypeBase dim u
forall a b. (a -> b) -> a -> b
$ PrimType -> ScalarTypeBase dim u
forall dim u. PrimType -> ScalarTypeBase dim u
Prim (PrimType -> ScalarTypeBase dim u)
-> PrimType -> ScalarTypeBase dim u
forall a b. (a -> b) -> a -> b
$ IntType -> PrimType
Signed IntType
Int64
isBuiltin :: FilePath -> Bool
isBuiltin :: FilePath -> Bool
isBuiltin = (FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"/prelude") (FilePath -> Bool) -> ShowS -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
takeDirectory
isBuiltinLoc :: (Located a) => a -> Bool
isBuiltinLoc :: forall a. Located a => a -> Bool
isBuiltinLoc a
x =
case a -> Loc
forall a. Located a => a -> Loc
locOf a
x of
Loc
NoLoc -> Bool
False
Loc Pos
pos Pos
_ -> FilePath -> Bool
isBuiltin (FilePath -> Bool) -> FilePath -> Bool
forall a b. (a -> b) -> a -> b
$ Pos -> FilePath
posFile Pos
pos
maxIntrinsicTag :: Int
maxIntrinsicTag :: Int
maxIntrinsicTag = [Int] -> Int
forall a (f :: * -> *). (Num a, Ord a, Foldable f) => f a -> a
maxinum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (VName -> Int) -> [VName] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map VName -> Int
baseTag ([VName] -> [Int]) -> [VName] -> [Int]
forall a b. (a -> b) -> a -> b
$ Map VName Intrinsic -> [VName]
forall k a. Map k a -> [k]
M.keys Map VName Intrinsic
intrinsics
qualName :: v -> QualName v
qualName :: forall v. v -> QualName v
qualName = [v] -> v -> QualName v
forall vn. [vn] -> vn -> QualName vn
QualName []
qualify :: v -> QualName v -> QualName v
qualify :: forall v. v -> QualName v -> QualName v
qualify v
k (QualName [v]
ks v
v) = [v] -> v -> QualName v
forall vn. [vn] -> vn -> QualName vn
QualName (v
k v -> [v] -> [v]
forall a. a -> [a] -> [a]
: [v]
ks) v
v
progImports :: ProgBase f vn -> [(String, Loc)]
progImports :: forall (f :: * -> *) vn. ProgBase f vn -> [(FilePath, Loc)]
progImports = (DecBase f vn -> [(FilePath, Loc)])
-> [DecBase f vn] -> [(FilePath, Loc)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap DecBase f vn -> [(FilePath, Loc)]
forall (f :: * -> *) vn. DecBase f vn -> [(FilePath, Loc)]
decImports ([DecBase f vn] -> [(FilePath, Loc)])
-> (ProgBase f vn -> [DecBase f vn])
-> ProgBase f vn
-> [(FilePath, Loc)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgBase f vn -> [DecBase f vn]
forall (f :: * -> *) vn. ProgBase f vn -> [DecBase f vn]
progDecs
decImports :: DecBase f vn -> [(String, Loc)]
decImports :: forall (f :: * -> *) vn. DecBase f vn -> [(FilePath, Loc)]
decImports (OpenDec ModExpBase f vn
x SrcLoc
_) = ModExpBase f vn -> [(FilePath, Loc)]
forall (f :: * -> *) vn. ModExpBase f vn -> [(FilePath, Loc)]
modExpImports ModExpBase f vn
x
decImports (ModDec ModBindBase f vn
md) = ModExpBase f vn -> [(FilePath, Loc)]
forall (f :: * -> *) vn. ModExpBase f vn -> [(FilePath, Loc)]
modExpImports (ModExpBase f vn -> [(FilePath, Loc)])
-> ModExpBase f vn -> [(FilePath, Loc)]
forall a b. (a -> b) -> a -> b
$ ModBindBase f vn -> ModExpBase f vn
forall (f :: * -> *) vn. ModBindBase f vn -> ModExpBase f vn
modExp ModBindBase f vn
md
decImports ModTypeDec {} = []
decImports TypeDec {} = []
decImports ValDec {} = []
decImports (LocalDec DecBase f vn
d SrcLoc
_) = DecBase f vn -> [(FilePath, Loc)]
forall (f :: * -> *) vn. DecBase f vn -> [(FilePath, Loc)]
decImports DecBase f vn
d
decImports (ImportDec FilePath
x f ImportName
_ SrcLoc
loc) = [(FilePath
x, SrcLoc -> Loc
forall a. Located a => a -> Loc
locOf SrcLoc
loc)]
modExpImports :: ModExpBase f vn -> [(String, Loc)]
modExpImports :: forall (f :: * -> *) vn. ModExpBase f vn -> [(FilePath, Loc)]
modExpImports ModVar {} = []
modExpImports (ModParens ModExpBase f vn
p SrcLoc
_) = ModExpBase f vn -> [(FilePath, Loc)]
forall (f :: * -> *) vn. ModExpBase f vn -> [(FilePath, Loc)]
modExpImports ModExpBase f vn
p
modExpImports (ModImport FilePath
f f ImportName
_ SrcLoc
loc) = [(FilePath
f, SrcLoc -> Loc
forall a. Located a => a -> Loc
locOf SrcLoc
loc)]
modExpImports (ModDecs [DecBase f vn]
ds SrcLoc
_) = (DecBase f vn -> [(FilePath, Loc)])
-> [DecBase f vn] -> [(FilePath, Loc)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap DecBase f vn -> [(FilePath, Loc)]
forall (f :: * -> *) vn. DecBase f vn -> [(FilePath, Loc)]
decImports [DecBase f vn]
ds
modExpImports (ModApply ModExpBase f vn
_ ModExpBase f vn
me f (Map VName VName)
_ f (Map VName VName)
_ SrcLoc
_) = ModExpBase f vn -> [(FilePath, Loc)]
forall (f :: * -> *) vn. ModExpBase f vn -> [(FilePath, Loc)]
modExpImports ModExpBase f vn
me
modExpImports (ModAscript ModExpBase f vn
me ModTypeExpBase f vn
_ f (Map VName VName)
_ SrcLoc
_) = ModExpBase f vn -> [(FilePath, Loc)]
forall (f :: * -> *) vn. ModExpBase f vn -> [(FilePath, Loc)]
modExpImports ModExpBase f vn
me
modExpImports ModLambda {} = []
progModuleTypes :: ProgBase Info VName -> S.Set VName
progModuleTypes :: ProgBase Info VName -> Set VName
progModuleTypes ProgBase Info VName
prog = (VName -> Set VName) -> Set VName -> Set VName
forall m a. Monoid m => (a -> m) -> Set a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap VName -> Set VName
reach Set VName
mtypes_used
where
reach :: VName -> Set VName
reach VName
v = VName -> Set VName
forall a. a -> Set a
S.singleton VName
v Set VName -> Set VName -> Set VName
forall a. Semigroup a => a -> a -> a
<> Set VName
-> (Set VName -> Set VName) -> Maybe (Set VName) -> Set VName
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Set VName
forall a. Monoid a => a
mempty ((VName -> Set VName) -> Set VName -> Set VName
forall m a. Monoid m => (a -> m) -> Set a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap VName -> Set VName
reach) (VName -> Map VName (Set VName) -> Maybe (Set VName)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup VName
v Map VName (Set VName)
reachable_from_mtype)
reachable_from_mtype :: Map VName (Set VName)
reachable_from_mtype = (DecBase Info VName -> Map VName (Set VName))
-> [DecBase Info VName] -> Map VName (Set VName)
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap DecBase Info VName -> Map VName (Set VName)
forall {a} {f :: * -> *}. Ord a => DecBase f a -> Map a (Set a)
onDec ([DecBase Info VName] -> Map VName (Set VName))
-> [DecBase Info VName] -> Map VName (Set VName)
forall a b. (a -> b) -> a -> b
$ ProgBase Info VName -> [DecBase Info VName]
forall (f :: * -> *) vn. ProgBase f vn -> [DecBase f vn]
progDecs ProgBase Info VName
prog
where
onDec :: DecBase f a -> Map a (Set a)
onDec OpenDec {} = Map a (Set a)
forall a. Monoid a => a
mempty
onDec ModDec {} = Map a (Set a)
forall a. Monoid a => a
mempty
onDec (ModTypeDec ModTypeBindBase f a
sb) =
a -> Set a -> Map a (Set a)
forall k a. k -> a -> Map k a
M.singleton (ModTypeBindBase f a -> a
forall (f :: * -> *) vn. ModTypeBindBase f vn -> vn
modTypeName ModTypeBindBase f a
sb) (ModTypeExpBase f a -> Set a
forall {a} {f :: * -> *}. Ord a => ModTypeExpBase f a -> Set a
onModTypeExp (ModTypeBindBase f a -> ModTypeExpBase f a
forall (f :: * -> *) vn.
ModTypeBindBase f vn -> ModTypeExpBase f vn
modTypeExp ModTypeBindBase f a
sb))
onDec TypeDec {} = Map a (Set a)
forall a. Monoid a => a
mempty
onDec ValDec {} = Map a (Set a)
forall a. Monoid a => a
mempty
onDec (LocalDec DecBase f a
d SrcLoc
_) = DecBase f a -> Map a (Set a)
onDec DecBase f a
d
onDec ImportDec {} = Map a (Set a)
forall a. Monoid a => a
mempty
onModTypeExp :: ModTypeExpBase f a -> Set a
onModTypeExp (ModTypeVar QualName a
v f (Map VName VName)
_ SrcLoc
_) = a -> Set a
forall a. a -> Set a
S.singleton (a -> Set a) -> a -> Set a
forall a b. (a -> b) -> a -> b
$ QualName a -> a
forall vn. QualName vn -> vn
qualLeaf QualName a
v
onModTypeExp (ModTypeParens ModTypeExpBase f a
e SrcLoc
_) = ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e
onModTypeExp (ModTypeSpecs [SpecBase f a]
ss SrcLoc
_) = (SpecBase f a -> Set a) -> [SpecBase f a] -> Set a
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap SpecBase f a -> Set a
onSpec [SpecBase f a]
ss
onModTypeExp (ModTypeWith ModTypeExpBase f a
e TypeRefBase f a
_ SrcLoc
_) = ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e
onModTypeExp (ModTypeArrow Maybe a
_ ModTypeExpBase f a
e1 ModTypeExpBase f a
e2 SrcLoc
_) = ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e1 Set a -> Set a -> Set a
forall a. Semigroup a => a -> a -> a
<> ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e2
onSpec :: SpecBase f a -> Set a
onSpec ValSpec {} = Set a
forall a. Monoid a => a
mempty
onSpec TypeSpec {} = Set a
forall a. Monoid a => a
mempty
onSpec TypeAbbrSpec {} = Set a
forall a. Monoid a => a
mempty
onSpec (ModSpec a
vn ModTypeExpBase f a
e Maybe DocComment
_ SrcLoc
_) = a -> Set a
forall a. a -> Set a
S.singleton a
vn Set a -> Set a -> Set a
forall a. Semigroup a => a -> a -> a
<> ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e
onSpec (IncludeSpec ModTypeExpBase f a
e SrcLoc
_) = ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e
mtypes_used :: Set VName
mtypes_used = (DecBase Info VName -> Set VName)
-> [DecBase Info VName] -> Set VName
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap DecBase Info VName -> Set VName
forall {f :: * -> *}. DecBase f VName -> Set VName
onDec ([DecBase Info VName] -> Set VName)
-> [DecBase Info VName] -> Set VName
forall a b. (a -> b) -> a -> b
$ ProgBase Info VName -> [DecBase Info VName]
forall (f :: * -> *) vn. ProgBase f vn -> [DecBase f vn]
progDecs ProgBase Info VName
prog
where
onDec :: DecBase f VName -> Set VName
onDec (OpenDec ModExpBase f VName
x SrcLoc
_) = ModExpBase f VName -> Set VName
onModExp ModExpBase f VName
x
onDec (ModDec ModBindBase f VName
md) =
Set VName
-> ((ModTypeExpBase f VName, f (Map VName VName)) -> Set VName)
-> Maybe (ModTypeExpBase f VName, f (Map VName VName))
-> Set VName
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Set VName
forall a. Monoid a => a
mempty (ModTypeExpBase f VName -> Set VName
forall {a} {f :: * -> *}. Ord a => ModTypeExpBase f a -> Set a
onModTypeExp (ModTypeExpBase f VName -> Set VName)
-> ((ModTypeExpBase f VName, f (Map VName VName))
-> ModTypeExpBase f VName)
-> (ModTypeExpBase f VName, f (Map VName VName))
-> Set VName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModTypeExpBase f VName, f (Map VName VName))
-> ModTypeExpBase f VName
forall a b. (a, b) -> a
fst) (ModBindBase f VName
-> Maybe (ModTypeExpBase f VName, f (Map VName VName))
forall (f :: * -> *) vn.
ModBindBase f vn
-> Maybe (ModTypeExpBase f vn, f (Map VName VName))
modType ModBindBase f VName
md) Set VName -> Set VName -> Set VName
forall a. Semigroup a => a -> a -> a
<> ModExpBase f VName -> Set VName
onModExp (ModBindBase f VName -> ModExpBase f VName
forall (f :: * -> *) vn. ModBindBase f vn -> ModExpBase f vn
modExp ModBindBase f VName
md)
onDec ModTypeDec {} = Set VName
forall a. Monoid a => a
mempty
onDec TypeDec {} = Set VName
forall a. Monoid a => a
mempty
onDec ValDec {} = Set VName
forall a. Monoid a => a
mempty
onDec LocalDec {} = Set VName
forall a. Monoid a => a
mempty
onDec ImportDec {} = Set VName
forall a. Monoid a => a
mempty
onModExp :: ModExpBase f VName -> Set VName
onModExp ModVar {} = Set VName
forall a. Monoid a => a
mempty
onModExp (ModParens ModExpBase f VName
p SrcLoc
_) = ModExpBase f VName -> Set VName
onModExp ModExpBase f VName
p
onModExp ModImport {} = Set VName
forall a. Monoid a => a
mempty
onModExp (ModDecs [DecBase f VName]
ds SrcLoc
_) = [Set VName] -> Set VName
forall a. Monoid a => [a] -> a
mconcat ([Set VName] -> Set VName) -> [Set VName] -> Set VName
forall a b. (a -> b) -> a -> b
$ (DecBase f VName -> Set VName) -> [DecBase f VName] -> [Set VName]
forall a b. (a -> b) -> [a] -> [b]
map DecBase f VName -> Set VName
onDec [DecBase f VName]
ds
onModExp (ModApply ModExpBase f VName
me1 ModExpBase f VName
me2 f (Map VName VName)
_ f (Map VName VName)
_ SrcLoc
_) = ModExpBase f VName -> Set VName
onModExp ModExpBase f VName
me1 Set VName -> Set VName -> Set VName
forall a. Semigroup a => a -> a -> a
<> ModExpBase f VName -> Set VName
onModExp ModExpBase f VName
me2
onModExp (ModAscript ModExpBase f VName
me ModTypeExpBase f VName
se f (Map VName VName)
_ SrcLoc
_) = ModExpBase f VName -> Set VName
onModExp ModExpBase f VName
me Set VName -> Set VName -> Set VName
forall a. Semigroup a => a -> a -> a
<> ModTypeExpBase f VName -> Set VName
forall {a} {f :: * -> *}. Ord a => ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f VName
se
onModExp (ModLambda ModParamBase f VName
p Maybe (ModTypeExpBase f VName, f (Map VName VName))
r ModExpBase f VName
me SrcLoc
_) =
ModParamBase f VName -> Set VName
forall {f :: * -> *}. ModParamBase f VName -> Set VName
onModParam ModParamBase f VName
p Set VName -> Set VName -> Set VName
forall a. Semigroup a => a -> a -> a
<> Set VName
-> ((ModTypeExpBase f VName, f (Map VName VName)) -> Set VName)
-> Maybe (ModTypeExpBase f VName, f (Map VName VName))
-> Set VName
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Set VName
forall a. Monoid a => a
mempty (ModTypeExpBase f VName -> Set VName
forall {a} {f :: * -> *}. Ord a => ModTypeExpBase f a -> Set a
onModTypeExp (ModTypeExpBase f VName -> Set VName)
-> ((ModTypeExpBase f VName, f (Map VName VName))
-> ModTypeExpBase f VName)
-> (ModTypeExpBase f VName, f (Map VName VName))
-> Set VName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModTypeExpBase f VName, f (Map VName VName))
-> ModTypeExpBase f VName
forall a b. (a, b) -> a
fst) Maybe (ModTypeExpBase f VName, f (Map VName VName))
r Set VName -> Set VName -> Set VName
forall a. Semigroup a => a -> a -> a
<> ModExpBase f VName -> Set VName
onModExp ModExpBase f VName
me
onModParam :: ModParamBase f VName -> Set VName
onModParam = ModTypeExpBase f VName -> Set VName
forall {a} {f :: * -> *}. Ord a => ModTypeExpBase f a -> Set a
onModTypeExp (ModTypeExpBase f VName -> Set VName)
-> (ModParamBase f VName -> ModTypeExpBase f VName)
-> ModParamBase f VName
-> Set VName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModParamBase f VName -> ModTypeExpBase f VName
forall (f :: * -> *) vn. ModParamBase f vn -> ModTypeExpBase f vn
modParamType
onModTypeExp :: ModTypeExpBase f a -> Set a
onModTypeExp (ModTypeVar QualName a
v f (Map VName VName)
_ SrcLoc
_) = a -> Set a
forall a. a -> Set a
S.singleton (a -> Set a) -> a -> Set a
forall a b. (a -> b) -> a -> b
$ QualName a -> a
forall vn. QualName vn -> vn
qualLeaf QualName a
v
onModTypeExp (ModTypeParens ModTypeExpBase f a
e SrcLoc
_) = ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e
onModTypeExp ModTypeSpecs {} = Set a
forall a. Monoid a => a
mempty
onModTypeExp (ModTypeWith ModTypeExpBase f a
e TypeRefBase f a
_ SrcLoc
_) = ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e
onModTypeExp (ModTypeArrow Maybe a
_ ModTypeExpBase f a
e1 ModTypeExpBase f a
e2 SrcLoc
_) = ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e1 Set a -> Set a -> Set a
forall a. Semigroup a => a -> a -> a
<> ModTypeExpBase f a -> Set a
onModTypeExp ModTypeExpBase f a
e2
identifierReference :: String -> Maybe ((String, String, Maybe FilePath), String)
identifierReference :: FilePath -> Maybe ((FilePath, FilePath, Maybe FilePath), FilePath)
identifierReference (Char
'`' : FilePath
s)
| (FilePath
identifier, Char
'`' : Char
'@' : FilePath
s') <- (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'`') FilePath
s,
(FilePath
namespace, FilePath
s'') <- (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isAlpha FilePath
s',
Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
namespace =
case FilePath
s'' of
Char
'@' : Char
'"' : FilePath
s'''
| (FilePath
file, Char
'"' : FilePath
s'''') <- (Char -> Bool) -> FilePath -> (FilePath, FilePath)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'"') FilePath
s''' ->
((FilePath, FilePath, Maybe FilePath), FilePath)
-> Maybe ((FilePath, FilePath, Maybe FilePath), FilePath)
forall a. a -> Maybe a
Just ((FilePath
identifier, FilePath
namespace, FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
file), FilePath
s'''')
FilePath
_ -> ((FilePath, FilePath, Maybe FilePath), FilePath)
-> Maybe ((FilePath, FilePath, Maybe FilePath), FilePath)
forall a. a -> Maybe a
Just ((FilePath
identifier, FilePath
namespace, Maybe FilePath
forall a. Maybe a
Nothing), FilePath
s'')
identifierReference FilePath
_ = Maybe ((FilePath, FilePath, Maybe FilePath), FilePath)
forall a. Maybe a
Nothing
leadingOperator :: Name -> BinOp
leadingOperator :: Name -> BinOp
leadingOperator Name
s =
BinOp
-> ((FilePath, BinOp) -> BinOp) -> Maybe (FilePath, BinOp) -> BinOp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe BinOp
Backtick (FilePath, BinOp) -> BinOp
forall a b. (a, b) -> b
snd (Maybe (FilePath, BinOp) -> BinOp)
-> Maybe (FilePath, BinOp) -> BinOp
forall a b. (a -> b) -> a -> b
$
((FilePath, BinOp) -> Bool)
-> [(FilePath, BinOp)] -> Maybe (FilePath, BinOp)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
s') (FilePath -> Bool)
-> ((FilePath, BinOp) -> FilePath) -> (FilePath, BinOp) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath, BinOp) -> FilePath
forall a b. (a, b) -> a
fst) ([(FilePath, BinOp)] -> Maybe (FilePath, BinOp))
-> [(FilePath, BinOp)] -> Maybe (FilePath, BinOp)
forall a b. (a -> b) -> a -> b
$
((FilePath, BinOp) -> Down Int)
-> [(FilePath, BinOp)] -> [(FilePath, BinOp)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (Int -> Down Int
forall a. a -> Down a
Down (Int -> Down Int)
-> ((FilePath, BinOp) -> Int) -> (FilePath, BinOp) -> Down Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (FilePath -> Int)
-> ((FilePath, BinOp) -> FilePath) -> (FilePath, BinOp) -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath, BinOp) -> FilePath
forall a b. (a, b) -> a
fst) ([(FilePath, BinOp)] -> [(FilePath, BinOp)])
-> [(FilePath, BinOp)] -> [(FilePath, BinOp)]
forall a b. (a -> b) -> a -> b
$
[FilePath] -> [BinOp] -> [(FilePath, BinOp)]
forall a b. [a] -> [b] -> [(a, b)]
zip ((BinOp -> FilePath) -> [BinOp] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map BinOp -> FilePath
forall a. Pretty a => a -> FilePath
prettyString [BinOp]
operators) [BinOp]
operators
where
s' :: FilePath
s' = Name -> FilePath
nameToString Name
s
operators :: [BinOp]
operators :: [BinOp]
operators = [BinOp
forall a. Bounded a => a
minBound .. BinOp
forall a. Bounded a => a
maxBound :: BinOp]
progHoles :: ProgBase Info VName -> [(Loc, StructType)]
progHoles :: ProgBase Info VName -> [(Loc, StructType)]
progHoles = (DecBase Info VName -> [(Loc, StructType)])
-> [DecBase Info VName] -> [(Loc, StructType)]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap DecBase Info VName -> [(Loc, StructType)]
holesInDec ([DecBase Info VName] -> [(Loc, StructType)])
-> (ProgBase Info VName -> [DecBase Info VName])
-> ProgBase Info VName
-> [(Loc, StructType)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgBase Info VName -> [DecBase Info VName]
forall (f :: * -> *) vn. ProgBase f vn -> [DecBase f vn]
progDecs
where
holesInDec :: DecBase Info VName -> [(Loc, StructType)]
holesInDec (ValDec ValBindBase Info VName
vb) = ExpBase Info VName -> [(Loc, StructType)]
holesInExp (ExpBase Info VName -> [(Loc, StructType)])
-> ExpBase Info VName -> [(Loc, StructType)]
forall a b. (a -> b) -> a -> b
$ ValBindBase Info VName -> ExpBase Info VName
forall (f :: * -> *) vn. ValBindBase f vn -> ExpBase f vn
valBindBody ValBindBase Info VName
vb
holesInDec (ModDec ModBindBase Info VName
me) = ModExpBase Info VName -> [(Loc, StructType)]
holesInModExp (ModExpBase Info VName -> [(Loc, StructType)])
-> ModExpBase Info VName -> [(Loc, StructType)]
forall a b. (a -> b) -> a -> b
$ ModBindBase Info VName -> ModExpBase Info VName
forall (f :: * -> *) vn. ModBindBase f vn -> ModExpBase f vn
modExp ModBindBase Info VName
me
holesInDec (OpenDec ModExpBase Info VName
me SrcLoc
_) = ModExpBase Info VName -> [(Loc, StructType)]
holesInModExp ModExpBase Info VName
me
holesInDec (LocalDec DecBase Info VName
d SrcLoc
_) = DecBase Info VName -> [(Loc, StructType)]
holesInDec DecBase Info VName
d
holesInDec TypeDec {} = [(Loc, StructType)]
forall a. Monoid a => a
mempty
holesInDec ModTypeDec {} = [(Loc, StructType)]
forall a. Monoid a => a
mempty
holesInDec ImportDec {} = [(Loc, StructType)]
forall a. Monoid a => a
mempty
holesInModExp :: ModExpBase Info VName -> [(Loc, StructType)]
holesInModExp (ModDecs [DecBase Info VName]
ds SrcLoc
_) = (DecBase Info VName -> [(Loc, StructType)])
-> [DecBase Info VName] -> [(Loc, StructType)]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap DecBase Info VName -> [(Loc, StructType)]
holesInDec [DecBase Info VName]
ds
holesInModExp (ModParens ModExpBase Info VName
me SrcLoc
_) = ModExpBase Info VName -> [(Loc, StructType)]
holesInModExp ModExpBase Info VName
me
holesInModExp (ModApply ModExpBase Info VName
x ModExpBase Info VName
y Info (Map VName VName)
_ Info (Map VName VName)
_ SrcLoc
_) = ModExpBase Info VName -> [(Loc, StructType)]
holesInModExp ModExpBase Info VName
x [(Loc, StructType)] -> [(Loc, StructType)] -> [(Loc, StructType)]
forall a. Semigroup a => a -> a -> a
<> ModExpBase Info VName -> [(Loc, StructType)]
holesInModExp ModExpBase Info VName
y
holesInModExp (ModAscript ModExpBase Info VName
me ModTypeExpBase Info VName
_ Info (Map VName VName)
_ SrcLoc
_) = ModExpBase Info VName -> [(Loc, StructType)]
holesInModExp ModExpBase Info VName
me
holesInModExp (ModLambda ModParamBase Info VName
_ Maybe (ModTypeExpBase Info VName, Info (Map VName VName))
_ ModExpBase Info VName
me SrcLoc
_) = ModExpBase Info VName -> [(Loc, StructType)]
holesInModExp ModExpBase Info VName
me
holesInModExp ModVar {} = [(Loc, StructType)]
forall a. Monoid a => a
mempty
holesInModExp ModImport {} = [(Loc, StructType)]
forall a. Monoid a => a
mempty
holesInExp :: ExpBase Info VName -> [(Loc, StructType)]
holesInExp = (State [(Loc, StructType)] (ExpBase Info VName)
-> [(Loc, StructType)] -> [(Loc, StructType)])
-> [(Loc, StructType)]
-> State [(Loc, StructType)] (ExpBase Info VName)
-> [(Loc, StructType)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip State [(Loc, StructType)] (ExpBase Info VName)
-> [(Loc, StructType)] -> [(Loc, StructType)]
forall s a. State s a -> s -> s
execState [(Loc, StructType)]
forall a. Monoid a => a
mempty (State [(Loc, StructType)] (ExpBase Info VName)
-> [(Loc, StructType)])
-> (ExpBase Info VName
-> State [(Loc, StructType)] (ExpBase Info VName))
-> ExpBase Info VName
-> [(Loc, StructType)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExpBase Info VName
-> State [(Loc, StructType)] (ExpBase Info VName)
forall {m :: * -> *}.
MonadState [(Loc, StructType)] m =>
ExpBase Info VName -> m (ExpBase Info VName)
onExp
onExp :: ExpBase Info VName -> m (ExpBase Info VName)
onExp e :: ExpBase Info VName
e@(Hole (Info StructType
t) SrcLoc
loc) = do
([(Loc, StructType)] -> [(Loc, StructType)]) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((SrcLoc -> Loc
forall a. Located a => a -> Loc
locOf SrcLoc
loc, StructType -> StructType
forall dim u. TypeBase dim u -> TypeBase dim NoUniqueness
toStruct StructType
t) :)
ExpBase Info VName -> m (ExpBase Info VName)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExpBase Info VName
e
onExp ExpBase Info VName
e = ASTMapper m -> ExpBase Info VName -> m (ExpBase Info VName)
forall x (m :: * -> *).
(ASTMappable x, Monad m) =>
ASTMapper m -> x -> m x
forall (m :: * -> *).
Monad m =>
ASTMapper m -> ExpBase Info VName -> m (ExpBase Info VName)
astMap (ASTMapper m
forall (m :: * -> *). Monad m => ASTMapper m
identityMapper {mapOnExp = onExp}) ExpBase Info VName
e
stripExp :: Exp -> Maybe Exp
stripExp :: ExpBase Info VName -> Maybe (ExpBase Info VName)
stripExp (Parens ExpBase Info VName
e SrcLoc
_) = ExpBase Info VName -> Maybe (ExpBase Info VName)
stripExp ExpBase Info VName
e Maybe (ExpBase Info VName)
-> Maybe (ExpBase Info VName) -> Maybe (ExpBase Info VName)
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` ExpBase Info VName -> Maybe (ExpBase Info VName)
forall a. a -> Maybe a
Just ExpBase Info VName
e
stripExp (Assert ExpBase Info VName
_ ExpBase Info VName
e Info Text
_ SrcLoc
_) = ExpBase Info VName -> Maybe (ExpBase Info VName)
stripExp ExpBase Info VName
e Maybe (ExpBase Info VName)
-> Maybe (ExpBase Info VName) -> Maybe (ExpBase Info VName)
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` ExpBase Info VName -> Maybe (ExpBase Info VName)
forall a. a -> Maybe a
Just ExpBase Info VName
e
stripExp (Attr AttrInfo VName
_ ExpBase Info VName
e SrcLoc
_) = ExpBase Info VName -> Maybe (ExpBase Info VName)
stripExp ExpBase Info VName
e Maybe (ExpBase Info VName)
-> Maybe (ExpBase Info VName) -> Maybe (ExpBase Info VName)
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` ExpBase Info VName -> Maybe (ExpBase Info VName)
forall a. a -> Maybe a
Just ExpBase Info VName
e
stripExp (Ascript ExpBase Info VName
e TypeExp Info VName
_ SrcLoc
_) = ExpBase Info VName -> Maybe (ExpBase Info VName)
stripExp ExpBase Info VName
e Maybe (ExpBase Info VName)
-> Maybe (ExpBase Info VName) -> Maybe (ExpBase Info VName)
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` ExpBase Info VName -> Maybe (ExpBase Info VName)
forall a. a -> Maybe a
Just ExpBase Info VName
e
stripExp ExpBase Info VName
_ = Maybe (ExpBase Info VName)
forall a. Maybe a
Nothing
similarSlices :: Slice -> Slice -> Maybe [(Exp, Exp)]
similarSlices :: SliceBase Info VName
-> SliceBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
similarSlices SliceBase Info VName
slice1 SliceBase Info VName
slice2
| SliceBase Info VName -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length SliceBase Info VName
slice1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== SliceBase Info VName -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length SliceBase Info VName
slice2 = do
[[(ExpBase Info VName, ExpBase Info VName)]]
-> [(ExpBase Info VName, ExpBase Info VName)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(ExpBase Info VName, ExpBase Info VName)]]
-> [(ExpBase Info VName, ExpBase Info VName)])
-> Maybe [[(ExpBase Info VName, ExpBase Info VName)]]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DimIndexBase Info VName
-> DimIndexBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)])
-> SliceBase Info VName
-> SliceBase Info VName
-> Maybe [[(ExpBase Info VName, ExpBase Info VName)]]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM DimIndexBase Info VName
-> DimIndexBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall {f :: * -> *} {vn} {f :: * -> *} {vn}.
DimIndexBase f vn
-> DimIndexBase f vn -> Maybe [(ExpBase f vn, ExpBase f vn)]
match SliceBase Info VName
slice1 SliceBase Info VName
slice2
| Bool
otherwise = Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. Maybe a
Nothing
where
match :: DimIndexBase f vn
-> DimIndexBase f vn -> Maybe [(ExpBase f vn, ExpBase f vn)]
match (DimFix ExpBase f vn
e1) (DimFix ExpBase f vn
e2) = [(ExpBase f vn, ExpBase f vn)]
-> Maybe [(ExpBase f vn, ExpBase f vn)]
forall a. a -> Maybe a
Just [(ExpBase f vn
e1, ExpBase f vn
e2)]
match (DimSlice Maybe (ExpBase f vn)
a1 Maybe (ExpBase f vn)
b1 Maybe (ExpBase f vn)
c1) (DimSlice Maybe (ExpBase f vn)
a2 Maybe (ExpBase f vn)
b2 Maybe (ExpBase f vn)
c2) =
[[(ExpBase f vn, ExpBase f vn)]] -> [(ExpBase f vn, ExpBase f vn)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(ExpBase f vn, ExpBase f vn)]]
-> [(ExpBase f vn, ExpBase f vn)])
-> Maybe [[(ExpBase f vn, ExpBase f vn)]]
-> Maybe [(ExpBase f vn, ExpBase f vn)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Maybe [(ExpBase f vn, ExpBase f vn)]]
-> Maybe [[(ExpBase f vn, ExpBase f vn)]]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [(Maybe (ExpBase f vn), Maybe (ExpBase f vn))
-> Maybe [(ExpBase f vn, ExpBase f vn)]
forall {a} {b}. (Maybe a, Maybe b) -> Maybe [(a, b)]
pair (Maybe (ExpBase f vn)
a1, Maybe (ExpBase f vn)
a2), (Maybe (ExpBase f vn), Maybe (ExpBase f vn))
-> Maybe [(ExpBase f vn, ExpBase f vn)]
forall {a} {b}. (Maybe a, Maybe b) -> Maybe [(a, b)]
pair (Maybe (ExpBase f vn)
b1, Maybe (ExpBase f vn)
b2), (Maybe (ExpBase f vn), Maybe (ExpBase f vn))
-> Maybe [(ExpBase f vn, ExpBase f vn)]
forall {a} {b}. (Maybe a, Maybe b) -> Maybe [(a, b)]
pair (Maybe (ExpBase f vn)
c1, Maybe (ExpBase f vn)
c2)]
match DimIndexBase f vn
_ DimIndexBase f vn
_ = Maybe [(ExpBase f vn, ExpBase f vn)]
forall a. Maybe a
Nothing
pair :: (Maybe a, Maybe b) -> Maybe [(a, b)]
pair (Maybe a
Nothing, Maybe b
Nothing) = [(a, b)] -> Maybe [(a, b)]
forall a. a -> Maybe a
Just []
pair (Just a
x, Just b
y) = [(a, b)] -> Maybe [(a, b)]
forall a. a -> Maybe a
Just [(a
x, b
y)]
pair (Maybe a, Maybe b)
_ = Maybe [(a, b)]
forall a. Maybe a
Nothing
similarExps :: Exp -> Exp -> Maybe [(Exp, Exp)]
similarExps :: ExpBase Info VName
-> ExpBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
similarExps ExpBase Info VName
e1 ExpBase Info VName
e2 | ExpBase Info VName -> ExpBase NoInfo VName
bareExp ExpBase Info VName
e1 ExpBase NoInfo VName -> ExpBase NoInfo VName -> Bool
forall a. Eq a => a -> a -> Bool
== ExpBase Info VName -> ExpBase NoInfo VName
bareExp ExpBase Info VName
e2 = [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just []
similarExps ExpBase Info VName
e1 ExpBase Info VName
e2 | Just ExpBase Info VName
e1' <- ExpBase Info VName -> Maybe (ExpBase Info VName)
stripExp ExpBase Info VName
e1 = ExpBase Info VName
-> ExpBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
similarExps ExpBase Info VName
e1' ExpBase Info VName
e2
similarExps ExpBase Info VName
e1 ExpBase Info VName
e2 | Just ExpBase Info VName
e2' <- ExpBase Info VName -> Maybe (ExpBase Info VName)
stripExp ExpBase Info VName
e2 = ExpBase Info VName
-> ExpBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
similarExps ExpBase Info VName
e1 ExpBase Info VName
e2'
similarExps
(AppExp (BinOp (QualName VName
op1, SrcLoc
_) Info StructType
_ (ExpBase Info VName
x1, Info (Maybe VName)
_) (ExpBase Info VName
y1, Info (Maybe VName)
_) SrcLoc
_) Info AppRes
_)
(AppExp (BinOp (QualName VName
op2, SrcLoc
_) Info StructType
_ (ExpBase Info VName
x2, Info (Maybe VName)
_) (ExpBase Info VName
y2, Info (Maybe VName)
_) SrcLoc
_) Info AppRes
_)
| QualName VName
op1 QualName VName -> QualName VName -> Bool
forall a. Eq a => a -> a -> Bool
== QualName VName
op2 = [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just [(ExpBase Info VName
x1, ExpBase Info VName
x2), (ExpBase Info VName
y1, ExpBase Info VName
y2)]
similarExps (AppExp (Apply ExpBase Info VName
f1 NonEmpty (Info (Diet, Maybe VName), ExpBase Info VName)
args1 SrcLoc
_) Info AppRes
_) (AppExp (Apply ExpBase Info VName
f2 NonEmpty (Info (Diet, Maybe VName), ExpBase Info VName)
args2 SrcLoc
_) Info AppRes
_)
| ExpBase Info VName
f1 ExpBase Info VName -> ExpBase Info VName -> Bool
forall a. Eq a => a -> a -> Bool
== ExpBase Info VName
f2 = [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just ([(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)])
-> [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a b. (a -> b) -> a -> b
$ [ExpBase Info VName]
-> [ExpBase Info VName]
-> [(ExpBase Info VName, ExpBase Info VName)]
forall a b. [a] -> [b] -> [(a, b)]
zip (((Info (Diet, Maybe VName), ExpBase Info VName)
-> ExpBase Info VName)
-> [(Info (Diet, Maybe VName), ExpBase Info VName)]
-> [ExpBase Info VName]
forall a b. (a -> b) -> [a] -> [b]
map (Info (Diet, Maybe VName), ExpBase Info VName)
-> ExpBase Info VName
forall a b. (a, b) -> b
snd ([(Info (Diet, Maybe VName), ExpBase Info VName)]
-> [ExpBase Info VName])
-> [(Info (Diet, Maybe VName), ExpBase Info VName)]
-> [ExpBase Info VName]
forall a b. (a -> b) -> a -> b
$ NonEmpty (Info (Diet, Maybe VName), ExpBase Info VName)
-> [(Info (Diet, Maybe VName), ExpBase Info VName)]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Info (Diet, Maybe VName), ExpBase Info VName)
args1) (((Info (Diet, Maybe VName), ExpBase Info VName)
-> ExpBase Info VName)
-> [(Info (Diet, Maybe VName), ExpBase Info VName)]
-> [ExpBase Info VName]
forall a b. (a -> b) -> [a] -> [b]
map (Info (Diet, Maybe VName), ExpBase Info VName)
-> ExpBase Info VName
forall a b. (a, b) -> b
snd ([(Info (Diet, Maybe VName), ExpBase Info VName)]
-> [ExpBase Info VName])
-> [(Info (Diet, Maybe VName), ExpBase Info VName)]
-> [ExpBase Info VName]
forall a b. (a -> b) -> a -> b
$ NonEmpty (Info (Diet, Maybe VName), ExpBase Info VName)
-> [(Info (Diet, Maybe VName), ExpBase Info VName)]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Info (Diet, Maybe VName), ExpBase Info VName)
args2)
similarExps (AppExp (Index ExpBase Info VName
arr1 SliceBase Info VName
slice1 SrcLoc
_) Info AppRes
_) (AppExp (Index ExpBase Info VName
arr2 SliceBase Info VName
slice2 SrcLoc
_) Info AppRes
_)
| ExpBase Info VName
arr1 ExpBase Info VName -> ExpBase Info VName -> Bool
forall a. Eq a => a -> a -> Bool
== ExpBase Info VName
arr2,
SliceBase Info VName -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length SliceBase Info VName
slice1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== SliceBase Info VName -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length SliceBase Info VName
slice2 =
SliceBase Info VName
-> SliceBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
similarSlices SliceBase Info VName
slice1 SliceBase Info VName
slice2
similarExps (TupLit [ExpBase Info VName]
es1 SrcLoc
_) (TupLit [ExpBase Info VName]
es2 SrcLoc
_)
| [ExpBase Info VName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExpBase Info VName]
es1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [ExpBase Info VName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExpBase Info VName]
es2 =
[(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just ([(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)])
-> [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a b. (a -> b) -> a -> b
$ [ExpBase Info VName]
-> [ExpBase Info VName]
-> [(ExpBase Info VName, ExpBase Info VName)]
forall a b. [a] -> [b] -> [(a, b)]
zip [ExpBase Info VName]
es1 [ExpBase Info VName]
es2
similarExps (RecordLit [FieldBase Info VName]
fs1 SrcLoc
_) (RecordLit [FieldBase Info VName]
fs2 SrcLoc
_)
| [FieldBase Info VName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [FieldBase Info VName]
fs1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [FieldBase Info VName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [FieldBase Info VName]
fs2 =
(FieldBase Info VName
-> FieldBase Info VName
-> Maybe (ExpBase Info VName, ExpBase Info VName))
-> [FieldBase Info VName]
-> [FieldBase Info VName]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM FieldBase Info VName
-> FieldBase Info VName
-> Maybe (ExpBase Info VName, ExpBase Info VName)
forall {f :: * -> *} {vn} {f :: * -> *} {vn}.
FieldBase f vn
-> FieldBase f vn -> Maybe (ExpBase f vn, ExpBase f vn)
onFields [FieldBase Info VName]
fs1 [FieldBase Info VName]
fs2
where
onFields :: FieldBase f vn
-> FieldBase f vn -> Maybe (ExpBase f vn, ExpBase f vn)
onFields (RecordFieldExplicit Name
n1 ExpBase f vn
fe1 SrcLoc
_) (RecordFieldExplicit Name
n2 ExpBase f vn
fe2 SrcLoc
_)
| Name
n1 Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
n2 = (ExpBase f vn, ExpBase f vn) -> Maybe (ExpBase f vn, ExpBase f vn)
forall a. a -> Maybe a
Just (ExpBase f vn
fe1, ExpBase f vn
fe2)
onFields (RecordFieldImplicit vn
vn1 f StructType
ty1 SrcLoc
_) (RecordFieldImplicit vn
vn2 f StructType
ty2 SrcLoc
_) =
(ExpBase f vn, ExpBase f vn) -> Maybe (ExpBase f vn, ExpBase f vn)
forall a. a -> Maybe a
Just (QualName vn -> f StructType -> SrcLoc -> ExpBase f vn
forall (f :: * -> *) vn.
QualName vn -> f StructType -> SrcLoc -> ExpBase f vn
Var (vn -> QualName vn
forall v. v -> QualName v
qualName vn
vn1) f StructType
ty1 SrcLoc
forall a. Monoid a => a
mempty, QualName vn -> f StructType -> SrcLoc -> ExpBase f vn
forall (f :: * -> *) vn.
QualName vn -> f StructType -> SrcLoc -> ExpBase f vn
Var (vn -> QualName vn
forall v. v -> QualName v
qualName vn
vn2) f StructType
ty2 SrcLoc
forall a. Monoid a => a
mempty)
onFields FieldBase f vn
_ FieldBase f vn
_ = Maybe (ExpBase f vn, ExpBase f vn)
forall a. Maybe a
Nothing
similarExps (ArrayLit [ExpBase Info VName]
es1 Info StructType
_ SrcLoc
_) (ArrayLit [ExpBase Info VName]
es2 Info StructType
_ SrcLoc
_)
| [ExpBase Info VName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExpBase Info VName]
es1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [ExpBase Info VName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExpBase Info VName]
es2 =
[(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just ([(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)])
-> [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a b. (a -> b) -> a -> b
$ [ExpBase Info VName]
-> [ExpBase Info VName]
-> [(ExpBase Info VName, ExpBase Info VName)]
forall a b. [a] -> [b] -> [(a, b)]
zip [ExpBase Info VName]
es1 [ExpBase Info VName]
es2
similarExps (Project Name
field1 ExpBase Info VName
e1 Info StructType
_ SrcLoc
_) (Project Name
field2 ExpBase Info VName
e2 Info StructType
_ SrcLoc
_)
| Name
field1 Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
field2 =
[(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just [(ExpBase Info VName
e1, ExpBase Info VName
e2)]
similarExps (Negate ExpBase Info VName
e1 SrcLoc
_) (Negate ExpBase Info VName
e2 SrcLoc
_) =
[(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just [(ExpBase Info VName
e1, ExpBase Info VName
e2)]
similarExps (Not ExpBase Info VName
e1 SrcLoc
_) (Not ExpBase Info VName
e2 SrcLoc
_) =
[(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just [(ExpBase Info VName
e1, ExpBase Info VName
e2)]
similarExps (Constr Name
n1 [ExpBase Info VName]
es1 Info StructType
_ SrcLoc
_) (Constr Name
n2 [ExpBase Info VName]
es2 Info StructType
_ SrcLoc
_)
| [ExpBase Info VName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExpBase Info VName]
es1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [ExpBase Info VName] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExpBase Info VName]
es2,
Name
n1 Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
n2 =
[(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just ([(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)])
-> [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a b. (a -> b) -> a -> b
$ [ExpBase Info VName]
-> [ExpBase Info VName]
-> [(ExpBase Info VName, ExpBase Info VName)]
forall a b. [a] -> [b] -> [(a, b)]
zip [ExpBase Info VName]
es1 [ExpBase Info VName]
es2
similarExps (Update ExpBase Info VName
e1 SliceBase Info VName
slice1 ExpBase Info VName
e'1 SrcLoc
_) (Update ExpBase Info VName
e2 SliceBase Info VName
slice2 ExpBase Info VName
e'2 SrcLoc
_) =
([(ExpBase Info VName
e1, ExpBase Info VName
e2), (ExpBase Info VName
e'1, ExpBase Info VName
e'2)] ++) ([(ExpBase Info VName, ExpBase Info VName)]
-> [(ExpBase Info VName, ExpBase Info VName)])
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SliceBase Info VName
-> SliceBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
similarSlices SliceBase Info VName
slice1 SliceBase Info VName
slice2
similarExps (RecordUpdate ExpBase Info VName
e1 [Name]
names1 ExpBase Info VName
e'1 Info StructType
_ SrcLoc
_) (RecordUpdate ExpBase Info VName
e2 [Name]
names2 ExpBase Info VName
e'2 Info StructType
_ SrcLoc
_)
| [Name]
names1 [Name] -> [Name] -> Bool
forall a. Eq a => a -> a -> Bool
== [Name]
names2 =
[(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just [(ExpBase Info VName
e1, ExpBase Info VName
e2), (ExpBase Info VName
e'1, ExpBase Info VName
e'2)]
similarExps (OpSection QualName VName
op1 Info StructType
_ SrcLoc
_) (OpSection QualName VName
op2 Info StructType
_ SrcLoc
_)
| QualName VName
op1 QualName VName -> QualName VName -> Bool
forall a. Eq a => a -> a -> Bool
== QualName VName
op2 = [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just []
similarExps (OpSectionLeft QualName VName
op1 Info StructType
_ ExpBase Info VName
x1 (Info (PName, ParamType, Maybe VName), Info (PName, ParamType))
_ (Info ResRetType, Info [VName])
_ SrcLoc
_) (OpSectionLeft QualName VName
op2 Info StructType
_ ExpBase Info VName
x2 (Info (PName, ParamType, Maybe VName), Info (PName, ParamType))
_ (Info ResRetType, Info [VName])
_ SrcLoc
_)
| QualName VName
op1 QualName VName -> QualName VName -> Bool
forall a. Eq a => a -> a -> Bool
== QualName VName
op2 = [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just [(ExpBase Info VName
x1, ExpBase Info VName
x2)]
similarExps (OpSectionRight QualName VName
op1 Info StructType
_ ExpBase Info VName
x1 (Info (PName, ParamType), Info (PName, ParamType, Maybe VName))
_ Info ResRetType
_ SrcLoc
_) (OpSectionRight QualName VName
op2 Info StructType
_ ExpBase Info VName
x2 (Info (PName, ParamType), Info (PName, ParamType, Maybe VName))
_ Info ResRetType
_ SrcLoc
_)
| QualName VName
op1 QualName VName -> QualName VName -> Bool
forall a. Eq a => a -> a -> Bool
== QualName VName
op2 = [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just [(ExpBase Info VName
x1, ExpBase Info VName
x2)]
similarExps (ProjectSection [Name]
names1 Info StructType
_ SrcLoc
_) (ProjectSection [Name]
names2 Info StructType
_ SrcLoc
_)
| [Name]
names1 [Name] -> [Name] -> Bool
forall a. Eq a => a -> a -> Bool
== [Name]
names2 = [(ExpBase Info VName, ExpBase Info VName)]
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. a -> Maybe a
Just []
similarExps (IndexSection SliceBase Info VName
slice1 Info StructType
_ SrcLoc
_) (IndexSection SliceBase Info VName
slice2 Info StructType
_ SrcLoc
_) =
SliceBase Info VName
-> SliceBase Info VName
-> Maybe [(ExpBase Info VName, ExpBase Info VName)]
similarSlices SliceBase Info VName
slice1 SliceBase Info VName
slice2
similarExps ExpBase Info VName
_ ExpBase Info VName
_ = Maybe [(ExpBase Info VName, ExpBase Info VName)]
forall a. Maybe a
Nothing
type Ident = IdentBase Info VName
type DimIndex = DimIndexBase Info VName
type Slice = SliceBase Info VName
type Exp = ExpBase Info VName
type AppExp = AppExpBase Info VName
type Pat = PatBase Info VName
type ValBind = ValBindBase Info VName
type TypeBind = TypeBindBase Info VName
type ModBind = ModBindBase Info VName
type ModTypeBind = ModTypeBindBase Info VName
type ModExp = ModExpBase Info VName
type ModParam = ModParamBase Info VName
type ModTypeExp = ModTypeExpBase Info VName
type Dec = DecBase Info VName
type Spec = SpecBase Info VName
type Prog = ProgBase Info VName
type StructTypeArg = TypeArg Size
type TypeParam = TypeParamBase VName
type ScalarType = ScalarTypeBase ()
type Case = CaseBase Info VName
type UncheckedType = TypeBase (Shape Name) ()
type UncheckedTypeExp = TypeExp NoInfo Name
type UncheckedIdent = IdentBase NoInfo Name
type UncheckedDimIndex = DimIndexBase NoInfo Name
type UncheckedSlice = SliceBase NoInfo Name
type UncheckedExp = ExpBase NoInfo Name
type UncheckedModExp = ModExpBase NoInfo Name
type UncheckedModTypeExp = ModTypeExpBase NoInfo Name
type UncheckedTypeParam = TypeParamBase Name
type UncheckedPat = PatBase NoInfo Name
type UncheckedValBind = ValBindBase NoInfo Name
type UncheckedTypeBind = TypeBindBase NoInfo Name
type UncheckedModTypeBind = ModTypeBindBase NoInfo Name
type UncheckedModBind = ModBindBase NoInfo Name
type UncheckedDec = DecBase NoInfo Name
type UncheckedSpec = SpecBase NoInfo Name
type UncheckedProg = ProgBase NoInfo Name
type UncheckedCase = CaseBase NoInfo Name