Changeset 26 for sizechecking/branches


Ignore:
Timestamp:
May 4, 2014, 8:06:39 PM (11 years ago)
Author:
gobi
Message:

lambda

Location:
sizechecking/branches/macs
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • sizechecking/branches/macs/Lambda.hs

    r25 r26  
    1 {-# LANGUAGE TypeFamilies #-} 
     1{-# LANGUAGE TypeFamilies, GADTs #-} 
    22 
    33module Lambda where 
     
    3636    else showChar $ C.chr $ C.ord 'a' + x 
    3737 
    38 -- unS :: Value supply -> Precedence -> ShowS 
    3938newtype S a = S { unS :: S.Supply Int -> Int -> ShowS } 
    4039 
     
    5958 
    6059 
    61 type family Sem (m :: * -> *) a :: * 
    62 type instance Sem m Int      = Int 
    63 type instance Sem m (a -> b) = m (Sem m a) -> m (Sem m b) 
     60{- 
     61 - reduction 
     62 -} 
     63data IR h t where 
     64    Lit :: Int -> IR h Int 
     65    App :: IR h (a -> b) -> IR h a -> IR h b 
     66    Lam :: (IR h a -> IR h b) -> IR h (a -> b) 
    6467 
    65 newtype R m a = R { unR :: m (Sem m a) } 
     68instance Lambda (IR h) where 
     69    lam = Lam 
     70    app = App 
     71    lit = Lit 
    6672 
    67 share :: (MonadIO m) => m a -> m (m a) 
    68 share f = do 
    69     mem <- liftIO $ newIORef (False, f) 
    70     return $ do 
    71         (evald, thunk) <- liftIO $ readIORef mem 
    72         if evald then thunk 
    73         else do 
    74           value <- thunk 
    75           liftIO $ writeIORef mem (True, return value) 
    76           return value 
    77  
    78 instance (MonadIO m) => Lambda (R m) where  
    79     app x y = R $ unR x >>= ($ (unR y)) 
    80     lit = R . return 
    81     lam f   = R . return $ (\x -> share x >>= unR . f . R) 
     73toFinal :: (Lambda l) => IR h t 
  • sizechecking/branches/macs/Tests/LambdaTest.hs

    r24 r26  
    99test1 :: (Lambda l) => l Int 
    1010test1 = app (lam $ \_ -> lit 3) (lit 2) 
     11 
     12const2 :: (Lambda l) => l ( Int -> Int ) 
     13const2 = lam $ \_ -> lit 2 
     14 
     15t3 :: (Lambda l) => l ( (a -> a) -> (a -> a) ) 
     16t3 = (lam $ \f -> lam $ \v -> f `app` (f `app` (f `app` v))) 
     17 
    1118 
    1219test1ast :: IO Bool 
Note: See TracChangeset for help on using the changeset viewer.