
Hello everyone! I am trying to find out the execution time of mergesort for a list size of 1 million integers. I have done the same in Erlang as well and the execution time in Erlang was around 0.93 seconds. I have implemented the program in almost the same way in Haskell as well but for some reason the Haskell implementation is taking around 12 seconds which doesn't seem right. Here is the implementation in Haskell: *{-# LANGUAGE OverloadedStrings #-}* *{-# LANGUAGE BangPatterns #-}* *import Control.Exception* *import Formatting* *import Formatting.Clock* *import System.Clock* *import Control.DeepSeq* *mergesort [] = []* *mergesort [x] = [x]* *mergesort xs = let (lhalf, rhalf) = splitAt (length xs `div` 2) xs* * in merge' (mergesort lhalf) (mergesort rhalf)* *merge' lhalf rhalf = merge lhalf rhalf []* *merge [] [] acc = reverse acc* *merge [] y acc = reverse acc ++ y* *merge x [] acc = reverse acc ++ x* *merge (l:ls) (r:rs) acc* * | l < r = merge ls (r:rs) (l:acc)* * | otherwise = merge rs (l:ls) (r:acc)* *toList :: String -> [Integer]* *toList input = read ("[" ++ input ++ "]")* *main = do* * file <- getLine* * contents <- readFile file* * let !unsortedlist = (toList contents)* * start <- getTime Monotonic* * evaluate(force (mergesort unsortedlist))* * end <- getTime Monotonic* * fprint (timeSpecs % "\n") start end* What am I doing wrong?

I haven't looked at the code much yet
But might want to consider strictness 😎
--
Sent from an expensive device which will be obsolete in a few months
Casey
On Thu, Jul 5, 2018, 7:01 PM Awsaf Rahman,
Hello everyone!
I am trying to find out the execution time of mergesort for a list size of 1 million integers. I have done the same in Erlang as well and the execution time in Erlang was around 0.93 seconds. I have implemented the program in almost the same way in Haskell as well but for some reason the Haskell implementation is taking around 12 seconds which doesn't seem right.
Here is the implementation in Haskell:
*{-# LANGUAGE OverloadedStrings #-}* *{-# LANGUAGE BangPatterns #-}* *import Control.Exception* *import Formatting* *import Formatting.Clock* *import System.Clock* *import Control.DeepSeq*
*mergesort [] = []* *mergesort [x] = [x]* *mergesort xs = let (lhalf, rhalf) = splitAt (length xs `div` 2) xs* * in merge' (mergesort lhalf) (mergesort rhalf)*
*merge' lhalf rhalf = merge lhalf rhalf []*
*merge [] [] acc = reverse acc* *merge [] y acc = reverse acc ++ y* *merge x [] acc = reverse acc ++ x*
*merge (l:ls) (r:rs) acc* * | l < r = merge ls (r:rs) (l:acc)* * | otherwise = merge rs (l:ls) (r:acc)*
*toList :: String -> [Integer]* *toList input = read ("[" ++ input ++ "]")*
*main = do* * file <- getLine* * contents <- readFile file* * let !unsortedlist = (toList contents)* * start <- getTime Monotonic* * evaluate(force (mergesort unsortedlist))* * end <- getTime Monotonic* * fprint (timeSpecs % "\n") start end*
What am I doing wrong? _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

I did consider strictness and that is why the execution time has come down
from 16 seconds to 12 seconds! But I can't seem to find the issue anymore!
On Fri, Jul 6, 2018 at 4:06 AM, KC
I haven't looked at the code much yet But might want to consider strictness 😎
-- Sent from an expensive device which will be obsolete in a few months Casey
On Thu, Jul 5, 2018, 7:01 PM Awsaf Rahman,
wrote: Hello everyone!
I am trying to find out the execution time of mergesort for a list size of 1 million integers. I have done the same in Erlang as well and the execution time in Erlang was around 0.93 seconds. I have implemented the program in almost the same way in Haskell as well but for some reason the Haskell implementation is taking around 12 seconds which doesn't seem right.
Here is the implementation in Haskell:
*{-# LANGUAGE OverloadedStrings #-}* *{-# LANGUAGE BangPatterns #-}* *import Control.Exception* *import Formatting* *import Formatting.Clock* *import System.Clock* *import Control.DeepSeq*
*mergesort [] = []* *mergesort [x] = [x]* *mergesort xs = let (lhalf, rhalf) = splitAt (length xs `div` 2) xs* * in merge' (mergesort lhalf) (mergesort rhalf)*
*merge' lhalf rhalf = merge lhalf rhalf []*
*merge [] [] acc = reverse acc* *merge [] y acc = reverse acc ++ y* *merge x [] acc = reverse acc ++ x*
*merge (l:ls) (r:rs) acc* * | l < r = merge ls (r:rs) (l:acc)* * | otherwise = merge rs (l:ls) (r:acc)*
*toList :: String -> [Integer]* *toList input = read ("[" ++ input ++ "]")*
*main = do* * file <- getLine* * contents <- readFile file* * let !unsortedlist = (toList contents)* * start <- getTime Monotonic* * evaluate(force (mergesort unsortedlist))* * end <- getTime Monotonic* * fprint (timeSpecs % "\n") start end*
What am I doing wrong? _______________________________________________ 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

Appending to lists is slow
--
Sent from an expensive device which will be obsolete in a few months
Casey
On Thu, Jul 5, 2018, 7:14 PM Awsaf Rahman,
I did consider strictness and that is why the execution time has come down from 16 seconds to 12 seconds! But I can't seem to find the issue anymore!
On Fri, Jul 6, 2018 at 4:06 AM, KC
wrote: I haven't looked at the code much yet But might want to consider strictness 😎
-- Sent from an expensive device which will be obsolete in a few months Casey
On Thu, Jul 5, 2018, 7:01 PM Awsaf Rahman,
wrote: Hello everyone!
I am trying to find out the execution time of mergesort for a list size of 1 million integers. I have done the same in Erlang as well and the execution time in Erlang was around 0.93 seconds. I have implemented the program in almost the same way in Haskell as well but for some reason the Haskell implementation is taking around 12 seconds which doesn't seem right.
Here is the implementation in Haskell:
*{-# LANGUAGE OverloadedStrings #-}* *{-# LANGUAGE BangPatterns #-}* *import Control.Exception* *import Formatting* *import Formatting.Clock* *import System.Clock* *import Control.DeepSeq*
*mergesort [] = []* *mergesort [x] = [x]* *mergesort xs = let (lhalf, rhalf) = splitAt (length xs `div` 2) xs* * in merge' (mergesort lhalf) (mergesort rhalf)*
*merge' lhalf rhalf = merge lhalf rhalf []*
*merge [] [] acc = reverse acc* *merge [] y acc = reverse acc ++ y* *merge x [] acc = reverse acc ++ x*
*merge (l:ls) (r:rs) acc* * | l < r = merge ls (r:rs) (l:acc)* * | otherwise = merge rs (l:ls) (r:acc)*
*toList :: String -> [Integer]* *toList input = read ("[" ++ input ++ "]")*
*main = do* * file <- getLine* * contents <- readFile file* * let !unsortedlist = (toList contents)* * start <- getTime Monotonic* * evaluate(force (mergesort unsortedlist))* * end <- getTime Monotonic* * fprint (timeSpecs % "\n") start end*
What am I doing wrong? _______________________________________________ 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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (2)
-
Awsaf Rahman
-
KC