Re: [Haskell-cafe] Word8 literals in ByteString haddock?

2013-03-27 Thread Francesco Mazzoli
At Wed, 27 Mar 2013 00:50:21 +,
Niklas Hambüchen wrote:
 Hey,
 
 according to
 http://hackage.haskell.org/packages/archive/bytestring/0.10.2.0/doc/html/Data-ByteString.html#v:split
 I can write:
 
 split '\n' a\nb\nd\ne
 
 Can I really do that? I don't know of a way to make a '\n' literal be a
 Word8, so maybe these Haddocks are wrong? I guess they would apply for
 Data.ByteString.Char8, but this is Data.ByteString. Or is there a way?

No, there is no way—you’d need an ‘OverloadedChars’ extension that does not
exist.  I think that text is meant to show the semantics of ‘split’ rather than
being actual code.

Francesco

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


Re: [Haskell-cafe] my take at knucleotide

2013-03-27 Thread Branimir Maksimovic
I have posted this version.Mad home grown HashMap and replaced IOref with 
Ptr.This made program twice as fast as current entry.
{-# Language BangPatterns #-} The Computer Language Benchmarks Game-- 
http://benchmarksgame.alioth.debian.org/ Contributed by Branimir 
Maksimovic--import Data.Bitsimport Data.Charimport Data.Intimport 
Data.Listimport Data.Array.Baseimport Data.Array.Unboxedimport 
Data.Array.IOimport qualified Data.ByteString.Char8 as Simport 
Foreign.Ptrimport Foreign.Storableimport Foreign.Marshal.Allocimport 
Control.Concurrentimport Text.Printf
main = dolet skip = dol - S.getLineif S.isPrefixOf 
(S.pack THREE) lthen return ()else skip
skips - S.getContentslet content = S.filter ((/=) '\n') s;mapM_ 
(execute content) actionsdata Actions = I Int | S Stringactions = [I 1,I 2, 
  S GGT,S GGTA,S GGTATT,S GGTAAATT,S 
GGTAAATTTATAGT]execute content (I i) = writeFrequencies content iexecute 
content (S s) = writeCount content s
writeFrequencies :: S.ByteString - Int - IO ()writeFrequencies input size = 
doht - tcalculate input sizelst - Main.foldM (\lst (k,v)-do 
v' - peek vreturn $ (k,v'):lst) [] htlet sorted = sortBy (\(_,x) 
(_,y) - y `compare` x) lstsum = fromIntegral ((S.length input) + 1 - 
size)mapM_ (\(k,v)- doprintf %s %.3f\n (toString k) 
((100 * (fromIntegral v)/sum)::Double)) sortedputChar '\n'
writeCount :: S.ByteString - String - IO ()writeCount input string = do
let size = length stringk = T (toNum (S.pack string) 0 size) sizeht 
- tcalculate input sizeres - Main.lookup ht kcase res of 
Nothing - putStrLn $ string ++  not found...Just v - do
r - peek vprintf %d\t%s\n r string
tcalculate :: S.ByteString - Int - IO HMtcalculate input size = dolet 
l = [0..63]actions = map (\i - (calculate input i size (length 
l))) lvars - mapM (\action - dovar - newEmptyMVar
forkIO $ doanswer - action 
   putMVar var answerreturn var) actionsresult 
- newTable :: IO HMresults - mapM takeMVar varsmapM_ (\ht - 
Main.foldM (\lst (k,v) - do res - Main.lookup lst 
kcase res ofNothing 
- dor1 - peek v   
 r2 - mallocpoke r2 r1 
   Main.insert lst k r2Just 
v1 - dor1 - peek v1   
 r2 - peek vpoke v1 (r1+r2)
return lst) result ht) resultsreturn result
calculate :: S.ByteString - Int - Int - Int - IO HMcalculate input beg 
size incr = do!ht - newTable :: IO HMletcalculate' i  
| i = ((S.length input)+1 - size) = return ht | otherwise = do 
   let k =  T (toNum input i size) sizeres - Main.lookup ht k  
  case res ofNothing - do!r - malloc  
  poke r 1Main.insert ht k r
Just v - do !r - peek vpoke v (r+1)   
 calculate' (i+incr)calculate' beg
