Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/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.  OI UTCTime to String (sasa bogicevic)
   2. Re:  OI UTCTime to String (Francesco Ariis)
   3. Re:  OI UTCTime to String (Arjun Comar)
   4. Re:  OI UTCTime to String (David McBride)
   5. Re:  OI UTCTime to String (sasa bogicevic)


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

Message: 1
Date: Thu, 10 Nov 2016 19:44:17 +0100
From: sasa bogicevic <brutalles...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] OI UTCTime to String
Message-ID: <7085a8e2-7469-440c-bd04-747a05600...@gmail.com>
Content-Type: text/plain; charset=utf-8

Hi All,

This is a small program

{-# LANGUAGE OverloadedStrings #-}
module Main where

import           Control.Monad.IO.Class     (liftIO)
import qualified Data.ByteString.Lazy.Char8 as L
import           Data.Time
import           Network                    (withSocketsDo)
import           Network.HTTP.Conduit


createRequestData today = [("index:brKursneListe",""),
 ("index:year","2016"),
 ("index:inputCalendar1", today),
 ("index:vrsta","3"),
 ("index:prikaz","0"),
 ("index:buttonShow","Prikazi")]


timeFromString  s = parseTimeOrError True defaultTimeLocale "%d %b %Y %l:%M %p" 
s

formatDateString time = formatTime defaultTimeLocale "%m/%d/%Y" time

getDateString = getCurrentTime

getFormatedDate  = formatDateString $ timeFromString getDateString

main = do
        print $ getFormatedDate


And here is my error

main.hs:25:54: error:
   • Couldn't match type ‘IO UTCTime’ with ‘[Char]’
     Expected type: String
       Actual type: IO UTCTime
   • In the first argument of ‘timeFromString’, namely ‘getDateString’
     In the second argument of ‘($)’, namely
       ‘timeFromString getDateString’
     In the expression: formatDateString $ timeFromString getDateString

Thanks!



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

Message: 2
Date: Thu, 10 Nov 2016 19:52:21 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] OI UTCTime to String
Message-ID: <20161110185221.ga18...@casa.casa>
Content-Type: text/plain; charset=utf-8

On Thu, Nov 10, 2016 at 07:44:17PM +0100, sasa bogicevic wrote:
> Hi All,
> 
> This is a small program
>
> [...]

Hey Sasa,
If we put this into ghci

    λ> :t formatDateString $ timeFromString _

the "hole" tells us we need something of type String, but `getDateString`
is not!

    λ> :t getDateString
    getDateString :: IO UTCTime

That means you have to bind it inside a `do` block (or use >>=).
Ask for more if I was not clear!


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

Message: 3
Date: Thu, 10 Nov 2016 19:07:09 +0000
From: Arjun Comar <nru...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] OI UTCTime to String
Message-ID:
        <CADjRcrUyNrgc7-yeta4myO-X-1x53gmrtq8PX23dsJbq=tn...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Adding to Francesco's reply, UTCTime is not a String either. Luckily, it
does have a Show instance however, which means you probably want something
like:

    getDateString = do
        date <- getCurrentTime
        return $ show date

Or, more simply: getDateString = fmap show getCurrentTime

You will still need to use bind, fmap, or do to get at the actual date
string however.

Thanks,
Arjun

On Thu, Nov 10, 2016 at 1:58 PM Francesco Ariis <fa...@ariis.it> wrote:

> On Thu, Nov 10, 2016 at 07:44:17PM +0100, sasa bogicevic wrote:
> > Hi All,
> >
> > This is a small program
> >
> > [...]
>
> Hey Sasa,
> If we put this into ghci
>
>     λ> :t formatDateString $ timeFromString _
>
> the "hole" tells us we need something of type String, but `getDateString`
> is not!
>
>     λ> :t getDateString
>     getDateString :: IO UTCTime
>
> That means you have to bind it inside a `do` block (or use >>=).
> Ask for more if I was not clear!
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20161110/59392610/attachment-0001.html>

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

Message: 4
Date: Thu, 10 Nov 2016 14:23:36 -0500
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] OI UTCTime to String
Message-ID:
        <can+tr402tebe-qhxrzdjxcfgrcbibnrcbf_tq-chamzjmbs...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

It looks like you are trying to get time in UTC, then figuring out what
date it is?  You should be able to get the answer you are looking for with

getFormattedDate = do
  utc <- getCurrentTime
  return $ formatTime defaultTimeLocale "%m/%d/%Y" utc

Just keep in mind that that is the date in UTC.  Not in your local time
zone and it ignores daylight savings time.  To get it in your time you'll
have to replace getCurrentTime with getZonedTime.

