[Haskell-cafe] Data.Sequence and replicateM

2013-01-24 Thread Daniel Díaz Casanueva
Hi Cafe,

I was coding this morning when I suddenly found something that surprised
me. It's been a short time since I am really caring about the performance
of my programs. Before, I was just caring about their correctness. So I am
trying different things and profiling to see differences. One difference I
have found surprising is that the function f is MUCH faster and less space
consuming than the function g:

import Control.Monad
import qualified Data.Sequence as Seq

type Seq = Seq.Seq

f :: Monad m = Int - m a - m (Seq a)
f n = fmap Seq.fromList . replicateM n

g :: Monad m = Int - m a - m (Seq a)
g = Seq.replicateM

Maybe is just in my test case, where the Int argument is big and the
monadic action short, but it looks to me that Data.Sequence.replicateM can
be faster than it is right now.

Regards,
Daniel Díaz.

-- 
E-mail sent by Daniel Díaz Casanueva

let f x = x in x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] hxt pickling question

2013-01-24 Thread briand
Hi,

Trying to understand how to write a document using a pickler but I can't make 
sense of the types.  

From the example:

 runX ( xunpickleDocument xpSeason
   [ withValidate no
   , withTrace 1
   , withRemoveWS yes
   , withPreserveComment no
   ] simple2.xml
   
 processSeason
   
 xpickleDocument   xpSeason
   [ withIndent yes
   ] new-simple2.xml
   )

So all I want to do is pickle a value directly instead of reading the value 
from a document.  I expected to do something like:

runX (someHXTPicklingFunction myValue

  xpickleDocument ...)


but I can't seem to figure out what someHXTPicklingFunction should be, it's 
certainly nothing obvious like pickleDoc, because that generates the wrong 
value.

Seems like I probably have a much more fundamental problem in that I really 
don't understand how the arrow part of this little example really works, but I 
was kind of hoping that doing something simple like this might shed some 
light on that.  And then was immediately stuck in type hell.

   
Thanks,

Brian


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


Re: [Haskell-cafe] hxt pickling question

2013-01-24 Thread Erik Hesselink
There's showPickled [0] and unpickleDoc [1], maybe those help?

Erik

[0] 
http://hackage.haskell.org/packages/archive/hxt/latest/doc/html/Text-XML-HXT-Arrow-Pickle-Xml.html#v:showPickled
[1] 
http://hackage.haskell.org/packages/archive/hxt/latest/doc/html/Text-XML-HXT-Arrow-Pickle-Xml.html#v:unpickleDoc

On Thu, Jan 24, 2013 at 4:40 PM,  bri...@aracnet.com wrote:
 Hi,

 Trying to understand how to write a document using a pickler but I can't make 
 sense of the types.

 From the example:

  runX ( xunpickleDocument xpSeason
[ withValidate no
, withTrace 1
, withRemoveWS yes
, withPreserveComment no
] simple2.xml
  
  processSeason
  
  xpickleDocument   xpSeason
[ withIndent yes
] new-simple2.xml
)

 So all I want to do is pickle a value directly instead of reading the value 
 from a document.  I expected to do something like:

 runX (someHXTPicklingFunction myValue
   
   xpickleDocument ...)


 but I can't seem to figure out what someHXTPicklingFunction should be, it's 
 certainly nothing obvious like pickleDoc, because that generates the wrong 
 value.

 Seems like I probably have a much more fundamental problem in that I really 
 don't understand how the arrow part of this little example really works, but 
 I was kind of hoping that doing something simple like this might shed some 
 light on that.  And then was immediately stuck in type hell.


 Thanks,

 Brian


 ___
 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] Data.Sequence and replicateM

2013-01-24 Thread Gershom Bazerman

On 1/24/13 9:31 AM, Daniel Díaz Casanueva wrote:


import Control.Monad
import qualified Data.Sequence as Seq

type Seq = Seq.Seq

f :: Monad m = Int - m a - m (Seq a)
f n = fmap Seq.fromList . replicateM n

g :: Monad m = Int - m a - m (Seq a)
g = Seq.replicateM

Maybe is just in my test case, where the Int argument is big and the 
monadic action short, but it looks to me that Data.Sequence.replicateM 
can be faster than it is right now.


Are you forcing the full sequence in both cases? In the former case, 
you'll get all the actions, but have a thunk containing the result of 
Seq.fromList. In the latter, you're performing the actions as you build 
the sequence, so the resultant sequence will be fully evaluated.


I imagine that this is the reason that the former seems faster to you.

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


Re: [Haskell-cafe] Data.Sequence and replicateM

2013-01-24 Thread Daniel Díaz Casanueva
Good point. However, I forced the result to evaluate using `deepseq` and I
still got similar results.


On Thu, Jan 24, 2013 at 11:41 AM, Gershom Bazerman gersh...@gmail.comwrote:

  On 1/24/13 9:31 AM, Daniel Díaz Casanueva wrote:


  import Control.Monad
  import qualified Data.Sequence as Seq

  type Seq = Seq.Seq

  f :: Monad m = Int - m a - m (Seq a)
 f n = fmap Seq.fromList . replicateM n

  g :: Monad m = Int - m a - m (Seq a)
  g = Seq.replicateM

  Maybe is just in my test case, where the Int argument is big and the
 monadic action short, but it looks to me that Data.Sequence.replicateM can
 be faster than it is right now.


 Are you forcing the full sequence in both cases? In the former case,
 you'll get all the actions, but have a thunk containing the result of
 Seq.fromList. In the latter, you're performing the actions as you build the
 sequence, so the resultant sequence will be fully evaluated.

 I imagine that this is the reason that the former seems faster to you.

 --g

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




-- 
E-mail sent by Daniel Díaz Casanueva

let f x = x in x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Manually instantiating Typeable w/DataKinds

2013-01-24 Thread Uri Braun
I've read the recent posting titled Non-derivable Typeable
(http://www.mail-archive.com/haskell-cafe@haskell.org/msg103616.html) which
explains that Typeable cannot be automatically derived for cases where the
kind is constrained.

I'm very impressed that a solution is imminent.  In the interim, can
somebody kindly suggest a workaround? I'm okay with a manual instance, but
I'd appreciate some help as to how to write one. I'm looking for a Typeable
instance for TaggedVar for the following example below (extracted from my
code).

Thank you in advance!

+Uri

{-# LANGUAGE DeriveDataTypeable, DataKinds, KindSignatures #-}
module Example where

import   Data.Typeable

data Tag = TagV | TagE | TagA | TagL
 deriving Typeable

newtype TaggedVar (t :: Tag) = TaggedVar Int



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


Re: [Haskell-cafe] hxt pickling question

2013-01-24 Thread briand
On Thu, 24 Jan 2013 17:05:15 +0100
Erik Hesselink hessel...@gmail.com wrote:

 There's showPickled [0] and unpickleDoc [1], maybe those help?
 

Thank you , they help a lot :-)  I was stuck looking in 
Text.XML.HXT.Arrow.Pickle for the answer and got lost trying to decipher 
IOStateArrow s a XmlTree and runX.

It's odd that there does not seem to be a way to use the example so that a tree 
can be written directly to a file.

  xpickleDocument :: PU a - SysConfigList - String - IOStateArrow s a 
XmlTreeSource

  store an arbitray value in a persistent XML document 

Except there doesn't seem to be a way to pass that value into xpickleDocument 
without reading a document first using xunpickleDocument.

Thanks again.

Brian

 Erik
 
 [0] 
 http://hackage.haskell.org/packages/archive/hxt/latest/doc/html/Text-XML-HXT-Arrow-Pickle-Xml.html#v:showPickled
 [1] 
 http://hackage.haskell.org/packages/archive/hxt/latest/doc/html/Text-XML-HXT-Arrow-Pickle-Xml.html#v:unpickleDoc
 
 On Thu, Jan 24, 2013 at 4:40 PM,  bri...@aracnet.com wrote:
  Hi,
 
  Trying to understand how to write a document using a pickler but I can't 
  make sense of the types.
 
  From the example:
 
   runX ( xunpickleDocument xpSeason
 [ withValidate no
 , withTrace 1
 , withRemoveWS yes
 , withPreserveComment no
 ] simple2.xml
   
   processSeason
   
   xpickleDocument   xpSeason
 [ withIndent yes
 ] new-simple2.xml
 )
 
  So all I want to do is pickle a value directly instead of reading the value 
  from a document.  I expected to do something like:
 
  runX (someHXTPicklingFunction myValue

xpickleDocument ...)
 
 
  but I can't seem to figure out what someHXTPicklingFunction should be, it's 
  certainly nothing obvious like pickleDoc, because that generates the wrong 
  value.
 
  Seems like I probably have a much more fundamental problem in that I really 
  don't understand how the arrow part of this little example really works, 
  but I was kind of hoping that doing something simple like this might shed 
  some light on that.  And then was immediately stuck in type hell.
 
 
  Thanks,
 
  Brian
 
 
  ___
  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] How to store Fixed data type in the database with persistent ?

