Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Text.XML.writeFile question (Alan Buxton)
   2. Re:  Text.XML.writeFile question (David McBride)
   3. Re:  How Haskell Fits Into an Operating System / API
      Environment (damodar kulkarni)


----------------------------------------------------------------------

Message: 1
Date: Mon, 12 Aug 2013 21:35:30 +0100
From: "Alan Buxton" <alanbux...@gmail.com>
To: <beginners@haskell.org>
Subject: [Haskell-beginners] Text.XML.writeFile question
Message-ID: <004001ce979b$7d5b8d00$7812a700$@gmail.com>
Content-Type: text/plain; charset="us-ascii"

Hi

 

I am trying to write an XML file where the filename is created based on a
timestamp. Simplified version below. This won't compile - I get this error
in doWrite2 

 

filepathtest.hs|24 col 17 error| Couldn't match expected type
`system-filepath-0.4.7:Filesystem.Path.Internal.FilePath'


||             with actual type `String'

|| In the second argument of `writeFile', namely `t1'

|| In a stmt of a 'do' block: writeFile def t1 doc

|| In the expression:

||   do { t1 <- tsString;

||        writeFile def t1 doc }

 

Somehow the String "text.xml" in doWrite1 is converted into a FilePath, but
not the String t1 in doWrite2. What am I doing wrong?

 

  {-# LANGUAGE OverloadedStrings #-}

  module Filepathtest  where

  

  import Text.XML

  import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)

  import Data.Time.Clock  (getCurrentTime)

  import Prelude hiding (writeFile, FilePath)

    

  tsString :: IO String

  tsString = do

    x <- getCurrentTime

    let x' = show $ floor $ utcTimeToPOSIXSeconds x

    return x'

  

  doWrite1 :: Document -> IO ()

  doWrite1 doc =

    writeFile def "test1.xml" doc

  

  doWrite2 :: Document -> IO ()

  doWrite2 doc = do

    t1 <- tsString

    writeFile def t1 doc

 

 

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130812/64e2b900/attachment-0001.html>

------------------------------

Message: 2
Date: Mon, 12 Aug 2013 16:52:06 -0400
From: David McBride <toa...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Text.XML.writeFile question
Message-ID:
        <can+tr43iak2sv+c_pymtgp6t4b0hy3geprkswjwhr7mbskw...@mail.gmail.com>
Content-Type: text/plain; charset="windows-1252"

When you use overloadedstrings, it will type all literal strings as
IsString a => a as a type.  Unfortunately your tsString is not a literal,
it is a run time function that always returns a string and a string is not
a filepath.

You should be able to do fmap fromString tsString, provided you import
Data.String.


On Mon, Aug 12, 2013 at 4:35 PM, Alan Buxton <alanbux...@gmail.com> wrote:

> Hi****
>
> ** **
>
> I am trying to write an XML file where the filename is created based on a
> timestamp. Simplified version below. This won?t compile ? I get this error
> in doWrite2 ****
>
> ** **
>
> *filepathtest.hs|24 col 17 error| Couldn't match expected type
> `system-filepath-0.4.7:Filesystem.Path.Internal.FilePath'
> *
>
> *||             with actual type `String'*
>
> *|| In the second argument of `writeFile', namely `t1'*
>
> *|| In a stmt of a 'do' block: writeFile def t1 doc*
>
> *|| In the expression:*
>
> *||   do { t1 <- tsString;*
>
> *||        writeFile def t1 doc }*
>
> * *
>
> Somehow the String ?text.xml? in doWrite1 is converted into a FilePath,
> but not the String t1 in doWrite2. What am I doing wrong?****
>
> ** **
>
>   {-# LANGUAGE OverloadedStrings #-}****
>
>   module Filepathtest  where****
>
>   ****
>
>   import Text.XML****
>
>   import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)****
>
>   import Data.Time.Clock  (getCurrentTime)****
>
>   import Prelude hiding (writeFile, FilePath)****
>
>     ****
>
>   tsString :: IO String****
>
>   tsString = do****
>
>     x <- getCurrentTime****
>
>     let x' = show $ floor $ utcTimeToPOSIXSeconds x****
>
>     return x'****
>
>   ****
>
>   doWrite1 :: Document -> IO ()****
>
>   doWrite1 doc =****
>
>     writeFile def "test1.xml" doc****
>
>   ****
>
>   doWrite2 :: Document -> IO ()****
>
>   doWrite2 doc = do****
>
>     t1 <- tsString****
>
>     writeFile def t1 doc****
>
> ** **
>
> ** **
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130812/63a26c59/attachment-0001.html>

