[Haskell-cafe] Why this cannot be compiled?

2009-07-13 Thread Magicloud Magiclouds
Hi,
  The following code failed to compiled, with error:
Attribute.hs:46:91:
Couldn't match expected type `[t]'
   against inferred type `(a, String)'
In the expression: (color_, rest_)
In a case alternative: [(color_, rest_)] - (color_, rest_)
In the expression:
case reads rest1 of {
  [(color_, rest_)] - (color_, rest_)
  _ - (Color 0 0 0, rest1) }

 43 instance Read Attribute where
 44   readsPrec _ str = [ (mkAttr attr_ color, rest) | (attr_, rest1) - lex str
 45  , (color, rest)
- case reads rest1 of
 46
   [(color_, rest_)] - (color_, rest_)
 47
   _ - (Color 0 0 0, rest1) ]
 48 where mkAttr AttrFgColor color = AttrFgColor color
 49   mkAttr AttrBgColor color = AttrBgColor color
 50   mkAttr AttrInverse _ = AttrInverse
 51   mkAttr AttrWeak _ = AttrWeak
 52   mkAttr AttrUnderline _ = AttrUnderline
-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why this cannot be compiled?

2009-07-13 Thread Ketil Malde
Magicloud Magiclouds magicloud.magiclo...@gmail.com writes:

  43 instance Read Attribute where
  44   readsPrec _ str = [ (mkAttr attr_ color, rest) | (attr_, rest1) - lex 
 str
  45  , (color, rest)  - case 
 reads rest1 of
  46[(color_, rest_)] 
 - (color_, rest_)
  47_ - (Color 0 0 0, 
 rest1) ]

Doesn't the (color,rest) pair in the list comprehension need to be
pulled from a list?  The case expression only returns a pair so you're
basically left with [something| something, (color,rest) - (somecolor,somerest) 
]

Since you're only producing a single (color,rest) for each rest1, you might
consider lifting it out in the left side of the list comprehension.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why this cannot be compiled?

2009-07-13 Thread Magicloud Magiclouds
Hum I must lost my mind
Thank you.

On Mon, Jul 13, 2009 at 3:33 PM, Ketil Maldeke...@malde.org wrote:
 Magicloud Magiclouds magicloud.magiclo...@gmail.com writes:

  43 instance Read Attribute where
  44   readsPrec _ str = [ (mkAttr attr_ color, rest) | (attr_, rest1) - lex 
 str
  45                                                  , (color, rest)  - 
 case reads rest1 of
  46                                                        [(color_, rest_)] 
 - (color_, rest_)
  47                                                        _ - (Color 0 0 
 0, rest1) ]

 Doesn't the (color,rest) pair in the list comprehension need to be
 pulled from a list?  The case expression only returns a pair so you're
 basically left with [something| something, (color,rest) - 
 (somecolor,somerest) ]

 Since you're only producing a single (color,rest) for each rest1, you might
 consider lifting it out in the left side of the list comprehension.

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants




-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Hylomorphisms (was: excercise - a completely lazy sorting algorithm)

2009-07-13 Thread Heinrich Apfelmus
Brent Yorgey wrote:
 Raynor Vliegendhart wrote:

 One of the examples I tried was:

hylo (unfoldr (\a - Just (a,a))) head $ 42

 This expression fails to determinate.

 Here are two examples copumpkin tried on IRC:

 copumpkin  let hylo f g = g . fmap (hylo f g) . f  in hylo (flip
 replicate 2) length 5
 lambdabot   5

 copumpkin  let hylo f g = g . fmap (hylo f g) . f  in hylo (flip
 replicate 2) sum 5
 lambdabot   * Exception: stack overflow
 
 [] is a strange functor to use with hylo, since it is already
 recursive and its only base case (the empty list) doesn't contain any
 a's.  Think about the intermediate structure that
 
   hylo (unfoldr (\a - Just (a,a))) head
 
 is building up: it is a list of lists of lists of lists of lists of
 lists of no wonder it doesn't terminate! =)

Yep, not terminating is the correct behavior here.


In particular, we have

example = hylo repeat head
= cata head . ana repeat

and the intermediate data structure is

Fix []

which is an infinite nested tower of infinite lists.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Kev Mahoney
Hi there,

I'm currently writing an interpreter that I would like to be able to
use with other haskell programs. I would like to be able to pass along
arbitrary types though the interpreter. I've seen hints that GADTs can
do this, but I am having trouble understanding them.

So far, I've learnt you can do this:

data Value where
VInt :: Integer - Value
...
VWrapper :: a - Value

which can let you encode arbitrary 'dynamic' types into Value. I was
hoping to be able to pattern match to get the value out again e.g.

doSomething :: Value - 
doSomething (VWrapper String s) = .

Also, anything that can help me out with GADTs in general will be much
appreciated.

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


Re: [Haskell-cafe] haskell.org: what can be improved causing what efforts?

2009-07-13 Thread Matthias Görgens
 code snippet: no hello world please. That's not a way to judge a
 language! But: a random haskell one line snippet with explanation would
 be cool.

Perhaps a solution to a problem like the ones you can find on Project
Euler (http://projecteuler.net/index.php?section=problems).  Of course
you can't take an actual problem from Project Euler, because they do
not like solutions to be posted in the wild.  But you can get your
inspiration from there.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type families and polymorphism

2009-07-13 Thread Jeremy Yallop

Dan Doel wrote:

Hope that helps.


It does, thanks!

Jeremy

--
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.

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


Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Chris Eidhof

Hey Kev,

The types are thrown away during compile time. Therefore, if you  
have a constructor VWrapper :: a - Value nothing is known about  
that a when you scrutinize it.


What you could do, however, is something like this:


data Value a where
  VInt :: Integer - Value Integer
  ...
  VWrapper :: a - Value a


And then you can write a function doSomething:


doSomething :: Value String - String
doSomething (VWrapper s) = s


HTH,

-chris

On 13 jul 2009, at 12:41, Kev Mahoney wrote:


Hi there,

I'm currently writing an interpreter that I would like to be able to
use with other haskell programs. I would like to be able to pass along
arbitrary types though the interpreter. I've seen hints that GADTs can
do this, but I am having trouble understanding them.

So far, I've learnt you can do this:

data Value where
VInt :: Integer - Value
...
VWrapper :: a - Value

which can let you encode arbitrary 'dynamic' types into Value. I was
hoping to be able to pattern match to get the value out again e.g.

doSomething :: Value - 
doSomething (VWrapper String s) = .

Also, anything that can help me out with GADTs in general will be much
appreciated.

Thanks,
Kevin.
___
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] haskell.org: what can be improved causing what efforts?

2009-07-13 Thread Henk-Jan van Tuyl
On Mon, 13 Jul 2009 12:43:07 +0200, Matthias Görgens  
matthias.goerg...@googlemail.com wrote:



code snippet: no hello world please. That's not a way to judge a
language! But: a random haskell one line snippet with explanation would
be cool.


Perhaps a solution to a problem like the ones you can find on Project
Euler (http://projecteuler.net/index.php?section=problems).  Of course
you can't take an actual problem from Project Euler, because they do
not like solutions to be posted in the wild.  But you can get your
inspiration from there.


I like the quicksort example at  
http://www.haskell.org/haskellwiki/Introduction very much; it shows how  
much time you can save when you use Haskell.


--
Regards,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--


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


Re: [Haskell-cafe] haskell.org: what can be improved causing what efforts?

2009-07-13 Thread Matthias Görgens
 I like the quicksort example at
 http://www.haskell.org/haskellwiki/Introduction very much; it shows how much
 time you can save when you use Haskell.

Nice idea.  Perhaps use a merge sort, because that is actually useful,
because it does not degenerate for large lists.

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


Re[2]: [Haskell-cafe] haskell.org: what can be improved causing what efforts?

2009-07-13 Thread Bulat Ziganshin
Hello Matthias,

Monday, July 13, 2009, 6:05:06 PM, you wrote:

 I like the quicksort example at

 Nice idea.  Perhaps use a merge sort, because that is actually useful,
 because it does not degenerate for large lists.

Great idea if we want to keep Haskell community compact :)))


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: Re[2]: [Haskell-cafe] haskell.org: what can be improved causing what efforts?

2009-07-13 Thread Matthias Görgens
 Nice idea.  Perhaps use a merge sort, because that is actually useful,
 because it does not degenerate for large lists.

 Great idea if we want to keep Haskell community compact :)))

Or stay with quicksort --- which is treesort. :o)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Chris Eidhof
Then you could add a specific constructor for String. The main point  
is: the case construct only works for values, not for types. There is  
no typecase construct. If you want to have certain restrictions on the  
'a', such as the Show class, you could also do something like this:


 data Value where
   VWrapper :: (Show a) = a - Value

If you could elaborate a bit on what you're trying to accomplish (from  
a higher viewpoint) then maybe we can help you   some more.


-chris

On 13 jul 2009, at 17:42, Kev Mahoney wrote:


Thanks, that helps.

I was hoping to not have to parametrize Value as there is a fair bit
of code to change, and it cascades down through the data structures
(maybe a forall a . Value a will help here?)

I will have a go at this approach. In case anyone is interested the
code is at http://github.com/KMahoney


2009/7/13 Chris Eidhof ch...@eidhof.nl:

Hey Kev,

The types are thrown away during compile time. Therefore, if you  
have a
constructor VWrapper :: a - Value nothing is known about that  
a when

you scrutinize it.

What you could do, however, is something like this:


data Value a where
 VInt :: Integer - Value Integer
 ...
 VWrapper :: a - Value a


And then you can write a function doSomething:


doSomething :: Value String - String
doSomething (VWrapper s) = s


HTH,

-chris

On 13 jul 2009, at 12:41, Kev Mahoney wrote:


Hi there,

I'm currently writing an interpreter that I would like to be able to
use with other haskell programs. I would like to be able to pass  
along
arbitrary types though the interpreter. I've seen hints that GADTs  
can

do this, but I am having trouble understanding them.

So far, I've learnt you can do this:

data Value where
VInt :: Integer - Value
...
VWrapper :: a - Value

which can let you encode arbitrary 'dynamic' types into Value. I was
hoping to be able to pattern match to get the value out again e.g.

doSomething :: Value - 
doSomething (VWrapper String s) = .

Also, anything that can help me out with GADTs in general will be  
much

appreciated.

Thanks,
Kevin.
___
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] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-13 Thread Robert Greayer
 It’s tempting to say, we should
 use the original English, which is British English.

Some suggest the original English remained in Britain when the North
American colonies were founded; others claim it was brought to the
Americas by the British settlers, leaving a pale imitation back in
Britain.  The truth is much stranger:  the original English was
actually smuggled out of Britain to the West Indies in a wardrobe
belonging to General Sir Ralph Abercromby, where it ended up on the
island of Trinidad after Sir Ralph took possession of that territory
in the name of the British Crown. It came to be used and modified
freely by the various immigrants to Trinidad (and later Tobago) and
their descendants (largely African, Indian, British, Portuguese,
German, Spanish, and Chinese).  Many of these peoples then emigrated,
bringing the original English to North America and back to Britain.  A
copy of it has fallen into my hands, and so I can, without bias, make
the following call: both color and colour shall be acceptable in
Haskell programming.  'Kerb' and 'gaol' are right out, however.

Cheers,
Robert

(who's grandfather is from London and grandmother from Trinidad; but
is nevertheless American)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Kev Mahoney
Oops, wrong mail account for my last email. Apologies.

What I'm trying to accomplish is being able to write haskell libraries
for the interpreter that don't use the interpreter's predefined Value
types, without having to edit the Value type itself and add a new
constructor (i.e. it's abstracted away).

I believe the concept is called 'userdata' in Lua, for example. In C
interpreters it is usually accomplished by throwing away type
information and casting to 'void*' and then casting back to the type
to get it out again.

That said, I think I may defer this until I understand the ins and
outs of Haskell's type system a little better. I think a parametrized
type will be the only way to do it. The only reason I thought GADTs
may be able to do this is because I read some literature that
suggested GADTs could be used as a kind of typecase construct (I think
it was 'Fun with Phantom Types'?) but I could have very easily
misunderstood it.


2009/7/13 Chris Eidhof ch...@eidhof.nl:
 Then you could add a specific constructor for String. The main point is: the
 case construct only works for values, not for types. There is no typecase
 construct. If you want to have certain restrictions on the 'a', such as the
 Show class, you could also do something like this:

 data Value where
   VWrapper :: (Show a) = a - Value

 If you could elaborate a bit on what you're trying to accomplish (from a
 higher viewpoint) then maybe we can help you   some more.

 -chris

 On 13 jul 2009, at 17:42, Kev Mahoney wrote:

 Thanks, that helps.

 I was hoping to not have to parametrize Value as there is a fair bit
 of code to change, and it cascades down through the data structures
 (maybe a forall a . Value a will help here?)

 I will have a go at this approach. In case anyone is interested the
 code is at http://github.com/KMahoney


 2009/7/13 Chris Eidhof ch...@eidhof.nl:

 Hey Kev,

 The types are thrown away during compile time. Therefore, if you have a
 constructor VWrapper :: a - Value nothing is known about that a when
 you scrutinize it.

 What you could do, however, is something like this:

 data Value a where
  VInt :: Integer - Value Integer
  ...
  VWrapper :: a - Value a

 And then you can write a function doSomething:

 doSomething :: Value String - String
 doSomething (VWrapper s) = s

 HTH,

 -chris

 On 13 jul 2009, at 12:41, Kev Mahoney wrote:

 Hi there,

 I'm currently writing an interpreter that I would like to be able to
 use with other haskell programs. I would like to be able to pass along
 arbitrary types though the interpreter. I've seen hints that GADTs can
 do this, but I am having trouble understanding them.

 So far, I've learnt you can do this:

 data Value where
 VInt :: Integer - Value
 ...
 VWrapper :: a - Value

 which can let you encode arbitrary 'dynamic' types into Value. I was
 hoping to be able to pattern match to get the value out again e.g.

 doSomething :: Value - 
 doSomething (VWrapper String s) = .

 Also, anything that can help me out with GADTs in general will be much
 appreciated.

 Thanks,
 Kevin.
 ___
 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] Are GADTs what I need?

2009-07-13 Thread Chaddaï Fouché
On Mon, Jul 13, 2009 at 12:41 PM, Kev
Mahoneymaill...@kevinmahoney.co.uk wrote:
 So far, I've learnt you can do this:

 data Value where
 VInt :: Integer - Value
 ...
 VWrapper :: a - Value

 which can let you encode arbitrary 'dynamic' types into Value. I was
 hoping to be able to pattern match to get the value out again e.g.

As such this type is pretty useless, since you don't know anything
about a, you can't do anything with it... Which is why you add
typeclass constraints, so you can use this value. Data.Dynamic adds a
Typeable constraint, which allows you to do safe coercing, so you can
have a typecase, if not like you tried to do it.

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


[Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Matthew Elder
Hello Cafe,

I am trying to improve the error reporting in my sendfile library, and I
know I can find out the current file name and line number with something
like this:

{-# LANGUAGE CPP #-}
main = putStrLn (__FILE__ ++ : ++ show __LINE__)

This outputs:
test.hs:2

Unfortunately, if your file is in a hierarchy of folders, this flat file
name doesn't give much context. Is there a macro to find out the current
module? IE if I had a module Foo.Bar.Car.MyModule, I would like to be able
to output something like this on error:
Foo.Bar.Car.MyModule:2

Any help is appreciated!

Thanks,
Matt

-- 
Need somewhere to put your code? http://patch-tag.com
Want to build a webapp? http://happstack.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Kev Mahoney
Thanks, I hadn't noticed Data.Dynamic. It never even occurred to me
that something like this would be in the standard libraries. It looks
like it's precisely what I was looking for, after a brief scan of the
documentation.

I will report back if I bump into any problems with it

2009/7/13 Chaddaï Fouché chaddai.fou...@gmail.com:
 On Mon, Jul 13, 2009 at 12:41 PM, Kev
 Mahoneymaill...@kevinmahoney.co.uk wrote:
 So far, I've learnt you can do this:

 data Value where
 VInt :: Integer - Value
 ...
 VWrapper :: a - Value

 which can let you encode arbitrary 'dynamic' types into Value. I was
 hoping to be able to pattern match to get the value out again e.g.

 As such this type is pretty useless, since you don't know anything
 about a, you can't do anything with it... Which is why you add
 typeclass constraints, so you can use this value. Data.Dynamic adds a
 Typeable constraint, which allows you to do safe coercing, so you can
 have a typecase, if not like you tried to do it.

 --
 Jedaï

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


Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Ryan Ingram
On Mon, Jul 13, 2009 at 9:18 AM, Kev Mahoneymaill...@kevinmahoney.co.uk wrote:
 That said, I think I may defer this until I understand the ins and
 outs of Haskell's type system a little better. I think a parametrized
 type will be the only way to do it. The only reason I thought GADTs
 may be able to do this is because I read some literature that
 suggested GADTs could be used as a kind of typecase construct (I think
 it was 'Fun with Phantom Types'?) but I could have very easily
 misunderstood it.

The big problem is that you haven't parametrized your Value type at
all, so there's no information about the value inside.

Try this:

 data Value a where
 VPrim :: Type a - a - Value a
 VAbs :: Type a - (Value a - Value b) - Value (a - b)
 VApp :: Value (a - b) - Value a - Value b

 data Type a where
TInt :: Type Int
TBool :: Type Bool
TChar :: Type Char
TList :: Type a - Type [a]
TFun :: Type a - Type b - Type (a - b)

data SomeType = forall a. SomeType (Type a)
data SomeValue = forall a. SomeValue (Value a)

Now you can do:

 interpret :: Value a - a
 interpret (VPrim _ x) = x
 interpret (VAbs t f) = \x - f (VPrim t x)
 interpret (VApp f x) = interpret f $ interpret x

And:

 typeOf :: Value a - Type a
 typeOf (VPrim t _) = t
 typeOf (VAbs t f) = typeOf (f $ VPrim t (representative t))
 typeOf (VApp f _) = case typeOf f of (TFun _ b) - b

 representative :: Type a - a
 representative TInt = 0
 representative TBool = False
 representative TChar = 'a'
 representative (TList _) = []
 representative (TFun _ b) = \_ - representative b

Your compiler will generally have type (String - Maybe SomeValue), or
(String - Type a - Maybe (Value a)).

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


Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Claus Reinke

I am trying to improve the error reporting in my sendfile library, and I
know I can find out the current file name and line number with something
like this:

{-# LANGUAGE CPP #-}
main = putStrLn (__FILE__ ++ : ++ show __LINE__)

This outputs:
test.hs:2

Unfortunately, if your file is in a hierarchy of folders, this flat file
name doesn't give much context. Is there a macro to find out the current
module? IE if I had a module Foo.Bar.Car.MyModule, I would like to be able
to output something like this on error:
Foo.Bar.Car.MyModule:2


Sounds like a job for cabal or ghc, to define appropriate macros for
package and module when compiling the source?


Any help is appreciated!


For actually making use of such information, see 

   http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack 
   http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack/StackTraceExperience


and also the recent thread on how to improve the quality of +RTS -xc
output via mapException (hmm, can't reach the archive at the moment,
one subject was Should exhaustiveness testing be on by default?, about
May; http://www.haskell.org/mailman/listinfo/glasgow-haskell-users ).

If you really mean any help, you could also use Template Haskell:-)

   {-# LANGUAGE TemplateHaskell #-}
   module Oh.Hi where 
   
   import Language.Haskell.TH
   
   main = print $( location = \(Loc f p m s e)- 
   stringE (f++:++p++:++m++:++show s++:++show e))


Claus


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


Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Stephan Friedrichs
Matthew Elder wrote:
 {-# LANGUAGE CPP #-}
 main = putStrLn (__FILE__ ++ : ++ show __LINE__)
 
 This outputs:
 test.hs:2
 
 Unfortunately, if your file is in a hierarchy of folders, this flat file
 name doesn't give much context. Is there a macro to find out the current
 module? IE if I had a module Foo.Bar.Car.MyModule, I would like to be
 able to output something like this on error:
 Foo.Bar.Car.MyModule:2

As mentioned by Claus, template-haskell offers a solution. But in some
cases, this is an overkill; consider using Control.Exception.assert, it
will provide module and line information without having to use CPP:

myHead :: [a] - a
myHead (x:_) = x
myHead []= assert False undefined

 
 [...]

//Stephan

-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Malcolm Wallace

{-# LANGUAGE CPP #-}
main = putStrLn (__FILE__ ++ : ++ show __LINE__)

This outputs:
test.hs:2


if I had a module Foo.Bar.Car.MyModule, I would like to be able to  
output something like this on error:

Foo.Bar.Car.MyModule:2


It works for me.  If you place that text in Try/Me.hs and call
ghc -E Try/Me.hs
you get
Try/Me.hs:2

If you just want to turn slashes into dots, and remove the suffix,  
that is a simple exercise in Haskell itself


main = putStrLn (mangle __FILE__)
  where mangle ('/':cs) = '.': mangle cs
mangle .

Regards,
Malcolm

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


Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Luke Palmer
On Mon, Jul 13, 2009 at 6:09 AM, Chris Eidhof ch...@eidhof.nl wrote:

 Hey Kev,

 The types are thrown away during compile time. Therefore, if you have a
 constructor VWrapper :: a - Value nothing is known about that a when
 you scrutinize it.

 What you could do, however, is something like this:

  data Value a where
  VInt :: Integer - Value Integer
  ...
  VWrapper :: a - Value a


 And then you can write a function doSomething:

  doSomething :: Value String - String
 doSomething (VWrapper s) = s


I would like to put in a thumbs up on this approach.  I'm currently
experimenting with interpreters, and have found that parameterizing over the
value type works quite smoothly.

Specifically, this is my usual starting point for the values:

data Value a
= VFun (Value a - Value a)
| VPrim a

Then I use a typeclass to endow the primitives with the structure they need:

class ValueType a where
apply :: a - a - a

Here's a simple interpreter for terms in De Bruijn notation:

data Term a
= TLit a
| TApp (Term a) (Term a)
| TLam (Term a)
| TVar Int

eval :: (ValueType a) = Term a - [Value a] - Value a
eval (TLit x) = const (VPrim x)
eval (TApp x y) =
let x' = eval x
y' = eval y
in \env - x' env % y' env
eval (TLam body) =
let body' = eval body
in \env - VFun (\x - body (x:env))
eval (TVar z) = \env - env !! z

(%) :: (ValueType a) = Value a - Value a - Value a
VFun f % x = f x
VPrim x % VFun _ = error Apply primitive to function not supported
VPrim x % VPrim y = VLit (x `apply` y)

And an example ValueType:

data Prim = PInt Int | PSucc
instance ValueType Prim where
apply PSucc (PInt z) = PInt $! z+1
apply _ _ = error Type error

This approach has been very nice and modular for experimenting with
dynamically typed interpreters. You could support application of literals to
functions with some more support from the type class, but it wasn't worth it
to me (and would limit the interpretation strategies that I would be able to
use).

The decision about what suite of primitives to include and how they combine
with each other is pushed out to the user, and the interpreter just focuses
on the important things: functions.  You could even write a little primitive
combinator library (perhaps made more composable by switching to dictionary
passing for ValueType instead of typeclass), so that users can easily
specify any suite of primitives.

Anyway, those were just some thoughts for you.

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


Re: [Haskell-cafe] Removing polymorphism from type classes (viz. Functor)

2009-07-13 Thread Henning Thielemann
George Pollard schrieb:
 Ok, so I have a small idea I'm trying to work on; call it a
 Prelude-rewrite if you want. For this I want to be able to have the
 hierarchy Functor → Applicative → Monad.
 
 For Functor, I would like to be able to implement it for a wider
 variety of types, as there are types which have aren't polymorphic
 which would also benefit from having an instance.
 My running example for this set of types is ByteString; the module
 contains the method:
 
 map ∷ (Word8 → Word8) → ByteString → ByteString
 
 However, we cannot use this for Functor because ByteString isn't
 polymorphic. To get around this, I devised the following:
 
 Introduce a type family which represents ‘points’ inside the type:
 
 type family Point f ∷ ★
 
 For ByteString we have:
 
 type instance Point ByteString = Word8
 
 For a polymorphic example (lists) we have:
 
 type instance Point [a] = a

I had the same in mind for Data.Set with Ord constraint for elements,
StorableVector with Storable constraint for the elements, and
Control.Monad.Excepetion.Asynchronous monad with Monoid constraint for
the monadic result.

I tried to come up with a class hierarchy:

http://code.haskell.org/~thielema/category-constrained/src/Control/Constrained/

but I encountered the same problem with the Applicative class. Different
from what I tried in Applicative.hs I think that the most flexible
approach is to convert the ByteString (or Data.Set or StorableVector) to
an interim data structure first where you do, say 'liftA3' aka
'zipWith3', then convert back to the real data structure, here
ByteString. The interim data structure can be stream-fusion:Data.Stream,
i.e. not a real data structure but an algorithm to read from the ByteString.


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


Re: [Haskell-cafe] Questions about haskell CPP macros

2009-07-13 Thread Stephan Friedrichs
Malcolm Wallace wrote:
  {-# LANGUAGE CPP #-}
 main = putStrLn (__FILE__ ++ : ++ show __LINE__)

 This outputs:
 test.hs:2
 
 if I had a module Foo.Bar.Car.MyModule, I would like to be able to
 output something like this on error:
 Foo.Bar.Car.MyModule:2
 
 It works for me.  If you place that text in Try/Me.hs and call
 ghc -E Try/Me.hs
 you get
 Try/Me.hs:2
 
 If you just want to turn slashes into dots, and remove the suffix, that
 is a simple exercise in Haskell itself
 
 main = putStrLn (mangle __FILE__)
   where mangle ('/':cs) = '.': mangle cs
 mangle .

Careful, '/' might be '\\' on another OS, the file might end with .hsc
instead of .hs, the line numbers might not fit in the .hsc case...


-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

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


[Haskell-cafe] Example for formatted show in HStringTemplate

2009-07-13 Thread Kemps-Benedix Torsten
Hello,

is there a working example of how to use the format clause with 
HStringTemplate, e.g. for Data.Time.Day? I think, if there is a parameter 
$day$, a reasonable template might contain e.g.:

$day;format=%d.%b.%Y$

But I only get toModifiedJulianDay: [54960] as the result which corresponds 
to the unformatted show.

Regards,

Torsten

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


Re: [Haskell-cafe] Removing polymorphism from type classes (viz. Functor)

2009-07-13 Thread George Pollard
It does seem that having quantified contexts would make this *much* easier...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to Read this?

2009-07-13 Thread Magicloud Magiclouds
Hi,
  I have a data structure, which shows like this: AttrBgColor {bgColor
= Color 0 0 0}
  And the following is my Read code. But it failed parsing
 31 instance Read Attribute where
 32   readsPrec _ str = [ (mkAttr attr_ color, rest) | (attr_, rest1) - lex str
 33  , (color, rest)
- if   (isPrefixOf  {bgColor =  rest1)
 34
   || (isPrefixOf  {fgColor =  rest1)
 35
   then case reads $ drop 12 rest1 of
 36
  [(color_, rest_)] - [(color_, rest_)]
 37
  _ - [(Color 0 0 0, rest1)]
 38
   else [(Color 0 0 0, rest1)] ]
 39 where mkAttr AttrFgColor color = AttrFgColor color
 40   mkAttr AttrBgColor color = AttrBgColor color
 41   mkAttr AttrInverse _ = AttrInverse
 42   mkAttr AttrWeak _ = AttrWeak
 43   mkAttr AttrUnderline _ = AttrUnderline
-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Are GADTs what I need?

2009-07-13 Thread Ashley Yakeley

Ryan Ingram wrote:


data Type a where
   TInt :: Type Int
   TBool :: Type Bool
   TChar :: Type Char
   TList :: Type a - Type [a]
   TFun :: Type a - Type b - Type (a - b)


Type here is what I call a simple type witness. Simple type witnesses 
are useful because they can be compared by value, and if they have the 
same value, then they have the same type.


So you can write this:

  data EqualType a b where
MkEqualType :: EqualType t t

  matchWitness :: Type a - Type b - Maybe (EqualType a b)
  matchWitness TInt TInt = Just MkEqualType
  matchWitness TBool TBool = Just MkEqualType
  matchWitness TChar TChar = Just MkEqualType
  matchWitness (TList w1) (TList w2) = do
MkEqualType - matchWitness w1 w2
return MkEqualType
  matchWitness (TFun wa1 wb1) (TFun wa2 wb2) = do
MkEqualType - matchWitness wa1 wa2
MkEqualType - matchWitness wb1 wb2
return MkEqualType
  matchWitness _ _ = Nothing

Now whenever you match some value with MkEqualType, the compiler will 
infer the identity of the two types. See my witness package:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/witness

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