Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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.  IO / State / Do Syntax (Christopher Howard)
   2. Re:  IO / State / Do Syntax (Alexander Bernauer)
   3.  Errors involving rigid skolem types (Matthew Moppett)
   4. Re:  Errors involving rigid skolem types (Matthew Moppett)
   5. Re:  Errors involving rigid skolem types (Brent Yorgey)
   6.  Are tuples really needed? (Carlos J. G. Duarte)
   7. Re:  Are tuples really needed? (Kyle Murphy)


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

Message: 1
Date: Mon, 27 Aug 2012 02:27:22 -0800
From: Christopher Howard <christopher.how...@frigidcode.com>
Subject: [Haskell-beginners] IO / State / Do Syntax
To: Haskell Beginners <beginners@haskell.org>
Message-ID: <503b4b8a.10...@frigidcode.com>
Content-Type: text/plain; charset="iso-8859-1"

So, I'm still working with my resource tracker idea -- keeping images
stored and organized inside a resource tracker structure that I can pass
around to functions that need them. Let's say I want a function like so:

code:
--------
initResources :: IO ResourceTracker
--------

The idea being that initResources loads the image files, stores them in
the resource tracker (RT) structure, and returns the RT. I know I can do
something like so:

code:
--------
initResources = do pic1 <- loadImage "someimage.png" -- IO function
                   pic2 <- loadImage "someimage2.png"
                   -- ... and so on ...
                   let rt = emptyResourceTracker in
                   let rt' = storeImage rt "pic1keyword" pic1 in
                   let rt'' = storeImage rt' "pic2keyword" pic2 in
                   -- ... and so on, until finally: ...
                   rt''''''''''''''''''''''''''
--------

Obviously, all the let statements and apostrophes are undesirable. So,
presumably what I need is to being using the State monad, yes? (I must
confess I have only a vague understanding of the State monad, even after
reading several tutorials.) But in my initResources function, how do I
mix use of the IO and State do syntax, and still get what I want?

I think this has something to do with Monad transformers, but I'm even
less clear on how those work.

-- 
frigidcode.com
indicium.us

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 554 bytes
Desc: OpenPGP digital signature
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120827/605a3eda/attachment-0001.pgp>

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

Message: 2
Date: Mon, 27 Aug 2012 13:49:35 +0200
From: Alexander Bernauer <alex-hask...@copton.net>
Subject: Re: [Haskell-beginners] IO / State / Do Syntax
To: Haskell Beginners <beginners@haskell.org>
Message-ID: <20120827114935.GB4253@apus>
Content-Type: text/plain; charset="us-ascii"

Hi

you don't need the State monad for your problem. Standard functional
composition is enough:

---8<---
initResources =
   let
      images = ["someimage.png", "someimage2.png"]
      keywords = ["pic1keyword", "pic2keyword"]
   in do
       pics <- mapM loadImage images
       let rt = foldr go emptyResourceTracker $ zip pics keywords
       -- use rt
   where
      go (pic, kw) rt = storeImage rt kw pic
--->8---

Anyways, if you are interested in Monad transformers in general, go
check out http://book.realworldhaskell.org/read/monad-transformers.html

HTH

Alex
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: Digital signature
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120827/c5f15557/attachment-0001.pgp>

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

Message: 3
Date: Mon, 27 Aug 2012 23:21:55 +1000
From: Matthew Moppett <matthewmopp...@gmail.com>
Subject: [Haskell-beginners] Errors involving rigid skolem types
To: beginners@haskell.org
Message-ID:
        <CAMLEjZAAhWGQWnLP=qto-kk2xqjrry5r4pzekuwmpi7y7c3...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

The following code is intended as a first step towards creating a
cyclical enumerable type, such that:
     (e.g.) [Cyc Friday .. Cyc Tuesday] would yield [Friday, Saturday,
Sunday, Monday, Tuesday]

module Cycle where

newtype Cyc a = Cyc a deriving (Eq, Ord, Bounded, Show, Read)

fromCyc :: Cyc a -> a
fromCyc (Cyc a) = a

