Problem with Unboxed Types
Simon Peyton-Jones
simonpj at microsoft.com
Fri Aug 27 03:45:20 EDT 2004
Just to be sure, I've just compiled and run this code with GHC 6.2.1, on
a Linux system. I can't account for your difficulty I'm afraid.
Simon
{-# OPTIONS -fglasgow-exts #-}
module Main where
import GHC.Exts
showUnboxedInt :: Int# -> String
showUnboxedInt n = (show $ I# n) ++ "#"
main = print (showUnboxedInt 3#)
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Jorge Adriano Aires
| Sent: 27 August 2004 02:55
| To: glasgow-haskell-users at haskell.org
| Subject: Problem with Unboxed Types
|
| Hello,
| I'd like to try using Unboxed types, but I always get a "parse error
on input
| `#'" error. To make sure I wasn't making some mistake I tried the
example in
| the wiki:
|
| http://www.haskell.org/hawiki/UnboxedType
| --------------------------------------------------------
| module Main where
| import GHC.Exts
|
| showUnboxedInt :: Int# -> String
| showUnboxedInt n = (show $ I# n) ++ "#"
| --------------------------------------------------------
|
| Even tried adding fglasgow-exts, nothing works though. I'm using GHC
6.2.1 on
| a SuSE 8.2 system (glibc 2.3) installed using the available RPMs. Any
idea?
|
| Thanks in advance,
| J.A.
|
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list