Re: [Haskell-cafe] existentially quantified data types - restrictions

2010-03-25 Thread andy morris
Can you have Typeable as an extra constraint? If so:

 {-# LANGUAGE ExistentialQuantification #-}

 import Data.Typeable

 data Baz = forall a. (Eq a, Typeable a) = Baz a

 instance Eq Baz where
   Baz x == Baz y =
 case cast y of
  Just y' - x == y'
  Nothing - False

ghci Baz 4 == Baz 4
True
ghci Baz 4 == Baz 5
False
ghci Baz 4 == Baz 'a'
False

On 25 March 2010 15:07, Ozgur Akgun ozgurak...@gmail.com wrote:
 Dear Cafe,

 I need to use a language feature which is explicitly documented to be a
 restriction, and -even worse- I think I reasonably need to use it.


 f2 (Baz1 a b) (Baz1 p q) = a==q
 It's ok to say a==b or p==q, but a==q is wrong because it equates the two
 distinct types arising from the two Baz1 constructors.
 [from 7.4.4.4. Restrictions at
 http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html]


 To simplify, let's say Baz is the only constructor of a data type,

 data Baz = forall a. Eq a = Baz a

 -- | this cannot be done:
 instance Eq (Baz a) where
     (Baz x) == (Baz y) = x == y


 I am quite tempted to use show functions for this equality comparison, but
 after trying to have a nicely type framework I really don't want to do that.
 What I simply want is, haskell to be able to compare them if they belong to
 the same type, and return False otherwise. (not that haskelly way of doing
 things, I know.)

 Any suggestions better than the following are very welcome:
     (==) = (==) `on` show


 Regards,

 --
 Ozgur Akgun

 ___
 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] difference cabal configure and runghc Setup.lhs configure

2009-10-08 Thread andy morris
2009/10/8 Andrew U. Frank fr...@geoinfo.tuwien.ac.at:
 i have a strange error, which does not occur when i run
 runghc Setup.lhs configure
 but when i use cabal configure and then build, it occurs.

 the error is
 Type constructor Control.Exception.Exception used as a class
 in the instance declaration.
 (i have imported qualified Control.Exception)

 two questions:
 1. Exception is a class (in Control.Exception) - why the error?
 2. why is there a difference between runghc and cabal (using the same cabal
 file).

 i attach the cabal file and the two configuratin files produced.


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



C.E.Exception used to be a type instead of a class, so you need to
have `base == 4.*` instead of `base -any`. Alternatively, use the
extensible-extensions package instead.

The difference in results you found is because cabal-install uses
base-3 if you don't specify otherwise. The reason for this is that a
lot of packages use `base -any` when they shouldn't: base-4 brought
enough incompatible changes (like making Exception a class) that they
don't work with it. (This is also, I assume, why GHC has two built-in
versions of base in the first place.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Debugging Haskell code

2009-09-27 Thread andy morris
2009/9/27 Paul Moore p.f.mo...@gmail.com:
 I'm still playing round with my random dieroll generation program. In
 doing so, I just hit a segmentation fault (I didn't think Haskell
 could *cause* a segfault!) I'm sure it's my code - I got this to
 compile by fiddling with types until the errors (which I didn't
 understand) went away. Certainly not the right way to code, I know,
 but never mind.

 The problem is that I have *no idea* how to begin debugging this. In
 C, Python, or any other imperative language, I'd put traces in, etc.
 But in Haskell, I don't even know where to start.

 I attach the code below. While help in the form of pointers to what I
 did wrong would of course be appreciated, what I'm really looking for
 is a pointer on how I'd find out for myself. (Hey! I just read the bit
 in the ghc manual which says if I am not using foreign or unsafe
 functions, a crash is a compiler bug. Did I find a compiler bug?)

 My code is below. All I did is ghc --make hist_3d6.hs, then run
 hist_3d6.exe. This is ghc 6.10.4 on Windows Vista Home 32-bit.

 Thanks for any help,
 Paul.

 import System.Random.Mersenne
 import qualified Data.Map as Map
 import Data.Map (Map)
 import Data.List

 takes :: Int - [a] - [[a]]
 takes n [] = []
 takes n xs = take n xs : takes n (drop n xs)

 sums :: Num a = Int - [a] - [a]
 sums n xs = map sum (takes n xs)

 simulate :: Int - IO [Double]
 simulate count = do
  gen - newMTGen Nothing
  dice - (randoms gen :: IO [Double])
  return (take count dice)

 histogram :: Ord a = [a] - [(a,Int)]
 histogram = Map.assocs . foldl' f Map.empty
  where
   f m k = Map.insertWith' (+) k 1 m

 simulation = do
  lst - simulate 10
  return lst
  --return (histogram lst)

 main = do
  s - simulation
  putStrLn (show s)
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


