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 (Timothy Washington)
   2.  Preorder function application (OxFord)
   3. Re:  Preorder function application (Theodore Lief Gannon)


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

Message: 1
Date: Sun, 3 Jul 2016 11:27:31 -0700
From: Timothy Washington <twash...@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:
        <CAADtM-a9xMTO4Jgq9PowA2YGY75Okunf=zkrhreso9s8bzk...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hmm, this is very helpful - didn't know it existed. Thanks very much, I'll
check it out!

Tim


On Thu, Jun 23, 2016 at 7:41 AM, David McBride <toa...@gmail.com> wrote:

> 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.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160703/de2cfd5d/attachment-0001.html>

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

Message: 2
Date: Mon, 4 Jul 2016 09:43:41 +0200
From: OxFord <fordfo...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Preorder function application
Message-ID:
        <CAPQ-+H+Aw4wVEHMHenp08Xadm8BUAgWttgRGotkXEiqWHx=_...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hello,

why Haskell doesn't apply functions in preorder?
e.g.

f x = x

max 1 f 2
> 2
max f 1 f 2
> 2
max max f 1 f 2 f 3
> 3
f f f f f f f f f f f 1
> 1


Thus you would need to put the arguments into brackets only when you want
to partially apply that function.


Is the current method more readable or error prone?

King regards,

Ford
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20160704/ee852d00/attachment-0001.html>

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

Message: 3
Date: Mon, 4 Jul 2016 04:20:32 -0700
From: Theodore Lief Gannon <tan...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Preorder function application
Message-ID:
        <cajopsubeppftwchgus0mkkelsacto65bpjm80gcitupmwr+...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

If I understand correctly, you're asking why function application is
left-associative rather than right-associative. With currying and
first-class functions, right-association doesn't really work well. It's not
obvious with a highly-constrained function like "max", but in practice most
Haskell functions get composed and applied with other functions; real data
only matters at the endpoints. For a reasonably simple example, consider
the interaction between a couple of other Prelude functions:

map :: (a -> b) -> [a] -> [b]
const :: a -> b -> a

Since (b -> a) is a type all by itself, it fits into a type variable for
other functions; that is, "const" is an (a -> b) for the purposes of
filling the first argument of "map". Applying this gets:

map const :: [a] -> [b -> a]

This takes a list of values, and returns a list of functions. So
considering the type of "map const", which of the following behaviors seems
more appropriate:

> :t (map const) [1,2,3]
map const [1,2,3] :: Num a => [b -> a]

> :t map (const [1,2,3])
map (const [1,2,3]) :: Num a => [b] -> [[a]]

Haskell chooses the first option, because giving an argument [a] to an
expression whose type is currently [a] -> [b -> a] should probably return
[b -> a].

On Mon, Jul 4, 2016 at 12:43 AM, OxFord <fordfo...@gmail.com> wrote:

> Hello,
>
> why Haskell doesn't apply functions in preorder?
> e.g.
>
> f x = x
>
> max 1 f 2
> > 2
> max f 1 f 2
> > 2
> max max f 1 f 2 f 3
> > 3
> f f f f f f f f f f f 1
> > 1
>
>
> Thus you would need to put the arguments into brackets only when you want
> to partially apply that function.
>
>
> Is the current method more readable or error prone?
>
> King regards,
>
> Ford
>
> _______________________________________________
> 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/20160704/0698a844/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 97, Issue 3
****************************************

Reply via email to