------------------------------

Message: 3
Date: Tue, 13 Aug 2013 10:15:07 +0530
From: damodar kulkarni <kdamodar2...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] How Haskell Fits Into an Operating
        System / API Environment
Message-ID:
        <CAD5Hsypf4bv4ovfpqhdGw=wotqvctk-jmbnziunnvvzaffe...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

> Curiously, whenever I use state, my programs start to become similarly
> brittle. There is no reason why state should be a fundamental element of a
> programming language, and as a design pattern, state is best avoided at all
> cost.


Just as a curiosity, how would one avoid state in cases like protocol
design? e.g. protocols specifications (like TCP/IP) do have a large element
of state dependent behavior that "seems essential" to the problem. How
would one deal with such cases?

@Philippe Sismondi:

I always feel as though I am using the robot arm on a space shuttle when a
> screwdriver would do.


+1 for this remark.

Thanks and regards,
-Damodar Kulkarni


On Mon, Aug 12, 2013 at 2:53 PM, Heinrich Apfelmus <
apfel...@quantentunnel.de> wrote:

> Philippe Sismondi wrote:
>
>>
>> Upon reflection, probably my real concern is not about mixing
>> dissimilar programming languages, but about the frequently discussed
>> issue of finding production-quality libraries for a language. [..]
>>
>>
>> For most of the software that I am interested in working on, there is
>> a vast collection of "native" stuff available in both OS X and
>> Windows. This includes, just as an example, Core Audio in OS X. [..]
>>
>>
>> Moreover, I am dissatisfied with the quality of Haskell libraries
>> even for those things that are not already supplied by OS vendors. In
>> my opinion (and I may be wrong), hackage is littered with half-baked
>> stuff, poorly documented projects started by extremely bright grad
>> students and then abandoned after a year or two. (Of course, there is
>> some great stuff on there too.)
>>
>
> Well, there are a lot of magazines at the news kiosk, too, while only a
> few are of outstanding quality. That is just how a news kiosk works.
>
> Speaking of quality, what I like most about Haskell libraries, even the
> half-baked ones, is that they have very few bugs. I've been programming
> functionally for a decade now, and whenever I venture into the world of
> imperative languages, I always trip up bugs that just shouldn't be there.
> Here two recent examples:
>
> * HTML 5 drag and drop. Apart from the fact that the specification is
> overcomplicated, Chrome doesn't even implement the spec correctly. When the
> mouse enters a child element of a "dropzone'd" element, the latter receives
> a "dragleave" event, but will not receive a "dragenter" event again when
> the mouse moves away from the child element. Argh!
>
> * HTML 5 WebSockets. Chrome or Safari. After a certain amount of
> inactivity on the server side, the browser will close the WebSocket.
> However, it will only close the client side, so the client cannot send
> messages anymore. The connection to the server is still *open*, though, and
> the server can happily send data. What? Also, if you connect with a
> WebSocket and then reload the page and connect again, the old connection
> will be reused. WTF?
>
> These are just examples, this happens to me all the time. Curiously,
> whenever I use state, my programs start to become similarly brittle. There
> is no reason why state should be a fundamental element of a programming
> language, and as a design pattern, state is best avoided at all cost.
>
>
>  As a result of this little thread I have come to another conclusion,
>> and this is just my subjective view. Most of the software that I am
>> interested in seems to live most comfortably with a stateful
>> conception of the world. (The native libraries I find most useful
>> certainly are stateful.) I am reasonably competent with monads and
>> monad transformers in Haskell. But, to be honest, after three years
>> of pluggin away at Haskell, I am not the least convinced that the
>> problem of handling a changing external world in a pure functional
>> language has been successfully solved by those techniques. I always
>> feel as though I am using the robot arm on a space shuttle when a
>> screwdriver would do. (Again, no need to rebut this - I may be wrong
>> or just to stupid to use Haskell effectively - so be it.)
>>
>> Perhaps in the end I do not really believe that functional
>> programming is the panacea that its devotees claim it to be.
>>
>> I think this post may mark the beginning of my abandonment of Haskell
>> for many purposes.
>>
>
> Haskell may not be easy to learn, but it's definitely worth the effort.
>
>
>
> Best regards,
> Heinrich Apfelmus
>
> --
> http://apfelmus.nfshost.com
>
>
> ______________________________**_________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/**mailman/listinfo/beginners<http://www.haskell.org/mailman/listinfo/beginners>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130813/a75b7b40/attachment.html>

------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 62, Issue 12
*****************************************

Reply via email to