Re: [Haskell-cafe] Detecting system endianness

2008-12-18 Thread George Pollard
On Thu, 2008-12-18 at 22:35 -0500, wren ng thornton wrote:
> In a similar vein, is there already a function available to give the 
> size of Word in bytes? Or should I write the usual Ptr conversion tricks 
> to figure it out?

How about this:

(`div` 8) $ ceiling $ logBase 2 $ fromIntegral (maxBound :: Word)

Could write an integral log_2 function to make it nicer :)

- George


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Detecting system endianness

2008-12-18 Thread Don Stewart
Foreign.Storable.sizeOf

wren:
> In a similar vein, is there already a function available to give the 
> size of Word in bytes? Or should I write the usual Ptr conversion tricks 
> to figure it out?
> 
> 
> 
> Holger Siegel wrote:
> >On Thursday 18 December 2008 13:40:47 Ryan Ingram wrote:
> >>Actually, this is probably safer:
> >>
> >>import Foreign.Marshal.Alloc
> >>import Foreign.Ptr
> >>import Foreign.Storable
> >>import Data.Word
> >>import System.IO.Unsafe
> >>
> >>endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 ::
> >>Word32) >> peek (castPtr p :: Ptr Word8)
> >>
> >>littleEndian = endianCheck == 4
> >>bigEndian = endianCheck == 1
> >>
> >>  -- ryan
> >
> >
> >Using modules Data.Binary, Data.Binary.Put and Data.Word, you can define
> >
> >  littleEndian =  (decode $ runPut $ putWord16host 42 :: Word8) == 42
> >
> >Under the hood, it also uses peek and poke, but it looks a bit more 
> >functional.
> 
> 
> -- 
> Live well,
> ~wren
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Detecting system endianness

2008-12-18 Thread wren ng thornton
In a similar vein, is there already a function available to give the 
size of Word in bytes? Or should I write the usual Ptr conversion tricks 
to figure it out?




Holger Siegel wrote:

On Thursday 18 December 2008 13:40:47 Ryan Ingram wrote:

Actually, this is probably safer:

import Foreign.Marshal.Alloc
import Foreign.Ptr
import Foreign.Storable
import Data.Word
import System.IO.Unsafe

endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 ::
Word32) >> peek (castPtr p :: Ptr Word8)

littleEndian = endianCheck == 4
bigEndian = endianCheck == 1

  -- ryan



Using modules Data.Binary, Data.Binary.Put and Data.Word, you can define

  littleEndian =  (decode $ runPut $ putWord16host 42 :: Word8) == 42

Under the hood, it also uses peek and poke, but it looks a bit more 
functional.



--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Detecting system endianness

2008-12-18 Thread Holger Siegel
On Thursday 18 December 2008 13:40:47 Ryan Ingram wrote:
> Actually, this is probably safer:
>
> import Foreign.Marshal.Alloc
> import Foreign.Ptr
> import Foreign.Storable
> import Data.Word
> import System.IO.Unsafe
>
> endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 ::
> Word32) >> peek (castPtr p :: Ptr Word8)
>
> littleEndian = endianCheck == 4
> bigEndian = endianCheck == 1
>
>   -- ryan
>
> On Thu, Dec 18, 2008 at 4:33 AM, Ryan Ingram  wrote:
> > I think something like this might work:
> >
> > Prelude GHC.Exts GHC.Word> let W64# x = 0x10002 in W32#
> > (unsafeCoerce# x) 2
> >
> > You should get 1 for big-endian and 2 for little-endian.
> >
> > (Disclaimer: not particularily well-tested.)


Using modules Data.Binary, Data.Binary.Put and Data.Word, you can define

  littleEndian =  (decode $ runPut $ putWord16host 42 :: Word8) == 42

Under the hood, it also uses peek and poke, but it looks a bit more 
functional.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Detecting system endianness

2008-12-18 Thread Ryan Ingram
Actually, this is probably safer:

import Foreign.Marshal.Alloc
import Foreign.Ptr
import Foreign.Storable
import Data.Word
import System.IO.Unsafe

endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 ::
Word32) >> peek (castPtr p :: Ptr Word8)

littleEndian = endianCheck == 4
bigEndian = endianCheck == 1

  -- ryan

On Thu, Dec 18, 2008 at 4:33 AM, Ryan Ingram  wrote:
> I think something like this might work:
>
> Prelude GHC.Exts GHC.Word> let W64# x = 0x10002 in W32# (unsafeCoerce# x)
> 2
>
> You should get 1 for big-endian and 2 for little-endian.
>
> (Disclaimer: not particularily well-tested.)
>
>  -- ryan
>
> On Thu, Dec 18, 2008 at 3:27 AM, Mauricio  wrote:
>> Hi,
>>
>> Is there some way I can check the endianness
>> of the machine my haskell code is running in?
>>
>> Thanks,
>> Maurício
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Detecting system endianness

2008-12-18 Thread Ryan Ingram
I think something like this might work:

Prelude GHC.Exts GHC.Word> let W64# x = 0x10002 in W32# (unsafeCoerce# x)
2

You should get 1 for big-endian and 2 for little-endian.

(Disclaimer: not particularily well-tested.)

  -- ryan

On Thu, Dec 18, 2008 at 3:27 AM, Mauricio  wrote:
> Hi,
>
> Is there some way I can check the endianness
> of the machine my haskell code is running in?
>
> Thanks,
> Maurício
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Detecting system endianness

2008-12-18 Thread Mauricio

Hi,

Is there some way I can check the endianness
of the machine my haskell code is running in?

Thanks,
Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe