[Haskell-cafe] Yet another monad transformer or silly usage of Either?

2010-07-25 Thread Eugeny N Dzhurinsky
Hello, everybody!

I am trying to develop some sort of library, which supposed to sign into a WEB
service, then perform some requests with it.

Initially I designed methods in the following way

data DServError = InvalidCredentials | InvalidRequest | ...

newtype Result a = Result { getOpResult :: Either DServError a }

data DSession = Session { ... }

data DLoginResponse = LoginResponse { currentSession :: DSession, ... }

login :: String - String - IO ( Result LoginResponse )

servRequest1 :: DSession - ParamType1 - ParamType2 - ... - IO ( Result 
DServResponse )


Now I want to be able of doing something like

authenticatedReq = do
loginResponse - login username password
let session = currentSession loginResponse
servRequest1 session ... ... ...
servRequest2 session ... ... ...
...

so if login succeeds - I will be able to extract Right data from the Either 
response ( with 
explicit or implicit usage of getOpResult), if any of operations within do
block will fail with DServError - then an error should be reported.

I think the solution for this may be using Control.Exception and it's
try/catch? Or may be there's some trick available for Either?

I looked at EitherT, and it seems that I have to wrap every invocation into
EitherT and then chain them with /=

-- 
Eugene Dzhurinsky


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


Re: [Haskell-cafe] MultiParamClasses question

2010-05-26 Thread Eugeny N Dzhurinsky
On Tue, May 25, 2010 at 10:46:47PM +0100, Stephen Tetley wrote:
 Hi Eugene
 
 You can store different things in a Map by collecting them with a
 simple 'sum' type:

Hello, Stephen!

The records to be stored into a Map are not related to each other. So wrapping
them into another type is not very smart solution in my case :)

The problem is really with the fact that records, created from such lines

user_1_name=user
group_1_name=group

do refer to the same key 1. But you gave me idea that I can use single map -
but as a key use something like 

type KeyT k i = (k,i)

where k is type of record (Group or User), and i is index, usually Int.

This way I will try to redesign my existing code.

Thank you for the idea :)

-- 
Eugene Dzhurinsky


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


[Haskell-cafe] MultiParamClasses question

2010-05-25 Thread Eugeny N Dzhurinsky
Hello, all!

I'm trying to create set of polymorphic functions for working with custom
containers. I decided to try out typeclass and define generic function, which
uses the methods from the typeclass. The quick and naive solution is listed
below:


{-# OPTIONS_GHC -XMultiParamTypeClasses -XTypeSynonymInstances #-}
import Data.List as L

class Storage k t a b where
stExists :: k - t - b - Bool
stAdjust :: k - t - ( a - a ) - b - b
stInsert :: k - t - a - b - b
stList :: b - [a]

type IxPair k t = ( k, t, String, String)

data Pair = Pair { name, value :: String }

type IxPairParser k t = Pair - Maybe (IxPair k t)

type RecordUpdateF r = String - String - r - r

convertPairsToRecords :: (Storage k t a b) = b - RecordUpdateF a - 
IxPairParser k t - a - [Pair] - [a]
convertPairsToRecords storg updateRecF parsePairF initRec = stList . 
processWithPairs
where
processWithPairs = foldl' ( (. parsePairF) . updateStorage ) storg
updateStorage st Nothing = st
updateStorage st ( Just (idx, sType, name, value) ) | stExists idx 
sType st = stAdjust idx sType (updateRecF name value) st
| otherwise = 
stInsert idx sType (updateRecF name value initRec) st


so I want to provide methods for checking if a record with given key exists,
update a record, insert a record and get list of records. Sounds similar as
for Map, but I want also to be able to operate on map of maps, or lists, or
whatever.

I don't really see any problem with the code above, however GHC 6.12.1 does
think that I am doing something weird. And it gives me this error log:


test.hs:19:60:
Could not deduce (Storage k t a1 b)
  from the context (Storage k1 t1 a1 b)
  arising from a use of `stList' at test.hs:19:60-65
Possible fix:
  add (Storage k t a1 b) to the context of
the type signature for `convertPairsToRecords'
In the first argument of `(.)', namely `stList'
In the expression: stList . processWithPairs
In the definition of `convertPairsToRecords':
convertPairsToRecords storg updateRecF parsePairF initRec
= stList . processWithPairs
where
processWithPairs = foldl' ((. parsePairF) . 
updateStorage) storg
updateStorage st Nothing = st
updateStorage st (Just (idx, sType, name, 
value))
| stExists idx sType st
= stAdjust idx sType 
(updateRecF name value) st
| otherwise
= stInsert
idx sType (updateRecF 
name value initRec) st

test.hs:21:53:
Could not deduce (Storage k1 t1 a b)
  from the context (Storage k1 t1 a1 b)
  arising from a use of `updateStorage' at test.hs:21:53-65
Possible fix:
  add (Storage k1 t1 a b) to the context of
the type signature for `convertPairsToRecords'
In the second argument of `(.)', namely `updateStorage'
In the first argument of `foldl'', namely
`((. parsePairF) . updateStorage)'
In the expression: foldl' ((. parsePairF) . updateStorage) storg


Can somebody please advice, what am I doing in wrong way?

Thank you all in advance!

-- 
Eugene Dzhurinsky


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


Re: [Haskell-cafe] MultiParamClasses question

2010-05-25 Thread Eugeny N Dzhurinsky
On Tue, May 25, 2010 at 07:59:24PM +0100, Stephen Tetley wrote:
 Hi Eugeny
 
 Its not that GHC thinks you're doing something weird, but that there
 is no relation between the type parameters in the Storage class. You
 could use either functional dependencies or type families to introduce
 a relation / relations, but personally I would look at doing something
 simpler - for instance why do you need a map type that is polymorphic
 on shape?

Currently I am creating set of objects from name-value pairs, and I decided to
use Map for keeping relations between an object id and record with the id. So
I will be able to parse the parameter like

param_1_propname=value

then take the object with ID=1 from Map, and update it's property 'propname'
with value, and put it back into the Map.

But I faced several cases when a set of name-value pairs describes  2 or even
more kinds of objects. And I want to be able to parse them all at one pass, so
I would need 2 or more maps. And I simply tried to generalize the solution.

Probably I should think in different way. May be a chain of Writer monads or
something similar.

-- 
Eugene Dzhurinsky


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


[Haskell-cafe] Calculating a value as side effect of converting list of strings into list of records.

2010-05-24 Thread Eugeny N Dzhurinsky
Hello, All!

I need some help to solve the following task:

=
import Data.Map as M 
import Data.List as L

data Pair = Pair { name, value :: String }

type IxPair = (Int, String, String)

type IxPairParser = Pair - Maybe IxPair

type RecordUpdateF r = String - String - r - r

convertPairsToRecords :: RecordUpdateF r - IxPairParser - r - [Pair] - [r]
convertPairsToRecords updateRecF parsePairF initRec pairs = M.elems $ L.foldl' 
processWithPairs initMap pairs
where
initMap = M.empty
processWithPairs resMap = maybe resMap (updateMapF resMap) . parsePairF
updateMapF res (idx, key, value) | idx `M.member` res = M.adjust 
(updateRecF key value) idx res
 | otherwise = M.insert idx (updateRecF 
key value initRec) res
=

In short, input looks like name=value pairs:
pair_1_username=user
pair_1_password=pass
pair_1_fullname=vasya poopking

The parser IxPairParser takes the pair of name=value, and extracts ordering
number of the current pair, making it a triple like below

(1, username, user)

then convertPairsToRecords takes the triple and performs lookup in the Map
for a record with given ID. Then it updates the record and places it back into
the map. If no record is found - then new one is created, updated and inserted
into the Map.

Now, I've got the case when input contains pairs like below

pair_1_lastlogin=2010-05-24 12:23
...
pair_2_lastlogin=2009-12-20 10:30
...
pair_2_lastlogin=2010-04-06 18:20

At this point I need to update the record and keep the latest date somewhere,
so it will be possible to extract the latest login date among all such pairs.

I can think about post-processing list [r], extract lastlogin field and simply
use fold to get the oldest one. But I'd like to calculate this information
during parsing of the input. And I am not allowed to change the interface of
convertPairsToRecords.

Can somebody please suggest how to solve the task? Probably with Writer monad,
or may be State?

Thank you in advance!

-- 
Eugene Dzhurinsky


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


Re: [Haskell-cafe] Data creation pattern?

2010-05-13 Thread Eugeny N Dzhurinsky
On Thu, May 13, 2010 at 04:43:26PM +0100, Stephen Tetley wrote:
 Hi Eugene
 
 You don't need to supply all the arguments to a constructor at once:
 
 makeWithOne :: String - (String - String - Object)
 makeWithOne s1 = \s2 s3 - Object s1 s2 s3
 
 -- or even:
 -- makeWithOne s1 = Object s1
 
 This builds a higher-order function that can be applied later to two
 Strings to finally make the Object.

Hello, Stephen!

Well, that's true, but I don't really know the order of incoming data. So for
constructor MyObject { prop1, prop2, prop3 :: String } there can be the cases
of order

prop1
prop2
prop3

prop3
prop2
prop1

prop1
prop3
prop2

...

so I may need to initialize prop1, then prop3, and finally prop2 to make
instance of MyObject. And similarly for another cases.

I don't see any easy solution for now except sort name-value pairs in some
pre-defined order, and then use something like

 props :: [(String,String)]
 result = MyObject (props' !! 0) (props' !! 1) (props' !! 2)
 where
 props' = map snd props

which looks ugly and involves some additional calculations for sorting.

-- 
Eugene Dzhurinsky


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


Re: [Haskell-cafe] Data creation pattern?

2010-05-13 Thread Eugeny N Dzhurinsky
On Thu, May 13, 2010 at 07:15:22PM +0100, Stephen Tetley wrote:
 On 13 May 2010 19:14, Stephen Tetley stephen.tet...@gmail.com wrote:
  Hi Eugene
 
 Hi Eugeny
 Whoops - apologies for the the name change...

In fact it doesn't make any difference, so both these names are equal :)

-- 
Eugene Dzhurinsky


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


Re: [Haskell-cafe] Data creation pattern?

2010-05-13 Thread Eugeny N Dzhurinsky
On Thu, May 13, 2010 at 07:14:25PM +0100, Stephen Tetley wrote:
 Hi Eugene
 
 Is something like this close to what you want:

Not really. First of all, there're many properties, not 3. So it may end up
with plenty of support (boilerplate) code.

Also, names of these parameters are not sortable. Of course I could make these
names as another data type with deriving from Eq/Ord - but that increase
complexity as well.

Original idea was

1) create Array
2) if line param_N_name=value appear, then 
2.1) try to take object N from array
2.2) if no object exists - then create one
2.3) set the property name to value
2.4) put resulting object back into array
3) take next line and go to 2

