{-# LANGUAGE Strict #-}
module Futhark.IR.Syntax.Core
( module Language.Futhark.Core,
module Language.Futhark.Primitive,
Commutativity (..),
Uniqueness (..),
ShapeBase (..),
Shape,
stripDims,
Ext (..),
ExtSize,
ExtShape,
Rank (..),
ArrayShape (..),
Space (..),
SpaceId,
TypeBase (..),
Type,
ExtType,
DeclType,
DeclExtType,
Diet (..),
ErrorMsg (..),
ErrorMsgPart (..),
errorMsgArgTypes,
ValueType (..),
OpaqueType (..),
OpaqueTypes (..),
Signedness (..),
EntryPointType (..),
Attr (..),
Attrs (..),
oneAttr,
inAttrs,
withoutAttrs,
mapAttrs,
PrimValue (..),
Ident (..),
Certs (..),
SubExp (..),
Param (..),
DimIndex (..),
Slice (..),
dimFix,
sliceIndices,
sliceDims,
sliceShape,
unitSlice,
fixSlice,
sliceSlice,
PatElem (..),
FlatSlice (..),
FlatDimIndex (..),
flatSliceDims,
flatSliceStrides,
)
where
import Control.Category
import Control.Monad
import Control.Monad.State
import Data.Bifoldable
import Data.Bifunctor
import Data.Bitraversable
import Data.Map.Strict qualified as M
import Data.Maybe
import Data.Set qualified as S
import Data.String
import Data.Text qualified as T
import Data.Traversable (fmapDefault, foldMapDefault)
import Language.Futhark.Core
import Language.Futhark.Primitive
import Prelude hiding (id, (.))
data Commutativity
= Noncommutative
| Commutative
deriving (Commutativity -> Commutativity -> Bool
(Commutativity -> Commutativity -> Bool)
-> (Commutativity -> Commutativity -> Bool) -> Eq Commutativity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Commutativity -> Commutativity -> Bool
== :: Commutativity -> Commutativity -> Bool
$c/= :: Commutativity -> Commutativity -> Bool
/= :: Commutativity -> Commutativity -> Bool
Eq, Eq Commutativity
Eq Commutativity
-> (Commutativity -> Commutativity -> Ordering)
-> (Commutativity -> Commutativity -> Bool)
-> (Commutativity -> Commutativity -> Bool)
-> (Commutativity -> Commutativity -> Bool)
-> (Commutativity -> Commutativity -> Bool)
-> (Commutativity -> Commutativity -> Commutativity)
-> (Commutativity -> Commutativity -> Commutativity)
-> Ord Commutativity
Commutativity -> Commutativity -> Bool
Commutativity -> Commutativity -> Ordering
Commutativity -> Commutativity -> Commutativity
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 :: Commutativity -> Commutativity -> Ordering
compare :: Commutativity -> Commutativity -> Ordering
$c< :: Commutativity -> Commutativity -> Bool
< :: Commutativity -> Commutativity -> Bool
$c<= :: Commutativity -> Commutativity -> Bool
<= :: Commutativity -> Commutativity -> Bool
$c> :: Commutativity -> Commutativity -> Bool
> :: Commutativity -> Commutativity -> Bool
$c>= :: Commutativity -> Commutativity -> Bool
>= :: Commutativity -> Commutativity -> Bool
$cmax :: Commutativity -> Commutativity -> Commutativity
max :: Commutativity -> Commutativity -> Commutativity
$cmin :: Commutativity -> Commutativity -> Commutativity
min :: Commutativity -> Commutativity -> Commutativity
Ord, Int -> Commutativity -> ShowS
[Commutativity] -> ShowS
Commutativity -> String
(Int -> Commutativity -> ShowS)
-> (Commutativity -> String)
-> ([Commutativity] -> ShowS)
-> Show Commutativity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Commutativity -> ShowS
showsPrec :: Int -> Commutativity -> ShowS
$cshow :: Commutativity -> String
show :: Commutativity -> String
$cshowList :: [Commutativity] -> ShowS
showList :: [Commutativity] -> ShowS
Show)
instance Semigroup Commutativity where
<> :: Commutativity -> Commutativity -> Commutativity
(<>) = Commutativity -> Commutativity -> Commutativity
forall a. Ord a => a -> a -> a
min
instance Monoid Commutativity where
mempty :: Commutativity
mempty = Commutativity
Commutative
newtype ShapeBase d = Shape {forall d. ShapeBase d -> [d]
shapeDims :: [d]}
deriving (ShapeBase d -> ShapeBase d -> Bool
(ShapeBase d -> ShapeBase d -> Bool)
-> (ShapeBase d -> ShapeBase d -> Bool) -> Eq (ShapeBase d)
forall d. Eq d => ShapeBase d -> ShapeBase d -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall d. Eq d => ShapeBase d -> ShapeBase d -> Bool
== :: ShapeBase d -> ShapeBase d -> Bool
$c/= :: forall d. Eq d => ShapeBase d -> ShapeBase d -> Bool
/= :: ShapeBase d -> ShapeBase d -> Bool
Eq, Eq (ShapeBase d)
Eq (ShapeBase d)
-> (ShapeBase d -> ShapeBase d -> Ordering)
-> (ShapeBase d -> ShapeBase d -> Bool)
-> (ShapeBase d -> ShapeBase d -> Bool)
-> (ShapeBase d -> ShapeBase d -> Bool)
-> (ShapeBase d -> ShapeBase d -> Bool)
-> (ShapeBase d -> ShapeBase d -> ShapeBase d)
-> (ShapeBase d -> ShapeBase d -> ShapeBase d)
-> Ord (ShapeBase d)
ShapeBase d -> ShapeBase d -> Bool
ShapeBase d -> ShapeBase d -> Ordering
ShapeBase d -> ShapeBase d -> ShapeBase d
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
forall {d}. Ord d => Eq (ShapeBase d)
forall d. Ord d => ShapeBase d -> ShapeBase d -> Bool
forall d. Ord d => ShapeBase d -> ShapeBase d -> Ordering
forall d. Ord d => ShapeBase d -> ShapeBase d -> ShapeBase d
$ccompare :: forall d. Ord d => ShapeBase d -> ShapeBase d -> Ordering
compare :: ShapeBase d -> ShapeBase d -> Ordering
$c< :: forall d. Ord d => ShapeBase d -> ShapeBase d -> Bool
< :: ShapeBase d -> ShapeBase d -> Bool
$c<= :: forall d. Ord d => ShapeBase d -> ShapeBase d -> Bool
<= :: ShapeBase d -> ShapeBase d -> Bool
$c> :: forall d. Ord d => ShapeBase d -> ShapeBase d -> Bool
> :: ShapeBase d -> ShapeBase d -> Bool
$c>= :: forall d. Ord d => ShapeBase d -> ShapeBase d -> Bool
>= :: ShapeBase d -> ShapeBase d -> Bool
$cmax :: forall d. Ord d => ShapeBase d -> ShapeBase d -> ShapeBase d
max :: ShapeBase d -> ShapeBase d -> ShapeBase d
$cmin :: forall d. Ord d => ShapeBase d -> ShapeBase d -> ShapeBase d
min :: ShapeBase d -> ShapeBase d -> ShapeBase d
Ord, Int -> ShapeBase d -> ShowS
[ShapeBase d] -> ShowS
ShapeBase d -> String
(Int -> ShapeBase d -> ShowS)
-> (ShapeBase d -> String)
-> ([ShapeBase d] -> ShowS)
-> Show (ShapeBase d)
forall d. Show d => Int -> ShapeBase d -> ShowS
forall d. Show d => [ShapeBase d] -> ShowS
forall d. Show d => ShapeBase d -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall d. Show d => Int -> ShapeBase d -> ShowS
showsPrec :: Int -> ShapeBase d -> ShowS
$cshow :: forall d. Show d => ShapeBase d -> String
show :: ShapeBase d -> String
$cshowList :: forall d. Show d => [ShapeBase d] -> ShowS
showList :: [ShapeBase d] -> ShowS
Show)
instance Functor ShapeBase where
fmap :: forall a b. (a -> b) -> ShapeBase a -> ShapeBase b
fmap = (a -> b) -> ShapeBase a -> ShapeBase b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Foldable ShapeBase where
foldMap :: forall m a. Monoid m => (a -> m) -> ShapeBase a -> m
foldMap = (a -> m) -> ShapeBase a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
instance Traversable ShapeBase where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ShapeBase a -> f (ShapeBase b)
traverse a -> f b
f = ([b] -> ShapeBase b) -> f [b] -> f (ShapeBase b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [b] -> ShapeBase b
forall d. [d] -> ShapeBase d
Shape (f [b] -> f (ShapeBase b))
-> (ShapeBase a -> f [b]) -> ShapeBase a -> f (ShapeBase b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> f b) -> [a] -> f [b]
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 a -> f b
f ([a] -> f [b]) -> (ShapeBase a -> [a]) -> ShapeBase a -> f [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ShapeBase a -> [a]
forall d. ShapeBase d -> [d]
shapeDims
instance Semigroup (ShapeBase d) where
Shape [d]
l1 <> :: ShapeBase d -> ShapeBase d -> ShapeBase d
<> Shape [d]
l2 = [d] -> ShapeBase d
forall d. [d] -> ShapeBase d
Shape ([d] -> ShapeBase d) -> [d] -> ShapeBase d
forall a b. (a -> b) -> a -> b
$ [d]
l1 [d] -> [d] -> [d]
forall a. Monoid a => a -> a -> a
`mappend` [d]
l2
instance Monoid (ShapeBase d) where
mempty :: ShapeBase d
mempty = [d] -> ShapeBase d
forall d. [d] -> ShapeBase d
Shape [d]
forall a. Monoid a => a
mempty
stripDims :: Int -> ShapeBase d -> ShapeBase d
stripDims :: forall d. Int -> ShapeBase d -> ShapeBase d
stripDims Int
n (Shape [d]
dims) = [d] -> ShapeBase d
forall d. [d] -> ShapeBase d
Shape ([d] -> ShapeBase d) -> [d] -> ShapeBase d
forall a b. (a -> b) -> a -> b
$ Int -> [d] -> [d]
forall a. Int -> [a] -> [a]
drop Int
n [d]
dims
type Shape = ShapeBase SubExp
data Ext a
= Ext Int
| Free a
deriving (Ext a -> Ext a -> Bool
(Ext a -> Ext a -> Bool) -> (Ext a -> Ext a -> Bool) -> Eq (Ext a)
forall a. Eq a => Ext a -> Ext a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Ext a -> Ext a -> Bool
== :: Ext a -> Ext a -> Bool
$c/= :: forall a. Eq a => Ext a -> Ext a -> Bool
/= :: Ext a -> Ext a -> Bool
Eq, Eq (Ext a)
Eq (Ext a)
-> (Ext a -> Ext a -> Ordering)
-> (Ext a -> Ext a -> Bool)
-> (Ext a -> Ext a -> Bool)
-> (Ext a -> Ext a -> Bool)
-> (Ext a -> Ext a -> Bool)
-> (Ext a -> Ext a -> Ext a)
-> (Ext a -> Ext a -> Ext a)
-> Ord (Ext a)
Ext a -> Ext a -> Bool
Ext a -> Ext a -> Ordering
Ext a -> Ext a -> Ext a
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
forall {a}. Ord a => Eq (Ext a)
forall a. Ord a => Ext a -> Ext a -> Bool
forall a. Ord a => Ext a -> Ext a -> Ordering
forall a. Ord a => Ext a -> Ext a -> Ext a
$ccompare :: forall a. Ord a => Ext a -> Ext a -> Ordering
compare :: Ext a -> Ext a -> Ordering
$c< :: forall a. Ord a => Ext a -> Ext a -> Bool
< :: Ext a -> Ext a -> Bool
$c<= :: forall a. Ord a => Ext a -> Ext a -> Bool
<= :: Ext a -> Ext a -> Bool
$c> :: forall a. Ord a => Ext a -> Ext a -> Bool
> :: Ext a -> Ext a -> Bool
$c>= :: forall a. Ord a => Ext a -> Ext a -> Bool
>= :: Ext a -> Ext a -> Bool
$cmax :: forall a. Ord a => Ext a -> Ext a -> Ext a
max :: Ext a -> Ext a -> Ext a
$cmin :: forall a. Ord a => Ext a -> Ext a -> Ext a
min :: Ext a -> Ext a -> Ext a
Ord, Int -> Ext a -> ShowS
[Ext a] -> ShowS
Ext a -> String
(Int -> Ext a -> ShowS)
-> (Ext a -> String) -> ([Ext a] -> ShowS) -> Show (Ext a)
forall a. Show a => Int -> Ext a -> ShowS
forall a. Show a => [Ext a] -> ShowS
forall a. Show a => Ext a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Ext a -> ShowS
showsPrec :: Int -> Ext a -> ShowS
$cshow :: forall a. Show a => Ext a -> String
show :: Ext a -> String
$cshowList :: forall a. Show a => [Ext a] -> ShowS
showList :: [Ext a] -> ShowS
Show)
instance Functor Ext where
fmap :: forall a b. (a -> b) -> Ext a -> Ext b
fmap = (a -> b) -> Ext a -> Ext b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Foldable Ext where
foldMap :: forall m a. Monoid m => (a -> m) -> Ext a -> m
foldMap = (a -> m) -> Ext a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
instance Traversable Ext where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Ext a -> f (Ext b)
traverse a -> f b
_ (Ext Int
i) = Ext b -> f (Ext b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ext b -> f (Ext b)) -> Ext b -> f (Ext b)
forall a b. (a -> b) -> a -> b
$ Int -> Ext b
forall a. Int -> Ext a
Ext Int
i
traverse a -> f b
f (Free a
v) = b -> Ext b
forall a. a -> Ext a
Free (b -> Ext b) -> f b -> f (Ext b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
v
type ExtSize = Ext SubExp
type ExtShape = ShapeBase ExtSize
newtype Rank = Rank Int
deriving (Int -> Rank -> ShowS
[Rank] -> ShowS
Rank -> String
(Int -> Rank -> ShowS)
-> (Rank -> String) -> ([Rank] -> ShowS) -> Show Rank
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Rank -> ShowS
showsPrec :: Int -> Rank -> ShowS
$cshow :: Rank -> String
show :: Rank -> String
$cshowList :: [Rank] -> ShowS
showList :: [Rank] -> ShowS
Show, Rank -> Rank -> Bool
(Rank -> Rank -> Bool) -> (Rank -> Rank -> Bool) -> Eq Rank
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rank -> Rank -> Bool
== :: Rank -> Rank -> Bool
$c/= :: Rank -> Rank -> Bool
/= :: Rank -> Rank -> Bool
Eq, Eq Rank
Eq Rank
-> (Rank -> Rank -> Ordering)
-> (Rank -> Rank -> Bool)
-> (Rank -> Rank -> Bool)
-> (Rank -> Rank -> Bool)
-> (Rank -> Rank -> Bool)
-> (Rank -> Rank -> Rank)
-> (Rank -> Rank -> Rank)
-> Ord Rank
Rank -> Rank -> Bool
Rank -> Rank -> Ordering
Rank -> Rank -> Rank
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 :: Rank -> Rank -> Ordering
compare :: Rank -> Rank -> Ordering
$c< :: Rank -> Rank -> Bool
< :: Rank -> Rank -> Bool
$c<= :: Rank -> Rank -> Bool
<= :: Rank -> Rank -> Bool
$c> :: Rank -> Rank -> Bool
> :: Rank -> Rank -> Bool
$c>= :: Rank -> Rank -> Bool
>= :: Rank -> Rank -> Bool
$cmax :: Rank -> Rank -> Rank
max :: Rank -> Rank -> Rank
$cmin :: Rank -> Rank -> Rank
min :: Rank -> Rank -> Rank
Ord)
class (Monoid a, Eq a, Ord a) => ArrayShape a where
shapeRank :: a -> Int
subShapeOf :: a -> a -> Bool
instance ArrayShape (ShapeBase SubExp) where
shapeRank :: ShapeBase SubExp -> Int
shapeRank (Shape [SubExp]
l) = [SubExp] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [SubExp]
l
subShapeOf :: ShapeBase SubExp -> ShapeBase SubExp -> Bool
subShapeOf = ShapeBase SubExp -> ShapeBase SubExp -> Bool
forall a. Eq a => a -> a -> Bool
(==)
instance ArrayShape (ShapeBase ExtSize) where
shapeRank :: ShapeBase ExtSize -> Int
shapeRank (Shape [ExtSize]
l) = [ExtSize] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExtSize]
l
subShapeOf :: ShapeBase ExtSize -> ShapeBase ExtSize -> Bool
subShapeOf (Shape [ExtSize]
ds1) (Shape [ExtSize]
ds2) =
[ExtSize] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExtSize]
ds1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [ExtSize] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ExtSize]
ds2
Bool -> Bool -> Bool
&& State (Map Int Int) Bool -> Map Int Int -> Bool
forall s a. State s a -> s -> a
evalState ([Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ([Bool] -> Bool)
-> StateT (Map Int Int) Identity [Bool] -> State (Map Int Int) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ExtSize -> ExtSize -> State (Map Int Int) Bool)
-> [ExtSize] -> [ExtSize] -> StateT (Map Int Int) Identity [Bool]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM ExtSize -> ExtSize -> State (Map Int Int) Bool
forall {f :: * -> *} {a}.
(Eq a, MonadState (Map Int Int) f) =>
Ext a -> Ext a -> f Bool
subDimOf [ExtSize]
ds1 [ExtSize]
ds2) Map Int Int
forall k a. Map k a
M.empty
where
subDimOf :: Ext a -> Ext a -> f Bool
subDimOf (Free a
se1) (Free a
se2) = Bool -> f Bool
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> f Bool) -> Bool -> f Bool
forall a b. (a -> b) -> a -> b
$ a
se1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
se2
subDimOf (Ext Int
_) (Free a
_) = Bool -> f Bool
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
subDimOf (Free a
_) (Ext Int
_) = Bool -> f Bool
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
subDimOf (Ext Int
x) (Ext Int
y) = do
Map Int Int
extmap <- f (Map Int Int)
forall s (m :: * -> *). MonadState s m => m s
get
case Int -> Map Int Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
y Map Int Int
extmap of
Just Int
ywas
| Int
ywas Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
x -> Bool -> f Bool
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
| Bool
otherwise -> Bool -> f Bool
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
Maybe Int
Nothing -> do
Map Int Int -> f ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (Map Int Int -> f ()) -> Map Int Int -> f ()
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Map Int Int -> Map Int Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Int
y Int
x Map Int Int
extmap
Bool -> f Bool
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
instance Semigroup Rank where
Rank Int
x <> :: Rank -> Rank -> Rank
<> Rank Int
y = Int -> Rank
Rank (Int -> Rank) -> Int -> Rank
forall a b. (a -> b) -> a -> b
$ Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
y
instance Monoid Rank where
mempty :: Rank
mempty = Int -> Rank
Rank Int
0
instance ArrayShape Rank where
shapeRank :: Rank -> Int
shapeRank (Rank Int
x) = Int
x
subShapeOf :: Rank -> Rank -> Bool
subShapeOf = Rank -> Rank -> Bool
forall a. Eq a => a -> a -> Bool
(==)
data Space
= DefaultSpace
| Space SpaceId
|
ScalarSpace [SubExp] PrimType
deriving (Int -> Space -> ShowS
[Space] -> ShowS
Space -> String
(Int -> Space -> ShowS)
-> (Space -> String) -> ([Space] -> ShowS) -> Show Space
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Space -> ShowS
showsPrec :: Int -> Space -> ShowS
$cshow :: Space -> String
show :: Space -> String
$cshowList :: [Space] -> ShowS
showList :: [Space] -> ShowS
Show, Space -> Space -> Bool
(Space -> Space -> Bool) -> (Space -> Space -> Bool) -> Eq Space
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Space -> Space -> Bool
== :: Space -> Space -> Bool
$c/= :: Space -> Space -> Bool
/= :: Space -> Space -> Bool
Eq, Eq Space
Eq Space
-> (Space -> Space -> Ordering)
-> (Space -> Space -> Bool)
-> (Space -> Space -> Bool)
-> (Space -> Space -> Bool)
-> (Space -> Space -> Bool)
-> (Space -> Space -> Space)
-> (Space -> Space -> Space)
-> Ord Space
Space -> Space -> Bool
Space -> Space -> Ordering
Space -> Space -> Space
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 :: Space -> Space -> Ordering
compare :: Space -> Space -> Ordering
$c< :: Space -> Space -> Bool
< :: Space -> Space -> Bool
$c<= :: Space -> Space -> Bool
<= :: Space -> Space -> Bool
$c> :: Space -> Space -> Bool
> :: Space -> Space -> Bool
$c>= :: Space -> Space -> Bool
>= :: Space -> Space -> Bool
$cmax :: Space -> Space -> Space
max :: Space -> Space -> Space
$cmin :: Space -> Space -> Space
min :: Space -> Space -> Space
Ord)
type SpaceId = String
data TypeBase shape u
= Prim PrimType
|
Acc VName Shape [Type] u
| Array PrimType shape u
| Mem Space
deriving (Int -> TypeBase shape u -> ShowS
[TypeBase shape u] -> ShowS
TypeBase shape u -> String
(Int -> TypeBase shape u -> ShowS)
-> (TypeBase shape u -> String)
-> ([TypeBase shape u] -> ShowS)
-> Show (TypeBase shape u)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall shape u.
(Show shape, Show u) =>
Int -> TypeBase shape u -> ShowS
forall shape u. (Show shape, Show u) => [TypeBase shape u] -> ShowS
forall shape u. (Show shape, Show u) => TypeBase shape u -> String
$cshowsPrec :: forall shape u.
(Show shape, Show u) =>
Int -> TypeBase shape u -> ShowS
showsPrec :: Int -> TypeBase shape u -> ShowS
$cshow :: forall shape u. (Show shape, Show u) => TypeBase shape u -> String
show :: TypeBase shape u -> String
$cshowList :: forall shape u. (Show shape, Show u) => [TypeBase shape u] -> ShowS
showList :: [TypeBase shape u] -> ShowS
Show, TypeBase shape u -> TypeBase shape u -> Bool
(TypeBase shape u -> TypeBase shape u -> Bool)
-> (TypeBase shape u -> TypeBase shape u -> Bool)
-> Eq (TypeBase shape u)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall shape u.
(Eq shape, Eq u) =>
TypeBase shape u -> TypeBase shape u -> Bool
$c== :: forall shape u.
(Eq shape, Eq u) =>
TypeBase shape u -> TypeBase shape u -> Bool
== :: TypeBase shape u -> TypeBase shape u -> Bool
$c/= :: forall shape u.
(Eq shape, Eq u) =>
TypeBase shape u -> TypeBase shape u -> Bool
/= :: TypeBase shape u -> TypeBase shape u -> Bool
Eq, Eq (TypeBase shape u)
Eq (TypeBase shape u)
-> (TypeBase shape u -> TypeBase shape u -> Ordering)
-> (TypeBase shape u -> TypeBase shape u -> Bool)
-> (TypeBase shape u -> TypeBase shape u -> Bool)
-> (TypeBase shape u -> TypeBase shape u -> Bool)
-> (TypeBase shape u -> TypeBase shape u -> Bool)
-> (TypeBase shape u -> TypeBase shape u -> TypeBase shape u)
-> (TypeBase shape u -> TypeBase shape u -> TypeBase shape u)
-> Ord (TypeBase shape u)
TypeBase shape u -> TypeBase shape u -> Bool
TypeBase shape u -> TypeBase shape u -> Ordering
TypeBase shape u -> TypeBase shape u -> TypeBase shape u
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
forall {shape} {u}. (Ord shape, Ord u) => Eq (TypeBase shape u)
forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> Bool
forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> Ordering
forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> TypeBase shape u
$ccompare :: forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> Ordering
compare :: TypeBase shape u -> TypeBase shape u -> Ordering
$c< :: forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> Bool
< :: TypeBase shape u -> TypeBase shape u -> Bool
$c<= :: forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> Bool
<= :: TypeBase shape u -> TypeBase shape u -> Bool
$c> :: forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> Bool
> :: TypeBase shape u -> TypeBase shape u -> Bool
$c>= :: forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> Bool
>= :: TypeBase shape u -> TypeBase shape u -> Bool
$cmax :: forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> TypeBase shape u
max :: TypeBase shape u -> TypeBase shape u -> TypeBase shape u
$cmin :: forall shape u.
(Ord shape, Ord u) =>
TypeBase shape u -> TypeBase shape u -> TypeBase shape u
min :: TypeBase shape u -> TypeBase shape u -> TypeBase shape u
Ord)
instance Bitraversable TypeBase where
bitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> TypeBase a b -> f (TypeBase c d)
bitraverse a -> f c
f b -> f d
g (Array PrimType
t a
shape b
u) = PrimType -> c -> d -> TypeBase c d
forall shape u. PrimType -> shape -> u -> TypeBase shape u
Array PrimType
t (c -> d -> TypeBase c d) -> f c -> f (d -> TypeBase c d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f c
f a
shape f (d -> TypeBase c d) -> f d -> f (TypeBase c d)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> f d
g b
u
bitraverse a -> f c
_ b -> f d
_ (Prim PrimType
pt) = TypeBase c d -> f (TypeBase c d)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TypeBase c d -> f (TypeBase c d))
-> TypeBase c d -> f (TypeBase c d)
forall a b. (a -> b) -> a -> b
$ PrimType -> TypeBase c d
forall shape u. PrimType -> TypeBase shape u
Prim PrimType
pt
bitraverse a -> f c
_ b -> f d
g (Acc VName
arrs ShapeBase SubExp
ispace [Type]
ts b
u) = VName -> ShapeBase SubExp -> [Type] -> d -> TypeBase c d
forall shape u.
VName -> ShapeBase SubExp -> [Type] -> u -> TypeBase shape u
Acc VName
arrs ShapeBase SubExp
ispace [Type]
ts (d -> TypeBase c d) -> f d -> f (TypeBase c d)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> b -> f d
g b
u
bitraverse a -> f c
_ b -> f d
_ (Mem Space
s) = TypeBase c d -> f (TypeBase c d)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TypeBase c d -> f (TypeBase c d))
-> TypeBase c d -> f (TypeBase c d)
forall a b. (a -> b) -> a -> b
$ Space -> TypeBase c d
forall shape u. Space -> TypeBase shape u
Mem Space
s
instance Functor (TypeBase shape) where
fmap :: forall a b. (a -> b) -> TypeBase shape a -> TypeBase shape b
fmap = (a -> b) -> TypeBase shape a -> TypeBase shape b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Foldable (TypeBase shape) where
foldMap :: forall m a. Monoid m => (a -> m) -> TypeBase shape a -> m
foldMap = (a -> m) -> TypeBase shape a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
instance Traversable (TypeBase shape) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TypeBase shape a -> f (TypeBase shape b)
traverse = (shape -> f shape)
-> (a -> f b) -> TypeBase shape a -> f (TypeBase shape b)
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 shape -> f shape
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance Bifunctor TypeBase where
bimap :: forall a b c d.
(a -> b) -> (c -> d) -> TypeBase a c -> TypeBase b d
bimap = (a -> b) -> (c -> d) -> TypeBase a c -> TypeBase b d
forall (t :: * -> * -> *) a b c d.
Bitraversable t =>
(a -> b) -> (c -> d) -> t a c -> t b d
bimapDefault
instance Bifoldable TypeBase where
bifoldMap :: forall m a b. Monoid m => (a -> m) -> (b -> m) -> TypeBase a b -> m
bifoldMap = (a -> m) -> (b -> m) -> TypeBase a b -> m
forall (t :: * -> * -> *) m a b.
(Bitraversable t, Monoid m) =>
(a -> m) -> (b -> m) -> t a b -> m
bifoldMapDefault
type Type = TypeBase Shape NoUniqueness
type ExtType = TypeBase ExtShape NoUniqueness
type DeclType = TypeBase Shape Uniqueness
type DeclExtType = TypeBase ExtShape Uniqueness
data Diet
=
Consume
|
Observe
|
ObservePrim
deriving (Diet -> Diet -> Bool
(Diet -> Diet -> Bool) -> (Diet -> Diet -> Bool) -> Eq Diet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Diet -> Diet -> Bool
== :: Diet -> Diet -> Bool
$c/= :: Diet -> Diet -> Bool
/= :: Diet -> Diet -> Bool
Eq, Eq Diet
Eq Diet
-> (Diet -> Diet -> Ordering)
-> (Diet -> Diet -> Bool)
-> (Diet -> Diet -> Bool)
-> (Diet -> Diet -> Bool)
-> (Diet -> Diet -> Bool)
-> (Diet -> Diet -> Diet)
-> (Diet -> Diet -> Diet)
-> Ord Diet
Diet -> Diet -> Bool
Diet -> Diet -> Ordering
Diet -> Diet -> Diet
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 :: Diet -> Diet -> Ordering
compare :: Diet -> Diet -> Ordering
$c< :: Diet -> Diet -> Bool
< :: Diet -> Diet -> Bool
$c<= :: Diet -> Diet -> Bool
<= :: Diet -> Diet -> Bool
$c> :: Diet -> Diet -> Bool
> :: Diet -> Diet -> Bool
$c>= :: Diet -> Diet -> Bool
>= :: Diet -> Diet -> Bool
$cmax :: Diet -> Diet -> Diet
max :: Diet -> Diet -> Diet
$cmin :: Diet -> Diet -> Diet
min :: Diet -> Diet -> Diet
Ord, Int -> Diet -> ShowS
[Diet] -> ShowS
Diet -> String
(Int -> Diet -> ShowS)
-> (Diet -> String) -> ([Diet] -> ShowS) -> Show Diet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Diet -> ShowS
showsPrec :: Int -> Diet -> ShowS
$cshow :: Diet -> String
show :: Diet -> String
$cshowList :: [Diet] -> ShowS
showList :: [Diet] -> ShowS
Show)
data Ident = Ident
{ Ident -> VName
identName :: VName,
Ident -> Type
identType :: Type
}
deriving (Int -> Ident -> ShowS
[Ident] -> ShowS
Ident -> String
(Int -> Ident -> ShowS)
-> (Ident -> String) -> ([Ident] -> ShowS) -> Show Ident
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ident -> ShowS
showsPrec :: Int -> Ident -> ShowS
$cshow :: Ident -> String
show :: Ident -> String
$cshowList :: [Ident] -> ShowS
showList :: [Ident] -> ShowS
Show)
instance Eq Ident where
Ident
x == :: Ident -> Ident -> Bool
== Ident
y = Ident -> VName
identName Ident
x VName -> VName -> Bool
forall a. Eq a => a -> a -> Bool
== Ident -> VName
identName Ident
y
instance Ord Ident where
Ident
x compare :: Ident -> Ident -> Ordering
`compare` Ident
y = Ident -> VName
identName Ident
x VName -> VName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Ident -> VName
identName Ident
y
newtype Certs = Certs {Certs -> [VName]
unCerts :: [VName]}
deriving (Certs -> Certs -> Bool
(Certs -> Certs -> Bool) -> (Certs -> Certs -> Bool) -> Eq Certs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Certs -> Certs -> Bool
== :: Certs -> Certs -> Bool
$c/= :: Certs -> Certs -> Bool
/= :: Certs -> Certs -> Bool
Eq, Eq Certs
Eq Certs
-> (Certs -> Certs -> Ordering)
-> (Certs -> Certs -> Bool)
-> (Certs -> Certs -> Bool)
-> (Certs -> Certs -> Bool)
-> (Certs -> Certs -> Bool)
-> (Certs -> Certs -> Certs)
-> (Certs -> Certs -> Certs)
-> Ord Certs
Certs -> Certs -> Bool
Certs -> Certs -> Ordering
Certs -> Certs -> Certs
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 :: Certs -> Certs -> Ordering
compare :: Certs -> Certs -> Ordering
$c< :: Certs -> Certs -> Bool
< :: Certs -> Certs -> Bool
$c<= :: Certs -> Certs -> Bool
<= :: Certs -> Certs -> Bool
$c> :: Certs -> Certs -> Bool
> :: Certs -> Certs -> Bool
$c>= :: Certs -> Certs -> Bool
>= :: Certs -> Certs -> Bool
$cmax :: Certs -> Certs -> Certs
max :: Certs -> Certs -> Certs
$cmin :: Certs -> Certs -> Certs
min :: Certs -> Certs -> Certs
Ord, Int -> Certs -> ShowS
[Certs] -> ShowS
Certs -> String
(Int -> Certs -> ShowS)
-> (Certs -> String) -> ([Certs] -> ShowS) -> Show Certs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Certs -> ShowS
showsPrec :: Int -> Certs -> ShowS
$cshow :: Certs -> String
show :: Certs -> String
$cshowList :: [Certs] -> ShowS
showList :: [Certs] -> ShowS
Show)
instance Semigroup Certs where
Certs [VName]
x <> :: Certs -> Certs -> Certs
<> Certs [VName]
y = [VName] -> Certs
Certs ([VName]
x [VName] -> [VName] -> [VName]
forall a. Semigroup a => a -> a -> a
<> (VName -> Bool) -> [VName] -> [VName]
forall a. (a -> Bool) -> [a] -> [a]
filter (VName -> [VName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [VName]
x) [VName]
y)
instance Monoid Certs where
mempty :: Certs
mempty = [VName] -> Certs
Certs [VName]
forall a. Monoid a => a
mempty
data SubExp
= Constant PrimValue
| Var VName
deriving (Int -> SubExp -> ShowS
[SubExp] -> ShowS
SubExp -> String
(Int -> SubExp -> ShowS)
-> (SubExp -> String) -> ([SubExp] -> ShowS) -> Show SubExp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubExp -> ShowS
showsPrec :: Int -> SubExp -> ShowS
$cshow :: SubExp -> String
show :: SubExp -> String
$cshowList :: [SubExp] -> ShowS
showList :: [SubExp] -> ShowS
Show, SubExp -> SubExp -> Bool
(SubExp -> SubExp -> Bool)
-> (SubExp -> SubExp -> Bool) -> Eq SubExp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubExp -> SubExp -> Bool
== :: SubExp -> SubExp -> Bool
$c/= :: SubExp -> SubExp -> Bool
/= :: SubExp -> SubExp -> Bool
Eq, Eq SubExp
Eq SubExp
-> (SubExp -> SubExp -> Ordering)
-> (SubExp -> SubExp -> Bool)
-> (SubExp -> SubExp -> Bool)
-> (SubExp -> SubExp -> Bool)
-> (SubExp -> SubExp -> Bool)
-> (SubExp -> SubExp -> SubExp)
-> (SubExp -> SubExp -> SubExp)
-> Ord SubExp
SubExp -> SubExp -> Bool
SubExp -> SubExp -> Ordering
SubExp -> SubExp -> SubExp
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 :: SubExp -> SubExp -> Ordering
compare :: SubExp -> SubExp -> Ordering
$c< :: SubExp -> SubExp -> Bool
< :: SubExp -> SubExp -> Bool
$c<= :: SubExp -> SubExp -> Bool
<= :: SubExp -> SubExp -> Bool
$c> :: SubExp -> SubExp -> Bool
> :: SubExp -> SubExp -> Bool
$c>= :: SubExp -> SubExp -> Bool
>= :: SubExp -> SubExp -> Bool
$cmax :: SubExp -> SubExp -> SubExp
max :: SubExp -> SubExp -> SubExp
$cmin :: SubExp -> SubExp -> SubExp
min :: SubExp -> SubExp -> SubExp
Ord)
data Param dec = Param
{
forall dec. Param dec -> Attrs
paramAttrs :: Attrs,
forall dec. Param dec -> VName
paramName :: VName,
forall dec. Param dec -> dec
paramDec :: dec
}
deriving (Eq (Param dec)
Eq (Param dec)
-> (Param dec -> Param dec -> Ordering)
-> (Param dec -> Param dec -> Bool)
-> (Param dec -> Param dec -> Bool)
-> (Param dec -> Param dec -> Bool)
-> (Param dec -> Param dec -> Bool)
-> (Param dec -> Param dec -> Param dec)
-> (Param dec -> Param dec -> Param dec)
-> Ord (Param dec)
Param dec -> Param dec -> Bool
Param dec -> Param dec -> Ordering
Param dec -> Param dec -> Param dec
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
forall {dec}. Ord dec => Eq (Param dec)
forall dec. Ord dec => Param dec -> Param dec -> Bool
forall dec. Ord dec => Param dec -> Param dec -> Ordering
forall dec. Ord dec => Param dec -> Param dec -> Param dec
$ccompare :: forall dec. Ord dec => Param dec -> Param dec -> Ordering
compare :: Param dec -> Param dec -> Ordering
$c< :: forall dec. Ord dec => Param dec -> Param dec -> Bool
< :: Param dec -> Param dec -> Bool
$c<= :: forall dec. Ord dec => Param dec -> Param dec -> Bool
<= :: Param dec -> Param dec -> Bool
$c> :: forall dec. Ord dec => Param dec -> Param dec -> Bool
> :: Param dec -> Param dec -> Bool
$c>= :: forall dec. Ord dec => Param dec -> Param dec -> Bool
>= :: Param dec -> Param dec -> Bool
$cmax :: forall dec. Ord dec => Param dec -> Param dec -> Param dec
max :: Param dec -> Param dec -> Param dec
$cmin :: forall dec. Ord dec => Param dec -> Param dec -> Param dec
min :: Param dec -> Param dec -> Param dec
Ord, Int -> Param dec -> ShowS
[Param dec] -> ShowS
Param dec -> String
(Int -> Param dec -> ShowS)
-> (Param dec -> String)
-> ([Param dec] -> ShowS)
-> Show (Param dec)
forall dec. Show dec => Int -> Param dec -> ShowS
forall dec. Show dec => [Param dec] -> ShowS
forall dec. Show dec => Param dec -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall dec. Show dec => Int -> Param dec -> ShowS
showsPrec :: Int -> Param dec -> ShowS
$cshow :: forall dec. Show dec => Param dec -> String
show :: Param dec -> String
$cshowList :: forall dec. Show dec => [Param dec] -> ShowS
showList :: [Param dec] -> ShowS
Show, Param dec -> Param dec -> Bool
(Param dec -> Param dec -> Bool)
-> (Param dec -> Param dec -> Bool) -> Eq (Param dec)
forall dec. Eq dec => Param dec -> Param dec -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall dec. Eq dec => Param dec -> Param dec -> Bool
== :: Param dec -> Param dec -> Bool
$c/= :: forall dec. Eq dec => Param dec -> Param dec -> Bool
/= :: Param dec -> Param dec -> Bool
Eq)
instance Foldable Param where
foldMap :: forall m a. Monoid m => (a -> m) -> Param a -> m
foldMap = (a -> m) -> Param a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
instance Functor Param where
fmap :: forall a b. (a -> b) -> Param a -> Param b
fmap = (a -> b) -> Param a -> Param b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Traversable Param where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Param a -> f (Param b)
traverse a -> f b
f (Param Attrs
attr VName
name a
dec) = Attrs -> VName -> b -> Param b
forall dec. Attrs -> VName -> dec -> Param dec
Param Attrs
attr VName
name (b -> Param b) -> f b -> f (Param b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
dec
data DimIndex d
=
DimFix d
|
DimSlice d d d
deriving (DimIndex d -> DimIndex d -> Bool
(DimIndex d -> DimIndex d -> Bool)
-> (DimIndex d -> DimIndex d -> Bool) -> Eq (DimIndex d)
forall d. Eq d => DimIndex d -> DimIndex d -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall d. Eq d => DimIndex d -> DimIndex d -> Bool
== :: DimIndex d -> DimIndex d -> Bool
$c/= :: forall d. Eq d => DimIndex d -> DimIndex d -> Bool
/= :: DimIndex d -> DimIndex d -> Bool
Eq, Eq (DimIndex d)
Eq (DimIndex d)
-> (DimIndex d -> DimIndex d -> Ordering)
-> (DimIndex d -> DimIndex d -> Bool)
-> (DimIndex d -> DimIndex d -> Bool)
-> (DimIndex d -> DimIndex d -> Bool)
-> (DimIndex d -> DimIndex d -> Bool)
-> (DimIndex d -> DimIndex d -> DimIndex d)
-> (DimIndex d -> DimIndex d -> DimIndex d)
-> Ord (DimIndex d)
DimIndex d -> DimIndex d -> Bool
DimIndex d -> DimIndex d -> Ordering
DimIndex d -> DimIndex d -> DimIndex d
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
forall {d}. Ord d => Eq (DimIndex d)
forall d. Ord d => DimIndex d -> DimIndex d -> Bool
forall d. Ord d => DimIndex d -> DimIndex d -> Ordering
forall d. Ord d => DimIndex d -> DimIndex d -> DimIndex d
$ccompare :: forall d. Ord d => DimIndex d -> DimIndex d -> Ordering
compare :: DimIndex d -> DimIndex d -> Ordering
$c< :: forall d. Ord d => DimIndex d -> DimIndex d -> Bool
< :: DimIndex d -> DimIndex d -> Bool
$c<= :: forall d. Ord d => DimIndex d -> DimIndex d -> Bool
<= :: DimIndex d -> DimIndex d -> Bool
$c> :: forall d. Ord d => DimIndex d -> DimIndex d -> Bool
> :: DimIndex d -> DimIndex d -> Bool
$c>= :: forall d. Ord d => DimIndex d -> DimIndex d -> Bool
>= :: DimIndex d -> DimIndex d -> Bool
$cmax :: forall d. Ord d => DimIndex d -> DimIndex d -> DimIndex d
max :: DimIndex d -> DimIndex d -> DimIndex d
$cmin :: forall d. Ord d => DimIndex d -> DimIndex d -> DimIndex d
min :: DimIndex d -> DimIndex d -> DimIndex d
Ord, Int -> DimIndex d -> ShowS
[DimIndex d] -> ShowS
DimIndex d -> String
(Int -> DimIndex d -> ShowS)
-> (DimIndex d -> String)
-> ([DimIndex d] -> ShowS)
-> Show (DimIndex d)
forall d. Show d => Int -> DimIndex d -> ShowS
forall d. Show d => [DimIndex d] -> ShowS
forall d. Show d => DimIndex d -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall d. Show d => Int -> DimIndex d -> ShowS
showsPrec :: Int -> DimIndex d -> ShowS
$cshow :: forall d. Show d => DimIndex d -> String
show :: DimIndex d -> String
$cshowList :: forall d. Show d => [DimIndex d] -> ShowS
showList :: [DimIndex d] -> ShowS
Show)
instance Functor DimIndex where
fmap :: forall a b. (a -> b) -> DimIndex a -> DimIndex b
fmap a -> b
f (DimFix a
i) = b -> DimIndex b
forall d. d -> DimIndex d
DimFix (b -> DimIndex b) -> b -> DimIndex b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
i
fmap a -> b
f (DimSlice a
i a
j a
s) = b -> b -> b -> DimIndex b
forall d. d -> d -> d -> DimIndex d
DimSlice (a -> b
f a
i) (a -> b
f a
j) (a -> b
f a
s)
instance Foldable DimIndex where
foldMap :: forall m a. Monoid m => (a -> m) -> DimIndex a -> m
foldMap a -> m
f (DimFix a
d) = a -> m
f a
d
foldMap a -> m
f (DimSlice a
i a
j a
s) = a -> m
f a
i m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
j m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
s
instance Traversable DimIndex where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> DimIndex a -> f (DimIndex b)
traverse a -> f b
f (DimFix a
d) = b -> DimIndex b
forall d. d -> DimIndex d
DimFix (b -> DimIndex b) -> f b -> f (DimIndex b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
d
traverse a -> f b
f (DimSlice a
i a
j a
s) = b -> b -> b -> DimIndex b
forall d. d -> d -> d -> DimIndex d
DimSlice (b -> b -> b -> DimIndex b) -> f b -> f (b -> b -> DimIndex b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
i f (b -> b -> DimIndex b) -> f b -> f (b -> DimIndex b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
j f (b -> DimIndex b) -> f b -> f (DimIndex b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
s
newtype Slice d = Slice {forall d. Slice d -> [DimIndex d]
unSlice :: [DimIndex d]}
deriving (Slice d -> Slice d -> Bool
(Slice d -> Slice d -> Bool)
-> (Slice d -> Slice d -> Bool) -> Eq (Slice d)
forall d. Eq d => Slice d -> Slice d -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall d. Eq d => Slice d -> Slice d -> Bool
== :: Slice d -> Slice d -> Bool
$c/= :: forall d. Eq d => Slice d -> Slice d -> Bool
/= :: Slice d -> Slice d -> Bool
Eq, Eq (Slice d)
Eq (Slice d)
-> (Slice d -> Slice d -> Ordering)
-> (Slice d -> Slice d -> Bool)
-> (Slice d -> Slice d -> Bool)
-> (Slice d -> Slice d -> Bool)
-> (Slice d -> Slice d -> Bool)
-> (Slice d -> Slice d -> Slice d)
-> (Slice d -> Slice d -> Slice d)
-> Ord (Slice d)
Slice d -> Slice d -> Bool
Slice d -> Slice d -> Ordering
Slice d -> Slice d -> Slice d
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
forall {d}. Ord d => Eq (Slice d)
forall d. Ord d => Slice d -> Slice d -> Bool
forall d. Ord d => Slice d -> Slice d -> Ordering
forall d. Ord d => Slice d -> Slice d -> Slice d
$ccompare :: forall d. Ord d => Slice d -> Slice d -> Ordering
compare :: Slice d -> Slice d -> Ordering
$c< :: forall d. Ord d => Slice d -> Slice d -> Bool
< :: Slice d -> Slice d -> Bool
$c<= :: forall d. Ord d => Slice d -> Slice d -> Bool
<= :: Slice d -> Slice d -> Bool
$c> :: forall d. Ord d => Slice d -> Slice d -> Bool
> :: Slice d -> Slice d -> Bool
$c>= :: forall d. Ord d => Slice d -> Slice d -> Bool
>= :: Slice d -> Slice d -> Bool
$cmax :: forall d. Ord d => Slice d -> Slice d -> Slice d
max :: Slice d -> Slice d -> Slice d
$cmin :: forall d. Ord d => Slice d -> Slice d -> Slice d
min :: Slice d -> Slice d -> Slice d
Ord, Int -> Slice d -> ShowS
[Slice d] -> ShowS
Slice d -> String
(Int -> Slice d -> ShowS)
-> (Slice d -> String) -> ([Slice d] -> ShowS) -> Show (Slice d)
forall d. Show d => Int -> Slice d -> ShowS
forall d. Show d => [Slice d] -> ShowS
forall d. Show d => Slice d -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall d. Show d => Int -> Slice d -> ShowS
showsPrec :: Int -> Slice d -> ShowS
$cshow :: forall d. Show d => Slice d -> String
show :: Slice d -> String
$cshowList :: forall d. Show d => [Slice d] -> ShowS
showList :: [Slice d] -> ShowS
Show)
instance Traversable Slice where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Slice a -> f (Slice b)
traverse a -> f b
f = ([DimIndex b] -> Slice b) -> f [DimIndex b] -> f (Slice b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [DimIndex b] -> Slice b
forall d. [DimIndex d] -> Slice d
Slice (f [DimIndex b] -> f (Slice b))
-> (Slice a -> f [DimIndex b]) -> Slice a -> f (Slice b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (DimIndex a -> f (DimIndex b)) -> [DimIndex a] -> f [DimIndex b]
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 ((a -> f b) -> DimIndex a -> f (DimIndex b)
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) -> DimIndex a -> f (DimIndex b)
traverse a -> f b
f) ([DimIndex a] -> f [DimIndex b])
-> (Slice a -> [DimIndex a]) -> Slice a -> f [DimIndex b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Slice a -> [DimIndex a]
forall d. Slice d -> [DimIndex d]
unSlice
instance Functor Slice where
fmap :: forall a b. (a -> b) -> Slice a -> Slice b
fmap = (a -> b) -> Slice a -> Slice b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Foldable Slice where
foldMap :: forall m a. Monoid m => (a -> m) -> Slice a -> m
foldMap = (a -> m) -> Slice a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
dimFix :: DimIndex d -> Maybe d
dimFix :: forall d. DimIndex d -> Maybe d
dimFix (DimFix d
d) = d -> Maybe d
forall a. a -> Maybe a
Just d
d
dimFix DimIndex d
_ = Maybe d
forall a. Maybe a
Nothing
sliceIndices :: Slice d -> Maybe [d]
sliceIndices :: forall d. Slice d -> Maybe [d]
sliceIndices = (DimIndex d -> Maybe d) -> [DimIndex d] -> Maybe [d]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM DimIndex d -> Maybe d
forall d. DimIndex d -> Maybe d
dimFix ([DimIndex d] -> Maybe [d])
-> (Slice d -> [DimIndex d]) -> Slice d -> Maybe [d]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Slice d -> [DimIndex d]
forall d. Slice d -> [DimIndex d]
unSlice
sliceDims :: Slice d -> [d]
sliceDims :: forall a. Slice a -> [a]
sliceDims = (DimIndex d -> Maybe d) -> [DimIndex d] -> [d]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe DimIndex d -> Maybe d
forall d. DimIndex d -> Maybe d
dimSlice ([DimIndex d] -> [d])
-> (Slice d -> [DimIndex d]) -> Slice d -> [d]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Slice d -> [DimIndex d]
forall d. Slice d -> [DimIndex d]
unSlice
where
dimSlice :: DimIndex a -> Maybe a
dimSlice (DimSlice a
_ a
d a
_) = a -> Maybe a
forall a. a -> Maybe a
Just a
d
dimSlice DimFix {} = Maybe a
forall a. Maybe a
Nothing
sliceShape :: Slice d -> ShapeBase d
sliceShape :: forall d. Slice d -> ShapeBase d
sliceShape = [d] -> ShapeBase d
forall d. [d] -> ShapeBase d
Shape ([d] -> ShapeBase d) -> (Slice d -> [d]) -> Slice d -> ShapeBase d
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Slice d -> [d]
forall a. Slice a -> [a]
sliceDims
unitSlice :: (Num d) => d -> d -> DimIndex d
unitSlice :: forall d. Num d => d -> d -> DimIndex d
unitSlice d
offset d
n = d -> d -> d -> DimIndex d
forall d. d -> d -> d -> DimIndex d
DimSlice d
offset d
n d
1
fixSlice :: (Num d) => Slice d -> [d] -> [d]
fixSlice :: forall d. Num d => Slice d -> [d] -> [d]
fixSlice = [DimIndex d] -> [d] -> [d]
forall {a}. Num a => [DimIndex a] -> [a] -> [a]
fixSlice' ([DimIndex d] -> [d] -> [d])
-> (Slice d -> [DimIndex d]) -> Slice d -> [d] -> [d]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Slice d -> [DimIndex d]
forall d. Slice d -> [DimIndex d]
unSlice
where
fixSlice' :: [DimIndex a] -> [a] -> [a]
fixSlice' (DimFix a
j : [DimIndex a]
mis') [a]
is' =
a
j a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [DimIndex a] -> [a] -> [a]
fixSlice' [DimIndex a]
mis' [a]
is'
fixSlice' (DimSlice a
orig_k a
_ a
orig_s : [DimIndex a]
mis') (a
i : [a]
is') =
(a
orig_k a -> a -> a
forall a. Num a => a -> a -> a
+ a
i a -> a -> a
forall a. Num a => a -> a -> a
* a
orig_s) a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [DimIndex a] -> [a] -> [a]
fixSlice' [DimIndex a]
mis' [a]
is'
fixSlice' [DimIndex a]
_ [a]
_ = []
sliceSlice :: (Num d) => Slice d -> Slice d -> Slice d
sliceSlice :: forall d. Num d => Slice d -> Slice d -> Slice d
sliceSlice (Slice [DimIndex d]
jslice) (Slice [DimIndex d]
islice) = [DimIndex d] -> Slice d
forall d. [DimIndex d] -> Slice d
Slice ([DimIndex d] -> Slice d) -> [DimIndex d] -> Slice d
forall a b. (a -> b) -> a -> b
$ [DimIndex d] -> [DimIndex d] -> [DimIndex d]
forall {d}. Num d => [DimIndex d] -> [DimIndex d] -> [DimIndex d]
sliceSlice' [DimIndex d]
jslice [DimIndex d]
islice
where
sliceSlice' :: [DimIndex d] -> [DimIndex d] -> [DimIndex d]
sliceSlice' (DimFix d
j : [DimIndex d]
js') [DimIndex d]
is' =
d -> DimIndex d
forall d. d -> DimIndex d
DimFix d
j DimIndex d -> [DimIndex d] -> [DimIndex d]
forall a. a -> [a] -> [a]
: [DimIndex d] -> [DimIndex d] -> [DimIndex d]
sliceSlice' [DimIndex d]
js' [DimIndex d]
is'
sliceSlice' (DimSlice d
j d
_ d
s : [DimIndex d]
js') (DimFix d
i : [DimIndex d]
is') =
d -> DimIndex d
forall d. d -> DimIndex d
DimFix (d
j d -> d -> d
forall a. Num a => a -> a -> a
+ (d
i d -> d -> d
forall a. Num a => a -> a -> a
* d
s)) DimIndex d -> [DimIndex d] -> [DimIndex d]
forall a. a -> [a] -> [a]
: [DimIndex d] -> [DimIndex d] -> [DimIndex d]
sliceSlice' [DimIndex d]
js' [DimIndex d]
is'
sliceSlice' (DimSlice d
j d
_ d
s0 : [DimIndex d]
js') (DimSlice d
i d
n d
s1 : [DimIndex d]
is') =
d -> d -> d -> DimIndex d
forall d. d -> d -> d -> DimIndex d
DimSlice (d
j d -> d -> d
forall a. Num a => a -> a -> a
+ (d
s0 d -> d -> d
forall a. Num a => a -> a -> a
* d
i)) d
n (d
s0 d -> d -> d
forall a. Num a => a -> a -> a
* d
s1) DimIndex d -> [DimIndex d] -> [DimIndex d]
forall a. a -> [a] -> [a]
: [DimIndex d] -> [DimIndex d] -> [DimIndex d]
sliceSlice' [DimIndex d]
js' [DimIndex d]
is'
sliceSlice' [DimIndex d]
_ [DimIndex d]
_ = []
data FlatDimIndex d
= FlatDimIndex
d
d
deriving (FlatDimIndex d -> FlatDimIndex d -> Bool
(FlatDimIndex d -> FlatDimIndex d -> Bool)
-> (FlatDimIndex d -> FlatDimIndex d -> Bool)
-> Eq (FlatDimIndex d)
forall d. Eq d => FlatDimIndex d -> FlatDimIndex d -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall d. Eq d => FlatDimIndex d -> FlatDimIndex d -> Bool
== :: FlatDimIndex d -> FlatDimIndex d -> Bool
$c/= :: forall d. Eq d => FlatDimIndex d -> FlatDimIndex d -> Bool
/= :: FlatDimIndex d -> FlatDimIndex d -> Bool
Eq, Eq (FlatDimIndex d)
Eq (FlatDimIndex d)
-> (FlatDimIndex d -> FlatDimIndex d -> Ordering)
-> (FlatDimIndex d -> FlatDimIndex d -> Bool)
-> (FlatDimIndex d -> FlatDimIndex d -> Bool)
-> (FlatDimIndex d -> FlatDimIndex d -> Bool)
-> (FlatDimIndex d -> FlatDimIndex d -> Bool)
-> (FlatDimIndex d -> FlatDimIndex d -> FlatDimIndex d)
-> (FlatDimIndex d -> FlatDimIndex d -> FlatDimIndex d)
-> Ord (FlatDimIndex d)
FlatDimIndex d -> FlatDimIndex d -> Bool
FlatDimIndex d -> FlatDimIndex d -> Ordering
FlatDimIndex d -> FlatDimIndex d -> FlatDimIndex d
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
forall {d}. Ord d => Eq (FlatDimIndex d)
forall d. Ord d => FlatDimIndex d -> FlatDimIndex d -> Bool
forall d. Ord d => FlatDimIndex d -> FlatDimIndex d -> Ordering
forall d.
Ord d =>
FlatDimIndex d -> FlatDimIndex d -> FlatDimIndex d
$ccompare :: forall d. Ord d => FlatDimIndex d -> FlatDimIndex d -> Ordering
compare :: FlatDimIndex d -> FlatDimIndex d -> Ordering
$c< :: forall d. Ord d => FlatDimIndex d -> FlatDimIndex d -> Bool
< :: FlatDimIndex d -> FlatDimIndex d -> Bool
$c<= :: forall d. Ord d => FlatDimIndex d -> FlatDimIndex d -> Bool
<= :: FlatDimIndex d -> FlatDimIndex d -> Bool
$c> :: forall d. Ord d => FlatDimIndex d -> FlatDimIndex d -> Bool
> :: FlatDimIndex d -> FlatDimIndex d -> Bool
$c>= :: forall d. Ord d => FlatDimIndex d -> FlatDimIndex d -> Bool
>= :: FlatDimIndex d -> FlatDimIndex d -> Bool
$cmax :: forall d.
Ord d =>
FlatDimIndex d -> FlatDimIndex d -> FlatDimIndex d
max :: FlatDimIndex d -> FlatDimIndex d -> FlatDimIndex d
$cmin :: forall d.
Ord d =>
FlatDimIndex d -> FlatDimIndex d -> FlatDimIndex d
min :: FlatDimIndex d -> FlatDimIndex d -> FlatDimIndex d
Ord, Int -> FlatDimIndex d -> ShowS
[FlatDimIndex d] -> ShowS
FlatDimIndex d -> String
(Int -> FlatDimIndex d -> ShowS)
-> (FlatDimIndex d -> String)
-> ([FlatDimIndex d] -> ShowS)
-> Show (FlatDimIndex d)
forall d. Show d => Int -> FlatDimIndex d -> ShowS
forall d. Show d => [FlatDimIndex d] -> ShowS
forall d. Show d => FlatDimIndex d -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall d. Show d => Int -> FlatDimIndex d -> ShowS
showsPrec :: Int -> FlatDimIndex d -> ShowS
$cshow :: forall d. Show d => FlatDimIndex d -> String
show :: FlatDimIndex d -> String
$cshowList :: forall d. Show d => [FlatDimIndex d] -> ShowS
showList :: [FlatDimIndex d] -> ShowS
Show)
instance Traversable FlatDimIndex where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FlatDimIndex a -> f (FlatDimIndex b)
traverse a -> f b
f (FlatDimIndex a
n a
s) = b -> b -> FlatDimIndex b
forall d. d -> d -> FlatDimIndex d
FlatDimIndex (b -> b -> FlatDimIndex b) -> f b -> f (b -> FlatDimIndex b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
n f (b -> FlatDimIndex b) -> f b -> f (FlatDimIndex b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
s
instance Functor FlatDimIndex where
fmap :: forall a b. (a -> b) -> FlatDimIndex a -> FlatDimIndex b
fmap = (a -> b) -> FlatDimIndex a -> FlatDimIndex b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Foldable FlatDimIndex where
foldMap :: forall m a. Monoid m => (a -> m) -> FlatDimIndex a -> m
foldMap = (a -> m) -> FlatDimIndex a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
data FlatSlice d = FlatSlice d [FlatDimIndex d]
deriving (FlatSlice d -> FlatSlice d -> Bool
(FlatSlice d -> FlatSlice d -> Bool)
-> (FlatSlice d -> FlatSlice d -> Bool) -> Eq (FlatSlice d)
forall d. Eq d => FlatSlice d -> FlatSlice d -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall d. Eq d => FlatSlice d -> FlatSlice d -> Bool
== :: FlatSlice d -> FlatSlice d -> Bool
$c/= :: forall d. Eq d => FlatSlice d -> FlatSlice d -> Bool
/= :: FlatSlice d -> FlatSlice d -> Bool
Eq, Eq (FlatSlice d)
Eq (FlatSlice d)
-> (FlatSlice d -> FlatSlice d -> Ordering)
-> (FlatSlice d -> FlatSlice d -> Bool)
-> (FlatSlice d -> FlatSlice d -> Bool)
-> (FlatSlice d -> FlatSlice d -> Bool)
-> (FlatSlice d -> FlatSlice d -> Bool)
-> (FlatSlice d -> FlatSlice d -> FlatSlice d)
-> (FlatSlice d -> FlatSlice d -> FlatSlice d)
-> Ord (FlatSlice d)
FlatSlice d -> FlatSlice d -> Bool
FlatSlice d -> FlatSlice d -> Ordering
FlatSlice d -> FlatSlice d -> FlatSlice d
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
forall {d}. Ord d => Eq (FlatSlice d)
forall d. Ord d => FlatSlice d -> FlatSlice d -> Bool
forall d. Ord d => FlatSlice d -> FlatSlice d -> Ordering
forall d. Ord d => FlatSlice d -> FlatSlice d -> FlatSlice d
$ccompare :: forall d. Ord d => FlatSlice d -> FlatSlice d -> Ordering
compare :: FlatSlice d -> FlatSlice d -> Ordering
$c< :: forall d. Ord d => FlatSlice d -> FlatSlice d -> Bool
< :: FlatSlice d -> FlatSlice d -> Bool
$c<= :: forall d. Ord d => FlatSlice d -> FlatSlice d -> Bool
<= :: FlatSlice d -> FlatSlice d -> Bool
$c> :: forall d. Ord d => FlatSlice d -> FlatSlice d -> Bool
> :: FlatSlice d -> FlatSlice d -> Bool
$c>= :: forall d. Ord d => FlatSlice d -> FlatSlice d -> Bool
>= :: FlatSlice d -> FlatSlice d -> Bool
$cmax :: forall d. Ord d => FlatSlice d -> FlatSlice d -> FlatSlice d
max :: FlatSlice d -> FlatSlice d -> FlatSlice d
$cmin :: forall d. Ord d => FlatSlice d -> FlatSlice d -> FlatSlice d
min :: FlatSlice d -> FlatSlice d -> FlatSlice d
Ord, Int -> FlatSlice d -> ShowS
[FlatSlice d] -> ShowS
FlatSlice d -> String
(Int -> FlatSlice d -> ShowS)
-> (FlatSlice d -> String)
-> ([FlatSlice d] -> ShowS)
-> Show (FlatSlice d)
forall d. Show d => Int -> FlatSlice d -> ShowS
forall d. Show d => [FlatSlice d] -> ShowS
forall d. Show d => FlatSlice d -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall d. Show d => Int -> FlatSlice d -> ShowS
showsPrec :: Int -> FlatSlice d -> ShowS
$cshow :: forall d. Show d => FlatSlice d -> String
show :: FlatSlice d -> String
$cshowList :: forall d. Show d => [FlatSlice d] -> ShowS
showList :: [FlatSlice d] -> ShowS
Show)
instance Traversable FlatSlice where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> FlatSlice a -> f (FlatSlice b)
traverse a -> f b
f (FlatSlice a
offset [FlatDimIndex a]
is) =
b -> [FlatDimIndex b] -> FlatSlice b
forall d. d -> [FlatDimIndex d] -> FlatSlice d
FlatSlice (b -> [FlatDimIndex b] -> FlatSlice b)
-> f b -> f ([FlatDimIndex b] -> FlatSlice b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
offset f ([FlatDimIndex b] -> FlatSlice b)
-> f [FlatDimIndex b] -> f (FlatSlice b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (FlatDimIndex a -> f (FlatDimIndex b))
-> [FlatDimIndex a] -> f [FlatDimIndex b]
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 ((a -> f b) -> FlatDimIndex a -> f (FlatDimIndex b)
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) -> FlatDimIndex a -> f (FlatDimIndex b)
traverse a -> f b
f) [FlatDimIndex a]
is
instance Functor FlatSlice where
fmap :: forall a b. (a -> b) -> FlatSlice a -> FlatSlice b
fmap = (a -> b) -> FlatSlice a -> FlatSlice b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Foldable FlatSlice where
foldMap :: forall m a. Monoid m => (a -> m) -> FlatSlice a -> m
foldMap = (a -> m) -> FlatSlice a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
flatSliceDims :: FlatSlice d -> [d]
flatSliceDims :: forall a. FlatSlice a -> [a]
flatSliceDims (FlatSlice d
_ [FlatDimIndex d]
ds) = (FlatDimIndex d -> d) -> [FlatDimIndex d] -> [d]
forall a b. (a -> b) -> [a] -> [b]
map FlatDimIndex d -> d
forall {d}. FlatDimIndex d -> d
dimSlice [FlatDimIndex d]
ds
where
dimSlice :: FlatDimIndex d -> d
dimSlice (FlatDimIndex d
n d
_) = d
n
flatSliceStrides :: FlatSlice d -> [d]
flatSliceStrides :: forall a. FlatSlice a -> [a]
flatSliceStrides (FlatSlice d
_ [FlatDimIndex d]
ds) = (FlatDimIndex d -> d) -> [FlatDimIndex d] -> [d]
forall a b. (a -> b) -> [a] -> [b]
map FlatDimIndex d -> d
forall {d}. FlatDimIndex d -> d
dimStride [FlatDimIndex d]
ds
where
dimStride :: FlatDimIndex d -> d
dimStride (FlatDimIndex d
_ d
s) = d
s
data PatElem dec = PatElem
{
forall dec. PatElem dec -> VName
patElemName :: VName,
forall dec. PatElem dec -> dec
patElemDec :: dec
}
deriving (Eq (PatElem dec)
Eq (PatElem dec)
-> (PatElem dec -> PatElem dec -> Ordering)
-> (PatElem dec -> PatElem dec -> Bool)
-> (PatElem dec -> PatElem dec -> Bool)
-> (PatElem dec -> PatElem dec -> Bool)
-> (PatElem dec -> PatElem dec -> Bool)
-> (PatElem dec -> PatElem dec -> PatElem dec)
-> (PatElem dec -> PatElem dec -> PatElem dec)
-> Ord (PatElem dec)
PatElem dec -> PatElem dec -> Bool
PatElem dec -> PatElem dec -> Ordering
PatElem dec -> PatElem dec -> PatElem dec
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
forall {dec}. Ord dec => Eq (PatElem dec)
forall dec. Ord dec => PatElem dec -> PatElem dec -> Bool
forall dec. Ord dec => PatElem dec -> PatElem dec -> Ordering
forall dec. Ord dec => PatElem dec -> PatElem dec -> PatElem dec
$ccompare :: forall dec. Ord dec => PatElem dec -> PatElem dec -> Ordering
compare :: PatElem dec -> PatElem dec -> Ordering
$c< :: forall dec. Ord dec => PatElem dec -> PatElem dec -> Bool
< :: PatElem dec -> PatElem dec -> Bool
$c<= :: forall dec. Ord dec => PatElem dec -> PatElem dec -> Bool
<= :: PatElem dec -> PatElem dec -> Bool
$c> :: forall dec. Ord dec => PatElem dec -> PatElem dec -> Bool
> :: PatElem dec -> PatElem dec -> Bool
$c>= :: forall dec. Ord dec => PatElem dec -> PatElem dec -> Bool
>= :: PatElem dec -> PatElem dec -> Bool
$cmax :: forall dec. Ord dec => PatElem dec -> PatElem dec -> PatElem dec
max :: PatElem dec -> PatElem dec -> PatElem dec
$cmin :: forall dec. Ord dec => PatElem dec -> PatElem dec -> PatElem dec
min :: PatElem dec -> PatElem dec -> PatElem dec
Ord, Int -> PatElem dec -> ShowS
[PatElem dec] -> ShowS
PatElem dec -> String
(Int -> PatElem dec -> ShowS)
-> (PatElem dec -> String)
-> ([PatElem dec] -> ShowS)
-> Show (PatElem dec)
forall dec. Show dec => Int -> PatElem dec -> ShowS
forall dec. Show dec => [PatElem dec] -> ShowS
forall dec. Show dec => PatElem dec -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall dec. Show dec => Int -> PatElem dec -> ShowS
showsPrec :: Int -> PatElem dec -> ShowS
$cshow :: forall dec. Show dec => PatElem dec -> String
show :: PatElem dec -> String
$cshowList :: forall dec. Show dec => [PatElem dec] -> ShowS
showList :: [PatElem dec] -> ShowS
Show, PatElem dec -> PatElem dec -> Bool
(PatElem dec -> PatElem dec -> Bool)
-> (PatElem dec -> PatElem dec -> Bool) -> Eq (PatElem dec)
forall dec. Eq dec => PatElem dec -> PatElem dec -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall dec. Eq dec => PatElem dec -> PatElem dec -> Bool
== :: PatElem dec -> PatElem dec -> Bool
$c/= :: forall dec. Eq dec => PatElem dec -> PatElem dec -> Bool
/= :: PatElem dec -> PatElem dec -> Bool
Eq)
instance Functor PatElem where
fmap :: forall a b. (a -> b) -> PatElem a -> PatElem b
fmap = (a -> b) -> PatElem a -> PatElem b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Foldable PatElem where
foldMap :: forall m a. Monoid m => (a -> m) -> PatElem a -> m
foldMap = (a -> m) -> PatElem a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
instance Traversable PatElem where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> PatElem a -> f (PatElem b)
traverse a -> f b
f (PatElem VName
name a
dec) =
VName -> b -> PatElem b
forall dec. VName -> dec -> PatElem dec
PatElem VName
name (b -> PatElem b) -> f b -> f (PatElem b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
dec
newtype ErrorMsg a = ErrorMsg [ErrorMsgPart a]
deriving (ErrorMsg a -> ErrorMsg a -> Bool
(ErrorMsg a -> ErrorMsg a -> Bool)
-> (ErrorMsg a -> ErrorMsg a -> Bool) -> Eq (ErrorMsg a)
forall a. Eq a => ErrorMsg a -> ErrorMsg a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => ErrorMsg a -> ErrorMsg a -> Bool
== :: ErrorMsg a -> ErrorMsg a -> Bool
$c/= :: forall a. Eq a => ErrorMsg a -> ErrorMsg a -> Bool
/= :: ErrorMsg a -> ErrorMsg a -> Bool
Eq, Eq (ErrorMsg a)
Eq (ErrorMsg a)
-> (ErrorMsg a -> ErrorMsg a -> Ordering)
-> (ErrorMsg a -> ErrorMsg a -> Bool)
-> (ErrorMsg a -> ErrorMsg a -> Bool)
-> (ErrorMsg a -> ErrorMsg a -> Bool)
-> (ErrorMsg a -> ErrorMsg a -> Bool)
-> (ErrorMsg a -> ErrorMsg a -> ErrorMsg a)
-> (ErrorMsg a -> ErrorMsg a -> ErrorMsg a)
-> Ord (ErrorMsg a)
ErrorMsg a -> ErrorMsg a -> Bool
ErrorMsg a -> ErrorMsg a -> Ordering
ErrorMsg a -> ErrorMsg a -> ErrorMsg a
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
forall {a}. Ord a => Eq (ErrorMsg a)
forall a. Ord a => ErrorMsg a -> ErrorMsg a -> Bool
forall a. Ord a => ErrorMsg a -> ErrorMsg a -> Ordering
forall a. Ord a => ErrorMsg a -> ErrorMsg a -> ErrorMsg a
$ccompare :: forall a. Ord a => ErrorMsg a -> ErrorMsg a -> Ordering
compare :: ErrorMsg a -> ErrorMsg a -> Ordering
$c< :: forall a. Ord a => ErrorMsg a -> ErrorMsg a -> Bool
< :: ErrorMsg a -> ErrorMsg a -> Bool
$c<= :: forall a. Ord a => ErrorMsg a -> ErrorMsg a -> Bool
<= :: ErrorMsg a -> ErrorMsg a -> Bool
$c> :: forall a. Ord a => ErrorMsg a -> ErrorMsg a -> Bool
> :: ErrorMsg a -> ErrorMsg a -> Bool
$c>= :: forall a. Ord a => ErrorMsg a -> ErrorMsg a -> Bool
>= :: ErrorMsg a -> ErrorMsg a -> Bool
$cmax :: forall a. Ord a => ErrorMsg a -> ErrorMsg a -> ErrorMsg a
max :: ErrorMsg a -> ErrorMsg a -> ErrorMsg a
$cmin :: forall a. Ord a => ErrorMsg a -> ErrorMsg a -> ErrorMsg a
min :: ErrorMsg a -> ErrorMsg a -> ErrorMsg a
Ord, Int -> ErrorMsg a -> ShowS
[ErrorMsg a] -> ShowS
ErrorMsg a -> String
(Int -> ErrorMsg a -> ShowS)
-> (ErrorMsg a -> String)
-> ([ErrorMsg a] -> ShowS)
-> Show (ErrorMsg a)
forall a. Show a => Int -> ErrorMsg a -> ShowS
forall a. Show a => [ErrorMsg a] -> ShowS
forall a. Show a => ErrorMsg a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> ErrorMsg a -> ShowS
showsPrec :: Int -> ErrorMsg a -> ShowS
$cshow :: forall a. Show a => ErrorMsg a -> String
show :: ErrorMsg a -> String
$cshowList :: forall a. Show a => [ErrorMsg a] -> ShowS
showList :: [ErrorMsg a] -> ShowS
Show)
instance IsString (ErrorMsg a) where
fromString :: String -> ErrorMsg a
fromString = [ErrorMsgPart a] -> ErrorMsg a
forall a. [ErrorMsgPart a] -> ErrorMsg a
ErrorMsg ([ErrorMsgPart a] -> ErrorMsg a)
-> (String -> [ErrorMsgPart a]) -> String -> ErrorMsg a
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ErrorMsgPart a -> [ErrorMsgPart a]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ErrorMsgPart a -> [ErrorMsgPart a])
-> (String -> ErrorMsgPart a) -> String -> [ErrorMsgPart a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ErrorMsgPart a
forall a. IsString a => String -> a
fromString
data ErrorMsgPart a
=
ErrorString T.Text
|
ErrorVal PrimType a
deriving (ErrorMsgPart a -> ErrorMsgPart a -> Bool
(ErrorMsgPart a -> ErrorMsgPart a -> Bool)
-> (ErrorMsgPart a -> ErrorMsgPart a -> Bool)
-> Eq (ErrorMsgPart a)
forall a. Eq a => ErrorMsgPart a -> ErrorMsgPart a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => ErrorMsgPart a -> ErrorMsgPart a -> Bool
== :: ErrorMsgPart a -> ErrorMsgPart a -> Bool
$c/= :: forall a. Eq a => ErrorMsgPart a -> ErrorMsgPart a -> Bool
/= :: ErrorMsgPart a -> ErrorMsgPart a -> Bool
Eq, Eq (ErrorMsgPart a)
Eq (ErrorMsgPart a)
-> (ErrorMsgPart a -> ErrorMsgPart a -> Ordering)
-> (ErrorMsgPart a -> ErrorMsgPart a -> Bool)
-> (ErrorMsgPart a -> ErrorMsgPart a -> Bool)
-> (ErrorMsgPart a -> ErrorMsgPart a -> Bool)
-> (ErrorMsgPart a -> ErrorMsgPart a -> Bool)
-> (ErrorMsgPart a -> ErrorMsgPart a -> ErrorMsgPart a)
-> (ErrorMsgPart a -> ErrorMsgPart a -> ErrorMsgPart a)
-> Ord (ErrorMsgPart a)
ErrorMsgPart a -> ErrorMsgPart a -> Bool
ErrorMsgPart a -> ErrorMsgPart a -> Ordering
ErrorMsgPart a -> ErrorMsgPart a -> ErrorMsgPart a
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
forall {a}. Ord a => Eq (ErrorMsgPart a)
forall a. Ord a => ErrorMsgPart a -> ErrorMsgPart a -> Bool
forall a. Ord a => ErrorMsgPart a -> ErrorMsgPart a -> Ordering
forall a.
Ord a =>
ErrorMsgPart a -> ErrorMsgPart a -> ErrorMsgPart a
$ccompare :: forall a. Ord a => ErrorMsgPart a -> ErrorMsgPart a -> Ordering
compare :: ErrorMsgPart a -> ErrorMsgPart a -> Ordering
$c< :: forall a. Ord a => ErrorMsgPart a -> ErrorMsgPart a -> Bool
< :: ErrorMsgPart a -> ErrorMsgPart a -> Bool
$c<= :: forall a. Ord a => ErrorMsgPart a -> ErrorMsgPart a -> Bool
<= :: ErrorMsgPart a -> ErrorMsgPart a -> Bool
$c> :: forall a. Ord a => ErrorMsgPart a -> ErrorMsgPart a -> Bool
> :: ErrorMsgPart a -> ErrorMsgPart a -> Bool
$c>= :: forall a. Ord a => ErrorMsgPart a -> ErrorMsgPart a -> Bool
>= :: ErrorMsgPart a -> ErrorMsgPart a -> Bool
$cmax :: forall a.
Ord a =>
ErrorMsgPart a -> ErrorMsgPart a -> ErrorMsgPart a
max :: ErrorMsgPart a -> ErrorMsgPart a -> ErrorMsgPart a
$cmin :: forall a.
Ord a =>
ErrorMsgPart a -> ErrorMsgPart a -> ErrorMsgPart a
min :: ErrorMsgPart a -> ErrorMsgPart a -> ErrorMsgPart a
Ord, Int -> ErrorMsgPart a -> ShowS
[ErrorMsgPart a] -> ShowS
ErrorMsgPart a -> String
(Int -> ErrorMsgPart a -> ShowS)
-> (ErrorMsgPart a -> String)
-> ([ErrorMsgPart a] -> ShowS)
-> Show (ErrorMsgPart a)
forall a. Show a => Int -> ErrorMsgPart a -> ShowS
forall a. Show a => [ErrorMsgPart a] -> ShowS
forall a. Show a => ErrorMsgPart a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> ErrorMsgPart a -> ShowS
showsPrec :: Int -> ErrorMsgPart a -> ShowS
$cshow :: forall a. Show a => ErrorMsgPart a -> String
show :: ErrorMsgPart a -> String
$cshowList :: forall a. Show a => [ErrorMsgPart a] -> ShowS
showList :: [ErrorMsgPart a] -> ShowS
Show)
instance IsString (ErrorMsgPart a) where
fromString :: String -> ErrorMsgPart a
fromString = Text -> ErrorMsgPart a
forall a. Text -> ErrorMsgPart a
ErrorString (Text -> ErrorMsgPart a)
-> (String -> Text) -> String -> ErrorMsgPart a
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Text
T.pack
instance Functor ErrorMsg where
fmap :: forall a b. (a -> b) -> ErrorMsg a -> ErrorMsg b
fmap a -> b
f (ErrorMsg [ErrorMsgPart a]
parts) = [ErrorMsgPart b] -> ErrorMsg b
forall a. [ErrorMsgPart a] -> ErrorMsg a
ErrorMsg ([ErrorMsgPart b] -> ErrorMsg b) -> [ErrorMsgPart b] -> ErrorMsg b
forall a b. (a -> b) -> a -> b
$ (ErrorMsgPart a -> ErrorMsgPart b)
-> [ErrorMsgPart a] -> [ErrorMsgPart b]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> ErrorMsgPart a -> ErrorMsgPart b
forall a b. (a -> b) -> ErrorMsgPart a -> ErrorMsgPart b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) [ErrorMsgPart a]
parts
instance Foldable ErrorMsg where
foldMap :: forall m a. Monoid m => (a -> m) -> ErrorMsg a -> m
foldMap a -> m
f (ErrorMsg [ErrorMsgPart a]
parts) = (ErrorMsgPart a -> m) -> [ErrorMsgPart a] -> m
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((a -> m) -> ErrorMsgPart a -> m
forall m a. Monoid m => (a -> m) -> ErrorMsgPart a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f) [ErrorMsgPart a]
parts
instance Traversable ErrorMsg where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ErrorMsg a -> f (ErrorMsg b)
traverse a -> f b
f (ErrorMsg [ErrorMsgPart a]
parts) = [ErrorMsgPart b] -> ErrorMsg b
forall a. [ErrorMsgPart a] -> ErrorMsg a
ErrorMsg ([ErrorMsgPart b] -> ErrorMsg b)
-> f [ErrorMsgPart b] -> f (ErrorMsg b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ErrorMsgPart a -> f (ErrorMsgPart b))
-> [ErrorMsgPart a] -> f [ErrorMsgPart b]
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 ((a -> f b) -> ErrorMsgPart a -> f (ErrorMsgPart b)
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) -> ErrorMsgPart a -> f (ErrorMsgPart b)
traverse a -> f b
f) [ErrorMsgPart a]
parts
instance Functor ErrorMsgPart where
fmap :: forall a b. (a -> b) -> ErrorMsgPart a -> ErrorMsgPart b
fmap = (a -> b) -> ErrorMsgPart a -> ErrorMsgPart b
forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault
instance Foldable ErrorMsgPart where
foldMap :: forall m a. Monoid m => (a -> m) -> ErrorMsgPart a -> m
foldMap = (a -> m) -> ErrorMsgPart a -> m
forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault
instance Traversable ErrorMsgPart where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ErrorMsgPart a -> f (ErrorMsgPart b)
traverse a -> f b
_ (ErrorString Text
s) = ErrorMsgPart b -> f (ErrorMsgPart b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ErrorMsgPart b -> f (ErrorMsgPart b))
-> ErrorMsgPart b -> f (ErrorMsgPart b)
forall a b. (a -> b) -> a -> b
$ Text -> ErrorMsgPart b
forall a. Text -> ErrorMsgPart a
ErrorString Text
s
traverse a -> f b
f (ErrorVal PrimType
t a
a) = PrimType -> b -> ErrorMsgPart b
forall a. PrimType -> a -> ErrorMsgPart a
ErrorVal PrimType
t (b -> ErrorMsgPart b) -> f b -> f (ErrorMsgPart b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a
errorMsgArgTypes :: ErrorMsg a -> [PrimType]
errorMsgArgTypes :: forall a. ErrorMsg a -> [PrimType]
errorMsgArgTypes (ErrorMsg [ErrorMsgPart a]
parts) = (ErrorMsgPart a -> Maybe PrimType)
-> [ErrorMsgPart a] -> [PrimType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ErrorMsgPart a -> Maybe PrimType
forall {a}. ErrorMsgPart a -> Maybe PrimType
onPart [ErrorMsgPart a]
parts
where
onPart :: ErrorMsgPart a -> Maybe PrimType
onPart ErrorString {} = Maybe PrimType
forall a. Maybe a
Nothing
onPart (ErrorVal PrimType
t a
_) = PrimType -> Maybe PrimType
forall a. a -> Maybe a
Just PrimType
t
data Attr
= AttrName Name
| AttrInt Integer
| AttrComp Name [Attr]
deriving (Eq Attr
Eq Attr
-> (Attr -> Attr -> Ordering)
-> (Attr -> Attr -> Bool)
-> (Attr -> Attr -> Bool)
-> (Attr -> Attr -> Bool)
-> (Attr -> Attr -> Bool)
-> (Attr -> Attr -> Attr)
-> (Attr -> Attr -> Attr)
-> Ord Attr
Attr -> Attr -> Bool
Attr -> Attr -> Ordering
Attr -> Attr -> Attr
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 :: Attr -> Attr -> Ordering
compare :: Attr -> Attr -> Ordering
$c< :: Attr -> Attr -> Bool
< :: Attr -> Attr -> Bool
$c<= :: Attr -> Attr -> Bool
<= :: Attr -> Attr -> Bool
$c> :: Attr -> Attr -> Bool
> :: Attr -> Attr -> Bool
$c>= :: Attr -> Attr -> Bool
>= :: Attr -> Attr -> Bool
$cmax :: Attr -> Attr -> Attr
max :: Attr -> Attr -> Attr
$cmin :: Attr -> Attr -> Attr
min :: Attr -> Attr -> Attr
Ord, Int -> Attr -> ShowS
[Attr] -> ShowS
Attr -> String
(Int -> Attr -> ShowS)
-> (Attr -> String) -> ([Attr] -> ShowS) -> Show Attr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Attr -> ShowS
showsPrec :: Int -> Attr -> ShowS
$cshow :: Attr -> String
show :: Attr -> String
$cshowList :: [Attr] -> ShowS
showList :: [Attr] -> ShowS
Show, Attr -> Attr -> Bool
(Attr -> Attr -> Bool) -> (Attr -> Attr -> Bool) -> Eq Attr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Attr -> Attr -> Bool
== :: Attr -> Attr -> Bool
$c/= :: Attr -> Attr -> Bool
/= :: Attr -> Attr -> Bool
Eq)
instance IsString Attr where
fromString :: String -> Attr
fromString = Name -> Attr
AttrName (Name -> Attr) -> (String -> Name) -> String -> Attr
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Name
forall a. IsString a => String -> a
fromString
newtype Attrs = Attrs {Attrs -> Set Attr
unAttrs :: S.Set Attr}
deriving (Eq Attrs
Eq Attrs
-> (Attrs -> Attrs -> Ordering)
-> (Attrs -> Attrs -> Bool)
-> (Attrs -> Attrs -> Bool)
-> (Attrs -> Attrs -> Bool)
-> (Attrs -> Attrs -> Bool)
-> (Attrs -> Attrs -> Attrs)
-> (Attrs -> Attrs -> Attrs)
-> Ord Attrs
Attrs -> Attrs -> Bool
Attrs -> Attrs -> Ordering
Attrs -> Attrs -> Attrs
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 :: Attrs -> Attrs -> Ordering
compare :: Attrs -> Attrs -> Ordering
$c< :: Attrs -> Attrs -> Bool
< :: Attrs -> Attrs -> Bool
$c<= :: Attrs -> Attrs -> Bool
<= :: Attrs -> Attrs -> Bool
$c> :: Attrs -> Attrs -> Bool
> :: Attrs -> Attrs -> Bool
$c>= :: Attrs -> Attrs -> Bool
>= :: Attrs -> Attrs -> Bool
$cmax :: Attrs -> Attrs -> Attrs
max :: Attrs -> Attrs -> Attrs
$cmin :: Attrs -> Attrs -> Attrs
min :: Attrs -> Attrs -> Attrs
Ord, Int -> Attrs -> ShowS
[Attrs] -> ShowS
Attrs -> String
(Int -> Attrs -> ShowS)
-> (Attrs -> String) -> ([Attrs] -> ShowS) -> Show Attrs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Attrs -> ShowS
showsPrec :: Int -> Attrs -> ShowS
$cshow :: Attrs -> String
show :: Attrs -> String
$cshowList :: [Attrs] -> ShowS
showList :: [Attrs] -> ShowS
Show, Attrs -> Attrs -> Bool
(Attrs -> Attrs -> Bool) -> (Attrs -> Attrs -> Bool) -> Eq Attrs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Attrs -> Attrs -> Bool
== :: Attrs -> Attrs -> Bool
$c/= :: Attrs -> Attrs -> Bool
/= :: Attrs -> Attrs -> Bool
Eq, Semigroup Attrs
Attrs
Semigroup Attrs
-> Attrs
-> (Attrs -> Attrs -> Attrs)
-> ([Attrs] -> Attrs)
-> Monoid Attrs
[Attrs] -> Attrs
Attrs -> Attrs -> Attrs
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: Attrs
mempty :: Attrs
$cmappend :: Attrs -> Attrs -> Attrs
mappend :: Attrs -> Attrs -> Attrs
$cmconcat :: [Attrs] -> Attrs
mconcat :: [Attrs] -> Attrs
Monoid, NonEmpty Attrs -> Attrs
Attrs -> Attrs -> Attrs
(Attrs -> Attrs -> Attrs)
-> (NonEmpty Attrs -> Attrs)
-> (forall b. Integral b => b -> Attrs -> Attrs)
-> Semigroup Attrs
forall b. Integral b => b -> Attrs -> Attrs
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Attrs -> Attrs -> Attrs
<> :: Attrs -> Attrs -> Attrs
$csconcat :: NonEmpty Attrs -> Attrs
sconcat :: NonEmpty Attrs -> Attrs
$cstimes :: forall b. Integral b => b -> Attrs -> Attrs
stimes :: forall b. Integral b => b -> Attrs -> Attrs
Semigroup)
oneAttr :: Attr -> Attrs
oneAttr :: Attr -> Attrs
oneAttr = Set Attr -> Attrs
Attrs (Set Attr -> Attrs) -> (Attr -> Set Attr) -> Attr -> Attrs
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Attr -> Set Attr
forall a. a -> Set a
S.singleton
inAttrs :: Attr -> Attrs -> Bool
inAttrs :: Attr -> Attrs -> Bool
inAttrs Attr
attr (Attrs Set Attr
attrs) = Attr
attr Attr -> Set Attr -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Set Attr
attrs
withoutAttrs :: Attrs -> Attrs -> Attrs
withoutAttrs :: Attrs -> Attrs -> Attrs
withoutAttrs (Attrs Set Attr
x) (Attrs Set Attr
y) = Set Attr -> Attrs
Attrs (Set Attr -> Attrs) -> Set Attr -> Attrs
forall a b. (a -> b) -> a -> b
$ Set Attr
x Set Attr -> Set Attr -> Set Attr
forall a. Ord a => Set a -> Set a -> Set a
`S.difference` Set Attr
y
mapAttrs :: (Attr -> a) -> Attrs -> [a]
mapAttrs :: forall a. (Attr -> a) -> Attrs -> [a]
mapAttrs Attr -> a
f (Attrs Set Attr
attrs) = (Attr -> a) -> [Attr] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Attr -> a
f ([Attr] -> [a]) -> [Attr] -> [a]
forall a b. (a -> b) -> a -> b
$ Set Attr -> [Attr]
forall a. Set a -> [a]
S.toList Set Attr
attrs
data Signedness
= Unsigned
| Signed
deriving (Signedness -> Signedness -> Bool
(Signedness -> Signedness -> Bool)
-> (Signedness -> Signedness -> Bool) -> Eq Signedness
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Signedness -> Signedness -> Bool
== :: Signedness -> Signedness -> Bool
$c/= :: Signedness -> Signedness -> Bool
/= :: Signedness -> Signedness -> Bool
Eq, Eq Signedness
Eq Signedness
-> (Signedness -> Signedness -> Ordering)
-> (Signedness -> Signedness -> Bool)
-> (Signedness -> Signedness -> Bool)
-> (Signedness -> Signedness -> Bool)
-> (Signedness -> Signedness -> Bool)
-> (Signedness -> Signedness -> Signedness)
-> (Signedness -> Signedness -> Signedness)
-> Ord Signedness
Signedness -> Signedness -> Bool
Signedness -> Signedness -> Ordering
Signedness -> Signedness -> Signedness
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 :: Signedness -> Signedness -> Ordering
compare :: Signedness -> Signedness -> Ordering
$c< :: Signedness -> Signedness -> Bool
< :: Signedness -> Signedness -> Bool
$c<= :: Signedness -> Signedness -> Bool
<= :: Signedness -> Signedness -> Bool
$c> :: Signedness -> Signedness -> Bool
> :: Signedness -> Signedness -> Bool
$c>= :: Signedness -> Signedness -> Bool
>= :: Signedness -> Signedness -> Bool
$cmax :: Signedness -> Signedness -> Signedness
max :: Signedness -> Signedness -> Signedness
$cmin :: Signedness -> Signedness -> Signedness
min :: Signedness -> Signedness -> Signedness
Ord, Int -> Signedness -> ShowS
[Signedness] -> ShowS
Signedness -> String
(Int -> Signedness -> ShowS)
-> (Signedness -> String)
-> ([Signedness] -> ShowS)
-> Show Signedness
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Signedness -> ShowS
showsPrec :: Int -> Signedness -> ShowS
$cshow :: Signedness -> String
show :: Signedness -> String
$cshowList :: [Signedness] -> ShowS
showList :: [Signedness] -> ShowS
Show)
data ValueType
= ValueType Signedness Rank PrimType
deriving (ValueType -> ValueType -> Bool
(ValueType -> ValueType -> Bool)
-> (ValueType -> ValueType -> Bool) -> Eq ValueType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValueType -> ValueType -> Bool
== :: ValueType -> ValueType -> Bool
$c/= :: ValueType -> ValueType -> Bool
/= :: ValueType -> ValueType -> Bool
Eq, Eq ValueType
Eq ValueType
-> (ValueType -> ValueType -> Ordering)
-> (ValueType -> ValueType -> Bool)
-> (ValueType -> ValueType -> Bool)
-> (ValueType -> ValueType -> Bool)
-> (ValueType -> ValueType -> Bool)
-> (ValueType -> ValueType -> ValueType)
-> (ValueType -> ValueType -> ValueType)
-> Ord ValueType
ValueType -> ValueType -> Bool
ValueType -> ValueType -> Ordering
ValueType -> ValueType -> ValueType
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 :: ValueType -> ValueType -> Ordering
compare :: ValueType -> ValueType -> Ordering
$c< :: ValueType -> ValueType -> Bool
< :: ValueType -> ValueType -> Bool
$c<= :: ValueType -> ValueType -> Bool
<= :: ValueType -> ValueType -> Bool
$c> :: ValueType -> ValueType -> Bool
> :: ValueType -> ValueType -> Bool
$c>= :: ValueType -> ValueType -> Bool
>= :: ValueType -> ValueType -> Bool
$cmax :: ValueType -> ValueType -> ValueType
max :: ValueType -> ValueType -> ValueType
$cmin :: ValueType -> ValueType -> ValueType
min :: ValueType -> ValueType -> ValueType
Ord, Int -> ValueType -> ShowS
[ValueType] -> ShowS
ValueType -> String
(Int -> ValueType -> ShowS)
-> (ValueType -> String)
-> ([ValueType] -> ShowS)
-> Show ValueType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValueType -> ShowS
showsPrec :: Int -> ValueType -> ShowS
$cshow :: ValueType -> String
show :: ValueType -> String
$cshowList :: [ValueType] -> ShowS
showList :: [ValueType] -> ShowS
Show)
data EntryPointType
=
TypeOpaque Name
|
TypeTransparent ValueType
deriving (EntryPointType -> EntryPointType -> Bool
(EntryPointType -> EntryPointType -> Bool)
-> (EntryPointType -> EntryPointType -> Bool) -> Eq EntryPointType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EntryPointType -> EntryPointType -> Bool
== :: EntryPointType -> EntryPointType -> Bool
$c/= :: EntryPointType -> EntryPointType -> Bool
/= :: EntryPointType -> EntryPointType -> Bool
Eq, Int -> EntryPointType -> ShowS
[EntryPointType] -> ShowS
EntryPointType -> String
(Int -> EntryPointType -> ShowS)
-> (EntryPointType -> String)
-> ([EntryPointType] -> ShowS)
-> Show EntryPointType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EntryPointType -> ShowS
showsPrec :: Int -> EntryPointType -> ShowS
$cshow :: EntryPointType -> String
show :: EntryPointType -> String
$cshowList :: [EntryPointType] -> ShowS
showList :: [EntryPointType] -> ShowS
Show, Eq EntryPointType
Eq EntryPointType
-> (EntryPointType -> EntryPointType -> Ordering)
-> (EntryPointType -> EntryPointType -> Bool)
-> (EntryPointType -> EntryPointType -> Bool)
-> (EntryPointType -> EntryPointType -> Bool)
-> (EntryPointType -> EntryPointType -> Bool)
-> (EntryPointType -> EntryPointType -> EntryPointType)
-> (EntryPointType -> EntryPointType -> EntryPointType)
-> Ord EntryPointType
EntryPointType -> EntryPointType -> Bool
EntryPointType -> EntryPointType -> Ordering
EntryPointType -> EntryPointType -> EntryPointType
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 :: EntryPointType -> EntryPointType -> Ordering
compare :: EntryPointType -> EntryPointType -> Ordering
$c< :: EntryPointType -> EntryPointType -> Bool
< :: EntryPointType -> EntryPointType -> Bool
$c<= :: EntryPointType -> EntryPointType -> Bool
<= :: EntryPointType -> EntryPointType -> Bool
$c> :: EntryPointType -> EntryPointType -> Bool
> :: EntryPointType -> EntryPointType -> Bool
$c>= :: EntryPointType -> EntryPointType -> Bool
>= :: EntryPointType -> EntryPointType -> Bool
$cmax :: EntryPointType -> EntryPointType -> EntryPointType
max :: EntryPointType -> EntryPointType -> EntryPointType
$cmin :: EntryPointType -> EntryPointType -> EntryPointType
min :: EntryPointType -> EntryPointType -> EntryPointType
Ord)
data OpaqueType
= OpaqueType [ValueType]
|
OpaqueRecord [(Name, EntryPointType)]
deriving (OpaqueType -> OpaqueType -> Bool
(OpaqueType -> OpaqueType -> Bool)
-> (OpaqueType -> OpaqueType -> Bool) -> Eq OpaqueType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpaqueType -> OpaqueType -> Bool
== :: OpaqueType -> OpaqueType -> Bool
$c/= :: OpaqueType -> OpaqueType -> Bool
/= :: OpaqueType -> OpaqueType -> Bool
Eq, Eq OpaqueType
Eq OpaqueType
-> (OpaqueType -> OpaqueType -> Ordering)
-> (OpaqueType -> OpaqueType -> Bool)
-> (OpaqueType -> OpaqueType -> Bool)
-> (OpaqueType -> OpaqueType -> Bool)
-> (OpaqueType -> OpaqueType -> Bool)
-> (OpaqueType -> OpaqueType -> OpaqueType)
-> (OpaqueType -> OpaqueType -> OpaqueType)
-> Ord OpaqueType
OpaqueType -> OpaqueType -> Bool
OpaqueType -> OpaqueType -> Ordering
OpaqueType -> OpaqueType -> OpaqueType
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 :: OpaqueType -> OpaqueType -> Ordering
compare :: OpaqueType -> OpaqueType -> Ordering
$c< :: OpaqueType -> OpaqueType -> Bool
< :: OpaqueType -> OpaqueType -> Bool
$c<= :: OpaqueType -> OpaqueType -> Bool
<= :: OpaqueType -> OpaqueType -> Bool
$c> :: OpaqueType -> OpaqueType -> Bool
> :: OpaqueType -> OpaqueType -> Bool
$c>= :: OpaqueType -> OpaqueType -> Bool
>= :: OpaqueType -> OpaqueType -> Bool
$cmax :: OpaqueType -> OpaqueType -> OpaqueType
max :: OpaqueType -> OpaqueType -> OpaqueType
$cmin :: OpaqueType -> OpaqueType -> OpaqueType
min :: OpaqueType -> OpaqueType -> OpaqueType
Ord, Int -> OpaqueType -> ShowS
[OpaqueType] -> ShowS
OpaqueType -> String
(Int -> OpaqueType -> ShowS)
-> (OpaqueType -> String)
-> ([OpaqueType] -> ShowS)
-> Show OpaqueType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpaqueType -> ShowS
showsPrec :: Int -> OpaqueType -> ShowS
$cshow :: OpaqueType -> String
show :: OpaqueType -> String
$cshowList :: [OpaqueType] -> ShowS
showList :: [OpaqueType] -> ShowS
Show)
newtype OpaqueTypes = OpaqueTypes [(Name, OpaqueType)]
deriving (OpaqueTypes -> OpaqueTypes -> Bool
(OpaqueTypes -> OpaqueTypes -> Bool)
-> (OpaqueTypes -> OpaqueTypes -> Bool) -> Eq OpaqueTypes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpaqueTypes -> OpaqueTypes -> Bool
== :: OpaqueTypes -> OpaqueTypes -> Bool
$c/= :: OpaqueTypes -> OpaqueTypes -> Bool
/= :: OpaqueTypes -> OpaqueTypes -> Bool
Eq, Eq OpaqueTypes
Eq OpaqueTypes
-> (OpaqueTypes -> OpaqueTypes -> Ordering)
-> (OpaqueTypes -> OpaqueTypes -> Bool)
-> (OpaqueTypes -> OpaqueTypes -> Bool)
-> (OpaqueTypes -> OpaqueTypes -> Bool)
-> (OpaqueTypes -> OpaqueTypes -> Bool)
-> (OpaqueTypes -> OpaqueTypes -> OpaqueTypes)
-> (OpaqueTypes -> OpaqueTypes -> OpaqueTypes)
-> Ord OpaqueTypes
OpaqueTypes -> OpaqueTypes -> Bool
OpaqueTypes -> OpaqueTypes -> Ordering
OpaqueTypes -> OpaqueTypes -> OpaqueTypes
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 :: OpaqueTypes -> OpaqueTypes -> Ordering
compare :: OpaqueTypes -> OpaqueTypes -> Ordering
$c< :: OpaqueTypes -> OpaqueTypes -> Bool
< :: OpaqueTypes -> OpaqueTypes -> Bool
$c<= :: OpaqueTypes -> OpaqueTypes -> Bool
<= :: OpaqueTypes -> OpaqueTypes -> Bool
$c> :: OpaqueTypes -> OpaqueTypes -> Bool
> :: OpaqueTypes -> OpaqueTypes -> Bool
$c>= :: OpaqueTypes -> OpaqueTypes -> Bool
>= :: OpaqueTypes -> OpaqueTypes -> Bool
$cmax :: OpaqueTypes -> OpaqueTypes -> OpaqueTypes
max :: OpaqueTypes -> OpaqueTypes -> OpaqueTypes
$cmin :: OpaqueTypes -> OpaqueTypes -> OpaqueTypes
min :: OpaqueTypes -> OpaqueTypes -> OpaqueTypes
Ord, Int -> OpaqueTypes -> ShowS
[OpaqueTypes] -> ShowS
OpaqueTypes -> String
(Int -> OpaqueTypes -> ShowS)
-> (OpaqueTypes -> String)
-> ([OpaqueTypes] -> ShowS)
-> Show OpaqueTypes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpaqueTypes -> ShowS
showsPrec :: Int -> OpaqueTypes -> ShowS
$cshow :: OpaqueTypes -> String
show :: OpaqueTypes -> String
$cshowList :: [OpaqueTypes] -> ShowS
showList :: [OpaqueTypes] -> ShowS
Show)
instance Monoid OpaqueTypes where
mempty :: OpaqueTypes
mempty = [(Name, OpaqueType)] -> OpaqueTypes
OpaqueTypes [(Name, OpaqueType)]
forall a. Monoid a => a
mempty
instance Semigroup OpaqueTypes where
OpaqueTypes [(Name, OpaqueType)]
x <> :: OpaqueTypes -> OpaqueTypes -> OpaqueTypes
<> OpaqueTypes [(Name, OpaqueType)]
y =
[(Name, OpaqueType)] -> OpaqueTypes
OpaqueTypes ([(Name, OpaqueType)] -> OpaqueTypes)
-> [(Name, OpaqueType)] -> OpaqueTypes
forall a b. (a -> b) -> a -> b
$ [(Name, OpaqueType)]
x [(Name, OpaqueType)]
-> [(Name, OpaqueType)] -> [(Name, OpaqueType)]
forall a. Semigroup a => a -> a -> a
<> ((Name, OpaqueType) -> Bool)
-> [(Name, OpaqueType)] -> [(Name, OpaqueType)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Name -> [Name] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ((Name, OpaqueType) -> Name) -> [(Name, OpaqueType)] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (Name, OpaqueType) -> Name
forall a b. (a, b) -> a
fst [(Name, OpaqueType)]
x) (Name -> Bool)
-> ((Name, OpaqueType) -> Name) -> (Name, OpaqueType) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Name, OpaqueType) -> Name
forall a b. (a, b) -> a
fst) [(Name, OpaqueType)]
y