File: Test5.hs

package info (click to toggle)
haskell-data-reify 0.6.4-1
  • links: PTS, VCS
  • area: main
  • in suites: sid
  • size: 124 kB
  • sloc: haskell: 611; makefile: 3
file content (50 lines) | stat: -rw-r--r-- 1,179 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Main (main) where

import Common

import Control.Applicative hiding (Const)

import Data.Dynamic
import Data.Reify

import System.CPUTime

import Prelude

data List a b = Nil | Cons a b
  deriving Show

instance Typeable a => MuRef [a] where
  type DeRef [a] = List a

  mapDeRef f (x:xs) = Cons x <$> f xs
  mapDeRef _ []     = pure Nil


instance Functor (List a) where
   fmap _ Nil = Nil
   fmap f (Cons a b) = Cons a (f b)

main :: IO ()
main = do
        let g1 = [1..(10::Int)]
        reifyGraph g1 >>= print
        let g2 = [1..(10::Int)] ++ g2
        reifyGraph g2 >>= print

        -- now, some timings.
        ns <- sequence [ timeme n | n <- take 8 (iterate (*2) 1024) ]
        print $ reverse $ take 4 $ reverse [ n2 / n1 | (n1,n2) <- zip ns (tail_ ns) ]

timeme :: Int -> IO Float
timeme n = do
        i <- getCPUTime
        let g3 = [1..n] ++ g3
        reifyGraph g3 >>= \ (Graph xs _) -> putStr $ show (length xs)
        j <- getCPUTime
        let n' :: Float
            n' = fromIntegral ((j - i) `div` 1000000000)
        putStrLn $ " ==> " ++ show (n' / 1000)
        return n'