On Thu, Nov 10, 2016 at 1:44 PM, sasa bogicevic <brutalles...@gmail.com>
wrote:

> Hi All,
>
> This is a small program
>
> {-# LANGUAGE OverloadedStrings #-}
> module Main where
>
> import           Control.Monad.IO.Class     (liftIO)
> import qualified Data.ByteString.Lazy.Char8 as L
> import           Data.Time
> import           Network                    (withSocketsDo)
> import           Network.HTTP.Conduit
>
>
> createRequestData today = [("index:brKursneListe",""),
>  ("index:year","2016"),
>  ("index:inputCalendar1", today),
>  ("index:vrsta","3"),
>  ("index:prikaz","0"),
>  ("index:buttonShow","Prikazi")]
>
>
> timeFromString  s = parseTimeOrError True defaultTimeLocale "%d %b %Y
> %l:%M %p" s
>
> formatDateString time = formatTime defaultTimeLocale "%m/%d/%Y" time
>
> getDateString = getCurrentTime
>
> getFormatedDate  = formatDateString $ timeFromString getDateString
>
> main = do
>         print $ getFormatedDate
>
>
> And here is my error
>
> main.hs:25:54: error:
>    • Couldn't match type ‘IO UTCTime’ with ‘[Char]’
>      Expected type: String
>        Actual type: IO UTCTime
>    • In the first argument of ‘timeFromString’, namely ‘getDateString’
>      In the second argument of ‘($)’, namely
>        ‘timeFromString getDateString’
>      In the expression: formatDateString $ timeFromString getDateString
>
> Thanks!
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20161110/c74c57d4/attachment-0001.html>

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

Message: 5
Date: Thu, 10 Nov 2016 21:44:37 +0100
From: sasa bogicevic <brutalles...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] OI UTCTime to String
Message-ID: <69791b07-41a4-4397-96db-469e42c34...@gmail.com>
Content-Type: text/plain; charset=utf-8

Thanks guys!
Didn't expect this much help so fast, great community!
I think my main problem was that I was constantly trying to print the result 
for my formatted date string which was of type IO String (at some point)
I just learned that to print IO you need to bind it something like this
 
main =  getFormattedDate >>= putStrLn

Thanks a lot, You rock!




> On Nov 10, 2016, at 20:23, David McBride <toa...@gmail.com> wrote:
> 
> It looks like you are trying to get time in UTC, then figuring out what date 
> it is?  You should be able to get the answer you are looking for with
> 
> getFormattedDate = do
>   utc <- getCurrentTime
>   return $ formatTime defaultTimeLocale "%m/%d/%Y" utc
> 
> Just keep in mind that that is the date in UTC.  Not in your local time zone 
> and it ignores daylight savings time.  To get it in your time you'll have to 
> replace getCurrentTime with getZonedTime.
> 
> On Thu, Nov 10, 2016 at 1:44 PM, sasa bogicevic <brutalles...@gmail.com> 
> wrote:
> Hi All,
> 
> This is a small program
> 
> {-# LANGUAGE OverloadedStrings #-}
> module Main where
> 
> import           Control.Monad.IO.Class     (liftIO)
> import qualified Data.ByteString.Lazy.Char8 as L
> import           Data.Time
> import           Network                    (withSocketsDo)
> import           Network.HTTP.Conduit
> 
> 
> createRequestData today = [("index:brKursneListe",""),
>  ("index:year","2016"),
>  ("index:inputCalendar1", today),
>  ("index:vrsta","3"),
>  ("index:prikaz","0"),
>  ("index:buttonShow","Prikazi")]
> 
> 
> timeFromString  s = parseTimeOrError True defaultTimeLocale "%d %b %Y %l:%M 
> %p" s
> 
> formatDateString time = formatTime defaultTimeLocale "%m/%d/%Y" time
> 
> getDateString = getCurrentTime
> 
> getFormatedDate  = formatDateString $ timeFromString getDateString
> 
> main = do
>         print $ getFormatedDate
> 
> 
> And here is my error
> 
> main.hs:25:54: error:
>    • Couldn't match type ‘IO UTCTime’ with ‘[Char]’
>      Expected type: String
>        Actual type: IO UTCTime
>    • In the first argument of ‘timeFromString’, namely ‘getDateString’
>      In the second argument of ‘($)’, namely
>        ‘timeFromString getDateString’
>      In the expression: formatDateString $ timeFromString getDateString
> 
> Thanks!
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners



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

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

End of Beginners Digest, Vol 101, Issue 6
*****************************************

Reply via email to