[Haskell-cafe] Printing the empty list.

2011-06-30 Thread Joshua Ball
GHCi seems to be clever about some things:

If I try to print the empty list in ghci, I encounter no problems:

Prelude []
[]
Prelude show []
[]
Prelude print []
[]

Even though the type of the list is clearly unknown, it must be
picking SOME type. (why does it print [] instead of )?

If I write a program in a file and load it in

main = print []

Then I get the ambiguous type variable error that I would expect. Why
doesn't ghci generate this error at the prompt?

-- 
Borrow my books: http://goo.gl/UBbSH

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


[Haskell-cafe] Tying the recursive knot

2011-03-24 Thread Joshua Ball
{-
 - Hi all,
 -
 - I'm having trouble tying the recursive knot in one of my programs.
 -
 - Suppose I have the following data structures and functions:
 -}
module Recursion where

import Control.Monad.Fix
import Data.Map ((!))
import qualified Data.Map as M
import Debug.Trace

newtype Key = Key { unKey :: String }
  deriving (Eq, Ord, Show)

data Chain = Link Int Chain | Trace String Chain | Ref Key
  deriving (Show)

reduce :: M.Map Key Chain - Key - [Int]
reduce env k = follow (env ! k) where
  follow (Link i c) = i : follow c
  follow (Ref k) = reduce env k
  follow (Trace message c) = trace message (follow c)

-- Now I want a force function that expands all of the chains into
int sequences.
force1, force2 :: M.Map Key Chain - M.Map Key [Int]

-- This is pretty easy to do:
force1 mp = M.fromList (map (\k - (k, reduce mp k)) (M.keys mp))

-- But I want the int sequences to be lazy. The following example
illustrates that they are not:
example = M.fromList [(Key ones, Link 1 . Trace expensive
computation here . Ref . Key $ ones)]
-- Run force1 example in ghci, and you will see the expensive
computation here messages interleaved with an infinite
-- list of ones. I would prefer for the expensive computation to
happen only once.

-- Here was my first attempt at regaining laziness:
fixpointee :: M.Map Key Chain - M.Map Key [Int] - M.Map Key [Int]
fixpointee env mp = M.fromList (map (\k - (k, reduce env k)) (M.keys mp))

force2 env = fix (fixpointee env)

main = print $ force2 example

{-
 - However, this gets stuck in an infinite loop and doesn't make it
past printing fromList .
 - (It was not difficult for me to see why, once I thought about it.)
 -
 - How do I recover laziness? A pure solution would be nice, but in
the actual program
 - I am working on, I am in the IO monad, so I am ok with an impure solution.
 - It's also perfectly ok for me to modify the reduce function.
 -
 - Thanks in advance for you help,
 - Josh Ua Ball
 -}

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


Re: [Haskell-cafe] Tying the recursive knot

2011-03-24 Thread Joshua Ball
Never mind. I figured it out on my own. Here's my solution for
posterity. There's probably a fix hiding in there somewhere - notice
the new type of reduce.

module Recursion where

import Data.Map ((!))
import qualified Data.Map as M
import Debug.Trace

newtype Key = Key { unKey :: String }
  deriving (Eq, Ord, Show)

data Chain = Link Int Chain | Trace String Chain | Ref Key
  deriving (Show)

force :: M.Map Key Chain - M.Map Key [Int]
force mp = ret where
  ret = M.fromList (map (\k - (k, reduce mp (ret !) k)) (M.keys mp))

reduce :: M.Map Key Chain - (Key - [Int]) - Key - [Int]
reduce mp lookup key = follow (mp ! key) where
  follow (Link i c) = i : follow c
  follow (Ref k) = lookup k
  follow (Trace message c) = trace message (follow c)

example = M.fromList [(Key ones, Link 1 . Trace expensive
computation here . Ref . Key $ ones)]

main = print $ take 10 $ (force example ! Key ones)

On Thu, Mar 24, 2011 at 12:35 PM, Joshua Ball joshbb...@gmail.com wrote:
 {-
  - Hi all,
  -
  - I'm having trouble tying the recursive knot in one of my programs.
  -
  - Suppose I have the following data structures and functions:
  -}
 module Recursion where

 import Control.Monad.Fix
 import Data.Map ((!))
 import qualified Data.Map as M
 import Debug.Trace

 newtype Key = Key { unKey :: String }
  deriving (Eq, Ord, Show)

 data Chain = Link Int Chain | Trace String Chain | Ref Key
  deriving (Show)

 reduce :: M.Map Key Chain - Key - [Int]
 reduce env k = follow (env ! k) where
  follow (Link i c) = i : follow c
  follow (Ref k) = reduce env k
  follow (Trace message c) = trace message (follow c)

 -- Now I want a force function that expands all of the chains into
 int sequences.
 force1, force2 :: M.Map Key Chain - M.Map Key [Int]

 -- This is pretty easy to do:
 force1 mp = M.fromList (map (\k - (k, reduce mp k)) (M.keys mp))

 -- But I want the int sequences to be lazy. The following example
 illustrates that they are not:
 example = M.fromList [(Key ones, Link 1 . Trace expensive
 computation here . Ref . Key $ ones)]
 -- Run force1 example in ghci, and you will see the expensive
 computation here messages interleaved with an infinite
 -- list of ones. I would prefer for the expensive computation to
 happen only once.

 -- Here was my first attempt at regaining laziness:
 fixpointee :: M.Map Key Chain - M.Map Key [Int] - M.Map Key [Int]
 fixpointee env mp = M.fromList (map (\k - (k, reduce env k)) (M.keys mp))

 force2 env = fix (fixpointee env)

 main = print $ force2 example

 {-
  - However, this gets stuck in an infinite loop and doesn't make it
 past printing fromList .
  - (It was not difficult for me to see why, once I thought about it.)
  -
  - How do I recover laziness? A pure solution would be nice, but in
 the actual program
  - I am working on, I am in the IO monad, so I am ok with an impure solution.
  - It's also perfectly ok for me to modify the reduce function.
  -
  - Thanks in advance for you help,
  - Josh Ua Ball
  -}


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