mersenne-random uses the FFI, so it's probably that. I just ran your
code with mersenne-random-1.0 and didn't get a segfault. What version
are you using?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] About the import module

2009-08-05 Thread andy morris
2009/8/5 xu zhang douy...@gmail.com:
 Hi there,

 If I import a module and do not explicitly point out the entities I have
 imported. And I want the ghc to point out the entities automatically. Is
 there any method to do this? any methods to have the ghc point out the
 entities I import and export?
 Because there are so many files and I don't want to change them one by one,
 so I just want to find if there is a simple and automatic way to have the
 entities pointed out.

 Thank you in advance!


`ghc --make -ddump-minimal-imports Main.hs` will output *.imports
files containing what you want.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] fromInteger for Lists

2009-05-01 Thread andy morris
2009/5/1 Paul Keir pk...@dcs.gla.ac.uk:
 There's nothing better than making a data type an instance of Num. In
 particular, fromInteger is a joy. But how about lists?

 For example, if I have

 data Foo a = F [a]

 I can create a fromInteger such as
 fromInteger i = F [fromInteger i]

 and then a 19::(Foo Int), could become F [19].

 Is it possible to do something similar for lists? So could
 [1,2,3]::(Foo Int) become something slightly different, say,

 F [1,2,3]

 Paul

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



If you mean what I think you're referring to, you can't. The only
reason it works for integer literals is that the compiler replaces
occurrences of, say, 19 with (fromInteger 19).

