Changeset 10


Ignore:
Timestamp:
Nov 14, 2012, 8:45:28 PM (13 years ago)
Author:
gobi
Message:

adding a new implementation of Lambda

Files:
2 added
1 edited
1 moved

Legend:

Unmodified
Added
Removed
  • sizechecking/Examples.hs

    r5 r10  
    210210comp :: (SizedExp se)  => Size se ( (b->c) -> (a->b) -> a->c ) 
    211211comp = bind comps $ \f g x -> f `app` (g `app` x) 
     212 
     213test1s = Abs 2 $ AAbs 19 6 $ (Var 2) `App` (List (Var 19) (Var 6)) 
     214test1 :: (SizedExp se)  => Size se (([a] -> [b]) -> [a] -> [b]) 
     215test1 = bind test1s $ \f l -> match (f `app` l) nil (\x xs -> f `app` l) 
     216 
     217 
     218test2s = Abs 2 $ AAbs 18 5  $ appends `App` (Var 2 `App` (List (Var 18) (Var 5))) `App` (List (Var 18) (Var 5)) 
     219test2 :: (SizedExp se)  => Size se (([a] -> [a]) -> [a] -> [a]) 
     220test2 = bind test2s $ \f l -> append `app` (f `app` l) `app` l 
    212221 
    213222data TestCase = forall a . TestCase P.String (forall se. SizedExp se => Size se a) 
  • sizechecking_branches/L.hs

    r9 r10  
    1 {-# Language GADTs, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, ScopedTypeVariables, TypeFamilies, NoMonomorphismRestriction #-} 
     1{-# Language GADTs, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, FunctionalDependencies, ScopedTypeVariables, TypeFamilies, NoMonomorphismRestriction, OverlappingInstances #-} 
     2module L where 
    23 
    34import Data.Char(ord, chr) 
     
    1112{- Lambda calculus without free variables -} 
    1213type Arr repr a b = repr a -> repr b 
    13 --type family Arr (repr :: * -> *) (a :: *) (b :: *) :: * 
    1414 
    1515class Lambda l where 
     
    2626    undef   :: l Bottom 
    2727    unsized :: l () 
     28 
     29instance Lambda l => Show (l a) where 
     30    showsPrec _ e = error "Error: no show" 
     31 
     32instance Lambda l => Eq (l a) where 
     33    (==) _ _ = error "Error: no eq" 
    2834 
    2935instance Lambda l => Num (l Int) where 
Note: See TracChangeset for help on using the changeset viewer.