[Haskell-cafe] Reference monad

2011-03-11 Thread Joshua Ball
Hi,

Suppose I want the following functions:

newRef :: a - RefMonad (Ref a)
readRef :: Ref a - RefMonad a
writeRef :: Ref a - a - RefMonad ()

for some appropriate data Ref = ...

Obviously these functions are already satisfied by IORefs and STM.

But if I wanted to implement my own (for fun)... would it be possible?
Particularly, in a pure way, without unsafePerformIO?

runRefMonad :: RefMonad a - a

I could try to do it with a state monad, and keep all of the refs in a
Data.Map, but then I would have to solve the garbage collection
problem, so that doesn't really work.

Josh Ua Ball

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


[Haskell-cafe] universal quantification is to type instantiations as existential quantification is to what

2010-08-12 Thread Joshua Ball
Hi,

If I have a universally quantified type

mapInt :: forall a. (Int - a) - [Int] - [a]

I can instantiate that function over a type and get a beta-reduced
version of the type

mapInt [String] :: (Int - String) - [Int] - [String]

(I'm borrowing syntax from Pierce here since I don't think Haskell
allows me to explicitly pass in a type to a function.)

This makes sense to me. The universal quantifier is basically a
lambda, but it works at the type level instead of the value level.

My question is... what is the analog to an existential type?

mapInt :: exists a. (Int - a) - [Int] - [a]

(I don't think this is valid syntax either. I understand that I can
rewrite this using foralls and a new type variable, doing something
that looks like double negation, but the point of my question is to
get an intuition for what exactly the universal quantifier means in
the context of function application... if this even makes sense.)

In particular:

1. If I can instantiate variables in a universal quantifier, what is
the corresponding word for variables in an existential quantifier?
2. If type instantiation of a universally quantified variable is
beta-reduction, what happens when existentially quantified variables
are [insert answer to question 1]?
3. Is there any analogue to existential quantifiers in the value
world? Forall is to lambda as exists is to what?

Also (separate question), is the following statement true?

forall T :: * - *.   (forall a. T a) - (exists a. T a)

If so, what does the implementation look like? (What function inhabits
it, if it is interpreted as a type?)

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


Re: [Haskell-cafe] *** JOB OFFER *** related to realtime 3D graphics, animation and reactive content

2008-02-15 Thread Joshua Ball
How unfortunate that I didn't see your announcement before, as I have
just accepted a job with another company.

However, I have added your company to the Haskell in Industry page on
the Haskell wiki.

http://haskell.org/haskellwiki/Haskell_in_industry

Please add a paragraph describing your company.

I have also added this announcement to the Haskell jobs page

http://haskell.org/haskellwiki/Jobs

which is the #1 Google result for a search of haskell jobs.

2008/2/15 Peter Verswyvelen [EMAIL PROTECTED]:




 Anygma is a startup company focusing on generating easy-to-use tools for
 creating audio-visual 2D/3D content, in the area of entertainment, media,
 corporate communication and the internet.

  Anygma has recently raised new capital in order to fund the development of
 a new platform targeted towards artists and designers for generating
 procedural and reactive geometry, animations and games.

  We are looking for talented and passionate computer scientists and software
 engineers to help us design and implement a prototype of this platform.

  If you are interested in applying Haskell, OpenGL, and some C/C++, to
 create such a platform, feel free to apply for the job by sending an email
 to peter AT nazooka DOT com.

  More information about the job offer can be found here.

  Thank you,
  Peter Verswyvelen,
  Software Architect,
  www.anygma.com



 PS: This job offer was already placed in the Haskell Café a while ago, but
 apparently many Haskellers did not notice it, so here's take#2








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


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


Re: [Haskell-cafe] Should do 1 compile

2007-05-23 Thread Joshua Ball

While we're on the topic of coupling/cohesion of types and syntactic
sugar (and because sometimes problems are made easier by generalizing
them), I have a question.

What is the rationale for disallowing the following code?