There's no function that's automatically applied to list literals, so
([1,2,3] :: Foo Int) isn't able to do anything useful, unfortunately.
However, there's an extension in GHC, OverloadedStrings, which lets
you use the method fromString of class Data.String.IsString to
overload literals. (That's not what you asked, though, I know. :) )
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Deriving type family data

2009-04-28 Thread andy morris
2009/4/28 Tuve Nordius t...@student.chalmers.se:
 If I for some data type wants to derive, in this case Data and Typeable for
 use with syb code, but the problem is the same regardless what I want to
 derive.



 data family Something

 data Tree = Leaf Something | Fork Something Tree Tree
        deriving (Data, Typeable)


 The problem is I want to derive a class for a data type that depends on some
 non instantiated data type.

 I can of course rewrite Tree as:

 data (Data a) = Tree a = Leaf a | Fork a Tree Tree
        deriving (Data, Typeable)


 but then data family Something is redundant, I want to think of Something as
 a not yet instantiated abstract data type

 Is there anyway to express that either the instance of Something used in
 Tree should be a member of Data, or even better
 any instance of Something should be a member of Data or maybe even better
 that every instance should  derive data.

 data family Something
        deriving Data


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


If you enable flexible contexts, you can have something like

class Data (Something a) = HasSomething a where
data Something a

It turns out you can't have contexts on family declarations
themselves, though, hence the dummy class. (BTW, you were missing the
parameters on your family declarations.)

Plus, trying it just now, you can't derive Typeable for family
instances, so you'll need to write it longhand. Data seems to be OK,
though.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using Data.Complex

2009-04-22 Thread andy morris
2009/4/22 michael rice nowg...@yahoo.com:
 Just exploring. How to load?

 Michael

 [mich...@localhost ~]$ ghci Data.Complex
 GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.

 no location info: module `Data.Complex' is a package module
 Failed, modules loaded: none.
 Prelude



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



Try ':module + Data.Complex' from within GHCi. (Or 'import
Data.Complex' from within a source file, of course.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Generating functions for games

2009-04-03 Thread andy morris
2009/4/4  gwe...@gmail.com:
 So some time ago I saw mentioned the game of Zendo
 https://secure.wikimedia.org/wikipedia/en/wiki/Zendo_(game) as a good game
 for programmers to play (and not just by Okasaki). The basic idea of Zendo
 is that another player is creating arrangements of little colored plastic
 shapes and you have to guess what rule they satisfy. I thought it'd be fun
 to play, but not knowing anyone who has it, I figured a Haskell version
 would be best.

 3D graphics and that sort of geometry is a bit complex, though. Better to
 start with a simplified version to get the fundamentals right. Why not
 sequences of numbers? For example: [2, 4, 6] could satisfy quite a few rules
 - the rule could be all evens, or it could be ascending evens, or it could
 be incrementing by 2, or it could just be ascending period.

 Now, being in the position of the player who created the rule is no good. A
 good guesser is basically AI, which is a bit far afield. But it seems
 reasonable to have the program create a rule and provide examples. Have a
 few basic rules, some ways to combine them (perhaps a QuickCheck generator),
 and bob's your uncle.

 So I set off creating a dataype. The user could type in their guessed rules
 and then read could be used to compare.  I got up to something like 'data
 Function = Not | Add' and began writing a 'translate' function, along the
 lines of 'translate Not = not\ntranslate Add = (+)', at which point I
 realized that translate was returning different types and this is a Bad
 Thing in Haskell. After trying out a few approaches, I decided the basic
 idea was flawed and sought help.

 Someone in #haskell suggested GADTs, which I've never used. Before I plunge
 into the abyss, I was wondering: does anyone know of any existing examples
 of this sort of thing or alternative approachs? I'd much rather crib than
 create. :)

 --
 gwern


A simple example for this using GADTs might be:

  data Function a where
Not :: Function (Bool - Bool)
Add :: Function (Int - Int - Int)
...

  -- BTW, type signatures are mandatory if you're using GADTs
  translate :: Function a - a
  translate Not = not
  translate Add = (+)
  ...

The important part here is the parameter to Function, and how it's
made more specific in the constructors: even though you're returning
values of different types from translate, it's always the same as the
type the argument is parametrised over.

Not to be all RTFM, but I found the example in the GHC docs quite
helpful as well:
  
http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#gadt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with prepose.lhs and ghc6.10.1

2009-04-02 Thread andy morris
2009/4/2 Henry Laxen nadine.and.he...@pobox.com:
 Dear Group,

 I'm trying to read the paper:
 Functional Pearl: Implicit Configurations
 at http://www.cs.rutgers.edu/~ccshan/prepose/
 and when running the code in prepose.lhs I get:
 ../haskell/prepose.lhs:707:0: Parse error in pattern
 which is pointing at:
 normalize a :: M s a = M (mod a (modulus (undefined :: s)))

 The paper says it uses lexically scoped type variables.  I tried reading about
 them at:
 http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extensions.html#scoped-type-variables

 so I added -XScopedTypeVariables to my OPTIONS but I still get the same error
 message.  I would really like to play with the code in the paper, but I'm 
 stuck
 at this point.  Any pointers would be appreciated.
 Best wishes,
 Henry Laxen

It probably needs brackets:
normalize (a :: M s a) = ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative combinators from Parsec

2009-03-13 Thread andy morris
2009/3/13 Martijn van Steenbergen mart...@van.steenbergen.nl:
 Hello,

 Looking at Parsec 3 I see:

 chainr1 :: (Stream s m t) = ParsecT s u m a -
           ParsecT s u m (a - a - a) - ParsecT s u m a
 chainr1 p op = scan where
  scan = do x - p; rest x
  rest x = (do f - op; y - scan; return (f x y)) | return x


 But if I remove the type signature and let GHC infer it for me, I get a much
 more generic type:

 chainr1 :: (Alternative m, Monad m) = m a - m (a - a - a) - m a

 But we don't really need m to be a monad since we're only doing applicative
 operations, so after some rewriting we get:

 chainr1 :: Alternative f = f a - f (a - a - a) - f a
 chainr1 p op = scan where
  scan = flip id $ p * rest
  rest = (flip $ op * scan) | pure id

 Would it be a good idea to:
 1) make the Parsec combinators as generic as possible and
 2) move the really generic applicative ones to Control.Applicative?

 Thanks,

 Martijn.

This reminds me of something similar I find a bit annoying:

There are some functions like (|) which are defined separately in
Text.Parsec and Control.Applicative, meaning that you have to hide one
of the sets. Would it be better perhaps to just have Parsec reexport
the existing functions from Applicative, or something like that?

(Currently the functions in Parsec have the more specific type as
Martijn says, but if they're generalised then I don't really see why
they need to be duplicated.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Vim support for cabal

2009-03-13 Thread andy morris
2009/3/13 Pavel Perikov peri...@gmail.com:
 Hi café !

 I googled for some kind of vim support for  cabal but found nothing. I mean
 syntax highlighting of .cabal and probably integration with haskellmode. Did
 anyone hear about such thing?

 Pavel

I've been wanting something like this as well, so you inspired me to
finally get round to writing it. :D

I've stuck it on Patch-tag, so:
darcs get http://patch-tag.com/publicrepos/cabal-vim

Nothing special at the moment; it just highlights field names and does
some basic autoindenting. If you (or someone else on the list) have
any suggestions, then just say (or send a patch if you want :) )

I might add to it over the weekend as well (highlighting of compiler
names in the 'tested-on' field, that sort of thing), so perhaps check
back in a few days.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] F# active patterns versus GHC's view

2009-01-15 Thread andy morris
If you don't mind using GHC extensions (which in a view pattern thread
probably isn't much of a stretch to assume :) ), there's always record
punning (-XNamedFieldPuns):

data Foo = { [snip] }
f (Foo { a, g }) = ...

2009/1/15 John Van Enk vane...@gmail.com:
 I've often thought having constructor views would be handy.
 data Foo = Foo A B C D E F G H I
 view Bar = (Foo A _ C _ _ _ G _ I) = Bar A C G I
 This does bring up problems with case alternatives though.
 I think the correct answer for these kinds of views is with the record
 pattern matching syntax, though, I wish there was a more terse way to notate
 it.
 data Foo = {
   a :: A,
   b :: B,
   c :: C,
   d :: D,
   e :: E,
   f :: F,
   g :: G
 }
 f (Foo {a = var_a, g = var_g}) = ...
 /jve


 2009/1/15 Peter Verswyvelen bugf...@gmail.com

 When I first read about active patterns in F#, I found it really cool
 idea, since it allows creating fake data constructors that can be used for
 pattern matching, giving many views to a single piece of data, and allowing
 backwards compatibility when you completely change or hide a data structure.
 So for example one could define a Polar pattern and a Rect pattern that
 give different views of a Complex number, e.g (pseudo code follows)
 pattern Polar c = (mag c, phase c)
 pattern Rect c = (real c, imag c)
 This seems handy:
 polarMul (Polar m1 p1) (Polar m2 p2) = mkComplexFromPolar (m1*m2) (p1+p2)
 However, I think it is flawed, since the following
 case c of
  Polar _ _ - it's polar!
  Rect _ _ - it's rect!
 seems like valid code but does not make any sense.
 So I think the GHC extension of view patterns is better than the active
 patterns in F#?
 A good coding style is to provide constructor functions and hide data
 constructors. But then one looses the ability to perform pattern matching,
 which is so cool in Haskell. Would I have to conclude that it would be good
 coding style to use view patterns as much as possible in Haskell,
 creating auxiliary data constructors to expose the public members of the
 hidden data constructors?




 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe