how to parse yahoo csv with parsec - haskell

how to parse into array such as open[i],high[i],low[i],close[i]
testhaskell.hs:22:5:
Couldn't match type `[]' with `IO'
Expected type: IO a0
Actual type: [a0]
In the return type of a call of `map'
In a stmt of a 'do' block: map (\ line -> sentence line) allLines
In the expression:
do { handle <- openFile
"C:\\Users\\ivan\\Downloads\\0388.HK.csv" ReadMode;
contents <- hGetContents handle;
let allLines = lines contents;
map (\ line -> sentence line) allLines;
.... }
testhaskell.hs:22:19:
Couldn't match expected type `String -> a0'
with actual type `Text.Parsec.Prim.ParsecT
String () Data.Functor.Identity.Identity [String]'
import System.IO
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString as Str
import Text.ParserCombinators.Parsec
word :: Parser String
word = many1 letter
sentence :: Parser [String]
sentence = do{ words <- sepBy1 word separator
; oneOf ".?!" <?> "end of sentence"
; return words
}
separator :: Parser ()
separator = skipMany1 (space <|> char ',' <?> "")
main = do
handle <- openFile "C:\\Users\\ivan\\Downloads\\0005.HK.csv" ReadMode
contents <- hGetContents handle
let allLines = lines contents
map (\line -> sentence line) allLines
--putStr contents
hClose handle
update:
module Main where
import qualified Data.ByteString.Char8 as B
import Data.Map ((!))
import Data.Text
import qualified Data.Vector as V
import System.Directory
import Test.Framework (Test, defaultMain, testGroup)
import Test.Framework.Providers.API
import Test.HUnit ((#=?))
import Data.CSV.Conduit
main :: IO ()
main = defaultMain tests
tests :: [Test]
tests = [testGroup "Basic Ops" baseTests]
baseTests :: [Test]
baseTests =
[
testCase "simple parsing works" test_simpleParse
]
test_simpleParse :: IO ()
test_simpleParse = do
(d :: V.Vector (MapRow B.ByteString)) <- readCSVFile csvSettings testFile1
V.mapM_ assertRow d
where
assertRow r = v3 #=? (v1 + v2)
where v1 = readBS $ r ! "Open"
v2 = readBS $ r ! "High"
v3 = readBS $ r ! "Low"
v4 = readBS $ r ! "Close"
csvSettings :: CSVSettings
csvSettings = defCSVSettings { csvQuoteChar = Just '`'}
testFile1 :: FilePath
testFile1 = "C:\\Users\\ivan\\Downloads\\0005.HK.csv"
readBS :: B.ByteString -> Int
readBS = read . B.unpack
testhaskell.hs:52:5: Not in scope: `testCase'
testhaskell.hs:58:9:
Illegal type signature: `V.Vector (MapRow B.ByteString)'
Perhaps you intended to use -XScopedTypeVariables
In a pattern type-signature

I'd strongly recommend you not do this. There are a number of high-quality CSV libraries on Hackage, and rolling your own is a recipe of problems. At FP Complete, we use csv-conduit, though cassava is also a great library. I'd recommend you try out one of them.

Related

Attoparsec - ensure entire contents consumed with sepBy1

