Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

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


Today's Topics:

   1.  Immutable refs for the functional code to get    emulation of
      o.o. inner/nested classes (Gabriel Riba)
   2. Re:  Immutable refs for the functional code to get emulation
      of o.o. inner/nested classes (Felipe Almeida Lessa)
   3. Re:  Immutable refs for the functional code to    get emulation
      of o.o. inner/nested classes (Gabriel Riba)
   4.  mailing list question (Gregory Guthrie)
   5. Re:  mailing list question (David Jacobs)


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

Message: 1
Date: Tue, 31 Jan 2012 12:56:52 +0000 (UTC)
From: Gabriel Riba <[email protected]>
Subject: [Haskell-beginners] Immutable refs for the functional code to
        get     emulation of o.o. inner/nested classes
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii

I have worked out a solution with System.IO.Unsafe.unsafePerformIO /
unsafeDupablePerformIO.

I would like any criticism in order to get a good solution.

The idea is to have immutable refs readable safely from the functional code.

Possible use:

--------------------------
import Data.ImmIORef (ImmIORef, newImmIORef, readImmIORef)

data Framework = Framework {prop :: Int} 
  deriving (Eq, Show)

-- ''Inner'' element with ref. to the framework
data FrameworkElement = FrameworkElement {dta::Int, 
                             frameworkRef :: (ImmIORef Framework)}  
  deriving (Eq, Show)

getElement'sFramework_Prop :: FrameworkElement -> Int
getElement'sFramework_Prop elem = k
  where 
    k = prop $ readImmIORef $ frameworkRef elem

--------------------------
-- Data.ImmIORef adapted from GHC.IORef
--

module Data.ImmIORef (
        ImmIORef,
        newImmIORef, readImmIORef
    ) where


import GHC.Base
import GHC.STRef
import GHC.IO
import Text.Show (Show, show)
import System.IO.Unsafe 

-- |An immutable variable in the 'IO' monad
newtype ImmIORef a = ImmIORef (STRef RealWorld a)

-- explicit instance 
instance Eq (ImmIORef a) where
  ImmIORef x == ImmIORef y = x == y

-- |Build a new 'ImmIORef'
newImmIORef    :: a -> IO (ImmIORef a)
newImmIORef v = stToIO (newSTRef v) >>= \ var -> return (ImmIORef var)

-- |Read the value of an 'ImmIORef' via unsafePerformIO
{-# NOINLINE readImmIORef #-}           -- recommended in System.IO.Unsafe doc
readImmIORef   :: ImmIORef a -> a

#if __GLASGOW_HASKELL__>=721
readImmIORef  (ImmIORef var) = unsafeDupablePerformIO $ stToIO (readSTRef var)
#else
readImmIORef  (ImmIORef var) = unsafePerformIO $ stToIO (readSTRef var)
#endif

instance (Show a) => Show (ImmIORef a) where
  show xRef = "ImmIORef->(" ++ show (readImmIORef xRef) ++ ")"





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

Message: 2
Date: Tue, 31 Jan 2012 11:18:08 -0200
From: Felipe Almeida Lessa <[email protected]>
Subject: Re: [Haskell-beginners] Immutable refs for the functional
        code to get emulation of o.o. inner/nested classes
To: Gabriel Riba <[email protected]>
Cc: [email protected]
Message-ID:
        <CANd=OGEG=zrzomhponmgxzh_a3eznyzpv6n9yvmhx08xlq2...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Tue, Jan 31, 2012 at 10:56 AM, Gabriel Riba <[email protected]> wrote:
> The idea is to have immutable refs readable safely from the functional code.

We already have this!

  let x = ...

Now x is an immutable reference readable safely from functional code
=).  And I'm being serious here, your ImmIORef does not have any
advantages over a plain value.

Maybe you could elaborate on what you're trying to achieve?

Cheers!

-- 
Felipe.



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

Message: 3
Date: Tue, 31 Jan 2012 13:33:06 +0000 (UTC)
From: Gabriel Riba <[email protected]>
Subject: Re: [Haskell-beginners] Immutable refs for the functional
        code to get emulation of o.o. inner/nested classes
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii

Thanks!/Gracias! 

I had some doubts about ''data'' datatypes.

Salud!








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

Message: 4
Date: Tue, 31 Jan 2012 22:12:59 -0600
From: Gregory Guthrie <[email protected]>
Subject: [Haskell-beginners] mailing list question
To: "[email protected]" <[email protected]>
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset="iso-8859-1"

I notice that the mailing list digest form is text only, so special symbols 
(Greek - alpha, beta, ..) all get mangled into "?".
This is not so common on the Beginners list, but not infrequent on the Caf? 
list.

To find the original version, one needs to go to the archives, but they are 
indexed by date, and the digest is by Vol, No, Topic.

So,
Is there any way to get an HTML version of the digest?
And/or, to add some indexing to the archives? (an indexed page into the 
archives?)

I presume the answer to these is no, since I did not see any such options on 
the mailman archive page;
so likely this is just either a comment or suggestion, or both.  :)


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120131/492c5f5a/attachment-0001.htm>

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

Message: 5
Date: Tue, 31 Jan 2012 22:46:05 -0800
From: David Jacobs <[email protected]>
Subject: Re: [Haskell-beginners] mailing list question
To: Gregory Guthrie <[email protected]>
Cc: "[email protected]" <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset="utf-8"

Or how about UTF-8 plain text?

On Jan 31, 2012, at 8:12 PM, Gregory Guthrie <[email protected]> wrote:

> I notice that the mailing list digest form is text only, so special symbols 
> (Greek ? alpha, beta, ..) all get mangled into ???.
> This is not so common on the Beginners list, but not infrequent on the Caf? 
> list.
>  
> To find the original version, one needs to go to the archives, but they are 
> indexed by date, and the digest is by Vol, No, Topic.
>  
> So,
> Is there any way to get an HTML version of the digest?
> And/or, to add some indexing to the archives? (an indexed page into the 
> archives?)
>  
> I presume the answer to these is no, since I did not see any such options on 
> the mailman archive page;
> so likely this is just either a comment or suggestion, or both.  J
>  
>  
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120131/d171ccb3/attachment-0001.htm>

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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 44, Issue 1
****************************************

Reply via email to