instance (Enum a, Bounded a) => Enum (Cyc a) where
    fromEnum = fromEnum . fromCyc
    toEnum n = Cyc x
        where (x, max) = (x', maxBound) :: (a, a)
              x' = toEnum $ n `mod` ((fromEnum max) - 1)

This yields a kind of error message that I've often bashed my head against
in other code I've written, without ever really understanding what the
problem is exactly:

Couldn't match type `a0' with `a1'
      because type variable `a1' would escape its scope
    This (rigid, skolem) type variable is bound by
      an expression type signature: (a1, a1)
    The following variables have types that mention a0
      x' :: a0 (bound at Cycle.hs:12:15)
    In the expression: (x', maxBound) :: (a, a)
    In a pattern binding: (x, max) = (x', maxBound) :: (a, a)
    In an equation for `toEnum':
        toEnum n
          = Cyc x
          where
              (x, max) = (x', maxBound) :: (a, a)
              x' = toEnum $ n `mod` ((fromEnum max) - 1)

The problem comes up when I'm trying to give hints to the compiler about
the type that a particular expression should have.

My questions are: (1) what exactly is going on here, and (2) is there any
general technique for specifying types in situations like this that gets
around this problem?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120827/c0e47bc9/attachment-0001.htm>

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

Message: 4
Date: Tue, 28 Aug 2012 00:04:37 +1000
From: Matthew Moppett <matthewmopp...@gmail.com>
Subject: Re: [Haskell-beginners] Errors involving rigid skolem types
To: beginners@haskell.org
Message-ID:
        <CAMLEjZAB=zjz9vnr16lqjzrshzbp_56cardlgmwkyf96-lt...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

A couple of clarifications regarding my previous post:

It should be ((fromEnum max) + 1) rather than ((fromEnum max) - 1); and

Perhaps question (2) should be: are there any lessons to be learnt about
how to avoid this problem in future?

On Mon, Aug 27, 2012 at 11:21 PM, Matthew Moppett
<matthewmopp...@gmail.com>wrote:

> The following code is intended as a first step towards creating a
> cyclical enumerable type, such that:
>      (e.g.) [Cyc Friday .. Cyc Tuesday] would yield [Friday, Saturday,
> Sunday, Monday, Tuesday]
>
> module Cycle where
>
> newtype Cyc a = Cyc a deriving (Eq, Ord, Bounded, Show, Read)
>
> fromCyc :: Cyc a -> a
> fromCyc (Cyc a) = a
>
> instance (Enum a, Bounded a) => Enum (Cyc a) where
>     fromEnum = fromEnum . fromCyc
>     toEnum n = Cyc x
>         where (x, max) = (x', maxBound) :: (a, a)
>               x' = toEnum $ n `mod` ((fromEnum max) - 1)
>
> This yields a kind of error message that I've often bashed my head against
> in other code I've written, without ever really understanding what the
> problem is exactly:
>
> Couldn't match type `a0' with `a1'
>       because type variable `a1' would escape its scope
>     This (rigid, skolem) type variable is bound by
>       an expression type signature: (a1, a1)
>     The following variables have types that mention a0
>       x' :: a0 (bound at Cycle.hs:12:15)
>     In the expression: (x', maxBound) :: (a, a)
>     In a pattern binding: (x, max) = (x', maxBound) :: (a, a)
>     In an equation for `toEnum':
>         toEnum n
>           = Cyc x
>           where
>               (x, max) = (x', maxBound) :: (a, a)
>               x' = toEnum $ n `mod` ((fromEnum max) - 1)
>
> The problem comes up when I'm trying to give hints to the compiler about
> the type that a particular expression should have.
>
> My questions are: (1) what exactly is going on here, and (2) is there any
> general technique for specifying types in situations like this that gets
> around this problem?
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120828/fb0348e5/attachment-0001.htm>

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

Message: 5
Date: Mon, 27 Aug 2012 10:45:58 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Errors involving rigid skolem types
To: beginners@haskell.org
Message-ID: <20120827144558.ga19...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Aug 27, 2012 at 11:21:55PM +1000, Matthew Moppett wrote:
> 
> This yields a kind of error message that I've often bashed my head against
> in other code I've written, without ever really understanding what the
> problem is exactly:
> 
> Couldn't match type `a0' with `a1'
>       because type variable `a1' would escape its scope
>     This (rigid, skolem) type variable is bound by
>       an expression type signature: (a1, a1)
>     The following variables have types that mention a0
>       x' :: a0 (bound at Cycle.hs:12:15)
>     In the expression: (x', maxBound) :: (a, a)
>     In a pattern binding: (x, max) = (x', maxBound) :: (a, a)
>     In an equation for `toEnum':
>         toEnum n
>           = Cyc x
>           where
>               (x, max) = (x', maxBound) :: (a, a)
>               x' = toEnum $ n `mod` ((fromEnum max) - 1)
> 
> The problem comes up when I'm trying to give hints to the compiler about
> the type that a particular expression should have.
> 
> My questions are: (1) what exactly is going on here, and (2) is there any
> general technique for specifying types in situations like this that gets
> around this problem?

What is going on here is that the occurrences of 'a' in (x', maxBound)
:: (a,a) are not the same as the occurrences of 'a' in the instance
head.  You might as well have written (x', maxBound) :: (b,b) or ::
(foo,foo).  The idea is that by default, any type with type variables
is generalized to a forall type, so what you really have is

  (x', maxBound) :: forall a. (a,a)

which makes it easier to see why those a's have nothing to do with
those in the instance head.  You don't want x' and maxBound to have
*any* type, you want them to have whatever *particular* type
corresponds to the chosen instance.

The solution is to use an extension called ScopedTypeVariables which
lets you connect type variables across different signatures in exactly
this way.  In this case, simply turning on the extension by putting

  {-# LANGUAGE ScopedTypeVariables #-}

at the top of your file is enough to get the program to compile.  Now
the 'a's in your local type annotation really do refer back to the 'a'
in the instance head.  In general, if you want to have a local type
variable refer to a top-level type signature (as opposed to an
instance head) you also have to put an explicit 'forall' on the
variables you want to be scoped in this way, like

  {-# LANGUAGE ScopedTypeVariables #-}
  foo :: forall a. a -> a -> a
  foo = ...
    where bar = ... :: a -> Int

note the 'forall a' in the top-level signature for foo.

-Brent



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

Message: 6
Date: Tue, 28 Aug 2012 02:47:28 +0100
From: "Carlos J. G. Duarte" <carlos.j.g.dua...@gmail.com>
Subject: [Haskell-beginners] Are tuples really needed?
To: beginners@haskell.org
Message-ID: <503c2330.7010...@gmail.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Sorry if this question is too insane, but I was wondering if tuples are 
really needed in Haskell. I mean, could tuples be generally replaced by 
variables unroll (f x y z) and explicit data types, or are there some 
things only possible to do via tuples?

Thx in advance (and sorry if this looks silly).




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

Message: 7
Date: Tue, 28 Aug 2012 00:40:20 -0400
From: Kyle Murphy <orc...@gmail.com>
Subject: Re: [Haskell-beginners] Are tuples really needed?
To: "Carlos J. G. Duarte" <carlos.j.g.dua...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CA+y6Jczs+Ga6JNci+wKovrY4gqDVXgHeharfjG=a+haj28_...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Tuples aren't really anything special, you could define your own (2 item)
type like:

data Pair a b = Pair a b

The main advantage you get with tuple is that first and foremost it's part
of the standard library so it's used all over the place. It's really just a
convenient shortcut for holding data, and arguably a explicit data type
that provides more meta-information about what exactly it contains is
usually a better choice rather than the abstract tuple which doesn't really
tell you much of anything. E.G. which is more obvious:

draw :: (Int, Int) -> (Int, Int) -> IO ()

or

data Line = Line { startX :: Int, startY :: Int, endX :: Int, endY :: Int }
draw :: Line -> IO ()

More commonly you'd use a tuple to represent a point, but a type
declaration to make the signature more explicit as in:

type Point = (Int,Int)
draw :: Point -> Point -> IO ()

or possibly

type Point = (Int, Int)
data Line = Line { lineStart :: Point, lineEnd :: Point }
draw :: Line -> IO ()

The need to have some generic data structure that holds 2 or more other
pieces of data however is something you run across so often that from a
practical standpoint it makes sense to have it as part of the standard
library, particularly for quick and dirty rapid calculations as it's one
less piece of boiler plate throw away you need to worry about creating. In
most cases you could even replace a tuple with a list of two elements, but
then you lose some of the type safety because lists don't guarantee the
number of elements they contain in the type signature.

-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.


On Mon, Aug 27, 2012 at 9:47 PM, Carlos J. G. Duarte <
carlos.j.g.dua...@gmail.com> wrote:

> Sorry if this question is too insane, but I was wondering if tuples are
> really needed in Haskell. I mean, could tuples be generally replaced by
> variables unroll (f x y z) and explicit data types, or are there some
> things only possible to do via tuples?
>
> Thx in advance (and sorry if this looks silly).
>
>
> ______________________________**_________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/**mailman/listinfo/beginners<http://www.haskell.org/mailman/listinfo/beginners>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120828/0e343975/attachment.htm>

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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 50, Issue 31
*****************************************

Reply via email to