aboutsummaryrefslogtreecommitdiff
path: root/src/Data/Array/Nested.hs
blob: e8496730dbb49ae65172846fba52bb64810c97c7 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE PatternSynonyms #-}
module Data.Array.Nested (
  -- * Ranked arrays
  Ranked(Ranked),
  ListR(ZR, (:::)),
  IxR(.., ZIR, (:.:)), IIxR,
  ShR(.., ZSR, (:$:)), IShR,
  rshape, rrank, rsize, rindex, rindexPartial, rgenerate, rsumOuter1Prim, rsumAllPrim,
  rtranspose, rappend, rconcat, rscalar, rfromVector, rtoVector, runScalar,
  remptyArray,
  rrerankPrim,
  rreplicate, rreplicatePrim,
  rfromListOuter, rfromListOuterN,
  rfromList1, rfromList1N,
  rfromListLinear,
  rfromList1Prim, rfromList1PrimN,
  rfromListPrimLinear,
  rtoList, rtoListOuter, rtoListLinear,
  rslice, rrev1, rreshape, rflatten, riota,
  rminIndexPrim, rmaxIndexPrim, rdot1Inner, rdot,
  rnest, runNest, rzip, runzip,
  -- ** Lifting orthotope operations to 'Ranked' arrays
  rlift, rlift2,
  -- ** Conversions
  rtoXArrayPrim, rfromXArrayPrim,
  rtoMixed, rcastToMixed, rcastToShaped,
  rfromOrthotope, rtoOrthotope,
  -- ** Additional arithmetic operations
  --
  -- $integralRealFloat
  rquotArray, rremArray, ratan2Array,

  -- * Shaped arrays
  Shaped(Shaped),
  ListS(ZS, (::$)),
  IxS(.., ZIS, (:.$)), IIxS,
  ShS(.., ZSS, (:$$)), KnownShS(..),
  sshape, srank, ssize, sindex, sindexPartial, sgenerate, ssumOuter1Prim, ssumAllPrim,
  stranspose, sappend, sscalar, sfromVector, stoVector, sunScalar,
  -- TODO: sconcat? What should its type be?
  semptyArray,
  srerankPrim,
  sreplicate, sreplicatePrim,
  sfromListOuter, sfromList1, sfromListLinear, sfromList1Prim, sfromListPrimLinear,
  stoList, stoListOuter, stoListLinear,
  sslice, srev1, sreshape, sflatten, siota,
  sminIndexPrim, smaxIndexPrim, sdot1Inner, sdot,
  snest, sunNest, szip, sunzip,
  -- ** Lifting orthotope operations to 'Shaped' arrays
  slift, slift2,
  -- ** Conversions
  stoXArrayPrim, sfromXArrayPrim,
  stoMixed, scastToMixed, stoRanked,
  sfromOrthotope, stoOrthotope,
  -- ** Additional arithmetic operations
  --
  -- $integralRealFloat
  squotArray, sremArray, satan2Array,

  -- * Mixed arrays
  Mixed,
  ListX(ZX, (::%)),
  IxX(.., ZIX, (:.%)), IIxX,
  ShX(.., ZSX, (:$%)), KnownShX(..), IShX,
  StaticShX(.., ZKX, (:!%)),
  SMayNat(..),
  mshape, mrank, msize, mindex, mindexPartial, mgenerate, msumOuter1Prim, msumAllPrim,
  mtranspose, mappend, mconcat, mscalar, mfromVector, mtoVector, munScalar,
  memptyArray,
  mrerankPrim,
  mreplicate, mreplicatePrim,
  mfromListOuter, mfromListOuterN, mfromListOuterSN,
  mfromList1, mfromList1N, mfromList1SN,
  mfromListLinear,
  mfromList1Prim, mfromList1PrimN, mfromList1PrimSN,
  mfromListPrimLinear,
  mtoList, mtoListOuter, mtoListLinear,
  msliceN, msliceSN, mrev1, mreshape, mflatten, miota,
  mminIndexPrim, mmaxIndexPrim, mdot1Inner, mdot,
  mnest, munNest, mzip, munzip,
  -- ** Lifting orthotope operations to 'Mixed' arrays
  mlift, mlift2,
  -- ** Conversions
  mtoXArrayPrim, mfromXArrayPrim,
  mcast,
  mcastToShaped, mtoRanked,
  convert, Conversion(..),
  -- ** Additional arithmetic operations
  --
  -- $integralRealFloat
  mquotArray, mremArray, matan2Array,

  -- * Array elements
  Elt,
  PrimElt,
  Primitive(..),
  KnownElt,

  -- * Further utilities / re-exports
  type (++),
  Storable,
  SNat, pattern SNat,
  pattern SZ, pattern SS,
  Perm(..),
  IsPermutation,
  KnownPerm(..),
  NumElt, IntElt, FloatElt,
  Rank, Product,
  Replicate,
  MapJust,
) where

import Prelude hiding (mappend, mconcat)

import Data.Array.Nested.Convert
import Data.Array.Nested.Mixed
import Data.Array.Nested.Mixed.Shape
import Data.Array.Nested.Permutation
import Data.Array.Nested.Ranked
import Data.Array.Nested.Ranked.Shape
import Data.Array.Nested.Shaped
import Data.Array.Nested.Shaped.Shape
import Data.Array.Nested.Types
import Data.Array.Strided.Arith
import Foreign.Storable
import GHC.TypeLits

-- $integralRealFloat
--
-- These functions are separate top-level functions, and not exposed in
-- instances for 'RealFloat' and 'Integral', because those classes include a
-- variety of other functions that make no sense for arrays.
-- This problem already occurs with 'fromInteger', 'fromRational' and 'pi', but
-- having 'Num', 'Fractional' and 'Floating' available is just too useful.