Send Beginners mailing list submissions to
[email protected]
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
[email protected]
You can reach the person managing the list at
[email protected]
When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."
Today's Topics:
1. (Basic?) IO question (Guillaume Basse)
2. Re: (Basic?) IO question (David McBride)
3. Re: (Basic?) IO question (Isaac Dupree)
4. Error in converting List of Lists into PArray ( Parray a )
(mukesh tiwari)
5. Re: questions about product types (AntC)
6. Re: Is there an "unscan" function? (AntC)
----------------------------------------------------------------------
Message: 1
Date: Wed, 18 Jan 2012 13:35:34 -0500
From: Guillaume Basse <[email protected]>
Subject: [Haskell-beginners] (Basic?) IO question
To: [email protected]
Message-ID:
<CA+cj2zEqZJBGn3VwS230h1LVrwpYgz=5ys_y1-xclpn0hvj...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"
Hello,
So I've been trying to print some information in a file. I have two
versions of the same function: one of them doesn't work and I don't
understand why.
Here are the functions:
# # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
-- This one works as intended when called from ghci
renderTrackInfosToFile :: FilePath -> String -> IO [TrackInfos] -> IO ()
renderTrackInfosToFile filename sep ls = do nls <- ls
writeFile
filename (intercalate "\n" $ map (renderTrackInfo sep) nls)
return ()
-- This one does nothing when called from ghci
renderTrackInfosToFile2 :: FilePath -> String -> [TrackInfos] -> IO ()
renderTrackInfosToFile2 filename sep ls = writeFile filename (intercalate
"\n" $ map (renderTrackInfo sep) ls)
renderTrackInfo :: String -> TrackInfos -> String
# # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
Both functions load in ghci, and the following commands are issued:
> -- c :: IO [TrackInfos]
> liftM (renderTrackInfosToFile2 "blabla.txt" "|") c -- this command seems
to do absolutely nothing
> renderTrackInfosToFile "blabla.txt" "|" c -- this one works as intended
# # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
And this is not the first time I have this sort of problem using liftM. I
now that I'm missing something important here,
can anyone explain me my mistake?
Much thanks,
Guillaume Basse
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://www.haskell.org/pipermail/beginners/attachments/20120118/c7ff4d17/attachment-0001.htm>
------------------------------
Message: 2
Date: Wed, 18 Jan 2012 14:38:07 -0500
From: David McBride <[email protected]>
Subject: Re: [Haskell-beginners] (Basic?) IO question
To: Guillaume Basse <[email protected]>
Cc: [email protected]
Message-ID:
<CAN+Tr431C4=kzofdmxq9aeu2egefgwsrapubz6qwz3zw523...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1
When you go with something like:
putStrLn "asdf" :: IO ()
but when you go:
liftM putStrLn (return "asdf") :: Monad m => m (IO ())
These are totally different. The first one is an IO action. The
second one is a monad that returns an IO action. When run in ghci,
ghci decides that the outer monad must be IO as well, so the type
becomes IO (IO ()). When you run that action, all you get is an IO ()
which has not been run and as such will not execute or print.
I'm not sure what you are attempting to get with liftM, but just make
sure to check out the final types of your statements with the :t
command in ghci and you should be able to figure it out.
On Wed, Jan 18, 2012 at 1:35 PM, Guillaume Basse <[email protected]> wrote:
> Hello,
>
> So I've been trying to print some information in a file. I have two versions
> of the same function: one of them doesn't work and I don't understand why.
> Here are the functions:
>
> # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
>
> -- This one works as intended when called from ghci
> renderTrackInfosToFile :: FilePath -> String -> IO [TrackInfos] -> IO ()
> renderTrackInfosToFile filename sep ls = do nls <- ls
> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? writeFile
> filename (intercalate "\n" $ map (renderTrackInfo sep) nls)
> ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? ? return ()
>
> -- This one does nothing when called from ghci
> renderTrackInfosToFile2 :: FilePath -> String -> [TrackInfos] -> IO ()
> renderTrackInfosToFile2 filename sep ls = writeFile filename (intercalate
> "\n" $ map (renderTrackInfo sep) ls)
>
>
> renderTrackInfo :: String -> TrackInfos -> String
>
> # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
>
> Both functions load in ghci, and the following commands are issued:
>
>> -- c :: IO [TrackInfos]
>> liftM (renderTrackInfosToFile2 "blabla.txt" "|") ?c -- this command seems
>> to do absolutely nothing
>>?renderTrackInfosToFile "blabla.txt" "|" ?c -- this one works as intended
>
> # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
>
> And this is not the first time I have this sort of problem using liftM. I
> now that I'm missing something important here,
> can anyone explain me my mistake?
>
> Much thanks,
>
> Guillaume Basse
>
>
>
>
>
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
------------------------------
Message: 3
Date: Wed, 18 Jan 2012 14:49:23 -0500
From: Isaac Dupree <[email protected]>
Subject: Re: [Haskell-beginners] (Basic?) IO question
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
The one that's doing nothing is returning type
IO (IO ()), which executes the outer IO (which is "c") and returns the
inner IO (which is the contents of renderTrackInfosToFile2).
You want a different combinator. Try playing with "join" and/or ">>="
(pronounced "bind") and you should be able to figure out ways to do it.
Try looking at the types of liftM and liftM2 and see if you can figure
out why they don't work. In ghci, try :t expression (:type expression)
to find the type of any expression you input. The Control.Monad
documentation has types of lots of convenient operations (look at the
synopsis which has all their types together) (all of these operations
are written using the basic operations of Monads.)
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html
By the way, 'liftM' is equivalent to 'fmap', if you're ever wondering.
-Isaac
On 01/18/2012 01:35 PM, Guillaume Basse wrote:
> Hello,
>
> So I've been trying to print some information in a file. I have two
> versions of the same function: one of them doesn't work and I don't
> understand why.
> Here are the functions:
>
> # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
>
> -- This one works as intended when called from ghci
> renderTrackInfosToFile :: FilePath -> String -> IO [TrackInfos] -> IO ()
> renderTrackInfosToFile filename sep ls = do nls<- ls
> writeFile
> filename (intercalate "\n" $ map (renderTrackInfo sep) nls)
> return ()
>
> -- This one does nothing when called from ghci
> renderTrackInfosToFile2 :: FilePath -> String -> [TrackInfos] -> IO ()
> renderTrackInfosToFile2 filename sep ls = writeFile filename (intercalate
> "\n" $ map (renderTrackInfo sep) ls)
>
>
> renderTrackInfo :: String -> TrackInfos -> String
>
> # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
>
> Both functions load in ghci, and the following commands are issued:
>
>> -- c :: IO [TrackInfos]
>> liftM (renderTrackInfosToFile2 "blabla.txt" "|") c -- this command seems
> to do absolutely nothing
>> renderTrackInfosToFile "blabla.txt" "|" c -- this one works as intended
>
> # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
>
> And this is not the first time I have this sort of problem using liftM. I
> now that I'm missing something important here,
> can anyone explain me my mistake?
>
> Much thanks,
>
> Guillaume Basse
>
>
>
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
------------------------------
Message: 4
Date: Thu, 19 Jan 2012 01:26:30 +0530
From: mukesh tiwari <[email protected]>
Subject: [Haskell-beginners] Error in converting List of Lists into
PArray ( Parray a )
To: [email protected]
Message-ID:
<CAFHZvE8qBALb+7Z+dSfcV1HYESXc1Y5dNTjsCjLv+zcCqWO=c...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"
Hello all
I am trying to convert List of Lists ( [[(Int , Double )]] ) into PArray (
PArray ( Int , Double )) but getting run time error. This code works fine
and print list of PArray ( Int , Double ) but when i put print $ P.fromList
( map P.fromList c ) then i am getting runtime error. It says "Main:
Data/Array/Parallel/PArray/PDataInstances.hs:337:10-30: No instance nor
default method for class operation
Data.Array.Parallel.PArray.PData.fromListPR". Could some one please tell me
how to resolve this issue.
Thank you
--import ParallelMat
import Data.List
import System.Environment
import Data.Array.Parallel
import qualified Data.Array.Parallel.PArray as P
processMatrix :: [ [ Double ] ] -> [ [ Double ] ] -> [ ( [ ( Int , Double )
] , [ ( Int , Double ) ]) ]
processMatrix [] [] = []
processMatrix ( x : xs ) ( y : ys )
| ( all ( == 0 ) x ) Prelude.|| ( all ( == 0 ) y ) = processMatrix xs ys
| otherwise = ( filter ( \( x , y ) -> y /= 0 ) . zip [ 1..] $ x ,filter
( \( x , y ) -> y /= 0 ) . zip [1..] $ y ) : processMatrix xs ys
main = do
[ first , second ] <- getArgs
a <- readFile first
b <- readFile second
let a' = transpose . tail . map ( map ( read :: String -> Double ) .
words ) . lines $ a
b' = tail . map ( map ( read :: String -> Double ) . words ) .
lines $ b
( c , d ) = unzip $ processMatrix a' b'
print $ ( map P.fromList c )
--print d
Macintosh-0026bb610428:Haskell mukesh$ ghc --make -Odph -fdph-par Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )
Linking Main ...
Macintosh-0026bb610428:Haskell mukesh$ ./Main A.in A.in
[fromList<PArray> [(1,1.0),(6,1.0)],fromList<PArray>
[(4,11.0),(9,11.0)],fromList<PArray> [(1,4.0),(4,2.0),(6,4.0),(9,2.0)]]
Putting print $ P.fromList ( map P.fromList c )
Macintosh-0026bb610428:Haskell mukesh$ ghc --make -Odph -fdph-par Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )
Linking Main ...
Macintosh-0026bb610428:Haskell mukesh$ ./Main A.in A.in
Main: Data/Array/Parallel/PArray/PDataInstances.hs:337:10-30: No instance
nor default method for class operation
Data.Array.Parallel.PArray.PData.fromListPR
Input file A.in
10 10
1 2 3 0 0 0 0 0 0 4
0 0 0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0 0 0
0 0 0 0 0 0 1 2 11 2
0 1 2 0 0 0 0 0 0 0
1 2 3 0 0 0 0 0 0 4
0 0 0 0 0 0 0 0 0 0
0 0 0 0 0 0 0 0 0 0
0 0 0 0 0 0 1 2 11 2
0 1 2 0 0 0 0 0 0 0
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
<http://www.haskell.org/pipermail/beginners/attachments/20120119/f5ac0182/attachment-0001.htm>
------------------------------
Message: 5
Date: Wed, 18 Jan 2012 22:09:40 +0000 (UTC)
From: AntC <[email protected]>
Subject: Re: [Haskell-beginners] questions about product types
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
Tom Doris <tomdoris <at> gmail.com> writes:
> 3) In type theory, are product types consisting of distinct member types
considered special in any way? i.e. does the concept have a name and what
special properties do they have?
>
I don't know about type theory, but I've seen them called 'Type Indexed
Products'. See the HList Paper [1] section 7, which refers to [31].
I've found TIP's very successful in practice. They've gotten more rugged
through the gradual innovations in type inference that have been introduced
into GHC. (Especially the type equality constraint (~), which improves on
HList's TypeCast.) But the 'groundness issues' in HList section 9 still apply.
Using TIP's relies on overlapping instances (but _not_ necessarily Functional
Dependencies), so it's still a 'poor cousin' and (it seems) not to be
mentioned in polite company.
[1] Strongly Typed Heterogenous Collections, August 2004,
Kiselyov/Laemmel/Schupke.
[31] Type-indexed Rows, POPL 2001, Shields/Meijer
------------------------------
Message: 6
Date: Thu, 19 Jan 2012 02:46:42 +0000 (UTC)
From: AntC <[email protected]>
Subject: Re: [Haskell-beginners] Is there an "unscan" function?
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
Christian Maeder <Christian.Maeder <at> dfki.de> writes:
>
> Am 13.01.2012 19:19, schrieb Stephen Tetley:
> > unscan :: (a -> a -> b) -> [a] -> [b]
> > unscan f (a:b:bs) = f a b : unscan f (b:bs)
> > unscan _ _ = []
> >
>
> "putting the second element back" can be avoided by @-Patterns!
>
> unscan f (a : bs@(b : _)) = f a b : unscan bs
>
And if Stephen or Christian had gone that little extra step to actually run
their code they would find:
unscan (flip (-)) [1,3,6,10] ===> [2,3,4]
This is not what the OP asked for. (Because [1,3,6,10] is the result of scanl1
(+) [1,2,3,4]. Where did the 1 go?)
The reason? The suffix-1 family of list combinators expect their list to
contain at least one element, which they treat specially. So to unscanl1 we
need to put the 'zeroeth' element back where scanl1 takes it from -- that is,
on the front of the result.
To follow the style in the Prelude:
unscanl1 :: (a -> a -> a) -> [a] -> [a]
unscanl1 _ [] = [] -- error-trap for empty lists
unscanl1 f (x0: xs) = x0: unscanl f x0 xs -- zeroeth element on the front
unscanl :: (a -> a -> b) -> a -> [a] -> [b]
unscanl f x0 (x:xs) = f x0 x : unscanl f x xs
unscanl _ _ _ = []
Then:
unscanl1 (flip (-)) [1,3,6,10] ===> [1,2,3,4]
(I think that style of definition is the clearest to understand. You could
possibly avoid repeating 'x' using @-patterns or a helper function (go) or a
sub-case (per the Prelude), but I doubt it would make much difference to
efficiency.)
AntC
------------------------------
_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 43, Issue 23
*****************************************