List comprehension on indices

Is it better to avoid list comprehensions on indices like this one?

a = [[1, 2, 4], [3, 2, 8], [2, 6, 1]] --matrix
traceM x = sum [(x!!i)!!i | i <- [0..(length x - 1)]] --trace of a matrix

traceM a -- 4

It doesn’t seem functional style, should I avoid it?

1 Like

No type signature and list comprehensions, I had to reread it to understand what it does.

I would say yes, try to avoid non-obvious list comprehensions.

1 Like

Probably, yeah, you would like to avoid the indexing there; mostly just because it’s slow.

Part of the “magic”, if there is any, of a “functional style”, is getting your data representation right.

One may take some inspiration from hmatrix here - https://hackage.haskell.org/package/hmatrix-0.20.2/docs/src/Internal.Element.html#takeDiag - and note that actually they just do the indexing like you; but there it’s fast because it’s a vector.

1 Like

Feels like Array’s imap to me?

I think what you wrote is pretty readable, especially if you already know what a trace is.

The biggest downside in my opinion is how fragile it is if it receives anything other than a square matrix. Since there’s nothing guaranteeing that the input is square in the types, you’re entirely on your own for preventing run-time errors. It’s up to you how much you care about this—maybe this function is only used in highly controlled circumstances and you prefer this style over alternatives.

But if you wanted a more robust alternative, I’d probably do something like this:

{-# LANGUAGE BlockArguments, LambdaCase #-}

import Data.List (unfoldr)

tailMay = \case
  _ : t -> Just t
  _ -> Nothing

traceM = sum . unfoldr \case
  (h : _) : t -> (h, ) <$> traverse tailMay t
  _ -> Nothing

(The semantics of this implementation on non-square inputs are that it takes the trace of the square matrix found by taking the least entirely filled dimension in both directions, if that makes sense. Give it a ragged input like [[0, 1, 2], [3, 4, 5, 6], [7, 8, 9], [10, 11]], and it computes the trace of [[0, 1], [3, 4]], since the fourth row has length 2.)

1 Like

Indexing seems unavoidable as long as you’re using lists, but you can limit it to only one occurrence and avoid length:

traceM xs = sum (zipWith (!!) xs [0..]) --trace of a matrix
4 Likes

Your answer makes me think of another question.
I noticed that in haskell zipWith and fmap are widely used functions.
I have defined my own operators, which I use instead of fmap and zipWith, when I am faced with common vectorized operations on lists.
Here is an example with the +

-- +: adds the same number to each item in the list
(+:) :: Num b => [b] -> b -> [b]
(+:) j k = map (+k) j 
-- +| sum the respective elements of the lists
(+|) :: Num c => [c] -> [c] -> [c]
(+|) j k = zipWith (+) j k

a = [1, 2, 3]
b = [5, 6, 7]
a +| b -- gives [6,8,10]
a +: 3 -- gives [4,5,6]

and I have defined also a vectorized function application:

(~) :: Functor f => (a -> b) -> f a -> f b
(~) f q = fmap f q

exp ~ a -- [2.718281828459045,7.38905609893065,20.085536923187668]

Should I avoid this practice and explicitly write fmpa and zipWith?
I could rewrite your function like this:

(!!|) :: [[c]] -> [Int] -> [c]
(!!|) a b = zipWith (!!) a b

traceM xs = sum (xs !!| [0..])

If you expect your code to be read by other people, then I’d avoid defining your own functions for these things. Many people know what zipWith (!!) a b means, but very few will understand a !!| b.

But if you have a particular library where you are really using these kinds of functions all the time and writing out zipWith does become a problem, then it might be useful.

By the way, have you used APL or one of its derivatives before?

1 Like

What are APL and its derivatives?

APL is an old programming language that takes the idea of defining short operators like !!| to the absolute limit. Every such operator gets their own symbol and there are symbols that operate on other symbols. APL does not have variables, only top level definitions.

That makes certain functions very compact. I expect the trace of a matrix would only require a few symbols. And APL notation can make it easy to recognise certain algorithms quickly if you master its notation. But that takes some practice.

There are modern derivative languages that have some more features you’d expect of modern programming languages and there are derivatives that use latin characters instead of all the symbols.

See Introduction — Learning APL for an introduction to APL.

2 Likes

In the dialect of APL that Dyalog uses, you can define trace as trace ← +/ 1 1∘⍉. It’s not quite as succinct to define in all APLs, because they might lack the bind meaning of Bind - APL Wiki.

Or if you want to generalised version that supports an arbitrary number of dimensions, instead of just 2, trace ← +/(⍴∘1∘⍴⍴)⍉⊢

However, it’s also with mentioning that most APL users wouldn’t “define trace”. trace some_matrix isn’t much shorter than +/ 1 1 ⍉ some_matrix and the latter has a “name” that unambiguously describes what it does.

1 Like