toNum :: S.ByteString - Int - Int - Int64toNum s beg size = toNum' 0 size
wheretoNum' v 0 = vtoNum' v i = toNum' ((v `shiftL` 2) .|.  
   (toNumA `unsafeAt` (ord (S.index s (beg+i-1) (i-1)
toString :: T - StringtoString (T v s) = toString' v swhere
toString' v 0 = []toString' v i = case v..3 of
0 - 'A'1 - 'C'2 - 'T'
3 - 'G'  : toString' (v `shiftR` 2) (i-1)
toNumA :: UArray Int Int64toNumA = array (0,255) [(ord 'a',0),(ord 'c',1),(ord 
't',2),(ord 'g',3),(ord 'A',0),(ord 'C',1),(ord 'T',2),(ord 'G',3)]
data T = T !Int64 !Intinstance Eq T where(T a _) == (T b _) = a == bclass 
Hash h wherehash :: h - Int64instance Hash T wherehash (T a _) = a
type HM = HashMap T (Ptr Int)data HashMap k v = HashMap !(IOArray Int64 
[(k,v)])tsz = 4096newTable :: IO (HashMap k v)newTable = do!array - 
newArray (0,(tsz-1)) []return $ HashMap array
lookup :: (Eq k, Hash k)=HashMap k v - k - IO (Maybe v)lookup (HashMap a) k 
= dolet h = hash k!lst - readArray a (h .. (tsz-1))let
loop [] = return Nothingloop ((!k',!v):xs) | k /= k' = loop 
xs| otherwise = return $ Just vloop lst
insert :: (Eq k, Hash k)=HashMap k v - k - v - IO ()insert (HashMap a) k v 
= dolet h = hash k!lst - 

Re: [Haskell-cafe] Pattern matching with singletons

2013-03-27 Thread Paul Brauner
Very helpful, thanks! I may come back with more singleton/type families
questions :)


On Tue, Mar 26, 2013 at 6:41 PM, Richard Eisenberg e...@cis.upenn.eduwrote:

 Hello Paul,

  - Forwarded message from Paul Brauner polux2...@gmail.com -

 snip

- is a ~ ('CC ('Left 'CA)) a consequence of the definitions of SCC,
SLeft, ... (in which case GHC could infer it but for some reason can't)
- or are these pattern + definitions not sufficient to prove that a
~ ('CC ('Left 'CA)) no matter what?

 The first one. GHC can deduce that (a ~ ('CC ('Left b))), for some fresh
 variable (b :: TA), but it can't yet take the next step and decide that,
 because TA has only one constructor, b must in fact be 'CA. In type-theory
 lingo, this deduction is called eta-expansion. There have been on-and-off
 debates about how best to add this sort of eta-expansion into GHC, but all
 seem to agree that it's not totally straightforward. For example, see GHC
 bug #7259. There's a non-negligible chance I will be taking a closer look
 into this at some point, but not for a few months, so don't hold your
 breath. I'm not aware of anyone else currently focusing on this problem
 either, I'm afraid.

 I'm glad you're finding use in the singletons package! Let me know if I
 can be of further help.

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


[Haskell-cafe] [extension]syntactic sugar for maps

2013-03-27 Thread Răzvan Rotaru
Hi,

I am terribly missing some syntactic sugar for maps (associative data
structures) in Haskell. I find myself using them more than any other data
structure, and I think there is no big deal in adding some sugar for this
to the language. I could not find out whether such an extension is beeing
discussed. If not, I would like to propose and extension. Any help and
suggestions are very welcome here. Thanks.

Also related to the topic:

1/ Is there a list of proposals for extensions to Haskell that has
currently been accepted in the new standard? I have not found one on
Haskell' (
http://hackage.haskell.org/trac/haskell-prime/query?status=newstatus=assignedstatus=reopenedgroup=state),
but it looks outdated. No mentions to the new standard!

2/ I have seen somewhere a statement that a new language standard will be
published yearly. Didn't happen until now. Is there even a new standard on
the way?

Cheers,
Răzvan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [extension]syntactic sugar for maps

2013-03-27 Thread Ivan Lazar Miljenovic
On 28 March 2013 06:30, Răzvan Rotaru razvan.rot...@gmail.com wrote:
 Hi,

 I am terribly missing some syntactic sugar for maps (associative data
 structures) in Haskell. I find myself using them more than any other data
 structure, and I think there is no big deal in adding some sugar for this to
 the language. I could not find out whether such an extension is beeing
 discussed. If not, I would like to propose and extension. Any help and
 suggestions are very welcome here. Thanks.

What kind of syntactic sugar are you wanting?


 Also related to the topic:

 1/ Is there a list of proposals for extensions to Haskell that has currently
 been accepted in the new standard? I have not found one on Haskell'
 (http://hackage.haskell.org/trac/haskell-prime/query?status=newstatus=assignedstatus=reopenedgroup=state),
 but it looks outdated. No mentions to the new standard!

 2/ I have seen somewhere a statement that a new language standard will be
 published yearly. Didn't happen until now. Is there even a new standard on
 the way?

 Cheers,
 Răzvan

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




-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] [extension]syntactic sugar for maps

2013-03-27 Thread Tikhon Jelvis
I'm genuinely curious as to how you use maps. I've found I use them far
less in Haskell than in any other language: I only use them in select
circumstances. And most of those uses would not benefit from a mayo literal.

I suspect that many of the uses of map literals are better replaced with
something like a record. This has the advantage of being static and more
type safe. However, this is only based on my own use cases, so it's hard to
generalize.
On Mar 27, 2013 12:32 PM, Răzvan Rotaru razvan.rot...@gmail.com wrote:

 Hi,

 I am terribly missing some syntactic sugar for maps (associative data
 structures) in Haskell. I find myself using them more than any other data
 structure, and I think there is no big deal in adding some sugar for this
 to the language. I could not find out whether such an extension is beeing
 discussed. If not, I would like to propose and extension. Any help and
 suggestions are very welcome here. Thanks.

 Also related to the topic:

 1/ Is there a list of proposals for extensions to Haskell that has
 currently been accepted in the new standard? I have not found one on
 Haskell' (
 http://hackage.haskell.org/trac/haskell-prime/query?status=newstatus=assignedstatus=reopenedgroup=state),
 but it looks outdated. No mentions to the new standard!

 2/ I have seen somewhere a statement that a new language standard will be
 published yearly. Didn't happen until now. Is there even a new standard on
 the way?

 Cheers,
 Răzvan

 ___
 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] [extension]syntactic sugar for maps

2013-03-27 Thread Nicolas Trangez
On Wed, 2013-03-27 at 21:30 +0200, Răzvan Rotaru wrote:
 I am terribly missing some syntactic sugar for maps (associative data
 structures) in Haskell. I find myself using them more than any other
 data
 structure, and I think there is no big deal in adding some sugar for
 this
 to the language. I could not find out whether such an extension is
 beeing
 discussed. If not, I would like to propose and extension. Any help and
 suggestions are very welcome here. Thanks.

http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists comes to mind.

Nicolas


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


Re: [Haskell-cafe] [extension]syntactic sugar for maps

2013-03-27 Thread Răzvan Rotaru
Sorry, I forgot to explain (probably because I'm too used to it). I am
referring to a syntax for easy creation of maps. Something equivalent to
lists:

to build a list: [ 1, 2, 3]
to build a map; { 1, one, 2, two, 3, three}

Without it I am always forced to use fromList.

Răzvan



On 27 March 2013 21:48, Ivan Lazar Miljenovic ivan.miljeno...@gmail.comwrote:

 On 28 March 2013 06:30, Răzvan Rotaru razvan.rot...@gmail.com wrote:
  Hi,
 
  I am terribly missing some syntactic sugar for maps (associative data
  structures) in Haskell. I find myself using them more than any other data
  structure, and I think there is no big deal in adding some sugar for
 this to
  the language. I could not find out whether such an extension is beeing
  discussed. If not, I would like to propose and extension. Any help and
  suggestions are very welcome here. Thanks.

 What kind of syntactic sugar are you wanting?

 
  Also related to the topic:
 
  1/ Is there a list of proposals for extensions to Haskell that has
 currently
  been accepted in the new standard? I have not found one on Haskell'
  (
 http://hackage.haskell.org/trac/haskell-prime/query?status=newstatus=assignedstatus=reopenedgroup=state
 ),
  but it looks outdated. No mentions to the new standard!
 
  2/ I have seen somewhere a statement that a new language standard will be
  published yearly. Didn't happen until now. Is there even a new standard
 on
  the way?
 
  Cheers,
  Răzvan
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 http://IvanMiljenovic.wordpress.com

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


[Haskell-cafe] Remove redundancy with Template Haskell

2013-03-27 Thread Corentin Dupont
Hi Café,
I have a function that looks like this:
call :: SomeFunction - String - SomeState

The string is actually the representation of the function passed in
parameter. It is stored in the state for documentation.
So a call looks like that:
call (\a - putStrLn a)   \a - putStrLn a

There is a clear redundancy here, how could I remove it with Template
Haskell?
I cannot figure out...

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


Re: [Haskell-cafe] [extension]syntactic sugar for maps

2013-03-27 Thread Eli Frey
 Sorry, I forgot to explain (probably because I'm too used to it). I am
referring to a syntax for easy creation of maps. Something equivalent to
lists:

 to build a list: [ 1, 2, 3]
 to build a map; { 1, one, 2, two, 3, three}

 Without it I am always forced to use fromList.

This looks like something to use records for, or in any case something
where association list performance is not an issue.

If you just want to store some configuration-like structure and pass it
around, a record is great for this.  You might find where in other
languages you would simply leave a key null, in Haskell you can just fill
it with a Nothing.

Maps (hash or binary-tree) really pay off when they are filled dynamically
with massive numbers of associations.  I find when I am ending up in this
scenario, I am generating my map programatically, not writing it as a
literal.

Sometimes people even write maps simply as functions and not even as a
data-structure.

 myMap char = case char of
 'a' - 1
 'b' - 2
 'c' - 3

Perhaps you could describe a situation you are in where you are wanting
this, and we could see if there is something you can do already that is
satisfying and solves your problem.



On Wed, Mar 27, 2013 at 12:59 PM, Eli Frey eli.lee.f...@gmail.com wrote:

  http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists comes to mind.

 This assumes you can turn ANY list into a thing.  Maps only make sense to
 be constructed from association list.  If I've got a [Char], how do I make
 a map form it?


 On Wed, Mar 27, 2013 at 12:56 PM, Nicolas Trangez nico...@incubaid.comwrote:

 On Wed, 2013-03-27 at 21:30 +0200, Răzvan Rotaru wrote:
  I am terribly missing some syntactic sugar for maps (associative data
  structures) in Haskell. I find myself using them more than any other
  data
  structure, and I think there is no big deal in adding some sugar for
  this
  to the language. I could not find out whether such an extension is
  beeing
  discussed. If not, I would like to propose and extension. Any help and
  suggestions are very welcome here. Thanks.

 http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists comes to mind.

 Nicolas


 ___
 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] Remove redundancy with Template Haskell

2013-03-27 Thread Daniel Trstenjak

Hi Corentin,

On Wed, Mar 27, 2013 at 09:13:41PM +0100, Corentin Dupont wrote:
 I have a function that looks like this:
 call :: SomeFunction - String - SomeState
 
 The string is actually the representation of the function passed in
 parameter. It is stored in the state for documentation.
 So a call looks like that:
 call (\a - putStrLn a)   \a - putStrLn a
 
 There is a clear redundancy here, how could I remove it with Template
 Haskell?
 I cannot figure out...

You can even use cpp to get something like:

#define CALL(func) call (func) #func

CALL(\a - a + 1) = call (\a - a + 1) \a - a + 1


Greetings,
Daniel

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


Re: [Haskell-cafe] [extension]syntactic sugar for maps

2013-03-27 Thread Eric Rasmussen
I agree that fromList or pattern matching at the function or case level are
readable. We probably don't need new sugar. For what it's worth, in scala
you can use - to construct tuples, so you'll sometimes see maps created
like this:

Map(1 - one, 2 - two, 3 - foo)

You can always do something similar in haskell (keeping in mind that -
is reserved):

import qualified Data.Map as Map

(--) = (,)

makeMap = Map.fromList

myMap = makeMap [ 1 -- one
, 2 -- two
, 3 -- foo
]

Of course, it's not idiomatic and won't be immediately obvious to readers
that you are constructing tuples. However, if you find it easier to read
and need to write a lot of map literals in your code, it may be worth
coming up with a couple of aliases similar to those.


On Wed, Mar 27, 2013 at 1:16 PM, Eli Frey eli.lee.f...@gmail.com wrote:

  Sorry, I forgot to explain (probably because I'm too used to it). I am
 referring to a syntax for easy creation of maps. Something equivalent to
 lists:
 
  to build a list: [ 1, 2, 3]
  to build a map; { 1, one, 2, two, 3, three}
 
  Without it I am always forced to use fromList.

 This looks like something to use records for, or in any case something
 where association list performance is not an issue.

 If you just want to store some configuration-like structure and pass it
 around, a record is great for this.  You might find where in other
 languages you would simply leave a key null, in Haskell you can just fill
 it with a Nothing.

 Maps (hash or binary-tree) really pay off when they are filled dynamically
 with massive numbers of associations.  I find when I am ending up in this
 scenario, I am generating my map programatically, not writing it as a
 literal.

 Sometimes people even write maps simply as functions and not even as a
 data-structure.

  myMap char = case char of
  'a' - 1
  'b' - 2
  'c' - 3

 Perhaps you could describe a situation you are in where you are wanting
 this, and we could see if there is something you can do already that is
 satisfying and solves your problem.



 On Wed, Mar 27, 2013 at 12:59 PM, Eli Frey eli.lee.f...@gmail.com wrote:

  http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists comes to mind.

 This assumes you can turn ANY list into a thing.  Maps only make sense to
 be constructed from association list.  If I've got a [Char], how do I make
 a map form it?


 On Wed, Mar 27, 2013 at 12:56 PM, Nicolas Trangez 
 nico...@incubaid.comwrote:

 On Wed, 2013-03-27 at 21:30 +0200, Răzvan Rotaru wrote:
  I am terribly missing some syntactic sugar for maps (associative data
  structures) in Haskell. I find myself using them more than any other
  data
  structure, and I think there is no big deal in adding some sugar for
  this
  to the language. I could not find out whether such an extension is
  beeing
  discussed. If not, I would like to propose and extension. Any help and
  suggestions are very welcome here. Thanks.

 http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists comes to mind.

 Nicolas


 ___
 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