[Haskell-cafe] linking Haskell app with Curl on Windows

2012-08-16 Thread Eugene Dzhurinsky
Hi!

I'm facing strange issue with linking my application against Curl (using Haskell
Curl binding curl-1.3.7): the application compiles well, but fails on linking
stage:

=

C:\haskell\bin\ghc.exe --make -o dist\build\imgpaste\imgpaste.exe 
-hide-all-packages -fbuilding-cabal-package -package-conf 
dist\package.conf.inplace -i -idist\build\imgpaste\imgpaste-tmp -i. 
-idist\build\autogen -Idist\build\autogen -Idist\build\imgpaste\imgpaste-tmp 
-optP-include -optPdist\build\autogen\cabal_macros.h -odir 
dist\build\imgpaste\imgpaste-tmp -hidir dist\build\imgpaste\imgpaste-tmp 
-stubdir dist\build\imgpaste\imgpaste-tmp -package-id 
base-4.5.0.0-597748f6f53a7442bcae283373264bb6 -package-id 
bytestring-0.9.2.1-df82064cddbf74693df4e042927e015e -package-id 
curl-1.3.7-ed08f87bd8c487f1e11a8c3b67bf4e51 -package-id 
directory-1.1.0.2-0270278088d4b2588b52cbec49af4cb7 -package-id 
hxt-9.2.2-e687550fbbb6ff367ee9c95584c3f0a0 -package-id 
hxt-xpath-9.1.2-4a15d34a0b66fa21832bb4bb0f68477f -package-id 
regex-pcre-0.94.4-f2f06ed579a684904354d97b04a74d9e -O -XHaskell98 .\Main.hs 
-llibcrypto -lssh2 -lssl -lz -lidn -LC:\curl\lib
Linking dist\build\imgpaste\imgpaste.exe ...
C:\Program 
Files\Haskell\curl-1.3.7\ghc-7.4.1/libHScurl-1.3.7.a(curlc.o):curlc.c:(.text+0xd2):
 undefined reference to `_imp__curl_easy_getinfo'
C:\Program 
Files\Haskell\curl-1.3.7\ghc-7.4.1/libHScurl-1.3.7.a(curlc.o):curlc.c:(.text+0xee):
 undefined reference to `_imp__curl_easy_getinfo'
