问题
This question was severely rewritten as per suggestion from @leftaroundabout. An earlier version may be seen in the edit history.
Haskell is famous for the fact that it facilitates thought, allowing more direct encoding of mathematical abstractions. Cartesian product is a very basic mental object many are familiar with since the very childhood. Yet, there is barely a type for it in Haskell. I think I need one, to enable my thinking to flow, if nothing else. (Although this post is actually inspired by some down-to-earth code I have at hand.) Let us then form a common understanding of what this Cartesian thing (I'll be calling it just Cartesian for short) is.
Given a sequence of length d :: Int
of collections (e.g. [[1,2], ['a', 'b']]
), I'd like to have all the combinations of their elements at short reach. That means operating on them as though they were in a usual Functor, Foldable, Traversable, Monoid, and so on. Indeed, we may represent any Cartesian as a suitably nested list of tuples:
type Lattice = [[(x, y)]]
type WeightedLattice = [[(x, y, w)]]
zipWith2 :: (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
zipWith2 f = zipWith (zipWith f)
fmap2 :: (Functor f, Functor g) => (a -> b) -> g (f a) -> g (f b)
fmap2 = fmap . fmap
sequence2 :: (Traversable s, Traversable t, Monad m) => t (s (m a)) -> m (t (s a))
sequence2 = sequence . fmap sequence
Similar constructions can be writ out by hand for any depth of nesting.
We now introduce a distinction between a Cartesian and the initial Cartesian:
An n-dimensional Cartesian is constructed from a heterogeneous sequence of collections by taking one element from each collection and combining them, orderly, with a suitably typed function. This, a Cartesian of signature [Int, Char, Bool] may be formed by a function such as:
f :: Int -> Char -> Bool -> Either Char Int f i c b = if b then Left c else Right i
The initial Cartesian is formed with the tuple constructor of matching arity:
initial :: Int -> Char -> Bool -> (Int, Char, Bool) initial = (,,)
It is easy to see that we may convert the initial Cartesian, represented as a nested list, to any other Cartesian of the like nesting depth, with a function akin to:
(fmap . ... . fmap) (uncurryN f)
However, we may not always come back; indeed, would be hard to recover the right Char
from a Right 3
. So, the initial Cartesian can be used in place of any particular Cartesian, but not always the other way around.
As an example, we can use the Lattice
type defined above to visualize a field, computing its values for some regularly distributed points in space. We would do it with a function that assigns to coordinates a value. There may be any number of such functions, describing different fields in the same points, to each corresponding a Lattice of like dimensions. But there will only be one initial Lattice that contains nothing but coordinates.
However, our nested list encoding has its drawbacks. Besides inducing the ennuy of spelling out all the necessary functions for every next dimension, it is insecure: there is nothing to save you from mistaking an 128 x 64 matrix with a 64 x 128 one and zipping them together, ending up with a 64 x 64 one instead; the order of things in the tuple may or may not correspond to the order of list nesting. On the other hand, the type system works hard against you, not allowing things like foldr (.) id [replicate d concat]
that could have saved some pain. Not haskelly at all.
But the deepest source of disappointment with this system is that it does not support in any obvious way the very fundamental intuition of the Cartesian: its Monoid instance. It's a property that allows us to think of a point as having not one, not some, but any number p
of properties, easily adding, combining or throwing them away -- like elements of a list, indeed. Being nailed to a certain depth of nesting and a certain tuple arity is having your wings cut. That Cartesian product is a Monoid in the category of Set is a basic fact from category theory, but can we define a Monoid over arbirarily nested lists of arbitrarily typed tuples?
So, the challenge of writing a Cartesian done right involves such goals as:
Any dimension. A list, a matrix, and any other finite-dimensional space should have like interface. Some selection of the usual
Data.List
functions should be implementable.Type safety. That is, having the types and the dimensions of a given Cartesian encoded in the type system. For example, if I form a space like
[1..3] x ['a', 'b']
, and another like[1,2] x ['a'..'c']
, they should have distinct readable type, and not zip together.As the Cartesian is determined by the selection of the dimensions, any two Cartesians may be combined just as the lists of their dimensions. For example:
Cartesian [[1..3], ['a', 'b']] <> Cartesian [[True, False]]
-- should be the same thing as:
Cartesian [[1..3], ['a', 'b'], [True, False]]
-- Just the same as their generating lists would.
There should be some notion of the initial Cartesian and the decorations placed over it, so that the coordinates of points are never lost unless the loss is forced. For example, the coordinates of the points of a
Lattice
should be stored separately of the derived properties of the field it describes. We may then, say, obtain a superposition of fields if the Lattices describing them "match".The initial Cartesian should be a Monoid.
I sketched some poor thing of a type that's at least somewhat usable and I will post it as an answer in a moment, but for most of the above points I'm at loss. It must take some type trickery. I appreciate any ideas on how to make it.
回答1:
The question is fairly vague, but it looks like you might be interested in vinyl
-style records. My definitions are a bit different from vinyl
proper; use what you like.
{-# language DataKinds, PolyKinds, TypeOperators, GADTs #-}
module Cart where
import Data.Kind (Type)
import Data.Functor.Identity
infixr 4 :<
data Rec :: [k] -> (k -> Type) -> Type where
Nil :: Rec '[] f
(:<) :: f a -> Rec as f -> Rec (a ': as) f
newtype HList xs = HList (Rec xs Identity)
prod :: Rec as [] -> [HList as]
prod = map HList . go
where
go :: Rec as [] -> [Rec as Identity]
go Nil = [Nil]
go (xs :< xss) = [ Identity x :< r | x <- xs, r <- go xss]
With appropriate Show
instances (straightforward but a bit annoying), you'll get something like
> prod $ [3,4,5] :< ["hello", "goodbye"] :< ['x'] :< Nil
[ H[3,"hello",'x'], H[3,"goodbye",'x'], H[4,"hello",'x']
, H[4,"goodbye",'x'], H[5,"hello",'x'], H[5,"goodbye",'x'] ]
This version of prod
is perhaps a tad too specific, since it only works with Identity
and lists. Here's a straightforward generalization, where the traversal function "splits" the base functor of the Rec
and we use an arbitrary Applicative
rather than just []
:
class Trav (t :: (k -> Type) -> Type) where
trav :: Applicative g => (forall a. f a -> g (h a)) -> t f -> g (t h)
instance Trav (Rec as) where
trav f Nil = pure Nil
trav f (xs :< xss) = (:<) <$> f xs <*> trav f xss
This is just analogous to Data.Vinyl.rtraverse, as I finally bumbled my way into recognizing.
Records of this sort don't form a Monoid
, because mappend
couldn't be typed. But you can certainly append them:
type family (++) xs ys where
'[] ++ ys = ys
(x ': xs) ++ ys = x ': xs ++ ys
(><) :: Rec xs f -> Rec ys f -> Rec (xs ++ ys) f
Nil >< ys = ys
(x :< xs) >< ys = x :< (xs >< ys)
This behaves well. In particular, you can append the records and then traverse them, or traverse them and then append the results.
trav f (xs >< ys) = (><) <$> trav f xs <*> trav f ys
You can also rearrange them in principled ways (analogous to your bubble device). The type
forall f k (as :: [k]) (bs :: [k]). Rec as f -> Rec bs f
can be given to any function that rearranges a Rec
without caring what's in it.
Since you mention mapping:
class Functor1 (t :: (k -> Type) -> Type) where
map1 :: (forall x. f x -> g x) -> t f -> t g
instance Functor1 (Rec as) where
map1 f = runIdentity . trav (\x -> Identity (f x))
Zipping also works:
rzip :: (forall x. f x -> g x -> h x)
-> Rec as f -> Rec as g -> Rec as h
rzip f Nil Nil = Nil
rzip f (x :< xs) (y :< ys) = f x y :< rzip f xs ys
回答2:
Some of the pain may be taken away by a type like this one:
type A e = Array Int e
data Cartesian v = Cartesian
{ _dimensions :: [Int]
, _values :: A v
} deriving (Show, Eq, Ord, Functor, Foldable, Traversable)
-- # Some helper functions.
autoListArray :: [a] -> A a
autoListArray xs = listArray (0, pred (length xs)) xs
-- | Get elements of an array such that they all belong to the
-- congruence class c modulo n.
getByCongruentIndices :: Int -> Int -> A v -> [v]
getByCongruentIndices n c arr =
let (low, high) = bounds arr
in (arr !) <$> [low + c, low + c + n.. high]
arr :: [v] -> A v
arr = autoListArray
unarr :: A v -> [v]
unarr = elems
congr :: Int -> Int -> A v -> [v]
congr = getByCongruentIndices
congr0 :: Int -> A v -> [v]
congr0 n = congr n 0
I will now go checking boxes about it.
Functor, Foldable, Traversable: Magically derivable out of the box.
Creating: You may create any Cartesian you wish by incrementally growing a
uni
withcons
.-- | Consruct a uni-dimensional Cartesian. uni :: [v] -> Cartesian v uni vs = Cartesian { _dimensions = [length vs], _values = arr vs } -- | Dimension increment. cons :: (u -> v -> w) -> [u] -> Cartesian v -> Cartesian w cons f xs Cartesian{..} = Cartesian { _dimensions = length xs: _dimensions , _values = arr [ x `f` y | x <- xs, y <- unarr _values ] }
Destroying: You may peel off layers of a Cartesian with
uncons
.-- | Dimension decrement. uncons :: (u -> (v, w)) -> Cartesian u -> Maybe ([v], Cartesian w) uncons _ Cartesian { _dimensions = [] } = Nothing uncons f Cartesian { _dimensions = (_: ds), _values = xs } = let ys = fmap (fst . f) . congr0 (product ds) $ xs zs = fmap (snd . f) . take (product ds) . unarr $ xs in Just (ys, Cartesian { _dimensions = ds, _values = arr zs })
Transpositions: You may change the order of dimensions with the
(↑)
bubble device. I don't have a proof, but I'm next to certain you can obtain any transposition you wish. In particular,(↑) x 1
is equivalent toData.List.traverse
.-- | Bubble: apply a cycle from 0 to (i - 1) to the dimensions. That is, make the i-th dimension -- the first. I believe bubbles to be the generators of the symmetric group. (↑) :: Cartesian u -> Int -> Cartesian u Cartesian{..} ↑ i = let d = product . drop i $ _dimensions ds = take i _dimensions ++ drop (succ i) _dimensions -- Delete the i-th. in Cartesian { _dimensions = ds , _values = arr . concat $ ($ _values) <$> (congr d <$> [0..pred d]) }
cons
,uncons
and(↑)
allow you to slice and combine again any two Cartesians, or parts thereof. But there is also a way to combine Cartesians directly:appendWith :: (u -> v -> w) -> Cartesian u -> Cartesian v -> Cartesian w appendWith f x y = Cartesian { _dimensions = _dimensions x ++ _dimensions y , _values = arr [ x `f` y | x <- unarr (_values x), y <- unarr (_values y) ] }
You can also zip things:
glue f x y | _dimensions x == _dimensions y = Cartesian { _dimensions = _dimensions x , _values = arr $ zipWith f (unarr $ _values x) (unarr $ _values y) } | otherwise = undefined
On the downside of this, you have to explicitly provide a binary function that could combine the types you have in your Cartesians, everywhere. This would usually be a tuple constructor, but you are not limited to it.
I had trouble defining an instance of Monoid, particularly the mempty
part, and the initial thing is not even near here.
来源:https://stackoverflow.com/questions/48743657/how-can-i-best-represent-a-cartesian-product-of-some-fixed-dimension