main = print Type 'True' on three lines or I will quit.  foo

foo = [ () | line1 - readLn, line1, line2 - readLn, line2, line3 -
readLn, line3]

Obviously this example is contrived, and you'd never want to use the
list comprehension syntax for the IO monad. But you might want to for,
say, the probability monad. Isn't that enough reason enough to
decouple the sugar from the typing? (Though I agree with Claus that
cryptic error messages are a bad thing.)

On 5/23/07, Stefan Holdermans [EMAIL PROTECTED] wrote:

Spencer,

 How about:

  do x == (x :: Monad m = m a)

That one does not do it, because now you demand x to be polymorphic
in all monad types m and all monad-element types a, which I guess
restricts x to

   undefined

and

   return undefined

and combinations thereof, glued together by monadic binds.

   do x == (asTypeOf x (return ()))

Again, no, for now you restrict the element type to () and, hence,
you preclude, for instance,

   do return False

Cheers,

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


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


Re: [Haskell-cafe] a question concerning type constructors

2007-05-05 Thread Joshua Ball

I'm not sure what you want to accomplish, but if you like type
hackery, this might be helpful:

http://okmij.org/ftp/Haskell/types.html#polyvar-fn

On 5/5/07, Eric [EMAIL PROTECTED] wrote:

Hi all,

In Haskell, is it possible to declare a type constructor with a variable
number of type variables e.g.

data Tuple * 

allowing the following declarations:

t: Tuple
u: Tuple Bool
v: Tuple Bool Int
w: Tuple Bool Int Char

?

E.


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


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


[Haskell-cafe] Any Haskellers in Chicagoland?

2007-05-03 Thread Joshua Ball

I'd love to post an ANN: Chicago Haskell user group, but i want to
make sure there's more than one of me.

-johnnn



I live in the Northwest Suburbs of Chicago (specifically Wheaton), and
I would LOVE to join a Chicago Haskell user group.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] multi parameter type classes for NP problems

2006-12-20 Thread Joshua Ball

Hi all,

For my own study, I've been playing around with various NP complete
problems. Previuosly I was doing so in Java, but because I want to
learn Haskell, I'm trying to port the algorithms. In Java, I had an
abstract class called AbstractNPProblem which looked like this:

public abstract class AbstractNPProblem implements NPProblem {
   public abstract boolean validates(Certificate c);
   public abstract ListCertificate certificates();
   public boolean decide() {
   for (Certificate c : certificates()) {
   if (validates(c)) {
   return true;
   }
   }
   return false;
   }
}

This has one problem, however: it is slightly dynamically typed.
Anybody that implements the verify method must cast the object c to a
particular type (could be a bitmask, a list of integers, a subgraph,
etc.) I'd like to get rid of this problem in porting to Haskell. Here
is how I am trying to solve the problem, using multi-parameter type
classes.

class NPProblem inst cert where
   validates :: cert - inst - Bool
   certificates :: inst - [cert]
   decide :: inst - Bool
   decide i = any (\x - x `validates` i) $ certificates i

Unfortunately, ghc throws the following type error:

NPProblem.hs:5:45
   Could not deduce (NPProblem inst a)
 from the context (NPProblem inst cert)
 arising from use of `certificates' at NPProblem.hs:5:45-58
   Possible fix:
 add (NPProblem inst a) to the class or instance method `decide'
   In the second argument of `($)', namely `certificates i'
   In the expression:
 (any (\ x - x `validates` i)) $ (certificates i)
   In the definition of `decide':
   decide i = (any (\ x - x `validates` i)) $ (certificates i)

Could somebody explain what is wrong with my intuitive approach? Also,
is multi parameter type classes the way to go, or is there a better
way?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] multi parameter type classes for NP problems

2006-12-20 Thread Joshua Ball

That works. Thanks. I didn't realize you could put types in the
expression itself.

On 12/20/06, Greg Buchholz [EMAIL PROTECTED] wrote:

Joshua Ball wrote:
 Here is how I am trying to solve the problem, using multi-parameter
 type classes.

 class NPProblem inst cert where
validates :: cert - inst - Bool
certificates :: inst - [cert]
decide :: inst - Bool
decide i = any (\x - x `validates` i) $ certificates i

 Unfortunately, ghc throws the following type error:

 NPProblem.hs:5:45
Could not deduce (NPProblem inst a)
  from the context (NPProblem inst cert)
  arising from use of `certificates' at NPProblem.hs:5:45-58
Possible fix:
  add (NPProblem inst a) to the class or instance method `decide'
In the second argument of `($)', namely `certificates i'
In the expression:
  (any (\ x - x `validates` i)) $ (certificates i)
In the definition of `decide':
decide i = (any (\ x - x `validates` i)) $ (certificates i)

Maybe something like?...

class NPProblem inst cert where
   validates :: cert - inst - Bool
   certificates :: inst - [cert]
   decide :: inst - Bool
   decide i = any (\x - x `validates` i) $ (certificates i :: [cert])

...or a functional dependency of some sort...

class NPProblem inst cert | inst - cert where

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


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