From fr.teodoro at gmail.com Tue Aug 4 14:07:31 2015 From: fr.teodoro at gmail.com (=?UTF-8?Q?F=C3=A1bio_Roberto_Teodoro?=) Date: Tue, 4 Aug 2015 11:07:31 -0300 Subject: [Haskell-beginners] latest Haskell Platform build fails In-Reply-To: References: Message-ID: ---------- Mensagem encaminhada ---------- De: "F?bio Roberto Teodoro" Data: 04/08/2015 11:04 Assunto: latest Haskell Platform build fails Para: One way I found to get rid of the "package(s) with this id already exist" problem was by doing a "ghc-pkg --force unregister " -------------- next part -------------- An HTML attachment was scrubbed... URL: From twashing at gmail.com Wed Aug 5 03:13:25 2015 From: twashing at gmail.com (Timothy Washington) Date: Tue, 4 Aug 2015 20:13:25 -0700 Subject: [Haskell-beginners] Haskell equivalent to Clojure's partition fn In-Reply-To: References: Message-ID: Hey Jacek, Thanks very much for this. I took a look around, and ended up using the *chop* function from that package. So there looks to be a lot of goodies in that package. Cheers Tim On Sun, Jul 26, 2015 at 2:01 PM, Jacek Dudek wrote: > Hi Timothy, > > You might want to check out the split package. > Here's the link: http://hackage.haskell.org/package/split > > On 7/25/15, Timothy Washington wrote: > > While I can say A), what I really need is B) > > > > *A)* > *take 5 $ chunksOf 10 [0..]* > > > [[0,1,2,3,4,5,6,7,8,9],[10,11,12,13,14,15,16,17,18,19],[20,21,22,23,24,25,26,27,28,29],[30,31,32,33,34,35,36,37,38,39],[40,41,42,43,44,45,46,47,48,49]] > > > > *B)* > take 5 $ someFn 10 1 [0..] > > > [[0,1,2,3,4,5,6,7,8,9],[1,2,3,4,5,6,7,8,9,10],[2,3,4,5,6,7,8,9,10,11],[3,4,5,6,7,8,9,10,11,12],[4,5,6,7,8,9,10,11,12,13]] > > > > > > The music theory package indeed has a working partition function (source > > here ). The > > implementation simply *i)* takes `n` from the source list, *ii)* drops by > > `m` then recurses. > > > > segments :: Int -> Int -> [a] -> [[a]] > > segments n m p = > > let q = take n p > > p' = drop m p > > in if length q /= n then [] else q : segments n m p' > > > > > > > > But that's rather manual. So I played around with this using *chop*, and > > came up with the *divvy* function. It does exactly what I need. > > > > divvy :: Int -> Int -> [a] -> [[a]] > > divvy n m lst = > > chop (\xs -> (take n xs , drop m xs)) lst > > > > > >> *take 5 $ partitionClojure 10 1 [0..]* > > > [[0,1,2,3,4,5,6,7,8,9],[1,2,3,4,5,6,7,8,9,10],[2,3,4,5,6,7,8,9,10,11],[3,4,5,6,7,8,9,10,11,12],[4,5,6,7,8,9,10,11,12,13]] > > > > > > Thanks guys. This helped a lot :) > > > > > > Tim > > > > > > On Sat, Jul 25, 2015 at 10:56 AM, Dan Serban > wrote: > > > >> It looks like chunksOf will take you most of the way there. Here's my > >> quick and dirty GHCi session output: > >> > >> ?> import Data.List.Split > >> ?> > >> ?> let clojurePartition n m = map (take n) $ chunksOf (n+m) [0..] > >> ?> > >> ?> take 3 $ clojurePartition 4 6 > >> [[0,1,2,3],[10,11,12,13],[20,21,22,23]] > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at schmong.org Wed Aug 5 21:22:59 2015 From: michael at schmong.org (Michael Litchard) Date: Wed, 5 Aug 2015 14:22:59 -0700 Subject: [Haskell-beginners] =?utf-8?q?How_would_I_increment_or_otherwise_?= =?utf-8?q?change_a_value_in_a_record_with_=E2=80=9CSimon-ness?= =?utf-8?b?4oCd?= Message-ID: The below code is from this tutorial http://dev.stephendiehl.com/hask/ it illustrates very well how to operate on values from records with "Simon-ness" (illustrated below). What I am struggling with is how to modify values inside records with "Simon-ness", say incrementing "age". I keep thinking it has to do with the way Label is defined with the constructor Get. Could I add another constructor Put? {-# LANGUAGE DataKinds #-}{-# LANGUAGE KindSignatures #-}{-# LANGUAGE MultiParamTypeClasses #-}{-# LANGUAGE FunctionalDependencies #-}{-# LANGUAGE FlexibleInstances #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE ExistentialQuantification #-}{-# LANGUAGE ConstraintKinds #-} import GHC.TypeLits newtype Field (n :: Symbol) v = Field { unField :: v } deriving Show data Person1 = Person1 { _age :: Field "age" Int , _name :: Field "name" String } data Person2 = Person2 { _age' :: Field "age" Int , _name' :: Field "name" String , _lib' :: Field "lib" String } deriving instance Show Person1deriving instance Show Person2 data Label (l :: Symbol) = Get class Has a l b | a l -> b where from :: a -> Label l -> b instance Has Person1 "age" Int where from (Person1 a _) _ = unField a instance Has Person1 "name" String where from (Person1 _ a) _ = unField a instance Has Person2 "age" Int where from (Person2 a _ _) _ = unField a instance Has Person2 "name" String where from (Person2 _ a _) _ = unField a age :: Has a "age" b => a -> b age pnt = from pnt (Get :: Label "age") name :: Has a "name" b => a -> b name pnt = from pnt (Get :: Label "name") -- Parameterized constraint kind for "Simon-ness" of a record.type Simon a = (Has a "name" String, Has a "age" Int) spj :: Person1 spj = Person1 (Field 56) (Field "Simon Peyton Jones") smarlow :: Person2 smarlow = Person2 (Field 38) (Field "Simon Marlow") (Field "rts") catNames :: (Simon a, Simon b) => a -> b -> String catNames a b = name a ++ name b addAges :: (Simon a, Simon b) => a -> b -> Int addAges a b = age a + age b names :: String names = name smarlow ++ "," ++ name spj-- "Simon Marlow,Simon Peyton Jones" ages :: Int ages = age spj + age smarlow-- 94 -------------- next part -------------- An HTML attachment was scrubbed... URL: From sumit.sahrawat.apm13 at iitbhu.ac.in Wed Aug 5 21:24:52 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Thu, 6 Aug 2015 02:54:52 +0530 Subject: [Haskell-beginners] =?utf-8?q?How_would_I_increment_or_otherwise_?= =?utf-8?q?change_a_value_in_a_record_with_=E2=80=9CSimon-ness?= =?utf-8?b?4oCd?= In-Reply-To: References: Message-ID: More suitable for the haskell-cafe. Routing. On 6 August 2015 at 02:52, Michael Litchard wrote: > > The below code is from this tutorial http://dev.stephendiehl.com/hask/ > > it illustrates very well how to operate on values from records with > "Simon-ness" (illustrated below). What I am struggling with is how to > modify values inside records with "Simon-ness", say incrementing "age". I > keep thinking it has to do with the way Label is defined with the > constructor Get. Could I add another constructor Put? > > {-# LANGUAGE DataKinds #-}{-# LANGUAGE KindSignatures #-}{-# LANGUAGE MultiParamTypeClasses #-}{-# LANGUAGE FunctionalDependencies #-}{-# LANGUAGE FlexibleInstances #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE ExistentialQuantification #-}{-# LANGUAGE ConstraintKinds #-} > > import GHC.TypeLits > newtype Field (n :: Symbol) v = Field { unField :: v } deriving Show > data Person1 = Person1 > { _age :: Field "age" Int > , _name :: Field "name" String > } > data Person2 = Person2 > { _age' :: Field "age" Int > , _name' :: Field "name" String > , _lib' :: Field "lib" String > } > deriving instance Show Person1deriving instance Show Person2 > data Label (l :: Symbol) = Get > class Has a l b | a l -> b where > from :: a -> Label l -> b > instance Has Person1 "age" Int where > from (Person1 a _) _ = unField a > instance Has Person1 "name" String where > from (Person1 _ a) _ = unField a > instance Has Person2 "age" Int where > from (Person2 a _ _) _ = unField a > instance Has Person2 "name" String where > from (Person2 _ a _) _ = unField a > > age :: Has a "age" b => a -> b > age pnt = from pnt (Get :: Label "age") > > name :: Has a "name" b => a -> b > name pnt = from pnt (Get :: Label "name") > -- Parameterized constraint kind for "Simon-ness" of a record.type Simon a = (Has a "name" String, Has a "age" Int) > > spj :: Person1 > spj = Person1 (Field 56) (Field "Simon Peyton Jones") > > smarlow :: Person2 > smarlow = Person2 (Field 38) (Field "Simon Marlow") (Field "rts") > > > catNames :: (Simon a, Simon b) => a -> b -> String > catNames a b = name a ++ name b > > addAges :: (Simon a, Simon b) => a -> b -> Int > addAges a b = age a + age b > > > names :: String > names = name smarlow ++ "," ++ name spj-- "Simon Marlow,Simon Peyton Jones" > > ages :: Int > ages = age spj + age smarlow-- 94 > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at schmong.org Wed Aug 5 21:53:25 2015 From: michael at schmong.org (Michael Litchard) Date: Wed, 5 Aug 2015 14:53:25 -0700 Subject: [Haskell-beginners] =?utf-8?q?How_would_I_increment_or_otherwise_?= =?utf-8?q?change_a_value_in_a_record_with_=E2=80=9CSimon-ness?= =?utf-8?b?4oCd?= In-Reply-To: References: Message-ID: I noticed the mail got archived, but I have yet to see it in my mail queue. Is it just me? Or did something go wrong with distribution? On Wed, Aug 5, 2015 at 2:24 PM, Sumit Sahrawat, Maths & Computing, IIT (BHU) wrote: > More suitable for the haskell-cafe. Routing. > > On 6 August 2015 at 02:52, Michael Litchard wrote: > >> >> The below code is from this tutorial http://dev.stephendiehl.com/hask/ >> >> it illustrates very well how to operate on values from records with >> "Simon-ness" (illustrated below). What I am struggling with is how to >> modify values inside records with "Simon-ness", say incrementing "age". I >> keep thinking it has to do with the way Label is defined with the >> constructor Get. Could I add another constructor Put? >> >> {-# LANGUAGE DataKinds #-}{-# LANGUAGE KindSignatures #-}{-# LANGUAGE MultiParamTypeClasses #-}{-# LANGUAGE FunctionalDependencies #-}{-# LANGUAGE FlexibleInstances #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE ExistentialQuantification #-}{-# LANGUAGE ConstraintKinds #-} >> >> import GHC.TypeLits >> newtype Field (n :: Symbol) v = Field { unField :: v } deriving Show >> data Person1 = Person1 >> { _age :: Field "age" Int >> , _name :: Field "name" String >> } >> data Person2 = Person2 >> { _age' :: Field "age" Int >> , _name' :: Field "name" String >> , _lib' :: Field "lib" String >> } >> deriving instance Show Person1deriving instance Show Person2 >> data Label (l :: Symbol) = Get >> class Has a l b | a l -> b where >> from :: a -> Label l -> b >> instance Has Person1 "age" Int where >> from (Person1 a _) _ = unField a >> instance Has Person1 "name" String where >> from (Person1 _ a) _ = unField a >> instance Has Person2 "age" Int where >> from (Person2 a _ _) _ = unField a >> instance Has Person2 "name" String where >> from (Person2 _ a _) _ = unField a >> >> age :: Has a "age" b => a -> b >> age pnt = from pnt (Get :: Label "age") >> >> name :: Has a "name" b => a -> b >> name pnt = from pnt (Get :: Label "name") >> -- Parameterized constraint kind for "Simon-ness" of a record.type Simon a = (Has a "name" String, Has a "age" Int) >> >> spj :: Person1 >> spj = Person1 (Field 56) (Field "Simon Peyton Jones") >> >> smarlow :: Person2 >> smarlow = Person2 (Field 38) (Field "Simon Marlow") (Field "rts") >> >> >> catNames :: (Simon a, Simon b) => a -> b -> String >> catNames a b = name a ++ name b >> >> addAges :: (Simon a, Simon b) => a -> b -> Int >> addAges a b = age a + age b >> >> >> names :: String >> names = name smarlow ++ "," ++ name spj-- "Simon Marlow,Simon Peyton Jones" >> >> ages :: Int >> ages = age spj + age smarlow-- 94 >> >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> >> > > > -- > Regards > > Sumit Sahrawat > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rein.henrichs at gmail.com Thu Aug 6 00:17:08 2015 From: rein.henrichs at gmail.com (Rein Henrichs) Date: Thu, 06 Aug 2015 00:17:08 +0000 Subject: [Haskell-beginners] =?utf-8?q?How_would_I_increment_or_otherwise_?= =?utf-8?q?change_a_value_in_a_record_with_=E2=80=9CSimon-ness?= =?utf-8?b?4oCd?= In-Reply-To: References: Message-ID: This sort of thing is (relatively) nicely solved by lenses with typeclasses, e.g., class HasName a where name :: Lens' a String Then, with the appropriate lenses, person ^. name person & name .~ "Ben" person1 ^. name person1 & name .~ "Jerry" On Wed, Aug 5, 2015 at 2:53 PM Michael Litchard wrote: > I noticed the mail got archived, but I have yet to see it in my mail > queue. Is it just me? Or did something go wrong with distribution? > > On Wed, Aug 5, 2015 at 2:24 PM, Sumit Sahrawat, Maths & Computing, IIT > (BHU) wrote: > >> More suitable for the haskell-cafe. Routing. >> >> On 6 August 2015 at 02:52, Michael Litchard wrote: >> >>> >>> The below code is from this tutorial http://dev.stephendiehl.com/hask/ >>> >>> it illustrates very well how to operate on values from records with >>> "Simon-ness" (illustrated below). What I am struggling with is how to >>> modify values inside records with "Simon-ness", say incrementing "age". I >>> keep thinking it has to do with the way Label is defined with the >>> constructor Get. Could I add another constructor Put? >>> >>> {-# LANGUAGE DataKinds #-}{-# LANGUAGE KindSignatures #-}{-# LANGUAGE MultiParamTypeClasses #-}{-# LANGUAGE FunctionalDependencies #-}{-# LANGUAGE FlexibleInstances #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE ExistentialQuantification #-}{-# LANGUAGE ConstraintKinds #-} >>> >>> import GHC.TypeLits >>> newtype Field (n :: Symbol) v = Field { unField :: v } deriving Show >>> data Person1 = Person1 >>> { _age :: Field "age" Int >>> , _name :: Field "name" String >>> } >>> data Person2 = Person2 >>> { _age' :: Field "age" Int >>> , _name' :: Field "name" String >>> , _lib' :: Field "lib" String >>> } >>> deriving instance Show Person1deriving instance Show Person2 >>> data Label (l :: Symbol) = Get >>> class Has a l b | a l -> b where >>> from :: a -> Label l -> b >>> instance Has Person1 "age" Int where >>> from (Person1 a _) _ = unField a >>> instance Has Person1 "name" String where >>> from (Person1 _ a) _ = unField a >>> instance Has Person2 "age" Int where >>> from (Person2 a _ _) _ = unField a >>> instance Has Person2 "name" String where >>> from (Person2 _ a _) _ = unField a >>> >>> age :: Has a "age" b => a -> b >>> age pnt = from pnt (Get :: Label "age") >>> >>> name :: Has a "name" b => a -> b >>> name pnt = from pnt (Get :: Label "name") >>> -- Parameterized constraint kind for "Simon-ness" of a record.type Simon a = (Has a "name" String, Has a "age" Int) >>> >>> spj :: Person1 >>> spj = Person1 (Field 56) (Field "Simon Peyton Jones") >>> >>> smarlow :: Person2 >>> smarlow = Person2 (Field 38) (Field "Simon Marlow") (Field "rts") >>> >>> >>> catNames :: (Simon a, Simon b) => a -> b -> String >>> catNames a b = name a ++ name b >>> >>> addAges :: (Simon a, Simon b) => a -> b -> Int >>> addAges a b = age a + age b >>> >>> >>> names :: String >>> names = name smarlow ++ "," ++ name spj-- "Simon Marlow,Simon Peyton Jones" >>> >>> ages :: Int >>> ages = age spj + age smarlow-- 94 >>> >>> >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >>> >> >> >> -- >> Regards >> >> Sumit Sahrawat >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> >> > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From shishir.srivastava at gmail.com Fri Aug 7 15:15:11 2015 From: shishir.srivastava at gmail.com (Shishir Srivastava) Date: Fri, 7 Aug 2015 16:15:11 +0100 Subject: [Haskell-beginners] Multiline code in GHCi Message-ID: Hi, I am trying to run this basic multiline code in GHCi. I am not sure if this is even possible without writing it in a file and compiling it in a traditional way. ------- Prelude> :set +m Prelude> let main1 = do Prelude| a <- readLn Prelude| return a Prelude| Prelude> Prelude> main1 :75:1: No instance for (Show (IO b0)) arising from a use of `print' In the first argument of `print', namely `it' In a stmt of an interactive GHCi command: print it ------- Could someone please confirm if the function can be defined and called like this in GHCi or point to where am going wrong. Thanks, Shishir Srivastava -------------- next part -------------- An HTML attachment was scrubbed... URL: From idivyanshu.ranjan at gmail.com Fri Aug 7 15:49:39 2015 From: idivyanshu.ranjan at gmail.com (divyanshu ranjan) Date: Fri, 7 Aug 2015 21:19:39 +0530 Subject: [Haskell-beginners] Multiline code in GHCi In-Reply-To: References: Message-ID: Hi Shishir, If you wrap multiline code in between Prelude> :{ Prelude| let main1 = do Prelude| a <- getLine Prelude| return a Prelude| :} Prelude> main1 hello "hello" It will work. On Fri, Aug 7, 2015 at 8:45 PM, Shishir Srivastava < shishir.srivastava at gmail.com> wrote: > Hi, > > I am trying to run this basic multiline code in GHCi. I am not sure if > this is even possible without writing it in a file and compiling it in a > traditional way. > > ------- > Prelude> :set +m > Prelude> let main1 = do > Prelude| a <- readLn > Prelude| return a > Prelude| > Prelude> > Prelude> main1 > > :75:1: > No instance for (Show (IO b0)) arising from a use of `print' > In the first argument of `print', namely `it' > In a stmt of an interactive GHCi command: print it > ------- > > Could someone please confirm if the function can be defined and called > like this in GHCi or point to where am going wrong. > > Thanks, > Shishir Srivastava > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Fri Aug 7 15:51:00 2015 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 7 Aug 2015 11:51:00 -0400 Subject: [Haskell-beginners] Multiline code in GHCi In-Reply-To: References: Message-ID: On Fri, Aug 7, 2015 at 11:15 AM, Shishir Srivastava < shishir.srivastava at gmail.com> wrote: > Prelude> :set +m > Prelude> let main1 = do > Prelude| a <- readLn > Prelude| return a > Prelude| > Prelude> > Prelude> main1 > > :75:1: > No instance for (Show (IO b0)) arising from a use of `print' > In an actual program, it would be able to apply defaulting rules and monomorphize `b0` to Integer. The somewhat unusual ghci environment, in particular how it tries to figure out whether to evaluate an expression and `print` the result or instead run an IO action --- coupled with the monomorphism restriction being disabled in the interactive context in ghci 7.8 and later --- is working against you here. As a result, you need to specify a result type when invoking `main1`, which is what the error message is telling you. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From rajatkumarzala at yahoo.com Sun Aug 9 04:21:16 2015 From: rajatkumarzala at yahoo.com (RAJATKUMAR ZALA) Date: Sun, 9 Aug 2015 12:21:16 +0800 Subject: [Haskell-beginners] Type assignment for List Message-ID: <1439094076.34613.YahooMailBasic@web190101.mail.sg3.yahoo.com> Hello Friends, I am totally new to Haskell. I am learning Haskell from a website on my own pace. From that site, I came to know about list in haskell and its type assignment. There is a confusable question on site. I am posting question here.... 1. Given that the expression []:xs is well typed, which of the following is not a possible type assignment for xs? Options:- 1. xs :: [Int] 2. xs :: [[Float]] 3. xs :: [[[Char]]] 4. xs :: [[[[Bool]]]] If any friend know about it then please clarify me on it. Thanks in advance Rajatkumar Zala India From zhiwudazhanjiangshi at gmail.com Sun Aug 9 05:11:47 2015 From: zhiwudazhanjiangshi at gmail.com (yi lu) Date: Sun, 9 Aug 2015 13:11:47 +0800 Subject: [Haskell-beginners] Type assignment for List In-Reply-To: <1439094076.34613.YahooMailBasic@web190101.mail.sg3.yahoo.com> References: <1439094076.34613.YahooMailBasic@web190101.mail.sg3.yahoo.com> Message-ID: 1 *Prelude> :t (:)* *(:) :: a -> [a] -> [a]* *xs will at least be a list of list.* On Sun, Aug 9, 2015 at 12:21 PM, RAJATKUMAR ZALA wrote: > Hello Friends, > > I am totally new to Haskell. I am learning Haskell from a website on my > own pace. From that site, I came to know about list in haskell and its type > assignment. There is a confusable question on site. I am posting question > here.... > > > > 1. Given that the expression []:xs is well typed, which of the following > is not a possible type assignment for xs? > > > Options:- > > 1. xs :: [Int] > 2. xs :: [[Float]] > 3. xs :: [[[Char]]] > 4. xs :: [[[[Bool]]]] > > > If any friend know about it then please clarify me on it. > > Thanks in advance > > Rajatkumar Zala > India > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rein.henrichs at gmail.com Sun Aug 9 06:24:11 2015 From: rein.henrichs at gmail.com (Rein Henrichs) Date: Sun, 09 Aug 2015 06:24:11 +0000 Subject: [Haskell-beginners] Type assignment for List In-Reply-To: References: <1439094076.34613.YahooMailBasic@web190101.mail.sg3.yahoo.com> Message-ID: What? On Sat, Aug 8, 2015 at 10:11 PM yi lu wrote: > 1 > > *Prelude> :t (:)* > *(:) :: a -> [a] -> [a]* > > *xs will at least be a list of list.* > > On Sun, Aug 9, 2015 at 12:21 PM, RAJATKUMAR ZALA > wrote: > >> Hello Friends, >> >> I am totally new to Haskell. I am learning Haskell from a website on my >> own pace. From that site, I came to know about list in haskell and its type >> assignment. There is a confusable question on site. I am posting question >> here.... >> >> >> >> 1. Given that the expression []:xs is well typed, which of the following >> is not a possible type assignment for xs? >> >> >> Options:- >> >> 1. xs :: [Int] >> 2. xs :: [[Float]] >> 3. xs :: [[[Char]]] >> 4. xs :: [[[[Bool]]]] >> >> >> If any friend know about it then please clarify me on it. >> >> Thanks in advance >> >> Rajatkumar Zala >> India >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From imantc at gmail.com Sun Aug 9 06:53:53 2015 From: imantc at gmail.com (Imants Cekusins) Date: Sun, 9 Aug 2015 08:53:53 +0200 Subject: [Haskell-beginners] Type assignment for List In-Reply-To: References: <1439094076.34613.YahooMailBasic@web190101.mail.sg3.yahoo.com> Message-ID: Yi Lu is spot on right: 1. xs :: [Int] Prelude> []:[1] :2:1: Non type-variable argument in the constraint: Num [t] (Use FlexibleContexts to permit this) When checking that ?it? has the inferred type it :: forall t. Num [t] => [[t]] 2. xs :: [[Float]] Prelude> []:[[0.1]] [[],[0.1]] 3. xs :: [[[Char]]] Prelude> []:[[['a']]] [[],["a"]] 4. xs :: [[[[Bool]]]] Prelude> []:[[[[True]]]] [[],[[[True]]]] From gogobebe2 at gmail.com Sun Aug 9 19:11:27 2015 From: gogobebe2 at gmail.com (William Bryant) Date: Mon, 10 Aug 2015 07:11:27 +1200 Subject: [Haskell-beginners] (no subject) Message-ID: Is the Haskell plugin for IntelliJ IDEA actually good or should I use a different IDE? I really like Intellij for Java and would like something just as good for Haskell . Any recommendations? -------------- next part -------------- An HTML attachment was scrubbed... URL: From vitalij_zad at libero.it Sun Aug 9 19:39:07 2015 From: vitalij_zad at libero.it (vitalij_zad at libero.it) Date: Sun, 9 Aug 2015 21:39:07 +0200 (CEST) Subject: [Haskell-beginners] IntelliJ Plugin and IDEs for Haskell Message-ID: <1947318115.7465391439149147481.JavaMail.httpd@webmail-18.iol.local> Hi William and welcome to the Haskell World! People complain about IntelliJ Haskell plugin to be buggy and slow. For this reason most programmers use Emacs or SpaceMacs editors. You can find an answer here: http://www.quora.com/What-is-the-best-IDE-for-programming-in-Haskell Il 09/08/2015 21:11, William Bryant ha scritto: Is the Haskell plugin for IntelliJ IDEA actually good or should I use a different IDE?I really like Intellij for Java and would like something just as good for Haskell . Any recommendations? _______________________________________________ Beginners mailing list Beginners at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners -------------- next part -------------- An HTML attachment was scrubbed... URL: From defigueiredo at ucdavis.edu Mon Aug 10 00:06:05 2015 From: defigueiredo at ucdavis.edu (Dimitri DeFigueiredo) Date: Sun, 9 Aug 2015 18:06:05 -0600 Subject: [Haskell-beginners] IntelliJ Plugin and IDEs for Haskell In-Reply-To: <1947318115.7465391439149147481.JavaMail.httpd@webmail-18.iol.local> References: <1947318115.7465391439149147481.JavaMail.httpd@webmail-18.iol.local> Message-ID: <55C7EAED.1050404@ucdavis.edu> I have been using the open source Atom editor for the last 4 months. https://atom.io/ It is not a full featured IDE, but haskell support is "good enough" and improving very quickly. I am very happy with it and where it's going. Cheers, Dimitri Em 09/08/15 13:39, vitalij_zad at libero.it escreveu: > Hi William and welcome to the Haskell World! > > People complain about IntelliJ Haskell plugin to be buggy and slow. > For this reason most programmers use Emacs or SpaceMacs editors. > > You can find an answer here: > http://www.quora.com/What-is-the-best-IDE-for-programming-in-Haskell > > Il 09/08/2015 21:11, William Bryant ha scritto: >> >> >> Is the Haskell plugin for IntelliJ IDEA actually good or should I >> use a different IDE? >> >> I really like Intellij for Java and would like something just as good >> for Haskell . Any recommendations? >> >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners -------------- next part -------------- An HTML attachment was scrubbed... URL: From gogobebe2 at gmail.com Mon Aug 10 19:13:01 2015 From: gogobebe2 at gmail.com (William Bryant) Date: Tue, 11 Aug 2015 07:13:01 +1200 Subject: [Haskell-beginners] IntelliJ Plugin and IDEs for Haskell (gogobebe2 - OP) Message-ID: Thanks guys. I saw Atom from googling, so I'll try it. :) -------------- next part -------------- An HTML attachment was scrubbed... URL: From tjakway at nyu.edu Thu Aug 13 03:52:20 2015 From: tjakway at nyu.edu (Thomas Jakway) Date: Wed, 12 Aug 2015 20:52:20 -0700 Subject: [Haskell-beginners] IntelliJ Plugin and IDEs for Haskell In-Reply-To: <1947318115.7465391439149147481.JavaMail.httpd@webmail-18.iol.local> References: <1947318115.7465391439149147481.JavaMail.httpd@webmail-18.iol.local> Message-ID: <55CC1474.5070406@nyu.edu> Haskell plugins for vim are also quite solid. vim2hs is a personal favorite: https://github.com/dag/vim2hs On 08/09/2015 12:39 PM, vitalij_zad at libero.it wrote: > Hi William and welcome to the Haskell World! > > People complain about IntelliJ Haskell plugin to be buggy and slow. > For this reason most programmers use Emacs or SpaceMacs editors. > > You can find an answer here: > http://www.quora.com/What-is-the-best-IDE-for-programming-in-Haskell > > Il 09/08/2015 21:11, William Bryant ha scritto: >> >> >> Is the Haskell plugin for IntelliJ IDEA actually good or should I >> use a different IDE? >> >> I really like Intellij for Java and would like something just as good >> for Haskell . Any recommendations? >> >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners -------------- next part -------------- An HTML attachment was scrubbed... URL: From defigueiredo at ucdavis.edu Fri Aug 14 18:53:48 2015 From: defigueiredo at ucdavis.edu (Dimitri DeFigueiredo) Date: Fri, 14 Aug 2015 12:53:48 -0600 Subject: [Haskell-beginners] cabal sandbox add-source installs but disappears Message-ID: <55CE393C.2080207@ucdavis.edu> Hello all, I am having "a bit" of an issue trying to use a source dependency with cabal. I have a very simple setup with only 2 packages: ~/code/haskell/package-tests/a-package a.cabal src/MainA.hs and ~/code/haskell/package-tests/MinhaCommon MinhaCommon.cabal setup.hs src/MainCommon.hs I have setup a sandbox for the MinhaCommon package and can build it. However, the first one (a-package) depends on the second (MinhaCommon). So, I also created a sandbox for it as such: a-package>cabal sandbox init and that seems to work fine... Writing a default package environment file to /Users/dimitri/code/haskell/package-tests/a-package/cabal.sandbox.config Creating a new sandbox at /Users/dimitri/code/haskell/package-tests/a-package/.cabal-sandbox I then add the source package and install... a-package>cabal sandbox add-source '../MinhaCommon/' a-package>cabal install --only-dep Resolving dependencies... Notice: installing into a sandbox located at /Users/dimitri/code/haskell/package-tests/a-package/.cabal-sandbox Configuring MinhaCommon-0.7.0... Building MinhaCommon-0.7.0... Installed MinhaCommon-0.7.0 Updating documentation index /Users/dimitri/code/haskell/package-tests/a-package/.cabal-sandbox/share/doc/x86_64-osx-ghc-7.10.2/index.html Here's the snag! a-package>cabal configure Resolving dependencies... Configuring a-0.1.0... cabal: At least the following dependencies are missing: MinhaCommon ==0.7.0 WTF!? I just installed that! The cabal file for package 'a' just includes the MinhaCommon package thru the build-depends section (http://pastebin.com/Wpz5845k) ------------------------------------------------ name: a version: 0.1.0 build-type: Simple cabal-version: >=1.20 ---------------------------------------------- executable a main-is: MainA.hs hs-source-dirs: ./src build-depends: base >= 4.4 , unordered-containers , unix , process , stm , MinhaCommon == 0.7.0 default-language: Haskell2010 ------------------------------------------------ Any pointers on how to get this to build are much appreciated. Thanks, Dimitri From allbery.b at gmail.com Fri Aug 14 19:00:30 2015 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 14 Aug 2015 15:00:30 -0400 Subject: [Haskell-beginners] cabal sandbox add-source installs but disappears In-Reply-To: <55CE393C.2080207@ucdavis.edu> References: <55CE393C.2080207@ucdavis.edu> Message-ID: On Fri, Aug 14, 2015 at 2:53 PM, Dimitri DeFigueiredo < defigueiredo at ucdavis.edu> wrote: > executable a > main-is: MainA.hs > hs-source-dirs: ./src > Looks to me like you have told it that MinhaCommon is an executable with no library component. Installing it therefore created and installed a program named "a", without registering a library. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From defigueiredo at ucdavis.edu Fri Aug 14 19:25:50 2015 From: defigueiredo at ucdavis.edu (Dimitri DeFigueiredo) Date: Fri, 14 Aug 2015 13:25:50 -0600 Subject: [Haskell-beginners] cabal sandbox add-source installs but disappears In-Reply-To: References: <55CE393C.2080207@ucdavis.edu> Message-ID: <55CE40BE.8010701@ucdavis.edu> Yes!! Thank you!!! You nailed it :-D Dimitri Em 14/08/15 13:00, Brandon Allbery escreveu: > On Fri, Aug 14, 2015 at 2:53 PM, Dimitri DeFigueiredo > > wrote: > > executable a > main-is: MainA.hs > hs-source-dirs: ./src > > > Looks to me like you have told it that MinhaCommon is an executable > with no library component. Installing it therefore created and > installed a program named "a", without registering a library. > > -- > brandon s allbery kf8nh sine nomine associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners -------------- next part -------------- An HTML attachment was scrubbed... URL: From shishir.srivastava at gmail.com Sat Aug 15 12:24:15 2015 From: shishir.srivastava at gmail.com (Shishir Srivastava) Date: Sat, 15 Aug 2015 13:24:15 +0100 Subject: [Haskell-beginners] Partial application and lazy evalutaion Message-ID: Hi, Is partial application feature of functions in haskell a direct outcome of lazy evaluation ? i.e Since functions are not evaluated until at the point where results are required this allows haskell functions to be partially applied because they're not evaluated and hence exist as thunk. Thanks, Shishir -------------- next part -------------- An HTML attachment was scrubbed... URL: From hanche at math.ntnu.no Sat Aug 15 15:16:04 2015 From: hanche at math.ntnu.no (Harald Hanche-Olsen) Date: Sat, 15 Aug 2015 17:16:04 +0200 Subject: [Haskell-beginners] Partial application and lazy evalutaion In-Reply-To: References: Message-ID: <55CF57B4.60408@math.ntnu.no> Shishir Srivastava wrote: > Is partial application feature of functions in haskell a direct outcome > of lazy evaluation ? I wouldn't say so. If f is a function of two variables, then you can think of (f x) as being just an easier way to write \y -> f x y. And surely, you can do that in any language with lambdas, whether lazy or not. You can even do it in javascript: function (y) { return f(x,y) }. ? Harald From debdutk at gnulinuxed.tk Mon Aug 17 06:25:25 2015 From: debdutk at gnulinuxed.tk (Debdut Karmakar) Date: Mon, 17 Aug 2015 02:25:25 -0400 Subject: [Haskell-beginners] oddsFrom3 function Message-ID: I am a haskell beginner and wondering how the following function works (in procedure) : oddsFrom3 :: [Integer] oddsFrom3 = map (+2) oddsFrom3 Thanks for your help. -------------- next part -------------- An HTML attachment was scrubbed... URL: From debdutk at gnulinuxed.tk Mon Aug 17 06:32:26 2015 From: debdutk at gnulinuxed.tk (Debdut Karmakar) Date: Mon, 17 Aug 2015 02:32:26 -0400 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: Sorry, I wrote a wrong function, the correct version is: oddsFrom3 :: [Integer] oddsFrom3 = 3 : map (+2) oddsFrom3 -- A GNU [1] LINUX [2] Patron Links: ------ [1] http://gnu.org [2] http://www.linuxfoundation.org/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 06:32:32 2015 From: akaberto at gmail.com (akash g) Date: Mon, 17 Aug 2015 12:02:32 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: Well, it won't work. Oh, it will compile and you can run it too (stuck in a infinte loop if you try to force it in any way). Compilation happens because this satisfies the type solver. However, the compiler cannot ensure non-termination of said program. Just unrolling it should show you what's wrong with it. Unroll once: oddsForm3 = map (+2) (map (+2) oddsForm3) Unroll again: oddsForm3 = map (+2) (map (+2) (map (+2) oddsForm3) And you can keep on going. It will never evaluate to a terminal value. On Mon, Aug 17, 2015 at 11:55 AM, Debdut Karmakar wrote: > I am a haskell beginner and wondering how the following function works (in > procedure) : > > > oddsFrom3 :: [Integer] > oddsFrom3 = map (+2) oddsFrom3 > > > Thanks for your help. > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 06:35:54 2015 From: akaberto at gmail.com (akash g) Date: Mon, 17 Aug 2015 12:05:54 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: Not a problem. And I should have thought about what you wanted too. This version will give you an infinite list of odd numbers from 3. On Mon, Aug 17, 2015 at 12:02 PM, Debdut Karmakar wrote: > Sorry, I wrote a wrong function, the correct version is: > > oddsFrom3 :: [Integer] > oddsFrom3 = 3 : map (+2) oddsFrom3 > -- > > A* GNU Linux * Patron > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 06:39:12 2015 From: akaberto at gmail.com (akash g) Date: Mon, 17 Aug 2015 12:09:12 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: Do note that if you force it so that it the value needs the last element, it will be stuck in an infinite loop of request-> response loop. Here's what will happen/ last [3,5 ..] -- Same thing as your function This will be forced to last [3,5, 7 ..] which will be forced till it terminates (which is never). So, be careful with that. However, things like this are perfectly fine. head [3,5 ..] yields 3 takeWhile (<10) [3,5 ..] yields [3,5,7,9] On Mon, Aug 17, 2015 at 12:05 PM, akash g wrote: > Not a problem. And I should have thought about what you wanted too. > > This version will give you an infinite list of odd numbers from 3. > > > On Mon, Aug 17, 2015 at 12:02 PM, Debdut Karmakar > wrote: > >> Sorry, I wrote a wrong function, the correct version is: >> >> oddsFrom3 :: [Integer] >> oddsFrom3 = 3 : map (+2) oddsFrom3 >> -- >> >> A* GNU Linux * Patron >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From debdutk at gnulinuxed.tk Mon Aug 17 07:05:36 2015 From: debdutk at gnulinuxed.tk (Debdut Karmakar) Date: Mon, 17 Aug 2015 03:05:36 -0400 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: On 2015-08-17 02:35, akash g wrote: > Not a problem. And I should have thought about what you wanted too. > > This version will give you an infinite list of odd numbers from 3. > > On Mon, Aug 17, 2015 at 12:02 PM, Debdut Karmakar wrote: > >> Sorry, I wrote a wrong function, the correct version is: >> >> oddsFrom3 :: [Integer] >> oddsFrom3 = 3 : map (+2) oddsFrom3 >> -- >> >> A GNU [1] LINUX [2] Patron >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners [3] > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners [3] I know that it will evaluate to a list of odd numbers >= 3, but how? Thanks, anyway. -- A GNU [1] LINUX [2] Patron Links: ------ [1] http://gnu.org [2] http://www.linuxfoundation.org/ [3] http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners -------------- next part -------------- An HTML attachment was scrubbed... URL: From rein.henrichs at gmail.com Mon Aug 17 07:10:59 2015 From: rein.henrichs at gmail.com (Rein Henrichs) Date: Mon, 17 Aug 2015 07:10:59 +0000 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: It will absolutely work. Lists can be infinite in Haskell and infinite lists are productive: ?> take 5 oddsFrom3 [3,5,7,9,11] On Mon, Aug 17, 2015 at 12:05 AM Debdut Karmakar wrote: > On 2015-08-17 02:35, akash g wrote: > > Not a problem. And I should have thought about what you wanted too. > > This version will give you an infinite list of odd numbers from 3. > > > On Mon, Aug 17, 2015 at 12:02 PM, Debdut Karmakar > wrote: > >> Sorry, I wrote a wrong function, the correct version is: >> >> oddsFrom3 :: [Integer] >> oddsFrom3 = 3 : map (+2) oddsFrom3 >> -- >> >> A* GNU Linux * Patron >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> >> > _______________________________________________ > Beginners mailing listBeginners at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > I know that it will evaluate to a list of odd numbers >= 3, but how? > > Thanks, anyway. > -- > > A* GNU Linux * Patron > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ky3 at atamo.com Mon Aug 17 07:21:45 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Mon, 17 Aug 2015 14:21:45 +0700 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: On Mon, Aug 17, 2015 at 1:32 PM, Debdut Karmakar wrote: > Sorry, I wrote a wrong function, the correct version is: > > oddsFrom3 :: [Integer] > oddsFrom3 = 3 : map (+2) oddsFrom3 > You can get some idea of lambda evaluation here: http://chrisuehlinger.com/LambdaBubblePop/ (Alas it doesn't support let expressions much less let rec.) Once you have a modicum of intuition, you're now ready to appreciate the illustrated step-by-step evaluation of this infinite list: http://stackoverflow.com/a/19749422 Based on the SO answer, you can now work out your function on your own. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 08:42:11 2015 From: akaberto at gmail.com (akash g) Date: Mon, 17 Aug 2015 14:12:11 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: Hi Rein, The initial version which the OP posted doesn't have a terminal value. The OP had posted the version that he'd wanted clarification on. On Mon, Aug 17, 2015 at 12:40 PM, Rein Henrichs wrote: > It will absolutely work. Lists can be infinite in Haskell and infinite > lists are productive: > > ?> take 5 oddsFrom3 > [3,5,7,9,11] > > > On Mon, Aug 17, 2015 at 12:05 AM Debdut Karmakar > wrote: > >> On 2015-08-17 02:35, akash g wrote: >> >> Not a problem. And I should have thought about what you wanted too. >> >> This version will give you an infinite list of odd numbers from 3. >> >> >> On Mon, Aug 17, 2015 at 12:02 PM, Debdut Karmakar >> wrote: >> >>> Sorry, I wrote a wrong function, the correct version is: >>> >>> oddsFrom3 :: [Integer] >>> oddsFrom3 = 3 : map (+2) oddsFrom3 >>> -- >>> >>> A* GNU Linux * Patron >>> >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >>> >> _______________________________________________ >> Beginners mailing listBeginners at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> >> I know that it will evaluate to a list of odd numbers >= 3, but how? >> >> Thanks, anyway. >> -- >> >> A* GNU Linux * Patron >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From debdutk at gnulinuxed.tk Mon Aug 17 08:44:55 2015 From: debdutk at gnulinuxed.tk (Debdut Karmakar) Date: Mon, 17 Aug 2015 04:44:55 -0400 Subject: [Haskell-beginners] oddsFrom3 function Message-ID: I am a haskell beginner and wondering how the following function works (in procedure) : oddsFrom3 :: [Integer] oddsFrom3 = 3 : map (+2) oddsFrom3 Thanks for your help. -- A GNU [1] LINUX [2] Patron Links: ------ [1] http://gnu.org [2] http://www.linuxfoundation.org/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 08:46:10 2015 From: akaberto at gmail.com (akash g) Date: Mon, 17 Aug 2015 14:16:10 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: You can also peruse SICP for knowing about how lazy evaluation works. The explanations are nice. It is in lisp, though. https://mitpress.mit.edu/sicp/full-text/book/book-Z-H-24.html#%_sec_3.5 On Mon, Aug 17, 2015 at 2:12 PM, akash g wrote: > Hi Rein, > > The initial version which the OP posted doesn't have a terminal value. > The OP had posted the version that he'd wanted clarification on. > > On Mon, Aug 17, 2015 at 12:40 PM, Rein Henrichs > wrote: > >> It will absolutely work. Lists can be infinite in Haskell and infinite >> lists are productive: >> >> ?> take 5 oddsFrom3 >> [3,5,7,9,11] >> >> >> On Mon, Aug 17, 2015 at 12:05 AM Debdut Karmakar >> wrote: >> >>> On 2015-08-17 02:35, akash g wrote: >>> >>> Not a problem. And I should have thought about what you wanted too. >>> >>> This version will give you an infinite list of odd numbers from 3. >>> >>> >>> On Mon, Aug 17, 2015 at 12:02 PM, Debdut Karmakar >> > wrote: >>> >>>> Sorry, I wrote a wrong function, the correct version is: >>>> >>>> oddsFrom3 :: [Integer] >>>> oddsFrom3 = 3 : map (+2) oddsFrom3 >>>> -- >>>> >>>> A* GNU Linux * Patron >>>> >>>> _______________________________________________ >>>> Beginners mailing list >>>> Beginners at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>> >>>> >>> _______________________________________________ >>> Beginners mailing listBeginners at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >>> I know that it will evaluate to a list of odd numbers >= 3, but how? >>> >>> Thanks, anyway. >>> -- >>> >>> A* GNU Linux * Patron >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Mon Aug 17 08:49:50 2015 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 17 Aug 2015 10:49:50 +0200 Subject: [Haskell-beginners] [Haskell-cafe] oddsFrom3 function In-Reply-To: References: Message-ID: <20150817084950.GA18244@machine> Hi Debdut, On Mon, Aug 17, 2015 at 04:44:55AM -0400, Debdut Karmakar wrote: > I am a haskell beginner and wondering how the following function works (in > procedure) : > > > oddsFrom3 :: [Integer] > oddsFrom3 = 3 : map (+2) oddsFrom3 > > > Thanks for your help. Try to expand a few steps of the recursion by hand e.g.: 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) As you can see, the deeper you go more 'map (+2)' are applied to '3'. Greetings, Daniel From debdutk at gnulinuxed.tk Mon Aug 17 08:59:53 2015 From: debdutk at gnulinuxed.tk (Debdut Karmakar) Date: Mon, 17 Aug 2015 04:59:53 -0400 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: Message-ID: <70785eb45949aea017f020194bf0aa19@gnulinuxed.tk> On 2015-08-17 03:21, Kim-Ee Yeoh wrote: > On Mon, Aug 17, 2015 at 1:32 PM, Debdut Karmakar wrote: > >> Sorry, I wrote a wrong function, the correct version is: >> >> oddsFrom3 :: [Integer] >> oddsFrom3 = 3 : map (+2) oddsFrom3 > > You can get some idea of lambda evaluation here: > > http://chrisuehlinger.com/LambdaBubblePop/ [2] > > (Alas it doesn't support let expressions much less let rec.) > > Once you have a modicum of intuition, you're now ready to appreciate the illustrated step-by-step evaluation of this infinite list: > > http://stackoverflow.com/a/19749422 [3] > > Based on the SO answer, you can now work out your function on your own. > > -- Kim-Ee > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners [1] Thanks, this is what I wanted. Thanks and the problem has been resolved. -- A GNU [4] LINUX [5] Patron Links: ------ [1] http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners [2] http://chrisuehlinger.com/LambdaBubblePop/ [3] http://stackoverflow.com/a/19749422 [4] http://gnu.org [5] http://www.linuxfoundation.org/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From doug at cs.dartmouth.edu Mon Aug 17 13:17:42 2015 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Mon, 17 Aug 2015 09:17:42 -0400 Subject: [Haskell-beginners] oddsFrom3 function Message-ID: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> > > oddsFrom3 :: [Integer] > > oddsFrom3 = 3 : map (+2) oddsFrom3 > > > > > > Thanks for your help. > > Try to expand a few steps of the recursion by hand e.g.: > > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) > > > As you can see, the deeper you go more 'map (+2)' are applied to '3'. Some more ways to describe the program, which may be useful: As with any recursive function, assume you know the whole series and then confirm that by verifying the inductive step. In this case oddsFrom3 = [3,5,7,9,11,...] map (+2) oddsFrom3 = [5,7,9,11,13,...] voila oddsFrom3 = 3 : map (+2) oddsFrom3 Assuming we have the whole series, we see its tail is computed from the whole by adding 2 to each element. Notice that we don't actually have to know the values in the tail in order to write the formula for the tail. Yet another way to describe the program: the "output" is taken as "input". This works because the first element of the output, namely 3, is provided in advance. Each output element can then be computed before it is needed as input. In an imperative language this would be done so: integer oddsFrom3[0:HUGE] oddsFrom3[0] := 3 for i:=1 to HUGE do oddsFrom3[i] = oddsFrom3[i-1] + 2 From rein.henrichs at gmail.com Mon Aug 17 16:53:19 2015 From: rein.henrichs at gmail.com (Rein Henrichs) Date: Mon, 17 Aug 2015 16:53:19 +0000 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> References: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> Message-ID: > The initial version which the OP posted doesn't have a terminal value. The point is that it doesn't need a terminal value. Infinite lists like oddsFrom3 and (repeat "foo") and (let xs = 1 : xs) are all perfectly valid Haskell values. On Mon, Aug 17, 2015 at 6:17 AM Doug McIlroy wrote: > > > oddsFrom3 :: [Integer] > > > oddsFrom3 = 3 : map (+2) oddsFrom3 > > > > > > > > > Thanks for your help. > > > > Try to expand a few steps of the recursion by hand e.g.: > > > > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) > > > > > > As you can see, the deeper you go more 'map (+2)' are applied to '3'. > > Some more ways to describe the program, which may be useful: > > As with any recursive function, assume you know the whole series and > then confirm that by verifying the inductive step. In this case > oddsFrom3 = [3,5,7,9,11,...] > map (+2) oddsFrom3 = [5,7,9,11,13,...] > voila > oddsFrom3 = 3 : map (+2) oddsFrom3 > > Assuming we have the whole series, we see its tail is > computed from the whole by adding 2 to each element. > Notice that we don't actually have to know the values in the > tail in order to write the formula for the tail. > > Yet another way to describe the program: the "output" is taken > as "input". This works because the first element of the output, > namely 3, is provided in advance. Each output element can then > be computed before it is needed as input. > > In an imperative language this would be done so: > integer oddsFrom3[0:HUGE] > oddsFrom3[0] := 3 > for i:=1 to HUGE do > oddsFrom3[i] = oddsFrom3[i-1] + 2 > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 17:27:24 2015 From: akaberto at gmail.com (akash g) Date: Mon, 17 Aug 2015 22:57:24 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> Message-ID: @Rein: Perhaps I should have been a bit more clear. There is no way to get a terminal value from said function. oddsFrom3 :: [Integer] oddsFrom3 = map (+2) oddsFrom3 Try a head for it perhaps. oddsFrom3 = map (+2) oddsFrom3 <=> ((head oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) <=> ((head (map (+2) oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) Sure, it doesn't hang until you try to evaluate this (in lazy language evaluators). However, for any inductive structure, there needs to be a (well any finite number of terminals) terminal (base case) which can be reached from the starting state in a finite amount of computational (condition for termination). Type sigs don't/can't guarantee termination. If they don't have a terminal value, you'll never get to the bottom (bad pun intended) of it. Take an infinite list as an example. x a = a : x a Here, one branch of the tree (representing the list as a highly unbalanced tree where every left branch is of depth one at any given point). If such a structure is not present, you can never compute it to a value and you'll have to infinitely recurse. Try x a = x a ++ x a And think of the getting the head from this. You're stuck in an infinite loop. You may also think of the above as a small BNF and try to see if termination is possible from the start state. A vaguely intuitive way of looking at it for me, but meh, I might be missing something. On Mon, Aug 17, 2015 at 10:23 PM, Rein Henrichs wrote: > > The initial version which the OP posted doesn't have a terminal value. > > The point is that it doesn't need a terminal value. Infinite lists like > oddsFrom3 and (repeat "foo") and (let xs = 1 : xs) are all perfectly valid > Haskell values. > > On Mon, Aug 17, 2015 at 6:17 AM Doug McIlroy > wrote: > >> > > oddsFrom3 :: [Integer] >> > > oddsFrom3 = 3 : map (+2) oddsFrom3 >> > > >> > > >> > > Thanks for your help. >> > >> > Try to expand a few steps of the recursion by hand e.g.: >> > >> > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) >> > >> > >> > As you can see, the deeper you go more 'map (+2)' are applied to '3'. >> >> Some more ways to describe the program, which may be useful: >> >> As with any recursive function, assume you know the whole series and >> then confirm that by verifying the inductive step. In this case >> oddsFrom3 = [3,5,7,9,11,...] >> map (+2) oddsFrom3 = [5,7,9,11,13,...] >> voila >> oddsFrom3 = 3 : map (+2) oddsFrom3 >> >> Assuming we have the whole series, we see its tail is >> computed from the whole by adding 2 to each element. >> Notice that we don't actually have to know the values in the >> tail in order to write the formula for the tail. >> >> Yet another way to describe the program: the "output" is taken >> as "input". This works because the first element of the output, >> namely 3, is provided in advance. Each output element can then >> be computed before it is needed as input. >> >> In an imperative language this would be done so: >> integer oddsFrom3[0:HUGE] >> oddsFrom3[0] := 3 >> for i:=1 to HUGE do >> oddsFrom3[i] = oddsFrom3[i-1] + 2 >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 17:29:51 2015 From: akaberto at gmail.com (akash g) Date: Mon, 17 Aug 2015 22:59:51 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> Message-ID: Oh, it is a valid value (I think I implied this by saying they'll compile and you can even evaluate). Just not useful in any given scenario (an inductive structure where you don't have terminals). On Mon, Aug 17, 2015 at 10:57 PM, akash g wrote: > @Rein: > Perhaps I should have been a bit more clear. There is no way to get a > terminal value from said function. > > > oddsFrom3 :: [Integer] > oddsFrom3 = map (+2) oddsFrom3 > > Try a head for it perhaps. > > oddsFrom3 = map (+2) oddsFrom3 > <=> ((head oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) > <=> ((head (map (+2) oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) > > Sure, it doesn't hang until you try to evaluate this (in lazy language > evaluators). However, for any inductive structure, there needs to be a > (well any finite number of terminals) terminal (base case) which can be > reached from the starting state in a finite amount of computational > (condition for termination). Type sigs don't/can't guarantee termination. > If they don't have a terminal value, you'll never get to the bottom (bad > pun intended) of it. > > > Take an infinite list as an example. > > x a = a : x a > > Here, one branch of the tree (representing the list as a highly unbalanced > tree where every left branch is of depth one at any given point). If such > a structure is not present, you can never compute it to a value and you'll > have to infinitely recurse. > > Try x a = x a ++ x a > > And think of the getting the head from this. You're stuck in an infinite > loop. > > You may also think of the above as a small BNF and try to see if > termination is possible from the start state. A vaguely intuitive way of > looking at it for me, but meh, I might be missing something. > > > > On Mon, Aug 17, 2015 at 10:23 PM, Rein Henrichs > wrote: > >> > The initial version which the OP posted doesn't have a terminal value. >> >> The point is that it doesn't need a terminal value. Infinite lists like >> oddsFrom3 and (repeat "foo") and (let xs = 1 : xs) are all perfectly valid >> Haskell values. >> >> On Mon, Aug 17, 2015 at 6:17 AM Doug McIlroy >> wrote: >> >>> > > oddsFrom3 :: [Integer] >>> > > oddsFrom3 = 3 : map (+2) oddsFrom3 >>> > > >>> > > >>> > > Thanks for your help. >>> > >>> > Try to expand a few steps of the recursion by hand e.g.: >>> > >>> > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) >>> > >>> > >>> > As you can see, the deeper you go more 'map (+2)' are applied to '3'. >>> >>> Some more ways to describe the program, which may be useful: >>> >>> As with any recursive function, assume you know the whole series and >>> then confirm that by verifying the inductive step. In this case >>> oddsFrom3 = [3,5,7,9,11,...] >>> map (+2) oddsFrom3 = [5,7,9,11,13,...] >>> voila >>> oddsFrom3 = 3 : map (+2) oddsFrom3 >>> >>> Assuming we have the whole series, we see its tail is >>> computed from the whole by adding 2 to each element. >>> Notice that we don't actually have to know the values in the >>> tail in order to write the formula for the tail. >>> >>> Yet another way to describe the program: the "output" is taken >>> as "input". This works because the first element of the output, >>> namely 3, is provided in advance. Each output element can then >>> be computed before it is needed as input. >>> >>> In an imperative language this would be done so: >>> integer oddsFrom3[0:HUGE] >>> oddsFrom3[0] := 3 >>> for i:=1 to HUGE do >>> oddsFrom3[i] = oddsFrom3[i-1] + 2 >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rein.henrichs at gmail.com Mon Aug 17 17:59:55 2015 From: rein.henrichs at gmail.com (Rein Henrichs) Date: Mon, 17 Aug 2015 17:59:55 +0000 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> Message-ID: It isn't an inductive structure. It's a *coinductive* structure. And yes, coinductive structures are useful in plenty of scenarios. On Mon, Aug 17, 2015 at 10:30 AM akash g wrote: > Oh, it is a valid value (I think I implied this by saying they'll compile > and you can even evaluate). Just not useful in any given scenario (an > inductive structure where you don't have terminals). > > > On Mon, Aug 17, 2015 at 10:57 PM, akash g wrote: > >> @Rein: >> Perhaps I should have been a bit more clear. There is no way to get a >> terminal value from said function. >> >> >> oddsFrom3 :: [Integer] >> oddsFrom3 = map (+2) oddsFrom3 >> >> Try a head for it perhaps. >> >> oddsFrom3 = map (+2) oddsFrom3 >> <=> ((head oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >> <=> ((head (map (+2) oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >> >> Sure, it doesn't hang until you try to evaluate this (in lazy language >> evaluators). However, for any inductive structure, there needs to be a >> (well any finite number of terminals) terminal (base case) which can be >> reached from the starting state in a finite amount of computational >> (condition for termination). Type sigs don't/can't guarantee termination. >> If they don't have a terminal value, you'll never get to the bottom (bad >> pun intended) of it. >> >> >> Take an infinite list as an example. >> >> x a = a : x a >> >> Here, one branch of the tree (representing the list as a highly >> unbalanced tree where every left branch is of depth one at any given >> point). If such a structure is not present, you can never compute it to a >> value and you'll have to infinitely recurse. >> >> Try x a = x a ++ x a >> >> And think of the getting the head from this. You're stuck in an infinite >> loop. >> >> You may also think of the above as a small BNF and try to see if >> termination is possible from the start state. A vaguely intuitive way of >> looking at it for me, but meh, I might be missing something. >> >> >> >> On Mon, Aug 17, 2015 at 10:23 PM, Rein Henrichs >> wrote: >> >>> > The initial version which the OP posted doesn't have a terminal >>> value. >>> >>> The point is that it doesn't need a terminal value. Infinite lists like >>> oddsFrom3 and (repeat "foo") and (let xs = 1 : xs) are all perfectly valid >>> Haskell values. >>> >>> On Mon, Aug 17, 2015 at 6:17 AM Doug McIlroy >>> wrote: >>> >>>> > > oddsFrom3 :: [Integer] >>>> > > oddsFrom3 = 3 : map (+2) oddsFrom3 >>>> > > >>>> > > >>>> > > Thanks for your help. >>>> > >>>> > Try to expand a few steps of the recursion by hand e.g.: >>>> > >>>> > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) >>>> > >>>> > >>>> > As you can see, the deeper you go more 'map (+2)' are applied to '3'. >>>> >>>> Some more ways to describe the program, which may be useful: >>>> >>>> As with any recursive function, assume you know the whole series and >>>> then confirm that by verifying the inductive step. In this case >>>> oddsFrom3 = [3,5,7,9,11,...] >>>> map (+2) oddsFrom3 = [5,7,9,11,13,...] >>>> voila >>>> oddsFrom3 = 3 : map (+2) oddsFrom3 >>>> >>>> Assuming we have the whole series, we see its tail is >>>> computed from the whole by adding 2 to each element. >>>> Notice that we don't actually have to know the values in the >>>> tail in order to write the formula for the tail. >>>> >>>> Yet another way to describe the program: the "output" is taken >>>> as "input". This works because the first element of the output, >>>> namely 3, is provided in advance. Each output element can then >>>> be computed before it is needed as input. >>>> >>>> In an imperative language this would be done so: >>>> integer oddsFrom3[0:HUGE] >>>> oddsFrom3[0] := 3 >>>> for i:=1 to HUGE do >>>> oddsFrom3[i] = oddsFrom3[i-1] + 2 >>>> _______________________________________________ >>>> Beginners mailing list >>>> Beginners at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>> >>> >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >>> >> > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 18:55:55 2015 From: akaberto at gmail.com (akash g) Date: Tue, 18 Aug 2015 00:25:55 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> Message-ID: Yes, it is a coinductive structure (though I had a mental picture of the list as a coinductive structure, which is what it exactly is as far as infinite lists in Haskell are concerned). I got my terms wrong; thanks for that. Let me clarify. By terminal, I meant that the structure itself is made up of finite and infinite structures and you've some way of getting to that finite part (my intuition as a terminal symbol). Take the following for an example. data Stream a = Stream a (Stream a) Stream, by virtue of construction, will have a finite element (or it can be a co-inductive structure again) and an infinite element (the continuation of the stream). However, take the OP's code under question oddsFrom3 = map (+2) oddsFrom3 -- Goes into an infinite loop; violates condition for co-inductiveness; See Link1 The above is not guarded by a constructor and there is no way to pull anything useful out of it without going to an infinite loop. So, it has essentially violated the guardedness condition (Link1 to blame/praise for this). This is basically something like ========== loop :: [Integer] loop = loop -- This compiles, but god it will never end ========== I shouldn't have used the term terminal and I think this is where the confusion stems from. My intuition and what it actually is very similar, yet subtly different. This might further clarify this (Link1) ============= every co-recursive call must be a direct argument to a constructor of the co-inductive type we are generating ============= As for inductive vs co-inductive meaning, I think it is because I see the co-inductive construction as a special case of the inductive step (at least Haskell lets me have this intuition). Link1: http://adam.chlipala.net/cpdt/html/Coinductive.html Link2: http://c2.com/cgi/wiki?CoinductiveDataType On Mon, Aug 17, 2015 at 11:29 PM, Rein Henrichs wrote: > It isn't an inductive structure. It's a *coinductive* structure. And yes, > coinductive structures are useful in plenty of scenarios. > > On Mon, Aug 17, 2015 at 10:30 AM akash g wrote: > >> Oh, it is a valid value (I think I implied this by saying they'll compile >> and you can even evaluate). Just not useful in any given scenario (an >> inductive structure where you don't have terminals). >> >> >> On Mon, Aug 17, 2015 at 10:57 PM, akash g wrote: >> >>> @Rein: >>> Perhaps I should have been a bit more clear. There is no way to get a >>> terminal value from said function. >>> >>> >>> oddsFrom3 :: [Integer] >>> oddsFrom3 = map (+2) oddsFrom3 >>> >>> Try a head for it perhaps. >>> >>> oddsFrom3 = map (+2) oddsFrom3 >>> <=> ((head oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >>> <=> ((head (map (+2) oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >>> >>> Sure, it doesn't hang until you try to evaluate this (in lazy language >>> evaluators). However, for any inductive structure, there needs to be a >>> (well any finite number of terminals) terminal (base case) which can be >>> reached from the starting state in a finite amount of computational >>> (condition for termination). Type sigs don't/can't guarantee termination. >>> If they don't have a terminal value, you'll never get to the bottom (bad >>> pun intended) of it. >>> >>> >>> Take an infinite list as an example. >>> >>> x a = a : x a >>> >>> Here, one branch of the tree (representing the list as a highly >>> unbalanced tree where every left branch is of depth one at any given >>> point). If such a structure is not present, you can never compute it to a >>> value and you'll have to infinitely recurse. >>> >>> Try x a = x a ++ x a >>> >>> And think of the getting the head from this. You're stuck in an >>> infinite loop. >>> >>> You may also think of the above as a small BNF and try to see if >>> termination is possible from the start state. A vaguely intuitive way of >>> looking at it for me, but meh, I might be missing something. >>> >>> >>> >>> On Mon, Aug 17, 2015 at 10:23 PM, Rein Henrichs >> > wrote: >>> >>>> > The initial version which the OP posted doesn't have a terminal >>>> value. >>>> >>>> The point is that it doesn't need a terminal value. Infinite lists like >>>> oddsFrom3 and (repeat "foo") and (let xs = 1 : xs) are all perfectly valid >>>> Haskell values. >>>> >>>> On Mon, Aug 17, 2015 at 6:17 AM Doug McIlroy >>>> wrote: >>>> >>>>> > > oddsFrom3 :: [Integer] >>>>> > > oddsFrom3 = 3 : map (+2) oddsFrom3 >>>>> > > >>>>> > > >>>>> > > Thanks for your help. >>>>> > >>>>> > Try to expand a few steps of the recursion by hand e.g.: >>>>> > >>>>> > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) >>>>> > >>>>> > >>>>> > As you can see, the deeper you go more 'map (+2)' are applied to '3'. >>>>> >>>>> Some more ways to describe the program, which may be useful: >>>>> >>>>> As with any recursive function, assume you know the whole series and >>>>> then confirm that by verifying the inductive step. In this case >>>>> oddsFrom3 = [3,5,7,9,11,...] >>>>> map (+2) oddsFrom3 = [5,7,9,11,13,...] >>>>> voila >>>>> oddsFrom3 = 3 : map (+2) oddsFrom3 >>>>> >>>>> Assuming we have the whole series, we see its tail is >>>>> computed from the whole by adding 2 to each element. >>>>> Notice that we don't actually have to know the values in the >>>>> tail in order to write the formula for the tail. >>>>> >>>>> Yet another way to describe the program: the "output" is taken >>>>> as "input". This works because the first element of the output, >>>>> namely 3, is provided in advance. Each output element can then >>>>> be computed before it is needed as input. >>>>> >>>>> In an imperative language this would be done so: >>>>> integer oddsFrom3[0:HUGE] >>>>> oddsFrom3[0] := 3 >>>>> for i:=1 to HUGE do >>>>> oddsFrom3[i] = oddsFrom3[i-1] + 2 >>>>> _______________________________________________ >>>>> Beginners mailing list >>>>> Beginners at haskell.org >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>>> >>>> >>>> _______________________________________________ >>>> Beginners mailing list >>>> Beginners at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>> >>>> >>> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 19:02:04 2015 From: akaberto at gmail.com (akash g) Date: Tue, 18 Aug 2015 00:32:04 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> Message-ID: Oh, I do apologize for the wrong use of the term `terminal` in this case which led to this exchange (one that I don't regret as I learned a lot today; thanks, Rein) . It had to do with my intuition of it (the - works for me, but can't explain to others - type of intuition). On Tue, Aug 18, 2015 at 12:25 AM, akash g wrote: > Yes, it is a coinductive structure (though I had a mental picture of the > list as a coinductive structure, which is what it exactly is as far as > infinite lists in Haskell are concerned). I got my terms wrong; thanks for > that. > > Let me clarify. By terminal, I meant that the structure itself is made up > of finite and infinite structures and you've some way of getting to that > finite part (my intuition as a terminal symbol). > > Take the following for an example. > > data Stream a = Stream a (Stream a) > > Stream, by virtue of construction, will have a finite element (or it can > be a co-inductive structure again) and an infinite element (the > continuation of the stream). > > However, take the OP's code under question > > oddsFrom3 = map (+2) oddsFrom3 -- Goes into an infinite loop; violates > condition for co-inductiveness; See Link1 > > The above is not guarded by a constructor and there is no way to pull > anything useful out of it without going to an infinite loop. So, it has > essentially violated the guardedness condition (Link1 to blame/praise for > this). This is basically something like > > ========== > loop :: [Integer] > loop = loop -- This compiles, but god it will never end > ========== > > I shouldn't have used the term terminal and I think this is where the > confusion stems from. My intuition and what it actually is very similar, > yet subtly different. This might further clarify this (Link1) > > > ============= > every co-recursive call must be a direct argument to a constructor of the > co-inductive type we are generating > ============= > > As for inductive vs co-inductive meaning, I think it is because I see the > co-inductive construction as a special case of the inductive step (at least > Haskell lets me have this intuition). > > > > Link1: http://adam.chlipala.net/cpdt/html/Coinductive.html > Link2: http://c2.com/cgi/wiki?CoinductiveDataType > > On Mon, Aug 17, 2015 at 11:29 PM, Rein Henrichs > wrote: > >> It isn't an inductive structure. It's a *coinductive* structure. And yes, >> coinductive structures are useful in plenty of scenarios. >> >> On Mon, Aug 17, 2015 at 10:30 AM akash g wrote: >> >>> Oh, it is a valid value (I think I implied this by saying they'll >>> compile and you can even evaluate). Just not useful in any given scenario >>> (an inductive structure where you don't have terminals). >>> >>> >>> On Mon, Aug 17, 2015 at 10:57 PM, akash g wrote: >>> >>>> @Rein: >>>> Perhaps I should have been a bit more clear. There is no way to get a >>>> terminal value from said function. >>>> >>>> >>>> oddsFrom3 :: [Integer] >>>> oddsFrom3 = map (+2) oddsFrom3 >>>> >>>> Try a head for it perhaps. >>>> >>>> oddsFrom3 = map (+2) oddsFrom3 >>>> <=> ((head oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >>>> <=> ((head (map (+2) oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >>>> >>>> Sure, it doesn't hang until you try to evaluate this (in lazy language >>>> evaluators). However, for any inductive structure, there needs to be a >>>> (well any finite number of terminals) terminal (base case) which can be >>>> reached from the starting state in a finite amount of computational >>>> (condition for termination). Type sigs don't/can't guarantee termination. >>>> If they don't have a terminal value, you'll never get to the bottom (bad >>>> pun intended) of it. >>>> >>>> >>>> Take an infinite list as an example. >>>> >>>> x a = a : x a >>>> >>>> Here, one branch of the tree (representing the list as a highly >>>> unbalanced tree where every left branch is of depth one at any given >>>> point). If such a structure is not present, you can never compute it to a >>>> value and you'll have to infinitely recurse. >>>> >>>> Try x a = x a ++ x a >>>> >>>> And think of the getting the head from this. You're stuck in an >>>> infinite loop. >>>> >>>> You may also think of the above as a small BNF and try to see if >>>> termination is possible from the start state. A vaguely intuitive way of >>>> looking at it for me, but meh, I might be missing something. >>>> >>>> >>>> >>>> On Mon, Aug 17, 2015 at 10:23 PM, Rein Henrichs < >>>> rein.henrichs at gmail.com> wrote: >>>> >>>>> > The initial version which the OP posted doesn't have a terminal >>>>> value. >>>>> >>>>> The point is that it doesn't need a terminal value. Infinite lists >>>>> like oddsFrom3 and (repeat "foo") and (let xs = 1 : xs) are all perfectly >>>>> valid Haskell values. >>>>> >>>>> On Mon, Aug 17, 2015 at 6:17 AM Doug McIlroy >>>>> wrote: >>>>> >>>>>> > > oddsFrom3 :: [Integer] >>>>>> > > oddsFrom3 = 3 : map (+2) oddsFrom3 >>>>>> > > >>>>>> > > >>>>>> > > Thanks for your help. >>>>>> > >>>>>> > Try to expand a few steps of the recursion by hand e.g.: >>>>>> > >>>>>> > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) >>>>>> > >>>>>> > >>>>>> > As you can see, the deeper you go more 'map (+2)' are applied to >>>>>> '3'. >>>>>> >>>>>> Some more ways to describe the program, which may be useful: >>>>>> >>>>>> As with any recursive function, assume you know the whole series and >>>>>> then confirm that by verifying the inductive step. In this case >>>>>> oddsFrom3 = [3,5,7,9,11,...] >>>>>> map (+2) oddsFrom3 = [5,7,9,11,13,...] >>>>>> voila >>>>>> oddsFrom3 = 3 : map (+2) oddsFrom3 >>>>>> >>>>>> Assuming we have the whole series, we see its tail is >>>>>> computed from the whole by adding 2 to each element. >>>>>> Notice that we don't actually have to know the values in the >>>>>> tail in order to write the formula for the tail. >>>>>> >>>>>> Yet another way to describe the program: the "output" is taken >>>>>> as "input". This works because the first element of the output, >>>>>> namely 3, is provided in advance. Each output element can then >>>>>> be computed before it is needed as input. >>>>>> >>>>>> In an imperative language this would be done so: >>>>>> integer oddsFrom3[0:HUGE] >>>>>> oddsFrom3[0] := 3 >>>>>> for i:=1 to HUGE do >>>>>> oddsFrom3[i] = oddsFrom3[i-1] + 2 >>>>>> _______________________________________________ >>>>>> Beginners mailing list >>>>>> Beginners at haskell.org >>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>>>> >>>>> >>>>> _______________________________________________ >>>>> Beginners mailing list >>>>> Beginners at haskell.org >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>>> >>>>> >>>> >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rein.henrichs at gmail.com Mon Aug 17 19:20:40 2015 From: rein.henrichs at gmail.com (Rein Henrichs) Date: Mon, 17 Aug 2015 19:20:40 +0000 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> Message-ID: Oh, we're just talking about two different things. `oddsFrom3 = map (+2) oddsFrom3` is just bottom. I was talking about `oddsFrom3 = 3 : map (+2) oddsFrom3`. On Mon, Aug 17, 2015 at 12:02 PM akash g wrote: > Oh, I do apologize for the wrong use of the term `terminal` in this case > which led to this exchange (one that I don't regret as I learned a lot > today; thanks, Rein) . It had to do with my intuition of it (the - works > for me, but can't explain to others - type of intuition). > > On Tue, Aug 18, 2015 at 12:25 AM, akash g wrote: > >> Yes, it is a coinductive structure (though I had a mental picture of the >> list as a coinductive structure, which is what it exactly is as far as >> infinite lists in Haskell are concerned). I got my terms wrong; thanks for >> that. >> >> Let me clarify. By terminal, I meant that the structure itself is made >> up of finite and infinite structures and you've some way of getting to that >> finite part (my intuition as a terminal symbol). >> >> Take the following for an example. >> >> data Stream a = Stream a (Stream a) >> >> Stream, by virtue of construction, will have a finite element (or it can >> be a co-inductive structure again) and an infinite element (the >> continuation of the stream). >> >> However, take the OP's code under question >> >> oddsFrom3 = map (+2) oddsFrom3 -- Goes into an infinite loop; violates >> condition for co-inductiveness; See Link1 >> >> The above is not guarded by a constructor and there is no way to pull >> anything useful out of it without going to an infinite loop. So, it has >> essentially violated the guardedness condition (Link1 to blame/praise for >> this). This is basically something like >> >> ========== >> loop :: [Integer] >> loop = loop -- This compiles, but god it will never end >> ========== >> >> I shouldn't have used the term terminal and I think this is where the >> confusion stems from. My intuition and what it actually is very similar, >> yet subtly different. This might further clarify this (Link1) >> >> >> ============= >> every co-recursive call must be a direct argument to a constructor of the >> co-inductive type we are generating >> ============= >> >> As for inductive vs co-inductive meaning, I think it is because I see the >> co-inductive construction as a special case of the inductive step (at least >> Haskell lets me have this intuition). >> >> >> >> Link1: http://adam.chlipala.net/cpdt/html/Coinductive.html >> Link2: http://c2.com/cgi/wiki?CoinductiveDataType >> >> On Mon, Aug 17, 2015 at 11:29 PM, Rein Henrichs >> wrote: >> >>> It isn't an inductive structure. It's a *coinductive* structure. And >>> yes, coinductive structures are useful in plenty of scenarios. >>> >>> On Mon, Aug 17, 2015 at 10:30 AM akash g wrote: >>> >>>> Oh, it is a valid value (I think I implied this by saying they'll >>>> compile and you can even evaluate). Just not useful in any given scenario >>>> (an inductive structure where you don't have terminals). >>>> >>>> >>>> On Mon, Aug 17, 2015 at 10:57 PM, akash g wrote: >>>> >>>>> @Rein: >>>>> Perhaps I should have been a bit more clear. There is no way to get a >>>>> terminal value from said function. >>>>> >>>>> >>>>> oddsFrom3 :: [Integer] >>>>> oddsFrom3 = map (+2) oddsFrom3 >>>>> >>>>> Try a head for it perhaps. >>>>> >>>>> oddsFrom3 = map (+2) oddsFrom3 >>>>> <=> ((head oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >>>>> <=> ((head (map (+2) oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >>>>> >>>>> Sure, it doesn't hang until you try to evaluate this (in lazy language >>>>> evaluators). However, for any inductive structure, there needs to be a >>>>> (well any finite number of terminals) terminal (base case) which can be >>>>> reached from the starting state in a finite amount of computational >>>>> (condition for termination). Type sigs don't/can't guarantee termination. >>>>> If they don't have a terminal value, you'll never get to the bottom (bad >>>>> pun intended) of it. >>>>> >>>>> >>>>> Take an infinite list as an example. >>>>> >>>>> x a = a : x a >>>>> >>>>> Here, one branch of the tree (representing the list as a highly >>>>> unbalanced tree where every left branch is of depth one at any given >>>>> point). If such a structure is not present, you can never compute it to a >>>>> value and you'll have to infinitely recurse. >>>>> >>>>> Try x a = x a ++ x a >>>>> >>>>> And think of the getting the head from this. You're stuck in an >>>>> infinite loop. >>>>> >>>>> You may also think of the above as a small BNF and try to see if >>>>> termination is possible from the start state. A vaguely intuitive way of >>>>> looking at it for me, but meh, I might be missing something. >>>>> >>>>> >>>>> >>>>> On Mon, Aug 17, 2015 at 10:23 PM, Rein Henrichs < >>>>> rein.henrichs at gmail.com> wrote: >>>>> >>>>>> > The initial version which the OP posted doesn't have a terminal >>>>>> value. >>>>>> >>>>>> The point is that it doesn't need a terminal value. Infinite lists >>>>>> like oddsFrom3 and (repeat "foo") and (let xs = 1 : xs) are all perfectly >>>>>> valid Haskell values. >>>>>> >>>>>> On Mon, Aug 17, 2015 at 6:17 AM Doug McIlroy >>>>>> wrote: >>>>>> >>>>>>> > > oddsFrom3 :: [Integer] >>>>>>> > > oddsFrom3 = 3 : map (+2) oddsFrom3 >>>>>>> > > >>>>>>> > > >>>>>>> > > Thanks for your help. >>>>>>> > >>>>>>> > Try to expand a few steps of the recursion by hand e.g.: >>>>>>> > >>>>>>> > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) >>>>>>> > >>>>>>> > >>>>>>> > As you can see, the deeper you go more 'map (+2)' are applied to >>>>>>> '3'. >>>>>>> >>>>>>> Some more ways to describe the program, which may be useful: >>>>>>> >>>>>>> As with any recursive function, assume you know the whole series and >>>>>>> then confirm that by verifying the inductive step. In this case >>>>>>> oddsFrom3 = [3,5,7,9,11,...] >>>>>>> map (+2) oddsFrom3 = [5,7,9,11,13,...] >>>>>>> voila >>>>>>> oddsFrom3 = 3 : map (+2) oddsFrom3 >>>>>>> >>>>>>> Assuming we have the whole series, we see its tail is >>>>>>> computed from the whole by adding 2 to each element. >>>>>>> Notice that we don't actually have to know the values in the >>>>>>> tail in order to write the formula for the tail. >>>>>>> >>>>>>> Yet another way to describe the program: the "output" is taken >>>>>>> as "input". This works because the first element of the output, >>>>>>> namely 3, is provided in advance. Each output element can then >>>>>>> be computed before it is needed as input. >>>>>>> >>>>>>> In an imperative language this would be done so: >>>>>>> integer oddsFrom3[0:HUGE] >>>>>>> oddsFrom3[0] := 3 >>>>>>> for i:=1 to HUGE do >>>>>>> oddsFrom3[i] = oddsFrom3[i-1] + 2 >>>>>>> _______________________________________________ >>>>>>> Beginners mailing list >>>>>>> Beginners at haskell.org >>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>>>>> >>>>>> >>>>>> _______________________________________________ >>>>>> Beginners mailing list >>>>>> Beginners at haskell.org >>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>>>> >>>>>> >>>>> >>>> _______________________________________________ >>>> Beginners mailing list >>>> Beginners at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>> >>> >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >>> >> > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From akaberto at gmail.com Mon Aug 17 19:29:40 2015 From: akaberto at gmail.com (akash g) Date: Tue, 18 Aug 2015 00:59:40 +0530 Subject: [Haskell-beginners] oddsFrom3 function In-Reply-To: References: <201508171317.t7HDHgHp023058@tahoe.cs.Dartmouth.EDU> Message-ID: I thought that was it but I realized it a bit late Anyway, I learned a lot, thanks to the tangent we went on. Thanks again, Rein. On Tue, Aug 18, 2015 at 12:50 AM, Rein Henrichs wrote: > Oh, we're just talking about two different things. > > `oddsFrom3 = map (+2) oddsFrom3` is just bottom. > > I was talking about `oddsFrom3 = 3 : map (+2) oddsFrom3`. > > On Mon, Aug 17, 2015 at 12:02 PM akash g wrote: > >> Oh, I do apologize for the wrong use of the term `terminal` in this case >> which led to this exchange (one that I don't regret as I learned a lot >> today; thanks, Rein) . It had to do with my intuition of it (the - works >> for me, but can't explain to others - type of intuition). >> >> On Tue, Aug 18, 2015 at 12:25 AM, akash g wrote: >> >>> Yes, it is a coinductive structure (though I had a mental picture of the >>> list as a coinductive structure, which is what it exactly is as far as >>> infinite lists in Haskell are concerned). I got my terms wrong; thanks for >>> that. >>> >>> Let me clarify. By terminal, I meant that the structure itself is made >>> up of finite and infinite structures and you've some way of getting to that >>> finite part (my intuition as a terminal symbol). >>> >>> Take the following for an example. >>> >>> data Stream a = Stream a (Stream a) >>> >>> Stream, by virtue of construction, will have a finite element (or it can >>> be a co-inductive structure again) and an infinite element (the >>> continuation of the stream). >>> >>> However, take the OP's code under question >>> >>> oddsFrom3 = map (+2) oddsFrom3 -- Goes into an infinite loop; violates >>> condition for co-inductiveness; See Link1 >>> >>> The above is not guarded by a constructor and there is no way to pull >>> anything useful out of it without going to an infinite loop. So, it has >>> essentially violated the guardedness condition (Link1 to blame/praise for >>> this). This is basically something like >>> >>> ========== >>> loop :: [Integer] >>> loop = loop -- This compiles, but god it will never end >>> ========== >>> >>> I shouldn't have used the term terminal and I think this is where the >>> confusion stems from. My intuition and what it actually is very similar, >>> yet subtly different. This might further clarify this (Link1) >>> >>> >>> ============= >>> every co-recursive call must be a direct argument to a constructor of >>> the co-inductive type we are generating >>> ============= >>> >>> As for inductive vs co-inductive meaning, I think it is because I see >>> the co-inductive construction as a special case of the inductive step (at >>> least Haskell lets me have this intuition). >>> >>> >>> >>> Link1: http://adam.chlipala.net/cpdt/html/Coinductive.html >>> Link2: http://c2.com/cgi/wiki?CoinductiveDataType >>> >>> On Mon, Aug 17, 2015 at 11:29 PM, Rein Henrichs >> > wrote: >>> >>>> It isn't an inductive structure. It's a *coinductive* structure. And >>>> yes, coinductive structures are useful in plenty of scenarios. >>>> >>>> On Mon, Aug 17, 2015 at 10:30 AM akash g wrote: >>>> >>>>> Oh, it is a valid value (I think I implied this by saying they'll >>>>> compile and you can even evaluate). Just not useful in any given scenario >>>>> (an inductive structure where you don't have terminals). >>>>> >>>>> >>>>> On Mon, Aug 17, 2015 at 10:57 PM, akash g wrote: >>>>> >>>>>> @Rein: >>>>>> Perhaps I should have been a bit more clear. There is no way to get >>>>>> a terminal value from said function. >>>>>> >>>>>> >>>>>> oddsFrom3 :: [Integer] >>>>>> oddsFrom3 = map (+2) oddsFrom3 >>>>>> >>>>>> Try a head for it perhaps. >>>>>> >>>>>> oddsFrom3 = map (+2) oddsFrom3 >>>>>> <=> ((head oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + 2) >>>>>> <=> ((head (map (+2) oddsFrom3) + 2) : map (+2) ((tail oddsFrom3) + >>>>>> 2) >>>>>> >>>>>> Sure, it doesn't hang until you try to evaluate this (in lazy >>>>>> language evaluators). However, for any inductive structure, there needs to >>>>>> be a (well any finite number of terminals) terminal (base case) which can >>>>>> be reached from the starting state in a finite amount of computational >>>>>> (condition for termination). Type sigs don't/can't guarantee termination. >>>>>> If they don't have a terminal value, you'll never get to the bottom (bad >>>>>> pun intended) of it. >>>>>> >>>>>> >>>>>> Take an infinite list as an example. >>>>>> >>>>>> x a = a : x a >>>>>> >>>>>> Here, one branch of the tree (representing the list as a highly >>>>>> unbalanced tree where every left branch is of depth one at any given >>>>>> point). If such a structure is not present, you can never compute it to a >>>>>> value and you'll have to infinitely recurse. >>>>>> >>>>>> Try x a = x a ++ x a >>>>>> >>>>>> And think of the getting the head from this. You're stuck in an >>>>>> infinite loop. >>>>>> >>>>>> You may also think of the above as a small BNF and try to see if >>>>>> termination is possible from the start state. A vaguely intuitive way of >>>>>> looking at it for me, but meh, I might be missing something. >>>>>> >>>>>> >>>>>> >>>>>> On Mon, Aug 17, 2015 at 10:23 PM, Rein Henrichs < >>>>>> rein.henrichs at gmail.com> wrote: >>>>>> >>>>>>> > The initial version which the OP posted doesn't have a terminal >>>>>>> value. >>>>>>> >>>>>>> The point is that it doesn't need a terminal value. Infinite lists >>>>>>> like oddsFrom3 and (repeat "foo") and (let xs = 1 : xs) are all perfectly >>>>>>> valid Haskell values. >>>>>>> >>>>>>> On Mon, Aug 17, 2015 at 6:17 AM Doug McIlroy >>>>>>> wrote: >>>>>>> >>>>>>>> > > oddsFrom3 :: [Integer] >>>>>>>> > > oddsFrom3 = 3 : map (+2) oddsFrom3 >>>>>>>> > > >>>>>>>> > > >>>>>>>> > > Thanks for your help. >>>>>>>> > >>>>>>>> > Try to expand a few steps of the recursion by hand e.g.: >>>>>>>> > >>>>>>>> > 3 : (map (+2) (3 : map (+2) (3 : map (+2) ...))) >>>>>>>> > >>>>>>>> > >>>>>>>> > As you can see, the deeper you go more 'map (+2)' are applied to >>>>>>>> '3'. >>>>>>>> >>>>>>>> Some more ways to describe the program, which may be useful: >>>>>>>> >>>>>>>> As with any recursive function, assume you know the whole series and >>>>>>>> then confirm that by verifying the inductive step. In this case >>>>>>>> oddsFrom3 = [3,5,7,9,11,...] >>>>>>>> map (+2) oddsFrom3 = [5,7,9,11,13,...] >>>>>>>> voila >>>>>>>> oddsFrom3 = 3 : map (+2) oddsFrom3 >>>>>>>> >>>>>>>> Assuming we have the whole series, we see its tail is >>>>>>>> computed from the whole by adding 2 to each element. >>>>>>>> Notice that we don't actually have to know the values in the >>>>>>>> tail in order to write the formula for the tail. >>>>>>>> >>>>>>>> Yet another way to describe the program: the "output" is taken >>>>>>>> as "input". This works because the first element of the output, >>>>>>>> namely 3, is provided in advance. Each output element can then >>>>>>>> be computed before it is needed as input. >>>>>>>> >>>>>>>> In an imperative language this would be done so: >>>>>>>> integer oddsFrom3[0:HUGE] >>>>>>>> oddsFrom3[0] := 3 >>>>>>>> for i:=1 to HUGE do >>>>>>>> oddsFrom3[i] = oddsFrom3[i-1] + 2 >>>>>>>> _______________________________________________ >>>>>>>> Beginners mailing list >>>>>>>> Beginners at haskell.org >>>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>>>>>> >>>>>>> >>>>>>> _______________________________________________ >>>>>>> Beginners mailing list >>>>>>> Beginners at haskell.org >>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>>>>> >>>>>>> >>>>>> >>>>> _______________________________________________ >>>>> Beginners mailing list >>>>> Beginners at haskell.org >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>>> >>>> >>>> _______________________________________________ >>>> Beginners mailing list >>>> Beginners at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>> >>>> >>> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From slussnoah at gmail.com Sun Aug 23 22:06:13 2015 From: slussnoah at gmail.com (Noah Sluss) Date: Sun, 23 Aug 2015 15:06:13 -0700 Subject: [Haskell-beginners] Websockets Library Message-ID: Hello, I've been trying to use the WebSockets library to connect to the coinbase feed. The library seems to be doing something behind the scenes that I'm not expecting. Here is my code: > {-# LANGUAGE ViewPatterns #-} > {-# LANGUAGE OverloadedStrings #-} > > import Data.Text > import Data.Text.Encoding (decodeUtf8) > import Network.WebSockets > import qualified Data.ByteString.Lazy as LBS > > main :: IO () > main = runClient "ws-feed.exchange.coinbase.com" 8080 "/" > handleConnection > handleConnection connection = do > send connection initSub > let loop = do > priceMsg <- receiveDataMessage connection > print priceMsg > loop > > initSub :: Message > initSub = DataMessage $ Text "{\"type\":\"subscribe\", > \"product_id\":\"BTC-USD\"}" When I run this, I get a print out showing a malformed response exception with a Moved permanently message. Now, it also shows the location that I was trying to connect to, which is: "https://ws-feed.exchange.coinbase.com/ ". This isn't right, because the websocket feed uses the wss:// protocol rather than https://. i've tried changing the url to be "wss:// ws-feed.exchange.coinbase.com/", but when I try that, dns resolution fails. If I had to guess, I could imagine that it tries to look for "https://wss:// ws-feed.exchange.coinbase.com", which would obviously not work. I'm wondering if there is a way within the library to change the protocol that client uses. If there is, it doesn't seem to be documented. Any insights as to what's going on here would be incredibly helpful. Thanks, Noah -------------- next part -------------- An HTML attachment was scrubbed... URL: From defigueiredo at ucdavis.edu Sun Aug 23 22:19:36 2015 From: defigueiredo at ucdavis.edu (Dimitri DeFigueiredo) Date: Sun, 23 Aug 2015 16:19:36 -0600 Subject: [Haskell-beginners] Websockets Library In-Reply-To: References: Message-ID: <55DA46F8.9060007@ucdavis.edu> Hi Noah, I haven't looked at your code, but this library parses that same feed. (It's also on Hackage) https://github.com/AndrewRademacher/coinbase-exchange You may want to either use it or take a look at the code. Cheers, Dimitri Em 23/08/15 16:06, Noah Sluss escreveu: > Hello, > > I've been trying to use the WebSockets library to connect to the > coinbase feed. The library seems to be doing something behind the > scenes that I'm not expecting. > > Here is my code: > > {-# LANGUAGE ViewPatterns #-} > {-# LANGUAGE OverloadedStrings #-} > > import Data.Text > import Data.Text.Encoding (decodeUtf8) > import Network.WebSockets > import qualified Data.ByteString.Lazy as LBS > > main :: IO () > main = runClient "ws-feed.exchange.coinbase.com > " 8080 "/" handleConnection > handleConnection connection = do > send connection initSub > let loop = do > priceMsg <- receiveDataMessage connection > print priceMsg > loop > > initSub :: Message > initSub = DataMessage $ Text "{\"type\":\"subscribe\", > \"product_id\":\"BTC-USD\"}" > > > When I run this, I get a print out showing a malformed response > exception with a Moved permanently message. Now, it also shows the > location that I was trying to connect to, which is: > "https://ws-feed.exchange.coinbase.com/". > > This isn't right, because the websocket feed uses the wss:// protocol > rather than https://. i've tried changing the url to be > "wss://ws-feed.exchange.coinbase.com/ > ", but when I try that, > dns resolution fails. If I had to guess, I could imagine that it tries > to look for "https://wss://ws-feed.exchange.coinbase.com > ", which would obviously not > work. I'm wondering if there is a way within the library to change the > protocol that client uses. If there is, it doesn't seem to be > documented. > > Any insights as to what's going on here would be incredibly helpful. > > Thanks, > Noah > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at adamflott.com Thu Aug 27 15:04:38 2015 From: adam at adamflott.com (Adam Flott) Date: Thu, 27 Aug 2015 11:04:38 -0400 Subject: [Haskell-beginners] converting a json encoded radix tree to a haskell data type Message-ID: <55DF2706.9090703@adamflott.com> I'm having trouble converting a JSON encoded Radix tree into a Haskell data type[1]. I've tried numerous ways to get the FromJSON instances to handle all cases, but failing miserably. [1] unfortunately these type layouts are unchangeable as they are auto generated types from Thrift Here is a stripped down version of what I'm working with. For the JSON file, all keys are unknown at parse time. I only know that a key will be a string and it's value will be another JSON object or a JSON array of fixed length. Any help is appreciated. -- radix.hs -- {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} import Control.Monad (mzero) import Data.Int import Data.Typeable import Data.Aeson import qualified Data.ByteString.Lazy as BL import Data.Text.Lazy as TL import qualified Data.Vector as V data Things = MkThings { thing :: TL.Text, times :: ThingTimes } deriving (Show, Eq, Typeable) data ThingTimes = MkThingtimes { ml :: V.Vector Times } deriving (Show, Eq, Typeable) data Times = MkTimes { t1 :: Maybe Int32, t2 :: Maybe Int32 } deriving (Show, Eq, Typeable) instance FromJSON (V.Vector Things) where parseJSON _ = return V.empty decodeRadix ::BL.ByteString -> Either String (V.Vector Things) decodeRadix = eitherDecode main :: IO () main = do j <- BL.readFile "radix.json" case decodeRadix j of Left err -> error err Right r -> print r -- radix.hs -- -- radix.json -- { "a" : { "b" : [ 1, 2 ], "c" : { "d" : [ 3, null ] } }, "a2" : { "b2" : [ 4, 5 ] } } -- radix.json -- From karl at karlv.net Thu Aug 27 15:18:45 2015 From: karl at karlv.net (Karl Voelker) Date: Thu, 27 Aug 2015 08:18:45 -0700 Subject: [Haskell-beginners] converting a json encoded radix tree to a haskell data type In-Reply-To: <55DF2706.9090703@adamflott.com> References: <55DF2706.9090703@adamflott.com> Message-ID: <1440688725.3956294.367671881.7F4D1AEF@webmail.messagingengine.com> On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote: > data Things = MkThings { > thing :: TL.Text, > times :: ThingTimes > } deriving (Show, Eq, Typeable) > > data ThingTimes = MkThingtimes { > ml :: V.Vector Times > } deriving (Show, Eq, Typeable) > > data Times = MkTimes { > t1 :: Maybe Int32, > t2 :: Maybe Int32 > } deriving (Show, Eq, Typeable) > > -- radix.json -- > { > "a" : { > "b" : [ 1, 2 ], > "c" : { > "d" : [ 3, null ] > } > }, > "a2" : { "b2" : [ 4, 5 ] } > } > -- radix.json -- It looks like your input file has Things nested inside Things, but your data types don't allow for that. Is that intentional? What value is that example input supposed to parse to? -Karl From adam at adamflott.com Thu Aug 27 15:30:36 2015 From: adam at adamflott.com (Adam Flott) Date: Thu, 27 Aug 2015 11:30:36 -0400 Subject: [Haskell-beginners] converting a json encoded radix tree to a haskell data type In-Reply-To: <1440688725.3956294.367671881.7F4D1AEF@webmail.messagingengine.com> References: <55DF2706.9090703@adamflott.com> <1440688725.3956294.367671881.7F4D1AEF@webmail.messagingengine.com> Message-ID: <55DF2D1C.9060801@adamflott.com> On 08/27/2015 11:18 AM, Karl Voelker wrote: > On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote: >> data Things = MkThings { >> thing :: TL.Text, >> times :: ThingTimes >> } deriving (Show, Eq, Typeable) >> >> data ThingTimes = MkThingtimes { >> ml :: V.Vector Times >> } deriving (Show, Eq, Typeable) >> >> data Times = MkTimes { >> t1 :: Maybe Int32, >> t2 :: Maybe Int32 >> } deriving (Show, Eq, Typeable) >> >> -- radix.json -- >> { >> "a" : { >> "b" : [ 1, 2 ], >> "c" : { >> "d" : [ 3, null ] >> } >> }, >> "a2" : { "b2" : [ 4, 5 ] } >> } >> -- radix.json -- > It looks like your input file has Things nested inside Things, but your > data types don't allow for that. Is that intentional? What value is that > example input supposed to parse to? Vector [ MkThings "ab" (MkThingTimes (Vector [ Just 1, Just 2 ])), MkThings "abcd" (MkThingsTimes (Vector [ Just 3, Nothing)) MkThings "a2b2" (MkThingTimes (Vector [ Just 4, Just 5 ])) ] From toad3k at gmail.com Thu Aug 27 17:45:54 2015 From: toad3k at gmail.com (David McBride) Date: Thu, 27 Aug 2015 13:45:54 -0400 Subject: [Haskell-beginners] converting a json encoded radix tree to a haskell data type In-Reply-To: <55DF2D1C.9060801@adamflott.com> References: <55DF2706.9090703@adamflott.com> <1440688725.3956294.367671881.7F4D1AEF@webmail.messagingengine.com> <55DF2D1C.9060801@adamflott.com> Message-ID: I was trying this but ran into a bit of trouble. Are you super attached to that data structure? I would expect a radix tree as you've described it to look more like this: data RadixTree = Node [(Text, RadixTree)] | Leaf Times data Times = Times (Maybe Int) (Maybe Int) In which case it is much easier to write the json instances. From there you shouldn't have too much of a problem writing a recursive function to do the rest, without dealing with all the aeson stuff at the same time. Here's what I ended up with (I think it could be cleaned up a bit). import Control.Monad import Data.Text as T import Data.Aeson import Data.HashMap.Strict as HM import Data.Vector as V hiding (mapM) data RadixTree = Node [(Text, RadixTree)] | Leaf Times deriving Show data Times = Times (Maybe Int) (Maybe Int) deriving Show instance FromJSON RadixTree where parseJSON (Object o) = do let els = HM.toList o contents <- mapM (\(t,v) -> do v' <- parseJSON v; return (t, v')) (HM.toList o) return $ Node contents parseJSON a@(Array _) = Leaf <$> parseJSON a parseJSON _ = mzero instance FromJSON Times where parseJSON (Array v) | (V.length v) >= 2 = let v0 = v V.! 0 v1 = v V.! 1 in Times <$> parseJSON v0 <*> parseJSON v1 parseJSON _ = mzero {- tree2things :: RadixTree -> [(Text, (Maybe Int, Maybe Int))] tree2things (Node xs) = _ tree2things (Leaf t) = _ -} On Thu, Aug 27, 2015 at 11:30 AM, Adam Flott wrote: > On 08/27/2015 11:18 AM, Karl Voelker wrote: > > On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote: > >> data Things = MkThings { > >> thing :: TL.Text, > >> times :: ThingTimes > >> } deriving (Show, Eq, Typeable) > >> > >> data ThingTimes = MkThingtimes { > >> ml :: V.Vector Times > >> } deriving (Show, Eq, Typeable) > >> > >> data Times = MkTimes { > >> t1 :: Maybe Int32, > >> t2 :: Maybe Int32 > >> } deriving (Show, Eq, Typeable) > >> > >> -- radix.json -- > >> { > >> "a" : { > >> "b" : [ 1, 2 ], > >> "c" : { > >> "d" : [ 3, null ] > >> } > >> }, > >> "a2" : { "b2" : [ 4, 5 ] } > >> } > >> -- radix.json -- > > It looks like your input file has Things nested inside Things, but your > > data types don't allow for that. Is that intentional? What value is that > > example input supposed to parse to? > > Vector [ > MkThings "ab" (MkThingTimes (Vector [ Just 1, Just 2 ])), > MkThings "abcd" (MkThingsTimes (Vector [ Just 3, Nothing)) > MkThings "a2b2" (MkThingTimes (Vector [ Just 4, Just 5 ])) ] > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at adamflott.com Thu Aug 27 20:31:25 2015 From: adam at adamflott.com (Adam Flott) Date: Thu, 27 Aug 2015 16:31:25 -0400 Subject: [Haskell-beginners] converting a json encoded radix tree to a haskell data type In-Reply-To: References: <55DF2706.9090703@adamflott.com> <1440688725.3956294.367671881.7F4D1AEF@webmail.messagingengine.com> <55DF2D1C.9060801@adamflott.com> Message-ID: <55DF739D.7040508@adamflott.com> I am attached to the data structure as it's what our Thrift message spits out and has to be mapped that way for the down stream consumers. On 08/27/2015 01:45 PM, David McBride wrote: > I was trying this but ran into a bit of trouble. Are you super > attached to that data structure? I would expect a radix tree as > you've described it to look more like this: > > data RadixTree = Node [(Text, RadixTree)] | Leaf Times > data Times = Times (Maybe Int) (Maybe Int) > > In which case it is much easier to write the json instances. From > there you shouldn't have too much of a problem writing a recursive > function to do the rest, without dealing with all the aeson stuff at > the same time. Here's what I ended up with (I think it could be > cleaned up a bit). > > import Control.Monad > import Data.Text as T > import Data.Aeson > import Data.HashMap.Strict as HM > import Data.Vector as V hiding (mapM) > > data RadixTree = Node [(Text, RadixTree)] | Leaf Times deriving Show > data Times = Times (Maybe Int) (Maybe Int) deriving Show > > instance FromJSON RadixTree where > parseJSON (Object o) = do > let els = HM.toList o > contents <- mapM (\(t,v) -> do v' <- parseJSON v; return (t, v')) > (HM.toList o) > return $ Node contents > parseJSON a@(Array _) = Leaf <$> parseJSON a > parseJSON _ = mzero > > instance FromJSON Times where > parseJSON (Array v) | (V.length v) >= 2 = > let v0 = v V.! 0 > v1 = v V.! 1 > in Times <$> parseJSON v0 <*> parseJSON v1 > parseJSON _ = mzero > > {- > tree2things :: RadixTree -> [(Text, (Maybe Int, Maybe Int))] > tree2things (Node xs) = _ > tree2things (Leaf t) = _ > -} > > On Thu, Aug 27, 2015 at 11:30 AM, Adam Flott > wrote: > > On 08/27/2015 11:18 AM, Karl Voelker wrote: > > On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote: > >> data Things = MkThings { > >> thing :: TL.Text, > >> times :: ThingTimes > >> } deriving (Show, Eq, Typeable) > >> > >> data ThingTimes = MkThingtimes { > >> ml :: V.Vector Times > >> } deriving (Show, Eq, Typeable) > >> > >> data Times = MkTimes { > >> t1 :: Maybe Int32, > >> t2 :: Maybe Int32 > >> } deriving (Show, Eq, Typeable) > >> > >> -- radix.json -- > >> { > >> "a" : { > >> "b" : [ 1, 2 ], > >> "c" : { > >> "d" : [ 3, null ] > >> } > >> }, > >> "a2" : { "b2" : [ 4, 5 ] } > >> } > >> -- radix.json -- > > It looks like your input file has Things nested inside Things, > but your > > data types don't allow for that. Is that intentional? What value > is that > > example input supposed to parse to? > > Vector [ > MkThings "ab" (MkThingTimes (Vector [ Just 1, Just 2 ])), > MkThings "abcd" (MkThingsTimes (Vector [ Just 3, Nothing)) > MkThings "a2b2" (MkThingTimes (Vector [ Just 4, Just 5 ])) ] > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners From toad3k at gmail.com Fri Aug 28 16:45:35 2015 From: toad3k at gmail.com (David McBride) Date: Fri, 28 Aug 2015 12:45:35 -0400 Subject: [Haskell-beginners] converting a json encoded radix tree to a haskell data type In-Reply-To: <55DF739D.7040508@adamflott.com> References: <55DF2706.9090703@adamflott.com> <1440688725.3956294.367671881.7F4D1AEF@webmail.messagingengine.com> <55DF2D1C.9060801@adamflott.com> <55DF739D.7040508@adamflott.com> Message-ID: Well I went ahead and completed that function, but I didn't use your data types exactly, but it should be a one to one mapping, just modify this function with your constructors. radix2things :: RadixTree -> [(Text, (Maybe Int, Maybe Int))] radix2things r = conv' mempty r where conv' :: Text -> RadixTree -> [(Text, (Maybe Int, Maybe Int))] conv' acc (Leaf (Times a b)) = [(acc, (a, b))] conv' acc r@(Node ns) = P.concatMap (\(t,r) -> conv' (acc <> t) r) ns And you'll get a result like: *Main> case decode teststr of Nothing -> undefined; Just a -> conv a [("a2b2",(Just 4,Just 5)),("ab",(Just 1,Just 2)),("acd",(Just 3,Nothing))] Good luck. On Thu, Aug 27, 2015 at 4:31 PM, Adam Flott wrote: > I am attached to the data structure as it's what our Thrift message > spits out and has to be mapped that way for the down stream consumers. > > > On 08/27/2015 01:45 PM, David McBride wrote: > > I was trying this but ran into a bit of trouble. Are you super > > attached to that data structure? I would expect a radix tree as > > you've described it to look more like this: > > > > data RadixTree = Node [(Text, RadixTree)] | Leaf Times > > data Times = Times (Maybe Int) (Maybe Int) > > > > In which case it is much easier to write the json instances. From > > there you shouldn't have too much of a problem writing a recursive > > function to do the rest, without dealing with all the aeson stuff at > > the same time. Here's what I ended up with (I think it could be > > cleaned up a bit). > > > > import Control.Monad > > import Data.Text as T > > import Data.Aeson > > import Data.HashMap.Strict as HM > > import Data.Vector as V hiding (mapM) > > > > data RadixTree = Node [(Text, RadixTree)] | Leaf Times deriving Show > > data Times = Times (Maybe Int) (Maybe Int) deriving Show > > > > instance FromJSON RadixTree where > > parseJSON (Object o) = do > > let els = HM.toList o > > contents <- mapM (\(t,v) -> do v' <- parseJSON v; return (t, v')) > > (HM.toList o) > > return $ Node contents > > parseJSON a@(Array _) = Leaf <$> parseJSON a > > parseJSON _ = mzero > > > > instance FromJSON Times where > > parseJSON (Array v) | (V.length v) >= 2 = > > let v0 = v V.! 0 > > v1 = v V.! 1 > > in Times <$> parseJSON v0 <*> parseJSON v1 > > parseJSON _ = mzero > > > > {- > > tree2things :: RadixTree -> [(Text, (Maybe Int, Maybe Int))] > > tree2things (Node xs) = _ > > tree2things (Leaf t) = _ > > -} > > > > On Thu, Aug 27, 2015 at 11:30 AM, Adam Flott > > wrote: > > > > On 08/27/2015 11:18 AM, Karl Voelker wrote: > > > On Thu, Aug 27, 2015, at 08:04 AM, Adam Flott wrote: > > >> data Things = MkThings { > > >> thing :: TL.Text, > > >> times :: ThingTimes > > >> } deriving (Show, Eq, Typeable) > > >> > > >> data ThingTimes = MkThingtimes { > > >> ml :: V.Vector Times > > >> } deriving (Show, Eq, Typeable) > > >> > > >> data Times = MkTimes { > > >> t1 :: Maybe Int32, > > >> t2 :: Maybe Int32 > > >> } deriving (Show, Eq, Typeable) > > >> > > >> -- radix.json -- > > >> { > > >> "a" : { > > >> "b" : [ 1, 2 ], > > >> "c" : { > > >> "d" : [ 3, null ] > > >> } > > >> }, > > >> "a2" : { "b2" : [ 4, 5 ] } > > >> } > > >> -- radix.json -- > > > It looks like your input file has Things nested inside Things, > > but your > > > data types don't allow for that. Is that intentional? What value > > is that > > > example input supposed to parse to? > > > > Vector [ > > MkThings "ab" (MkThingTimes (Vector [ Just 1, Just 2 ])), > > MkThings "abcd" (MkThingsTimes (Vector [ Just 3, Nothing)) > > MkThings "a2b2" (MkThingTimes (Vector [ Just 4, Just 5 ])) ] > > _______________________________________________ > > Beginners mailing list > > Beginners at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > > > > > > > > > _______________________________________________ > > Beginners mailing list > > Beginners at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From wewilliams at paypal.com Fri Aug 28 17:12:29 2015 From: wewilliams at paypal.com (Williams, Wes(AWF)) Date: Fri, 28 Aug 2015 17:12:29 +0000 Subject: [Haskell-beginners] applicative style Message-ID: Hi haskellers, I am trying to understand why I get the following error in learning applicative style. Prelude> let estimates = [5,5,8,8,2,1,5,2] Prelude> (/) <$> Just $ foldl (+) 0 estimates <*> Just . fromIntegral $ length estimates :54:1: Non type-variable argument in the constraint: Fractional (Maybe r) (Use FlexibleContexts to permit this) When checking that 'it' has the inferred type it :: forall a r. (Fractional (Maybe r), Num a, Num (Int -> Maybe a -> r)) => Maybe r -> Maybe r All the parts work individually. If use let and assign the parts to x and y it also works. E.g. This works let x = Just $ foldl (+) estimates Let y = Just . fromIntegral $ length estimates (/) <$> x <*> y I clearly do not understand exactly how these work. :-) Thanks for any help, -wes -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Fri Aug 28 17:23:10 2015 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 28 Aug 2015 13:23:10 -0400 Subject: [Haskell-beginners] applicative style In-Reply-To: References: Message-ID: On Fri, Aug 28, 2015 at 1:12 PM, Williams, Wes(AWF) wrote: > Num (Int -> Maybe a -> r)) That looks highly suspect. If it infers a function Num instance, you probably got your parentheses wrong. Or your $-s... ...in fact, that is the problem. That final $ does not do what you think; it produces (foldl (+) 0 estimates <*> Just . fromIntegral) (length estimates) when you presumably intended foldl (+) 0 estimates <+> (Just . fromIntegral) (length estimates) -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From wewilliams at paypal.com Fri Aug 28 18:31:39 2015 From: wewilliams at paypal.com (Williams, Wes(AWF)) Date: Fri, 28 Aug 2015 18:31:39 +0000 Subject: [Haskell-beginners] applicative style Message-ID: Awesome, I clearly am off on my understanding. How could I do this: "foldl (+) 0 estimates <+> (Just . fromIntegral) (length estimates)" without the parenthesis? Thanks, Wes -------------- next part -------------- An HTML attachment was scrubbed... URL: From wewilliams at paypal.com Fri Aug 28 18:51:46 2015 From: wewilliams at paypal.com (Williams, Wes(AWF)) Date: Fri, 28 Aug 2015 18:51:46 +0000 Subject: [Haskell-beginners] applicative style In-Reply-To: References: Message-ID: The actual code I have working is: let estimates = [5,5,8,8,2,1,5,2] (/) <$> (Just $ foldl (+) 0 estimates) <*> ((Just . fromIntegral) (length estimates)) What I want to do is get rid of all the parentheses except (/) Is it possible? Thanks, wes From: Beginners > on behalf of "Williams, Wes(AWF)" > Reply-To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell > Date: Friday, August 28, 2015 at 11:31 AM To: "beginners at haskell.org" > Subject: [Haskell-beginners] applicative style Awesome, I clearly am off on my understanding. How could I do this: "foldl (+) 0 estimates <+> (Just . fromIntegral) (length estimates)" without the parenthesis? Thanks, Wes -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Fri Aug 28 19:01:46 2015 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 28 Aug 2015 15:01:46 -0400 Subject: [Haskell-beginners] applicative style In-Reply-To: References: Message-ID: On Fri, Aug 28, 2015 at 2:51 PM, Williams, Wes(AWF) wrote: > What I want to do is get rid of all the parentheses except (/) > Is it possible? > Not without breaking it up into chunks like you did in ghci (probably using a let or where). -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From wewilliams at paypal.com Fri Aug 28 20:39:36 2015 From: wewilliams at paypal.com (Williams, Wes(AWF)) Date: Fri, 28 Aug 2015 20:39:36 +0000 Subject: [Haskell-beginners] applicative style In-Reply-To: References: Message-ID: Thanks for the feedback and guidance Brandon! From: Beginners > on behalf of Brandon Allbery > Reply-To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell > Date: Friday, August 28, 2015 at 12:01 PM To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell > Subject: Re: [Haskell-beginners] applicative style On Fri, Aug 28, 2015 at 2:51 PM, Williams, Wes(AWF) > wrote: What I want to do is get rid of all the parentheses except (/) Is it possible? Not without breaking it up into chunks like you did in ghci (probably using a let or where). -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From miroslav.karpis at gmail.com Fri Aug 28 23:57:48 2015 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Sat, 29 Aug 2015 01:57:48 +0200 Subject: [Haskell-beginners] recursion - more elegant solution Message-ID: Hi haskellers, I have made one recursive function, where input is: nodesIds: [1,2,4,3,5] edgesIds: [(3,5),(4,3),(2,4),(1,2)] and on output I need/have: [([1,2,4,3,5],(3,5)),([1,2,4,3],(4,3)),([1,2,4],(2,4)),([1,2],(1,2))] I have made one function for this, but it seems to me a bit too big and 'ugly'? Please, do you have any hints for a more elegant solution? joinEdgeNodes' :: [Int] -> [Int] -> [(Int, Int)] -> [([Int], (Int, Int))] joinEdgeNodes' [] _ [] = [] joinEdgeNodes' [] _ _ = [] joinEdgeNodes' _ _ [] = [] joinEdgeNodes' (n) (wn) [e] = [(n, e)] joinEdgeNodes' (n) [] (e:es) = joinEdgeNodes' n edgeNodes es ++ [(edgeNodes, e)] where edgeNodes = take 2 n joinEdgeNodes' (n) (wn) (e:es) = joinEdgeNodes' n edgeNodes es ++ [(edgeNodes, e)] where edgeNodes = take edgeNodesLength n edgeNodesLength = (length wn) + 1 I call the function with: let l = joinEdgeNodes' nodeIds [] edgeIds Cheers, Miro -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Sat Aug 29 00:23:12 2015 From: fa-ml at ariis.it (Francesco Ariis) Date: Sat, 29 Aug 2015 02:23:12 +0200 Subject: [Haskell-beginners] recursion - more elegant solution In-Reply-To: References: Message-ID: <20150829002312.GA13759@casa.casa> On Sat, Aug 29, 2015 at 01:57:48AM +0200, Miro Karpis wrote: > Hi haskellers, I have made one recursive function, where > > > input is: > nodesIds: [1,2,4,3,5] > edgesIds: [(3,5),(4,3),(2,4),(1,2)] > > and on output I need/have: > [([1,2,4,3,5],(3,5)),([1,2,4,3],(4,3)),([1,2,4],(2,4)),([1,2],(1,2))] > > I have made one function for this, but it seems to me a bit too big and > 'ugly'? Please, do you have any hints for a more elegant solution? > > joinEdgeNodes' :: [Int] -> [Int] -> [(Int, Int)] -> [([Int], (Int, Int))] > joinEdgeNodes' [] _ [] = [] > joinEdgeNodes' [] _ _ = [] > joinEdgeNodes' _ _ [] = [] > joinEdgeNodes' (n) (wn) [e] = [(n, e)] > joinEdgeNodes' (n) [] (e:es) = joinEdgeNodes' n edgeNodes es ++ > [(edgeNodes, e)] > where edgeNodes = take 2 n > joinEdgeNodes' (n) (wn) (e:es) = joinEdgeNodes' n edgeNodes es ++ > [(edgeNodes, e)] > where edgeNodes = take edgeNodesLength n > edgeNodesLength = (length wn) + 1 > > I call the function with: let l = joinEdgeNodes' nodeIds [] edgeIds Have you looked into `inits` (from Data.List), `reverse` and `zip`? something like: ?> :m +Data.List ?> let a = [1,2,4,3,5] ?> let b = [(3,5),(4,3),(2,4),(1,2)] ?> zip (reverse . inits $ a) b [([1,2,4,3,5],(3,5)),([1,2,4,3],(4,3)),([1,2,4],(2,4)),([1,2],(1,2))] seems to lead to the correct output -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From miroslav.karpis at gmail.com Sat Aug 29 06:38:56 2015 From: miroslav.karpis at gmail.com (Miro) Date: Sat, 29 Aug 2015 08:38:56 +0200 Subject: [Haskell-beginners] recursion - more elegant solution In-Reply-To: <20150829002312.GA13759@casa.casa> References: <20150829002312.GA13759@casa.casa> Message-ID: <55e153ac.4825980a.eb7e9.ffff876c@mx.google.com> Thank you! This is so much better :-) -----Original Message----- From: "Francesco Ariis" Sent: ?29/?08/?2015 02:24 To: "beginners at haskell.org" Subject: Re: [Haskell-beginners] recursion - more elegant solution On Sat, Aug 29, 2015 at 01:57:48AM +0200, Miro Karpis wrote: > Hi haskellers, I have made one recursive function, where > > > input is: > nodesIds: [1,2,4,3,5] > edgesIds: [(3,5),(4,3),(2,4),(1,2)] > > and on output I need/have: > [([1,2,4,3,5],(3,5)),([1,2,4,3],(4,3)),([1,2,4],(2,4)),([1,2],(1,2))] > > I have made one function for this, but it seems to me a bit too big and > 'ugly'? Please, do you have any hints for a more elegant solution? > > joinEdgeNodes' :: [Int] -> [Int] -> [(Int, Int)] -> [([Int], (Int, Int))] > joinEdgeNodes' [] _ [] = [] > joinEdgeNodes' [] _ _ = [] > joinEdgeNodes' _ _ [] = [] > joinEdgeNodes' (n) (wn) [e] = [(n, e)] > joinEdgeNodes' (n) [] (e:es) = joinEdgeNodes' n edgeNodes es ++ > [(edgeNodes, e)] > where edgeNodes = take 2 n > joinEdgeNodes' (n) (wn) (e:es) = joinEdgeNodes' n edgeNodes es ++ > [(edgeNodes, e)] > where edgeNodes = take edgeNodesLength n > edgeNodesLength = (length wn) + 1 > > I call the function with: let l = joinEdgeNodes' nodeIds [] edgeIds Have you looked into `inits` (from Data.List), `reverse` and `zip`? something like: ?> :m +Data.List ?> let a = [1,2,4,3,5] ?> let b = [(3,5),(4,3),(2,4),(1,2)] ?> zip (reverse . inits $ a) b [([1,2,4,3,5],(3,5)),([1,2,4,3],(4,3)),([1,2,4],(2,4)),([1,2],(1,2))] seems to lead to the correct output -------------- next part -------------- An HTML attachment was scrubbed... URL: From john2x at gmail.com Sun Aug 30 06:27:49 2015 From: john2x at gmail.com (John Del Rosario) Date: Sun, 30 Aug 2015 14:27:49 +0800 Subject: [Haskell-beginners] Difficulty understanding the Towers of Hanoi exercise from CIS194 Message-ID: I've just completed the first exercise (Credit Card Number Validation) and was quite happy with myself. But moving on to the next exercise I found myself having trouble trying to understand some parts of the question. I've solved Towers of Hanoi before with an imperative language, but I'm having trouble visualising the steps described in this paragraph: To move n discs (stacked in increasing size) from peg a to peg b using peg c as temporary storage, 1. move n-1 discs from a to c using b as temporary storage 2. move the top disc from a to b 3. move n-1 discs from c to b using a as temporary storage. I've never seen the solution described this way before. So if I start with 5 discs, then for the first step I'll be moving 4 (n-1) discs? But can't I only move 1 disc at a time? And step 2 says to move the top disc from a to b. Which disc is the top disc at this point? I'm still in a very imperative mindset (and having no formal training doesn't help), but I'm hoping that will improve as I go through this course! -------------- next part -------------- An HTML attachment was scrubbed... URL: From petr.vapenka at gmail.com Sun Aug 30 08:22:20 2015 From: petr.vapenka at gmail.com (=?UTF-8?Q?Petr_V=C3=A1penka?=) Date: Sun, 30 Aug 2015 10:22:20 +0200 Subject: [Haskell-beginners] Difficulty understanding the Towers of Hanoi exercise from CIS194 In-Reply-To: References: Message-ID: The tower of hanoi function you are writing is doing the "move n discs from peg A to peg C using peg B" stuff. 1. moving n-1 discs doesn't mean moving them in one step, but rather using the proper sequence of moves that results in (n-1) discs to be moved 2. after you've moved n-1 discs, only one disc is left on the peg and it is the largest disc from the set of n discs 3. do the same as in point 1 Try to translate the steps literally to code, it will work and understanding will come after that :) Best, PV On Sun, Aug 30, 2015 at 8:27 AM, John Del Rosario wrote: > I've just completed the first exercise (Credit Card Number Validation) > and was quite happy with myself. > > But moving on to the next exercise I found myself having trouble trying > to understand some parts of the question. > > I've solved Towers of Hanoi before with an imperative language, > but I'm having trouble visualising the steps described in this paragraph: > > To move n discs (stacked in increasing size) from peg a to peg b using peg > c > as temporary storage, > 1. move n-1 discs from a to c using b as temporary storage > 2. move the top disc from a to b > 3. move n-1 discs from c to b using a as temporary storage. > > I've never seen the solution described this way before. > So if I start with 5 discs, then for the first step I'll be moving 4 (n-1) > discs? But > can't I only move 1 disc at a time? > > And step 2 says to move the top disc from a to b. Which disc is the top > disc at this point? > > I'm still in a very imperative mindset (and having no formal training > doesn't help), > but I'm hoping that will improve as I go through this course! > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ky3 at atamo.com Sun Aug 30 09:16:44 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Sun, 30 Aug 2015 16:16:44 +0700 Subject: [Haskell-beginners] Difficulty understanding the Towers of Hanoi exercise from CIS194 In-Reply-To: References: Message-ID: On Sun, Aug 30, 2015 at 1:27 PM, John Del Rosario wrote: > So if I start with 5 discs, then for the first step I'll be moving 4 (n-1) > discs? But > can't I only move 1 disc at a time? > Yes, the problem description elides a few explanations. The idea is that there are two kinds of moves: "atomic" moves where we move 1 disc at a time. And then there's a "big" move, comprising a sequence of atomic moves. One big move accomplishes one unified goal. An example of a big move is moving 4 discs from one peg to another. In the problem text, whether a "move" refers to an atomic move or a big move is something left for the reader to infer. A shortcut is to take every mention of "move" to mean a sequence of one or more atomic moves. But that clashes with the fact that Move is a type synonym representing only atomic moves. Result: confusion. More precise wording of the problem will help. I have nothing to do with CIS194, but allow me to thank you for the pedagogical bug report all the same. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From tkoster at gmail.com Mon Aug 31 00:16:42 2015 From: tkoster at gmail.com (Thomas Koster) Date: Mon, 31 Aug 2015 10:16:42 +1000 Subject: [Haskell-beginners] Stack and packages not in the snapshot Message-ID: Good morning list, I have started to use stack with Stackage LTS for building my projects because I like the idea of a stable snapshot of packages known to work together. Then I tried to build "x509-util-1.5.2". This package fails to build and this is already known by upstream. And lo, "x509-util" is not in Stackage LTS 3.2, which makes sense. But what surprised me is that stack attempted to build a package not in the snapshot, when my resolver is "lts-3.2" (and no extra-deps). Is there a way to configure stack to build packages from the snapshot only? Or does it already work this way, only trying "x509-util" because *I* said "stack build x509-util"? Thanks in advance. -- Thomas Koster From michael at snoyman.com Mon Aug 31 06:16:59 2015 From: michael at snoyman.com (Michael Snoyman) Date: Mon, 31 Aug 2015 09:16:59 +0300 Subject: [Haskell-beginners] Stack and packages not in the snapshot In-Reply-To: References: Message-ID: Your last paragraph is correct: stack will never automatically pull in a package that's not explicitly added to your build plan (either via snapshot or extra-deps), but if you run `stack build foo`, it will listen to you and install it. The exact semantics of this are covered in: https://github.com/commercialhaskell/stack/wiki/Build-command On Mon, Aug 31, 2015 at 3:16 AM, Thomas Koster wrote: > Good morning list, > > I have started to use stack with Stackage LTS for building my projects > because I like the idea of a stable snapshot of packages known to work > together. > > Then I tried to build "x509-util-1.5.2". This package fails to build > and this is already known by upstream. > > And lo, "x509-util" is not in Stackage LTS 3.2, which makes sense. > > But what surprised me is that stack attempted to build a package not > in the snapshot, when my resolver is "lts-3.2" (and no extra-deps). > > Is there a way to configure stack to build packages from the snapshot > only? Or does it already work this way, only trying "x509-util" > because *I* said "stack build x509-util"? > > Thanks in advance. > -- > Thomas Koster > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tkoster at gmail.com Mon Aug 31 06:24:09 2015 From: tkoster at gmail.com (Thomas Koster) Date: Mon, 31 Aug 2015 16:24:09 +1000 Subject: [Haskell-beginners] Stack and packages not in the snapshot In-Reply-To: References: Message-ID: On Mon, Aug 31, 2015 at 3:16 AM, Thomas Koster wrote: > Is there a way to configure stack to build packages from the snapshot > only? Or does it already work this way, only trying "x509-util" > because *I* said "stack build x509-util"? On 31 August 2015 at 16:16, Michael Snoyman wrote: > Your last paragraph is correct: stack will never automatically pull in a > package that's not explicitly added to your build plan (either via snapshot > or extra-deps), but if you run `stack build foo`, it will listen to you and > install it. The exact semantics of this are covered in: > > https://github.com/commercialhaskell/stack/wiki/Build-command Thanks for the clarification. -- Thomas Koster