UArray for newtypes (LogFloat)
Don Stewart
dons at galois.com
Mon Mar 9 17:36:36 EDT 2009
bulat.ziganshin:
> Hello Felipe,
>
> Saturday, March 7, 2009, 4:22:04 PM, you wrote:
>
> > So, I would like to make an UArray of LogFloat. They are a newtype of Double
>
> this is possible in UArray reimplementation done in ArrayRef library
> http://haskell.org/haskellwiki/Library/ArrayRef
> although the library itself may be not compatible with ghc 6.10.
> try to search on hackage
>
Can't you also just using generic newtype deriving?
E.g. a UArr instance for free:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Data.Array.Vector
newtype LogFloat = LogFloat Double
deriving (Eq,Ord,Show,Num,UA)
main = print . sumU $ replicateU 1000 (LogFloat pi)
Which, btw, still triggers all the usual fusion:
$wfold :: Double# -> Int# -> Double#
$wfold =
\ (ww_s14A :: Double#) (ww1_s14E :: Int#) ->
case ww1_s14E of wild_B1 {
__DEFAULT ->
$wfold
(+## ww_s14A 3.141592653589793) (+# wild_B1 1);
1000 -> ww_s14A
$ time ./A
LogFloat 3141.5926535897806
./A 0.00s user 0.00s system 154% cpu 0.004 total
-- Don
More information about the Libraries
mailing list