Re: [Haskell-cafe] Joy Combinators (Occurs check: infinite type)

2005-03-11 Thread Keean Schupke
Greg Buchholz wrote:
   Wow.  Color me impressed.  A little under a week ago, I stumbled
onto Joy, and thought to myself that it could be translated almost
directly into Haskell (which would imply it was possible to statically
type).  Well, it wasn't quite as direct as I had initially thought, but
it looks like you've done it.  Are there any papers/books out there
which I could study to learn more about these (and other) tricks of the
type system wizards? 
 

Here's a cleaned up version, I have made the function composition and 
stack both
use HLists... a bit neater. Have also added primrec and a 5th factorial.

As for type tricks most of these should be in the HList or OOHaskell 
papers. The things to notice are using types as instance labels, that 
constraints form horn
clause compile time meta-programs (in a non-backtracking prolog style) 
and that multi-parameter classes with functional depandencies simulate 
some dependant
types.

   Keean.
{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-overlapping-instances #-}
{-# OPTIONS -fallow-undecidable-instances #-}

--Joy implemented in Haskell... extensible embedded language...

module Joy where

import MainGhcGeneric1

-- Building non-empty lists

type HOne = HSucc HZero
hOne :: HOne
hOne = undefined
type HTwo = HSucc HOne
hTwo :: HTwo
hTwo = undefined
type HThree = HSucc HTwo
hThree :: HThree
hThree = undefined

end :: HNil
end = hNil

instance HList s = Apply HNil s s where
	apply _ s = s
instance (HList s,HList s',HList l,Apply a s s',Apply l s' s'') = Apply (HCons a l) s s'' where
	apply (HCons a l) s = apply l (apply a s :: s')
instance HList s = Apply HZero s (HCons HZero s) where
	apply _ s = hCons hZero s
instance (HNat a,HList s) = Apply (HSucc a) s (HCons (HSucc a) s) where
	apply a s = hCons a s

data Lit a = Lit a
lit :: a - Lit a
lit a = Lit a
unl :: Lit a - a
unl (Lit a) = a
instance Show a = Show (Lit a) where
	showsPrec _ (Lit a) = showChar '[' . shows a . showChar ']'
instance HList s = Apply (Lit a) s (HCons a s) where
	apply (Lit a) s = hCons a s

class (HBool b,HList s) = HIfte b t f s s' | b t f s - s' where
	hIfte :: b - t - f - s - s'
instance (HList s,Apply t s s') = HIfte HTrue t f s s' where
	hIfte _ t _ s = apply t s
instance (HList s,Apply f s s') = HIfte HFalse t f s s' where
	hIfte _ _ f s = apply f s

data Ifte
ifte :: Ifte
ifte = undefined
instance Show Ifte where
	showsPrec _ _ = showString If
instance (Apply b s r,HHead r b',HIfte b' t f s s')
	= Apply Ifte (f :*: t :*: b :*: s) s' where
	apply _ (HCons f (HCons t (HCons b s))) = hIfte (hHead (apply b s :: r) :: b') t f s

data Nul
nul :: Nul
nul = undefined
instance Show Nul where
	showsPrec _ _ = showString Nul
instance HList s = Apply Nul (HCons HZero s) (HCons HTrue s) where
	apply _ (HCons _ s) = hCons hTrue s
instance HList s = Apply Nul (HCons (HSucc n) s) (HCons HFalse s) where
	apply _ (HCons _ s) = hCons hFalse s

data EQ
eq :: EQ
eq = undefined
instance Show EQ where
	showsPrec _ _ = showString Eq
instance (HList s,TypeEq a b t) = Apply EQ (HCons a (HCons b s)) (HCons t s) where
	apply _ (HCons a (HCons b s)) = hCons (typeEq a b) s

data Dip
dip :: Dip
dip = undefined
instance Show Dip where
	showsPrec _ _ = showString Dip
instance (HList s,HList s',Apply a s s') = Apply Dip (HCons a (HCons b s)) (HCons b s') where
	apply _ (HCons a (HCons b s)) = hCons b (apply a s)

data Dup 
dup :: Dup
dup = undefined
instance Show Dup where
	showsPrec _ _ = showString Dup
instance HList s = Apply Dup (HCons a s) (HCons a (HCons a s)) where
	apply _ s@(HCons a _) = hCons a s

data Pop
pop :: Pop
pop = undefined
instance Show Pop where
	showsPrec _ _ = showString Pop
instance HList s = Apply Pop (HCons a s) s where
	apply _ (HCons _ s) = s

data Swap
swap :: Swap
swap = undefined
instance Show Swap where
	showsPrec _ _ = showString Swap
instance HList s = Apply Swap (HCons a (HCons b s)) (HCons b (HCons a s)) where
	apply _ (HCons a (HCons b s)) = hCons b (hCons a s)

data Suc
suc :: Suc
suc = undefined
instance Show Suc where
	showsPrec _ _ = showString Suc
instance (HNat a,HList s) = Apply Suc (HCons a s) (HCons (HSucc a) s) where
	apply _ (HCons _ s) = hCons (undefined::HSucc a) s

data Pre
pre :: Pre
pre = undefined
instance Show Pre where
	showsPrec _ _ = showString Pre
instance (HNat a,HList s) = Apply Pre (HCons (HSucc a) s) (HCons a s) where
	apply _ (HCons _ s) = hCons (undefined::a) s

data Add
add :: Add
add = undefined
instance Show Add where
	showsPrec _ _ = showString Add
instance (HList s,HAdd a b c) = Apply Add (HCons a (HCons b s)) (HCons c s) where
	apply _ (HCons _ (HCons _ s)) = hCons (hAdd (undefined::a) (undefined::b)) s

class (HNat a,HNat b) = HAdd a b c | a b - c where
	hAdd :: a - b - c
instance HAdd HZero HZero HZero where
	hAdd _ _ = hZero
instance HNat b = HAdd HZero (HSucc b) (HSucc b) where
	hAdd _ b = b
instance HNat a = HAdd (HSucc a) HZero (HSucc a) where
	hAdd a _ = a
instance (HNat (HSucc a),HNat (HSucc b),HNat c,HAdd a b c)
	= HAdd 

Re: [Haskell-cafe] Joy Combinators (Occurs check: infinite type)

2005-03-11 Thread Greg Buchholz
Keean Schupke wrote:
 The things to notice are using types as instance labels, that constraints
 form horn clause compile time meta-programs (in a non-backtracking prolog
 style) and that multi-parameter classes with functional depandencies simulate
 some dependant types.
 

I think I understood everything in that sentance up to the word as ;-)


Greg

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


[Haskell-cafe] hFileSize vs length

2005-03-11 Thread S. Alexander Jacobson
I am using GHC 6.2 on windows and am finding that when I open a file 
and use hFileSize I get a different number than I get from reading in 
the file and calculating the length.  I assume this is not a bug, but 
I don't know why its happening.

Also, why isn't there getFileSize function in System.Directory?
-Alex-
__
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbern's Example 7

2005-03-11 Thread Alson Kemp
Title: Message



All,
 
I'm having substantial difficulty understanding Jeff Newbern's Example 7. 
Would love some help.
 My questions are: How does liftM2 know to lift fn into the _List_ monad? 
(Because it's the only possibility?) After fn is lifted, where is "bind" 
used in allCombinations?

 Basically, I'd some a detailed explanation of how allCombinations works, 
cause I'm not grokking it...


 - 
Alson
---import Monad

-- allCombinations returns a list containing the result of
-- folding the binary operator through all combinations
-- of elements of the given lists
-- For example, allCombinations (+) [[0,1],[1,2,3]] would be
--   [0+1,0+2,0+3,1+1,1+2,1+3], or [1,2,3,2,3,4]
-- and allCombinations (*) [[0,1],[1,2],[3,5]] would be
--   [0*1*3,0*1*5,0*2*3,0*2*5,1*1*3,1*1*5,1*2*3,1*2*5], or [0,0,0,0,3,5,6,10]
allCombinations :: (a - a - a) - [[a]] - [a]
allCombinations fn [] = []
allCombinations fn (l:ls) = foldl (liftM2 fn) l ls

-- print an example
showExample :: (Show a) = String - (a - a - a) - [[a]] - IO ()
showExample opName op ls = do putStrLn $ "opName over " ++ (show ls) ++ " = "
  putStrLn $ "  " ++ (show (allCombinations op ls)) 

-- shows a few examples of using allCombinations
main :: IO ()
main = do showExample "+" (+)   [[0,1],[1,2,3]]
  showExample "*" (*)   [[0,1],[1,2],[3,5]]
  showExample "/" div   [[100, 45, 365], [3, 5], [2, 4], [2]]

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


[Haskell-cafe] fgl and Windows

2005-03-11 Thread Tom Spencer
Does anyone have a build.bat that they have used to install fgl on
windows that they could donate to me?

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


Re: [Haskell-cafe] Parity of the number of inversions of a permutation

2005-03-11 Thread William Lee Irwin III
On Wed, Mar 09, 2005 at 12:42:09PM +0100, Henning Thielemann wrote:
 I think it is a quite popular problem. I have a permutation and I want to 
 count how often a big number is left from a smaller one. More precisely 
 I'm interested in whether this number is even or odd. That's for instance 
 the criterion to decide whether Lloyd's shuffle puzzle is solvable or not.
 Example:
   1 4 3 2
 I can choose six pairs (respecting the order) of numbers out of it, namely 
 (1,4) (1,3) (1,2) (4,3) (4,2) (3,2), where in the last three pairs the 
 first member is greater than the second one. Thus I have 3 inversions and 
 an odd parity.
 I'm searching for a function which sorts the numbers and determines the 
 parity of the number of inversions. I assume that there are elegant and 
 fast algorithms for this problem (n * log n time steps), e.g. a merge sort 
 algorithm. A brute force solution with quadratic time consumption is
 countInversions :: (Ord a) = [a] - Int
 countInversions = sum . map (\(x:xs) - length (filter (x) xs)) . init . 
 tails

That's not a permutation, that's a cycle. Permutations are sets of
disjoint cycles (which commute).


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


[Haskell-cafe] Solution to Thompson's Exercise 4.4

2005-03-11 Thread Kaoru Hosokawa
I have been working through the exercises in Thompson's The Craft of 
Functional Programming 2nd Ed book. I am looking for a solution web 
site for Thompson's book. Or maybe the people here can help.

In exercise 4.4, I am asked to define a function
howManyOfFourEqual :: Int - Int - Int - Int - Int
which returns the number of integers that are equal to each other. For 
example,

howManyOfFourEqual 1 1 1 1 = 4
howManyOfFourEqual 1 2 3 1 = 2
howManyOfFourEqual 1 2 3 4 = 0
This is my solution. I give it here, since it's not an elegant solution.
howManyOfFourEqual :: Int - Int - Int - Int - Int
howManyOfFourEqual a b c d
| a == b  howManyEqual b c d /= 0 = howManyEqual 
b c d + 1
| a == c  howManyEqual b c d /= 0 = howManyEqual 
b c d + 1
| a == d  howManyEqual b c d /= 0 = howManyEqual 
b c d + 1
| a == b  howManyEqual b c d == 0 = 2
| a == c  howManyEqual b c d == 0 = 2
| a == d  howManyEqual b c d == 0 = 2
| otherwise 
= howManyEqual b c d
howManyEqual is a function from a previous exercise.
howManyEqual :: Int - Int - Int - Int
howManyEqual a b c
| a == b  b == c  = 3
| a /= b  b /= c  a /= c= 0
| otherwise = 2
I hope to find a better solution. I googled but couldn't find the 
answer.

Kaoru Hosokawa
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Solution to Thompson's Exercise 4.4

2005-03-11 Thread Andy Georges
Hi Kaoru,

 I have been working through the exercises in Thompson's The Craft of
 Functional Programming 2nd Ed book. I am looking for a solution web
 site for Thompson's book. Or maybe the people here can help.

 In exercise 4.4, I am asked to define a function

  howManyOfFourEqual :: Int - Int - Int - Int - Int

 which returns the number of integers that are equal to each other. For
 example,

  howManyOfFourEqual 1 1 1 1 = 4
  howManyOfFourEqual 1 2 3 1 = 2
  howManyOfFourEqual 1 2 3 4 = 0

A solution which is applicable to any number of arguments is this:

import Data.List
howManyOfFourEqual a b c d = determineMaxEquals [a,b,c,d]

determineMaxEquals :: [a] - Int
determineMaxEquals ls = head $ reverse $ sort $ map length $ group $ sort ls

Of course, determineMaxEquals is fubar if used on an infinite list.

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