C:\Program 
Files\Haskell\curl-1.3.7\ghc-7.4.1/libHScurl-1.3.7.a(curlc.o):curlc.c:(.text+0x10a):
 undefined reference to `_imp__curl_easy_getinfo'

[ lots of error messages skipped ]

C:\curl\lib/libcurl.a(md5.o):(.text+0x3b): undefined reference to `MD5_Update'
C:\curl\lib/libcurl.a(md5.o):(.text+0x4e): undefined reference to `MD5_Final'
C:\curl\lib/libcurl.a(md5.o):(.rdata+0x0): undefined reference to `MD5_Init'
C:\curl\lib/libcurl.a(md5.o):(.rdata+0x4): undefined reference to `MD5_Update'
C:\curl\lib/libcurl.a(md5.o):(.rdata+0x8): undefined reference to `MD5_Final'
C:\curl\lib/libcurl.a(md5.o):(.rdata+0x14): undefined reference to `MD5_Init'
C:\curl\lib/libcurl.a(md5.o):(.rdata+0x18): undefined reference to `MD5_Update'
C:\curl\lib/libcurl.a(md5.o):(.rdata+0x1c): undefined reference to `MD5_Final'
cabal.EXE: Error: some packages failed to install:
imgpaste-0.2 failed during the building phase. The exception was:
ExitFailure 1

=

What may be wrong here? Curl itself was installed without errors. Looking for
symbols 'MD5_Final' in directory C:\curl\lib results in 'libcrypto.a',
'libcrypto.dll.a' and 'libcurl.a'

-- 
Eugene N Dzhurinsky


pgpj0k8gEAyFB.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Linking against Sqlite3 on Windows problem

2012-07-09 Thread Eugene Dzhurinsky
Hi all!

I created simple application, which uses sqlite3 as it's datastore back-end. I
faced no problems when building and running it on Linux, but after I tried to
build it on Windows, I see weird linking error:

Linking dist\build\hnotes\hnotes.exe ...
C:\Documents and Settings\Admin\Application 
Data\cabal\sqlite-0.5.2.2\ghc-7.0.4/libHSsqlite-0.5.2.2.
a(sqlite3-local.o):sqlite3-local.c:(.text+0x21): undefined reference to 
`sqlite3_temp_directory'
C:\Documents and Settings\Admin\Application 
Data\cabal\sqlite-0.5.2.2\ghc-7.0.4/libHSsqlite-0.5.2.2.
a(sqlite3-local.o):sqlite3-local.c:(.text+0x40): undefined reference to 
`sqlite3_temp_directory'
collect2: v ld 1
cabal.EXE: Error: some packages failed to install:
hnotes-0.1 failed during the building phase. The exception was:
ExitFailure 1

What may be wrong there? I suspect that qalite3.dll has to be added to linking 
stage, 
but have no idea how to do that. Adding --extra-lib-dirs=path-to-sqlite-dll 
doesn't 
help either (perhaps because I need to update my cabal file somehow, to support 
this?).

Thank you for the help!

-- 
Eugene N Dzhurinsky


pgpQJzjGTBAjt.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Reader monad, refactoring and missing the point all at once

2012-05-01 Thread Eugene Dzhurinsky
Hi all!

Last day I was trying to fix idiii library, because it uses utf8 for parsing
non-unicode content. I found the functions

> -- | Parses one value and returns it as a 'String'
> parseString :: CharEncoding -> TagParser String
> parseString enc = do
> v <- case enc of
>   0x01 -> parseUntilWord16Null -- UTF-16
>   0x02 -> parseUntilWord16Null -- UTF-16 BOM
>   _-> parseUntilWord8Null  -- ISO-8859-1 or UTF-8
> return $ encPack enc v
> 
> encPack :: CharEncoding -> [Token] -> String
> encPack 0x00s  = Text.unpack $ decodeASCII   $ BS.pack s
> encPack 0x01 (0xFF:0xFE:s) = Text.unpack $ decodeUtf16LE $ BS.pack s
> encPack 0x01 (0xFE:0xFF:s) = Text.unpack $ decodeUtf16BE $ BS.pack s
> encPack 0x02s  = Text.unpack $ decodeUtf16BE $ BS.pack s
> encPack _   s  = Text.unpack $ decodeUtf8$ BS.pack s

updated the dependency from 
> import Data.Text.Encoding (decodeASCII, decodeUtf16LE, decodeUtf16BE, 
> decodeUtf8)
to
> import Data.Text.ICU.Convert

and added implementation for decoding functions:

> decodeAny :: String -> BS.ByteString -> Text.Text
> decodeAny charset src = unsafePerformIO $ ((flip toUnicode) src) `fmap` open 
> charset (Just True)
>
> decodeASCII :: BS.ByteString -> Text.Text
> decodeASCII = decodeAny "latin1"
> 
> decodeUtf16LE = decodeAny "utf-16le"
> 
> decodeUtf16BE = decodeAny "utf-16be"
> 
> decodeUtf8 = decodeAny "utf-8"

Now I want to add possibility to specify encoding to yse with decodeASCII. I 
was 
thinking of adding Reader monad and providing some sort of charset
configuration there - but it will lead up to complicating the code, which uses
this parseString function. And this code is used inside Parser of 
Text.ParserCombinators.Poly.State - 
so I will need to update all usages of this parser.

Another approach might be to use IORef with encoding stored there, but I
don't really like this solution.

What would be the best way of refactoring of such kind?

Thanks!

-- 
Eugene N Dzhurinsky


pgp9sNFLGUKtm.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] XMonad.Shell.Prompt and unicode input

2012-01-24 Thread Eugene Dzhurinsky
Hello, community!

I have some strange issue with recent XMonad: with using of standard Shell
module it is not possible to use unicode input. It simply freezes up and in
console I can observe:

Enum.toEnum{Word8} : tag (1092) is outside of bounds (0,255).

What function may cause such error indirectly? I looked through the sources -
but have no idea where such conversion may have place and why Word8 is used.

-- 
Eugene N Dzhurinsky


pgpyGCsSpWzbI.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting a string from url-converted UTF8 input

2010-05-16 Thread Eugene Dzhurinsky
On Sun, May 16, 2010 at 06:55:33PM +0200, Daniel Fischer wrote:
> Is there any problem compiling from source on FreeBSD?

Well, good question :)

After I tried to find some sources, I realized that there are 

http://www.haskell.org/ghc/download_ghc_6_12_2.html#freebsd

-- 
Eugene N Dzhurinsky


pgpy69yloZfQp.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting a string from url-converted UTF8 input

2010-05-16 Thread Eugene Dzhurinsky
On Sun, May 16, 2010 at 06:56:58PM +0300, Roman Cheplyaka wrote:
> I assume you are using GHC < 6.12. The trouble is in conversion done by
> putStrLn. Use one from System.IO.UTF8.
> 
> Or try to upgrade to GHC 6.12 which respects the locale settings.

Hello, Roman!

Thank you very much for the hint, it really did help.

Unfortunately, there's no port of GHC 6.12 available for FreeBSD now, so I
used System.IO.UTF8

-- 
Eugene Dzhurinsky


pgp4pa7EBeen7.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Getting a string from url-converted UTF8 input

2010-05-16 Thread Eugene Dzhurinsky
Hello all!

Can somebody please explain wha am I doing in wrong way?

===
module UrlEncode where

import System
import Codec.Binary.UTF8.String as SU
import Codec.Binary.Url as U
import Data.Maybe

main :: IO ()
main = do
args <- getArgs
processWithArgs args

processWithArgs ("-d":[]) =
getLine >>= putStrLn .  maybe "" SU.decode .  U.decode 

processWithArgs ("-e":[]) =
getLine >>= putStrLn . U.encode . SU.encode

processWithArgs _ =
putStrLn "Usage: -e (encode) or -d (decode)"
===

With this script if fed with input:

===
1%29%20%D0%B3%D0%B4%D0%B5%20%D0%BD%D1%8B%D0%BD%D1%87%D0%B5%20%D0%BC%D0%BE%D0%B4%D0%BD%D0%BE%20%D0%B1%D1%80%D0%B0%D1%82%D1%8C%20%D0%BA%D0%BD%D0%B8%D0%B6%D0%BA%D0%B8%20%D0%B2%20%D0%B2%D0%B8%D0%B4%D0%B5%20FB2%3F%0D%0A%0D%0A2%29%20%D0%BA%D0%B0%D0%BA%D0%BE%D0%B9%20%D0%B5%D1%81%D1%82%D1%8C%20%D1%81%D0%BE%D1%84%D1%82%20%D0%BD%D0%B0%20%D0%B6%D0%B5%D0%BB%D0%B5%D0%B7%D0%BA%D1%83%20%D1%82%D0%B8%D0%BF%D0%B0%20%D1%82%D0%B5%D0%BB%D0%B5%D1%84%D0%BE%D0%BD%20%D1%81%20Symbian
===

I am getting the output:

===
1) 345 =K=G5 <>4=> 1...@0bl :=86:8 2 2845 FB2?

2) :0:>9 5ABL A>DB =0 65;57:C B8?0 B5;5D>= A Symbian
===

which is wrong. So what do I miss in encoding the data in UTF?

Thank you in advance!

-- 
Eugene Dzhurinsky


pgpUPu4ndYSxU.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Data creation pattern?

2010-05-13 Thread Eugene Dzhurinsky
Hello, all!

I need to create objects like this

data Object = MyObject { param1, param2, param3 :: String }

from the input file

param_1_param1=value11
param_2_param1=value21
param_2_param2=value22
param_1_param3=value13
param_2_param3=value23
param_1_param2=value12

so general pattern of recognizing parameter name and value is

param_{id}_{property name}={property value}

so I need to create function

> parseDataFile :: [String] -> [Object]

For now I can think on splitting the task into 2 functions

> groupSameObjectParameters :: [String] -> [[String]]

which will group the lines with same id into a list, and then apply function

> createObject :: [String] -> Object

so overall solution will be

> parseDataFile :: [String] -> [Object]
> parseDataFile = map createObject . groupSameObjectParameters

however I have no neat idea about how to create instance of MyObject - I need
to supply all of parameters to the constructor at once.

Also I don't like the idea of rearranging list first and then create objects
from another list, because the list can be relatively large.

In imperative programming with mutable objects I would create an array, then
for each line get the id and try to find if there is the object in the array
at 'id' index. If no - create one. Then set appropriate property from value.

Is it possible to do something similar in Haskell?

Thank you in advance!

-- 
Eugene N Dzhurinsky


pgpi8YKuw3492.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread Eugene Dzhurinsky
On Thu, May 06, 2010 at 10:05:05AM +0200, David Virebayre wrote:
> A constructor can be seen as a function that takes some parameters and
> produces a value
> 
> for example with the type Maybe a, which has 2 constructors ; Just and 
> Nothing :
> 
> Prelude> :t Just
> Just :: a -> Maybe a
> 
> the constructor Just is a function that takes a value of type a and
> makes a value of type Maybe a.
> 
> Prelude> :t Just
> Just :: a -> Maybe a

Ouch, that makes things clear. Thanks for the explanation!

-- 
Eugene N Dzhurinsky


pgpmfW4Cj0L7U.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] posting UTF8 data with Curl library

2010-05-06 Thread Eugene Dzhurinsky
On Wed, May 05, 2010 at 11:15:05PM +0200, Daniel Fischer wrote:
> It's the same type, so you can encode it using Data.ByteString.UTF8 and 
> send it over the network as a plain old ByteString.
> On the receiving end, you read it as a plain ByteString and then interpret 
> it as a utf-8 encoded ByteString.

Okay, I will give it a try. Seems like everything should be pretty simple and
straightforward. 

Thank you!

-- 
Eugene N Dzhurinsky


pgpPArUDUlH24.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread Eugene Dzhurinsky
On Wed, May 05, 2010 at 02:54:27PM -0700, Ryan Ingram wrote:
> ErrorT is just a newtype wrapper, changing the order/application of
> the type variables.
> 
> newtype ErrorT e m a = ErrorT (m (Either e a))
> runErrorT (ErrorT action) = action
> 
> This gives the bijection:
> 
> ErrorT :: m (Either e a) -> ErrorT e m a
> runErrorT :: ErrorT e m a -> m (Either e a)

That syntax is not clear for me - so ErrorT is some sort of function
(calculation), which takes a monad with type (Either e a) and produces type
ErrorT e m a ? Basically, i don't understand what does "ErrorT ::" means - it
should name the function - but it starts with capital letter?

I feel like I missed something when learning type system and syntax of Haskell
:(

-- 
Eugene N Dzhurinsky


pgp58bWRrrwfP.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-02 Thread Eugene Dzhurinsky
On Sat, May 01, 2010 at 02:42:26PM -0700, Ryan Ingram wrote:
> Check out ErrorT in Control.Monad.Error
> 
> > :t ErrorT
> ErrorT :: m (Either e a) -> ErrorT e m a

At this point I am lost. I'm not sure that I do understand this type
transformation correctly. So we have some sort of monadic type m, error type e
and resut of type a. If m = IO, e - Error, a - String, than

ErrorT :: IO (Either Error String) -> ErrorT Error IO String

I can think that can be written as 

ErrorT :: IO (Either Error String) -> ErrorT Error (IO String)

Am I correct?

> So, if you can make your Error type an instance of this class, you can do 
> this:
> runCalc = runErrorT (ErrorT (func1 p) >>= ErrorT . func2)

Sorry, I don't understand how does it work. Can you please explain the type
transformations involved here?

Thank you in advance!

-- 
Eugene N Dzhurinsky


pgpogj49pOZL5.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] listing mountpoints and getting their properties in Haskell

2010-02-27 Thread Eugene Dzhurinsky
Hello!

I need to list all currently mounted filesystems and get some stats like
total space, free space, mount point and physical device.

Is there any library capable of obtaining such information from OS itself?
Parsing output of 'df' is locale-dependent and error-prone (because of locale
settings, output settings etc).

Thank you in advance.

-- 
Eugene N Dzhurinsky


pgp87im5z8ywi.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] CURL and threads

2010-02-17 Thread Eugene Dzhurinsky
Hello, all!

Can somebody please explain, what is the best way of using CURL with several
threads? I wrote simple client, which tries to authenticate against HTTP
server. With running this client, it starts to eat memory insanely (and I know
this code is far, far away of even being close to be called good one )

=
module NTLMTest where

import System.IO
import Network.Curl
import Control.Concurrent
import Control.Concurrent.Chan

type ResponseState = Either Bool String

type RespChannel = Chan ResponseState

delay = 500 * 1000

isResponseOk :: String -> CurlResponse -> ResponseState
isResponseOk username response = case respCurlCode response of
CurlOK  -> Left True
_   -> Right $ username ++ " => " ++ 
respStatusLine response ++ " :: " ++ (show . respStatus $ response)


checkAuthResponse :: RespChannel -> String -> String -> String -> IO ()
checkAuthResponse state user passwd url = do 
response <- curlGetResponse_ url 
[CurlHttpAuth [HttpAuthAny], CurlUserPwd $ user ++ ":" ++ passwd]
writeChan state $ isResponseOk user response
threadDelay $ delay

runHTTPThread :: RespChannel -> (String,String) -> IO ()
runHTTPThread state (user,passwd) = checkAuthResponse state user passwd url


url = "http://localhost:8082/";
credentials = map (\i -> ("user" ++ show i,"123456")) [1..21]

main = withCurlDo $ do
chan <- newChan :: IO (RespChannel)
mapM_ ( \cred -> forkIO $ runHTTPThread chan cred ) credentials
dumpChannel chan $ length credentials
main
where
dumpChannel :: RespChannel -> Int -> IO ()
dumpChannel _chan n | n == 0= return ()
| otherwise = dostate <- readChan _chan
case state of
(Left _) -> return () 
--putStrLn "OK"
(Right err) -> putStrLn err
dumpChannel _chan $ n-1

=

If I get rid of forkIO - it stops at 40-50 megabytes and don't raise memory
usage anymore.

Also, I noticed that (either because of buffering, or may be something else)
results are appearing on console much slower than if I simply use "wget" with
looping in shell script. JMeter also reports awesome speed, so server can
authenticate tens of concurrent users per second (thus it's not server or
connection bandwidth issue).

Hopefully, someone could help me in overcoming my ignorance :)

-- 
Eugene N Dzhurinsky


pgpZlHfRhTKWZ.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe