Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Howto reverse a Data.Array (David McBride)


----------------------------------------------------------------------

Message: 1
Date: Thu, 23 Jun 2016 10:41:22 -0400
From: David McBride <toa...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Howto reverse a Data.Array
Message-ID:
        <CAN+Tr40qWG0wGT2mK=Dow_+=+-69csy1uqzwk_a49kjcocj...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

The problem isn't with array, but rather your index.  Ix instances are
always sorted in ascending order, as you might imagine.  You can however,
use your own index in arrays and they can be indexed in whatever order you
like.


{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Data.Array
import Data.Ix

newtype MyIx = MyIx Int deriving (Eq, Num, Show)

instance Ord MyIx where
  compare (MyIx a) (MyIx b) =
    case compare a b of
      LT -> GT
      GT -> LT
      EQ -> EQ

instance Ix MyIx where
  range (MyIx a, MyIx b) = map MyIx $ reverse [b..a]
  index (MyIx a, MyIx b) (MyIx c) = a - c
  inRange (MyIx a, MyIx b) (MyIx c) = c <= a && c >= b

blah :: Array MyIx Char
blah = array (3,0) [(0,'a'),(1,'b'),(2,'c'),(3,'d')]

Warning:  I only very lightly tested the above code.

You can mix your index and normal indexes to get the row / col ordering you
are hoping for.

blah2 :: [((MyIx, Int), Char)] -> Array (MyIx, Int) Char
blah2 = array ((3,0),(0,3))

Finally, if you are really looking for something that is designed to be a
matrix, you might try one of several libraries that are out there, like
hmatrix.

Hopefully this helps.

On Thu, Jun 23, 2016 at 3:58 AM, Timothy Washington <twash...@gmail.com>
wrote:

> I'm still trying to get an intuitive understanding of Haskell's Data.Array
> <http://hackage.haskell.org/package/array-0.5.1.1/docs/Data-Array.html#g:5>,
> in contrast to Data.List or Data.Vector.
>
> I very much want a nested array (a matrix), where the parent list (or
> rows) are reversed. But neither *A.array* nor *A.istArray* allow indicies
> to be reversed in their constructors, nor the list comprehensions that
> generate the elements
>
> The only reason I'm using an array, is for the *A.//* function (operating
> on a matrix). Otherwise, I'd use Data.Vector
> <https://hackage.haskell.org/package/vector-0.11.0.0/candidate/docs/Data-Vector.html>
> which does have a reverse function, but a less powerful *V.//* , that
> doesn't accept coordinates in a matrix.
>
> Can I reverse a Data.Array? If not, then why.
>
>
> Thanks
> Tim
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160623/01c9401f/attachment-0001.html>

------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 96, Issue 15
*****************************************

Reply via email to