I would like the below code to return [LoadInt 1,LoadDub 2.5,LoadInt 3], but it fails after parsing [LoadInt 1,LoadDub 2] and facing .5,3. How do I make it so it must parse all the way to the comma for a parse to succeed, and an int parse on 2.5 is a fail?
import qualified Data.Attoparsec.ByteString.Char8 as A
import Data.Attoparsec.ByteString.Char8 (Parser)
import Data.ByteString.Char8 (pack)
import Data.Attoparsec.Combinator
import Control.Applicative ((*>),(<$>),(<|>))
data LoadNum = LoadInt Int | LoadDub Double deriving (Show)
someFunc :: IO ()
someFunc = putStrLn . show $ A.parseOnly (lnParser <* A.endOfInput) (pack testString)
testString :: String
testString = "1,2.5,3"
lnParser :: Parser [LoadNum]
lnParser = (sepBy1' (ld <* A.atEnd) (A.char ','))
double :: Parser Double
double = A.double
int :: Parser Int
int = A.signed A.decimal
ld :: Parser LoadNum
ld = ((LoadInt <$> int ) <|> (LoadDub <$> double))
You could use a tiny bit of lookahead to decide whether you reached the end of a list element. So:
int :: Parser Int
int = do
i <- A.signed A.decimal
next <- A.peekChar
case next of
Nothing -> pure i
Just ',' -> pure i
_ -> fail "nah"

Can not print to file using IO Monad

Hello i have done my JSon type and i am trying to it to a file.
I can do this from the prelude but i can't do it when using the IO Monad.I get the following error:
Main.hs:13:24: error:
* Couldn't match type `Char' with `[Char]'
Expected type: String
Actual type: Char
* In the second argument of `writeFile', namely `val'
In a stmt of a 'do' block: writeFile out val
In the expression:
do val <- renderJValue sample
writeFile out val
|
13 | writeFile out val
| ^^^
Main
module Main where
import Jlib
import Put
import Data.Typeable
import System.Environment
out="data.txt"
main::IO()
main=do
val<-renderJValue sample
writeFile out val
Why would this not work in the IO Monad since renderJValue sample in the prelude works ok .
Jlib.hs
data JValue=JString String
|JNumber Double
|JBool Bool
|JNull
|JObject [(String,JValue)]
|JArray [JValue]
deriving (Eq,Ord,Show)
Put.hs
sample=JArray[
JObject [("name",JString "adita"),("age",JNumber 13)],
JObject [("name",JString "dan"),("kids",JNumber 3)] ,
JNumber 3,
JBool False,
JString "Howdy"
]
P.S renderJValue returns a string
P.S: if i start the prelude i load the module and i render the value it works:
Prelude System.Environment Put> :load Put
Ok, two modules loaded.
Prelude System.Environment Put> renderJValue sample
"[{name:adita,age:13.0},{name:dan,kids:3.0},3.0,False,Howdy]"
You here use renderJValue sample as if it is an IO String:
main :: IO()
main=do
val <- renderJValue sample
writeFile out val
But it is in fact (given it is a function similar to this one) a function with signature renderJValue :: JValue -> String. So no IO is involved. In that case we do not use the arrow notation.
We can call the function "inline":
main :: IO()
main = do
writeFile out (renderJValue sample)
or even shorter:
main :: IO()
main = writeFile out (renderJValue sample)
But in case the expression is rather long, this can become quite ugly. We can decide to use a let statement in that case.
You can solve this by either removing the putStrLn:
main :: IO()
main = do
let val = renderJValue sample
writeFile out val

I/O Monad and ByteString to Char conversion?

I'm testing some HTTP requests in haskell and have the below methods:
import qualified Data.ByteString.Lazy as LAZ
import Language.Haskell.TH.Ppr
import System.IO
import Data.Word (Word8)
request :: IO LAZ.ByteString
request = do
response <- simpleHttp "https://www.url.com"
return (response)
exampleFunctionOne:: IO LAZ.ByteString -> IO LAZ.ByteString
exampleFunctionOne bytes = do
html <- bytes
let bytesToChars = bytesToString $ LAZ.unpack html
let x = exampleFunctionTwo bytesToChars
bytes
exampleFunctionTwo :: [Char] -> [Char]
exampleFunctionTwo chars = --Do stuff...
main = do
exampleFunctionOe $ request
My questions are:
Is there a more straight forward way to convert the ByteString to [Char]? Currently I've having to convert to perform (ByteString -> Word8) and then (Word8 -> Char)
Am I correct in saying the 'return ()' statement in my request function is simply re-applying the monad context (in this case IO) to the value I've extracted (response <- simpleHttp)? Or does it have an additional purpose?
To answer your first question, note that there's a different "unpack" in Data.ByteString.Lazy.Char8 with the signature you want:
unpack :: ByteString -> String
It's not unusual for people to import both modules:
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as C
and mix and match functions from each.
To answer your second question, yes that's more or less it. For example:
redund = do x <- getLine
y <- return x
z <- return y
u <- return z
return u
is all equivalent to redund = getLine with a bunch of re-wrapping and extracting of pure values into an out of an IO monad.

how to parse yahoo historical csv with Attoparsec

i am a beginner of haskell, how to parse with attoparsec into open array, high array etc
module CsvParser (
Quote (..)
, csvFile
, quote
) where
import System.IO
import Data.Attoparsec.Text
import Data.Attoparsec.Combinator
import Data.Text (Text, unpack)
import Data.Time
import System.Locale
import Data.Maybe
data Quote = Quote {
qTime :: LocalTime,
qAsk :: Double,
qBid :: Double,
qAskVolume :: Double,
qBidVolume :: Double
} deriving (Show, Eq)
csvFile :: Parser [Quote]
csvFile = do
q <- many1 quote
endOfInput
return q
quote :: Parser Quote
quote = do
time <- qtime
qcomma
ask <- double
qcomma
bid <- double
qcomma
askVolume <- double
qcomma
bidVolume <- double
endOfLine
return $ Quote time ask bid askVolume bidVolume
qcomma :: Parser ()
qcomma = do
char ','
return ()
qtime :: Parser LocalTime
qtime = do
tstring <- takeTill (\x -> x == ',')
let time = parseTime defaultTimeLocale "%d.%m.%Y %H:%M:%S%Q" (unpack tstring)
return $ fromMaybe (LocalTime (fromGregorian 0001 01 01) (TimeOfDay 00 00 00 )) time
--testString :: Text
--testString = "01.10.2012 00:00:00.741,1.28082,1.28077,1500000.00,1500000.00\n"
quoteParser = parseOnly quote
main = do
handle <- openFile "C:\\Users\\ivan\\Downloads\\0005.HK.csv" ReadMode
contents <- hGetContents handle
let allLines = lines contents
map (\line -> quoteParser line) allLines
--putStr contents
hClose handle
Error message:
testhaskell.hs:89:5:
Couldn't match type `[]' with `IO'
Expected type: IO (Either String Quote)
Actual type: [Either String Quote]
In the return type of a call of `map'
In a stmt of a 'do' block:
map (\ line -> quoteParser line) allLines
In the expression:
do { handle <- openFile
"C:\\Users\\ivan\\Downloads\\0005.HK.csv" ReadMode;
contents <- hGetContents handle;
let allLines = lines contents;
map (\ line -> quoteParser line) allLines;
.... }
testhaskell.hs:89:37:
Couldn't match type `[Char]' with `Text'
Expected type: [Text]
Actual type: [String]
In the second argument of `map', namely `allLines'
In a stmt of a 'do' block:
map (\ line -> quoteParser line) allLines
In the expression:
do { handle <- openFile
"C:\\Users\\ivan\\Downloads\\0005.HK.csv" ReadMode;
contents <- hGetContents handle;
let allLines = lines contents;
map (\ line -> quoteParser line) allLines;
.... }
The error has nothing to do with parsec or attoparsec. The line the error message points to is not an IO action, so it causes the error when you try to use it as one:
main = do
handle <- openFile "C:\\Users\\ivan\\Downloads\\0005.HK.csv" ReadMode
contents <- hGetContents handle
let allLines = lines contents
map (\line -> quoteParser line) allLines -- <== This is not an IO action
--putStr contents
hClose handl
You ignore the result of the map call. You should store it in a variable with let, like you do with the result of lines.
The second error is because you are trying to use Text as String which are different types, even though they both represent ordered collections of characters (they also have different internal representations). You can convert between the two types with pack and unpack: http://hackage.haskell.org/package/text/docs/Data-Text.html#g:5
Also, you should always explicitly give main the type signature main :: IO (). It can sometimes lead to subtle problems if you don't.
As other people have said, though, you should probably use a csv parser package.
You can use attoparsec-csv package or you can take a look at its source code to have some idea on how to write it by yourself.
The code will be like
import qualified Data.Text.IO as T
import Text.ParseCSV
main = do
txt <- T.readFile "file.csv"
case parseCSV txt of
Left err -> error err
Right csv -> mapM_ (print . mkQuote) csv
mkQuote :: [T.Text] -> Quote
mkQuote = error "Not implemented yet"

Data.Text.Text and quasiquoting

I have a parser which parses to an ast which contains Text values. I
am trying to use this parser with quasiquoting, but the implementation
of Data for Text is incomplete. I've attached a smallish test case, when I try to compile Text.hs I get:
Text.hs:17:9:
Exception when trying to run compile-time code:
Data.Text.Text.toConstr
Code: Language.Haskell.TH.Quote.quoteExp expr " test "
Is there a way to get this working?
I read through the discussion here: http://www.haskell.org/pipermail/haskell-cafe/2010-January/072379.html
It seems that no-one has found a proper solution to this issue? Also, I tried the Data instance given there and it didn't work, I have no idea how to fix it (or how to use it since the text package already has a Data instance for Text). I don't really understand a lot of the generics stuff and how it works.
The only solution I have so far is to give up using Text in the ast and go back to using String.
{-# LANGUAGE DeriveDataTypeable #-}
module Syntax where
import Data.Data
import Data.Text
data Expr = Iden Text
| Num Integer
| AntiIden Text
deriving (Eq,Show,Data,Typeable)
---------------------
module Parser where
import Control.Applicative
import Control.Monad.Identity
import qualified Data.Text as T
import Text.Parsec hiding (many, optional, (<|>), string, label)
import Text.Parsec.Language
import qualified Text.Parsec.Token as P
import Text.Parsec.Text ()
import Syntax
parseExpr :: T.Text -> Either ParseError Expr
parseExpr s =
runParser expr () "" s
expr :: ParsecT T.Text () Identity Expr
expr =
whiteSpace >> choice
[do
_ <- char '$'
AntiIden <$> identifier
,Num <$> natural
,Iden <$> identifier
]
identifier :: ParsecT T.Text () Identity T.Text
identifier = T.pack <$> P.identifier lexer
natural :: ParsecT T.Text () Identity Integer
natural = P.natural lexer
lexer :: P.GenTokenParser T.Text () Identity
lexer = P.makeTokenParser langDef
whiteSpace :: ParsecT T.Text () Identity ()
whiteSpace = P.whiteSpace lexer
langDef :: GenLanguageDef T.Text st Identity
langDef = P.LanguageDef
{ P.commentStart = "{-"
, P.commentEnd = "-}"
, P.commentLine = "--"
, P.nestedComments = True
, P.identStart = letter <|> char '_'
, P.identLetter = alphaNum <|> oneOf "_"
, P.opStart = P.opLetter langDef
, P.opLetter = oneOf "+-*/<>="
, P.reservedOpNames= []
, P.reservedNames = []
, P.caseSensitive = False
}
-------------------
module Quasi where
import Language.Haskell.TH.Quote
import Language.Haskell.TH
import Data.Generics
import qualified Data.Text as T
import Syntax
import Parser (parseExpr)
expr :: QuasiQuoter
expr = QuasiQuoter {quoteExp = prs
,quotePat = undefined
,quoteType = undefined
,quoteDec = undefined}
where
prs :: String -> Q Exp
prs s = p s
>>= dataToExpQ (const Nothing
`extQ` antiExpE
)
p s = either (fail . show) return (parseExpr $ T.pack s)
antiExpE :: Expr -> Maybe ExpQ
antiExpE v = fmap varE (antiExp v)
antiExp :: Expr -> Maybe Name
antiExp (AntiIden v) = Just $ mkName $ T.unpack v
antiExp _ = Nothing
----------------------------
-- test.hs:
{-# LANGUAGE QuasiQuotes #-}
import Syntax
import Quasi
test,test1,test2 :: Expr
-- works
test = [expr| 1234 |]
-- works
test1 = let stuff = Num 42
in [expr| $stuff |]
-- doesn't work
test2 = [expr| test |]
main :: IO ()
main = putStrLn $ show test2
Solution: add this function using extQ to the dataToExpQ call:
handleText :: T.Text -> Maybe ExpQ
handleText x =
-- convert the text to a string literal
-- and wrap it with T.pack
Just $ appE (varE 'T.pack) $ litE $ StringL $ T.unpack x
Add an extQ for handleText where handleText explicitly takes Text to an ExpQ, rather than going through generic machinery.
Here's one for Strings, for example, that renders them more efficiently than as explicit cons cells:
handleStr :: String -> Maybe (TH.ExpQ)
handleStr x = Just $ TH.litE $ TH.StringL x

Resources