2013-01-24 Thread s9gf4ult
All modern databases has field type NUMERIC(x, y) with arbitrary precision.

I need to store financial data with absolute accuracy, and I decided to use 
Fixed.
How can I store Fixed data type as NUMERIC ? I decided to use Snoyman's 
persistent, bit persistent can not use it from the box and there is a problem 
with custom field declaration.

Here is the instance of PersistField for Fixed I wrote

instance (HasResolution a) = PersistField (Fixed a) where
  toPersistValue a = PersistText $ T.pack $ show a
  -- fromPersistValue (PersistDouble d) = Right $ fromRational $ toRational d
  fromPersistValue (PersistText d) = case reads dpt of
[(a, )] - Right a
_ - Left $ T.pack $ Could not read value  ++ dpt ++  as fixed 
value
where dpt = T.unpack d

  fromPersistValue a = Left $ T.append Unexpected data value can not be 
converted to Fixed:  $ T.pack $ show a

  sqlType a = SqlOther $ T.pack $ NUMERIC( ++ (show l) ++ , ++ (show p) ++ 
)
where
  p = round $ (log $ fromIntegral $ resolution a) / (log 10)
  l = p + 15--  FIXME: this is maybe not very good
  isNullable _ = False

I did not found any proper PersistValue to convert into Fixed from. As well as 
converting Fixed to PersistValue is just a converting to string. Anyway the 
saving works properly, but thre reading does not - it just reads Doubles with 
rounding error.

If you uncomment the commented string in instance you will see, that accuracy 
is not absolute.

Here is test project to demonstrate the problem.

https://github.com/s9gf4ult/xres

If you launch main you will see that precission is not very good because of 
converting database value to Double and then converting to Fixed.

How can i solve this with persistent or what other framework works well with 
NUMERIC database field type ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Manually instantiating Typeable w/DataKinds

2013-01-24 Thread Roman Cheplyaka
Hi Uri,

Here's how it might look.

  {-# LANGUAGE DeriveDataTypeable, DataKinds, KindSignatures, 
ScopedTypeVariables #-}
  module Example where

  import Data.Typeable
  import Data.Proxy

  data Tag = TagV | TagE | TagA | TagL
   deriving Typeable

  class TypeableTag (t :: Tag) where
tagRep :: Proxy t - TypeRep

  instance TypeableTag TagV where
tagRep _ = mkTyConApp (mkTyCon3 mypkg Example 'TagV) []

  -- ... same for the other tags

  newtype TaggedVar (t :: Tag) = TaggedVar Int

  instance TypeableTag t = Typeable (TaggedVar t) where
typeOf _ =
  mkTyConApp
(mkTyCon3 mkpkg Example TaggedVar)
[tagRep (Proxy :: Proxy t)]

Roman

* Uri Braun uribr...@eecs.harvard.edu [2013-01-24 16:14:53-0500]
 I've read the recent posting titled Non-derivable Typeable
 (http://www.mail-archive.com/haskell-cafe@haskell.org/msg103616.html) which
 explains that Typeable cannot be automatically derived for cases where the
 kind is constrained.
 
 I'm very impressed that a solution is imminent.  In the interim, can
 somebody kindly suggest a workaround? I'm okay with a manual instance, but
 I'd appreciate some help as to how to write one. I'm looking for a Typeable
 instance for TaggedVar for the following example below (extracted from my
 code).
 
 Thank you in advance!
 
 +Uri
 
 {-# LANGUAGE DeriveDataTypeable, DataKinds, KindSignatures #-}
 module Example where
 
 import   Data.Typeable
 
 data Tag = TagV | TagE | TagA | TagL
  deriving Typeable
 
 newtype TaggedVar (t :: Tag) = TaggedVar Int
 
 
 
 ___
 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