so if it is possible to have partially initialized objects in Haskell, then
this approach should work. If now - well, then replace creation of object with
adding name/value pair to an array. And then create objects from those arrays.

-- 
Eugene Dzhurinsky


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


Re: [Haskell-cafe] Data creation pattern?

2010-05-13 Thread Eugeny N Dzhurinsky
On Thu, May 13, 2010 at 09:03:48PM +0200, Daniel Fischer wrote:
  so if it is possible to have partially initialized objects in Haskell,
 If the fields aren't strict, there's no problem having
 ...

Wow! Thank you, that's it :)

-- 
Eugene Dzhurinsky


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


[Haskell-cafe] posting UTF8 data with Curl library

2010-05-05 Thread Eugeny N Dzhurinsky
Hello!

I need to submit data to HTTP server using UTF8 encoding. I found out that
libcurl for haskell can work with Data.ByteString - but it seems not able to
work with Data.ByteString.UTF8.

Can you please advice, how do I convert Data.ByteString.UTF8 into
Data.ByteString and visa versa?

Thank you in advance!

-- 
Eugene Dzhurinsky


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


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

2010-05-01 Thread Eugeny N Dzhurinsky
Hello!

I have some sort of strange question:

assume that there are 2 functions

func1 :: Int - IO (Either Error String)
func2 :: String - IO (Either Error [String])

in case if there will be no IO involved, I could use
Control.Monad.Either and write something like

runCalc :: Int - IO (Either Error [String])
runCalc param = func1 param = func2

but with that IO stuff I can't simply do in this way. Can somebody please
suggest, how to combine IO and Either monads, if that's even possible?

Thank you in advance!

-- 
Eugene Dzhurinsky


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


Re: [Haskell-cafe] CURL and threads

2010-02-17 Thread Eugeny N Dzhurinsky
On Wed, Feb 17, 2010 at 07:34:07PM +0200, Eugene Dzhurinsky wrote:
 Hopefully, someone could help me in overcoming my ignorance :)

I realized that I can share the same Chan instance over all invocations in
main, and wrap internal function into withCurlDo to ensure only one IO action
gets executed with this library. Finally I've come with the following code,
which however still has some memory leaks. May be someone will get an idea
what's wrong below?

=

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 = do
chan - newChan :: IO (RespChannel)
withCurlDo $ invokeThreads chan
where 
invokeThreads chan = do
mapM_ ( \cred - forkIO $ runHTTPThread chan cred ) credentials
dumpChannel chan $ length credentials
invokeThreads chan
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


=

Thank you in advance!

-- 
Eugene Dzhurinsky


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