From mike_k_houghton at yahoo.co.uk Wed Dec 2 10:30:37 2020 From: mike_k_houghton at yahoo.co.uk (mike h) Date: Wed, 2 Dec 2020 10:30:37 +0000 Subject: [Haskell-beginners] Desugar list comprehension References: <84D90B6C-8C1F-4EAB-A573-38D1E3388F97.ref@yahoo.co.uk> Message-ID: <84D90B6C-8C1F-4EAB-A573-38D1E3388F97@yahoo.co.uk> Hi, I have sumIs2020P1' xs = do x <- xs y <- xs guard (x + y == 2020) pure (x,y) which has been desugared from a list comprehension I would like to reduce this even more using >>= So I do sumIs2020P1'' xs = (a,b) where (a,b):rest = filter (\(x,y) -> x + y == 2020) pairs pairs = xs >>= \x -> xs >>= \y -> pure (x,y) but really I would like the guard to be within the >>= sections but I could not work out how to do it! i.e. I’m looking for something like (pseudo code) pairs = xs >>= \x -> xs >>= \y -> if (x + y == 2020) then pure (x,y) else DO_NOTHING which would then allow the filter to be removed. Many Thanks Mike Dr Mike Houghton mike_k_houghton at yahoo.co.uk -------------- next part -------------- An HTML attachment was scrubbed... URL: From toad3k at gmail.com Wed Dec 2 12:51:40 2020 From: toad3k at gmail.com (David McBride) Date: Wed, 2 Dec 2020 07:51:40 -0500 Subject: [Haskell-beginners] Desugar list comprehension In-Reply-To: <84D90B6C-8C1F-4EAB-A573-38D1E3388F97@yahoo.co.uk> References: <84D90B6C-8C1F-4EAB-A573-38D1E3388F97.ref@yahoo.co.uk> <84D90B6C-8C1F-4EAB-A573-38D1E3388F97@yahoo.co.uk> Message-ID: If you check on hoogle for how guard is written, it is just this guard True = pure () guard False = empty That means you can use the same thing in your own code import Control.Applicative pairs xs = xs >>= \x -> xs >>= \y -> if (x + y == 2020) then pure (x,y) else empty On Wed, Dec 2, 2020 at 5:31 AM mike h wrote: > Hi, > I have > sumIs2020P1' xs = do > x <- xs > y <- xs > guard (x + y == 2020) > pure (x,y) > > which has been desugared from a list comprehension > I would like to reduce this even more using >>= > So I do > sumIs2020P1'' xs = (a,b) where > (a,b):rest = filter (\(x,y) -> x + y == 2020) pairs > > pairs = xs >>= \x -> > xs >>= \y -> > pure (x,y) > > but really I would like the guard to be within the >>= sections but I > could not work out > how to do it! > i.e. I’m looking for something like (pseudo code) > > pairs = xs >>= \x -> > xs >>= \y -> > if (x + y == 2020) then pure (x,y) else DO_NOTHING > which would then allow the filter to be removed. > > > Many Thanks > > Mike > > > > Dr Mike Houghton > > mike_k_houghton at yahoo.co.uk > > > > _______________________________________________ > 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 mike_k_houghton at yahoo.co.uk Wed Dec 2 15:47:05 2020 From: mike_k_houghton at yahoo.co.uk (mike h) Date: Wed, 2 Dec 2020 15:47:05 +0000 Subject: [Haskell-beginners] Desugar list comprehension In-Reply-To: References: <84D90B6C-8C1F-4EAB-A573-38D1E3388F97.ref@yahoo.co.uk> <84D90B6C-8C1F-4EAB-A573-38D1E3388F97@yahoo.co.uk> Message-ID: <75D621D3-E4DD-4777-9806-5BE28A375623@yahoo.co.uk> Duh! Of course, thanks David. > On 2 Dec 2020, at 12:51, David McBride wrote: > > If you check on hoogle for how guard is written, it is just this > guard True = pure () > guard False = empty > That means you can use the same thing in your own code > > import Control.Applicative > > pairs xs = > xs >>= \x -> > xs >>= \y -> > if (x + y == 2020) then pure (x,y) else empty > > On Wed, Dec 2, 2020 at 5:31 AM mike h > wrote: > Hi, > I have > sumIs2020P1' xs = do > x <- xs > y <- xs > guard (x + y == 2020) > pure (x,y) > > which has been desugared from a list comprehension > I would like to reduce this even more using >>= > So I do > sumIs2020P1'' xs = (a,b) where > (a,b):rest = filter (\(x,y) -> x + y == 2020) pairs > > pairs = xs >>= \x -> > xs >>= \y -> > pure (x,y) > > but really I would like the guard to be within the >>= sections but I could not work out > how to do it! > i.e. I’m looking for something like (pseudo code) > > pairs = xs >>= \x -> > xs >>= \y -> > if (x + y == 2020) then pure (x,y) else DO_NOTHING > > which would then allow the filter to be removed. > > > Many Thanks > > Mike > > > > Dr Mike Houghton > > mike_k_houghton at yahoo.co.uk > > > > _______________________________________________ > 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 pietro.gra at hotmail.it Tue Dec 8 16:23:35 2020 From: pietro.gra at hotmail.it (Pietro Grandinetti) Date: Tue, 8 Dec 2020 16:23:35 +0000 Subject: [Haskell-beginners] Usage of type Message-ID: Hi, Playing around with code (very few lines) that represents long-form articles. I'd like to understand: 1- if the usage of `type' is correct, or if I should prefer `newtype', or something different altogheter. 2- what's the more idiomatic way to do the boxing and unboxing of renamed types? See last 2 functions in the code. import Data.Time (Day) import Data.List (intercalate) import Data.List.Split (splitOn) type Title = String type Author = String type Sentence = String type Paragraph = [Sentence] type Abstract = Paragraph type Content = [Paragraph] type Date = Day data Essay = Essay { title :: Title , authors :: [Author] , pubDate :: Date , startDate :: Date , abstract :: Abstract , content :: Content } deriving (Show) makeTitle :: String -> Title makeTitle x = x::Title makePar :: String -> Paragraph makePar = splitOn sep where sep = "." makeContent :: String -> Content makeContent x = map makePar $ splitOn sep x where sep = "\n\n" unboxPar :: Paragraph -> String unboxPar = intercalate ". " unboxContent :: Content -> String unboxContent x = intercalate "\n\n" $ map unboxPar x Thanks, Pete -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Tue Dec 8 18:42:30 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Tue, 8 Dec 2020 19:42:30 +0100 Subject: [Haskell-beginners] Usage of type In-Reply-To: References: Message-ID: <20201208184230.GE2781@extensa> Hello Pietro, Il 08 dicembre 2020 alle 16:23 Pietro Grandinetti ha scritto: > Hi, > > Playing around with code (very few lines) that represents long-form articles. I'd like to understand: > 1- if the usage of `type' is correct, or if I should prefer `newtype', or something different altogheter. Your usage of `type` is correct. The idea is that you start with type and can easily switch to newtype if the need arises (typeclass reasons, etc.). > 2- what's the more idiomatic way to do the boxing and unboxing of renamed types? See last 2 functions in the code. > > […] > > import Data.Time (Day) > import Data.List (intercalate) > import Data.List.Split (splitOn) > > type Sentence = String > type Paragraph = [Sentence] > type Content = [Paragraph] > > unboxPar :: Paragraph -> String > unboxPar = intercalate ". " > > unboxContent :: Content -> String > unboxContent x = intercalate "\n\n" $ map unboxPar x unboxPar and unboxContent are fine, I would personally name them slightly differently (`renderPar` and `renderContent`). —F From borgauf at gmail.com Thu Dec 10 20:53:51 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Thu, 10 Dec 2020 14:53:51 -0600 Subject: [Haskell-beginners] Haskell REPL doesn't accept type declaration Message-ID: If I simply put a type declaration into the GHCi (version 8.8.4), it complains: Prelude> divides :: Integer -> Integer -> Bool :18:1-7: error: Variable not in scope: divides :: Integer -> Integer -> Bool I'm trying to use Emacs org-mode babel, and I have to wrap the code block to get it to work. For example: #+begin_src haskell :results verbatim :exports both :{ factorial :: Int -> Int factorial 0 = 1 factorial n = n * factorial (n - 1) :} #+end_src #+begin_src haskell :results verbatim :exports both factorial 0 #+end_src #+RESULTS: : 1 I understand :set +m, but this doesn't help. Why won't a running Haskell REPL with set +m take a type declaration? Lawrence Bottorff Grand Marais, MN, USA -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Thu Dec 10 21:09:35 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Thu, 10 Dec 2020 22:09:35 +0100 Subject: [Haskell-beginners] Haskell REPL doesn't accept type declaration In-Reply-To: References: Message-ID: <20201210210935.GC851@extensa> Il 10 dicembre 2020 alle 14:53 Lawrence Bottorff ha scritto: > If I simply put a type declaration into the GHCi (version 8.8.4), it > complains: > > Prelude> divides :: Integer -> Integer -> Bool > :18:1-7: error: > Variable not in scope: divides :: Integer -> Integer -> Bool > > I'm trying to use Emacs org-mode babel, and I have to wrap the code block > to get it to work. I do not believe it solves your problem but λ> prova :: Int; prova = 8 λ> works —F From borgauf at gmail.com Thu Dec 10 21:41:06 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Thu, 10 Dec 2020 15:41:06 -0600 Subject: [Haskell-beginners] Haskell REPL doesn't accept type declaration In-Reply-To: <20201210210935.GC851@extensa> References: <20201210210935.GC851@extensa> Message-ID: Yes, but a simple λ> prova :: Int doesn't work. What am I missing? On Thu, Dec 10, 2020 at 3:11 PM Francesco Ariis wrote: > Il 10 dicembre 2020 alle 14:53 Lawrence Bottorff ha scritto: > > If I simply put a type declaration into the GHCi (version 8.8.4), it > > complains: > > > > Prelude> divides :: Integer -> Integer -> Bool > > :18:1-7: error: > > Variable not in scope: divides :: Integer -> Integer -> Bool > > > > I'm trying to use Emacs org-mode babel, and I have to wrap the code block > > to get it to work. > > I do not believe it solves your problem but > > λ> prova :: Int; prova = 8 > λ> > > works > —F > _______________________________________________ > 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 fa-ml at ariis.it Thu Dec 10 22:08:08 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Thu, 10 Dec 2020 23:08:08 +0100 Subject: [Haskell-beginners] Haskell REPL doesn't accept type declaration In-Reply-To: References: <20201210210935.GC851@extensa> Message-ID: <20201210220808.GA30311@extensa> Il 10 dicembre 2020 alle 15:41 Lawrence Bottorff ha scritto: > Yes, but a simple > > λ> prova :: Int > > doesn't work. What am I missing? No idea the reason why ghci does not accept it, maybe because if it did there would be a bodyless signature in scope? Also maybe this is slightly more palatable for you: λ> :set +m λ> let prova :: Int -> String prova = show [blank line] λ> prova 7 "7" From m.douglas.mcilroy at dartmouth.edu Fri Dec 11 03:57:26 2020 From: m.douglas.mcilroy at dartmouth.edu (M Douglas McIlroy) Date: Thu, 10 Dec 2020 22:57:26 -0500 Subject: [Haskell-beginners] =?utf-8?q?=28no_subject=29?= Message-ID: Is it possible to decorate a definition like this From m.douglas.mcilroy at dartmouth.edu Fri Dec 11 13:03:03 2020 From: m.douglas.mcilroy at dartmouth.edu (M Douglas McIlroy) Date: Fri, 11 Dec 2020 08:03:03 -0500 Subject: [Haskell-beginners] unwanted Fractional constraint Message-ID: For rational functions that take on integer values at integer arguments, for example n*(n+1)/2, is there a way to doctor the corresponding Haskell definition f n = n*(n+1)/2 so that the type signature becomes f :: Num a => a -> a rather than f :: Fractional a => a -> a Doug McIlroy From toad3k at gmail.com Fri Dec 11 13:42:03 2020 From: toad3k at gmail.com (David McBride) Date: Fri, 11 Dec 2020 08:42:03 -0500 Subject: [Haskell-beginners] unwanted Fractional constraint In-Reply-To: References: Message-ID: The problem is that the moment you divided by two, it can no longer be an instance of Num. Instances of Num include: Integers, Ints and Words. Once divided, you can no longer use that result in places where an Integer is required, because it won't be. What you can do is use the `div` function which will round down to the nearest Integer value. Then it is an instance of Integral, which includes Integers, Ints, and Words (but floating point types) You can also use `round`, `floor`, or `ceiling` to round your result to an appropriate integer after you've divided. On Fri, Dec 11, 2020 at 8:04 AM M Douglas McIlroy < m.douglas.mcilroy at dartmouth.edu> wrote: > For rational functions that take on integer values at integer > arguments, for example n*(n+1)/2, is there a way to doctor the > corresponding Haskell definition > > f n = n*(n+1)/2 > > so that the type signature becomes > > f :: Num a => a -> a > > rather than > > f :: Fractional a => a -> a > > Doug McIlroy > _______________________________________________ > 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 dj112358 at outlook.com Fri Dec 11 16:38:46 2020 From: dj112358 at outlook.com (David James) Date: Fri, 11 Dec 2020 16:38:46 +0000 Subject: [Haskell-beginners] unwanted Fractional constraint In-Reply-To: References: Message-ID: [Attempting to resend] Hi - I think your logic is: I can define these two: fFrac :: Fractional a => a -> a fFrac n = n * (n+1) / 2 fInt :: Integral a => a -> a fInt n = n * (n+1) `div` 2 so that, e.g. fFrac (5.0 :: Float) == 15.0 :: Float fInt (5 :: Integer) == 15 :: Integer And all number types are either Integral or Fractional, so surely I should be able to define a single function of type: f :: Num a => a -> a This would seem reasonable, but I think there’s a problem with the last assumption. It is indeed possible for other types to be instances of Num, but not of Integral or Fractional. For example, I could define: instance Num Bool where fromInteger 0 = False fromInteger _ = True (+) = (&&) (*) = (||) abs = id signum _ = True negate = not Now this would probably be pretty dumb (and probably doesn’t comply with expectations), but is possible. (And also pretty dumb to define it without also define an instance Integral Bool where ..., but still possible). So I don’t think f :: Num a => a -> a could be possible, since Num by itself (& the dumb Bool instance) has no way to do the division. (At least that I can think of, but would be very interested to hear if there is). Regards, David. From: Beginners on behalf of M Douglas McIlroy Sent: Friday, December 11, 2020 1:03:03 PM To: beginners at haskell.org Subject: [Haskell-beginners] unwanted Fractional constraint For rational functions that take on integer values at integer arguments, for example n*(n+1)/2, is there a way to doctor the corresponding Haskell definition f n = n*(n+1)/2 so that the type signature becomes f :: Num a => a -> a rather than f :: Fractional a => a -> a Doug McIlroy _______________________________________________ Beginners mailing list Beginners at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: F5B325D295EC4EFD853932C4105331AE.png Type: image/png Size: 144 bytes Desc: F5B325D295EC4EFD853932C4105331AE.png URL: From pietro.gra at hotmail.it Sun Dec 13 10:39:36 2020 From: pietro.gra at hotmail.it (Pietro Grandinetti) Date: Sun, 13 Dec 2020 10:39:36 +0000 Subject: [Haskell-beginners] Nested folds Message-ID: Hello, I have a piece of code to represents Sentences, Paragraphs and the Content of an article. I added functions to count the words, code below. My questions: 1- Are these functions idiomatic? 2- Is this an efficient way to do the computation? 3- In different languages, I could (and would) give the same name `wordCount` to the three functions, because the type of the input would clarify the usage. But here GHC throws an error. What's the most idiomatic way to do this in Haskell? type Sentence = String type Paragraph = [Sentence] type Content = [Paragraph] sentWordCount :: Sentence -> Int sentWordCount = length . words parWordCount :: Paragraph -> Int parWordCount = foldr ((+) . sentWordCount) 0 contWordCount :: Content -> Int contWordCount = foldr ((+) . parWordCount) 0 I also have two more practical questions on the following two functions: makeSentence :: String -> Sentence makeSentence x = x::Sentence sentCharCount :: Sentence -> Int sentCharCount x = length $ filter (/= ' ') x 4- About `makeSentence` -- does it make sense to write a function like that just to encapsulate the String type? 5- About `sentCharCount` -- I cannot take the argument x off, the compilator complains. What's the reason? Thanks, -P -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Sun Dec 13 17:25:03 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Sun, 13 Dec 2020 18:25:03 +0100 Subject: [Haskell-beginners] Nested folds In-Reply-To: References: Message-ID: <20201213172503.GA22875@extensa> Hello Pietro, Il 13 dicembre 2020 alle 10:39 Pietro Grandinetti ha scritto: > Hello, > I have a piece of code to represents Sentences, Paragraphs and the Content of an article. I added functions to count the words, code below. My questions: > > […] > > I also have two more practical questions on the following two functions: > > makeSentence :: String -> Sentence > makeSentence x = x::Sentence You can omit the `:: Sentence` part, since it is specified in the signature above. You can omit the whole function itself to be fair, Sentence is a type synonym! > sentCharCount :: Sentence -> Int > sentCharCount x = length $ filter (/= ' ') x You can write this point-free like this sentCharCount :: Sentence -> Int sentCharCount = length . filter (/= ' ') In this example you can regard `$` as «evaluate everything on the right before anything else», so length $ filter (/= ' ') ^^^^^^ ^^^^^^^^^^^^^^^ | | | | | +-- this has type :: [Char] -> [Char] | +-- length does not work on `[Char] -> [Char]` `.` instead is appropriate λ> :t (.) (.) :: (b -> c) -> (a -> b) -> a -> c Does this clear your doubts? —F From pietro.gra at hotmail.it Sun Dec 13 19:04:08 2020 From: pietro.gra at hotmail.it (Pietro Grandinetti) Date: Sun, 13 Dec 2020 19:04:08 +0000 Subject: [Haskell-beginners] Nested folds In-Reply-To: <20201213172503.GA22875@extensa> References: , <20201213172503.GA22875@extensa> Message-ID: Hello Francesco, Yes, that helped. However, I believe I shouldn't remove the `makeSentence`. A user of the module is not supposed to know what a `Sentence` is, hence I must provide a function such as `makeSentence`. Right now, its implementation is just a type conversion, but may change later. This would be my logic in different languages; does it make sense in Haskell? Do you have any feedback on my questions 1,2 and 3? Thanks, -P ________________________________ From: Beginners on behalf of Francesco Ariis Sent: Sunday, December 13, 2020 6:25 PM To: beginners at haskell.org Subject: Re: [Haskell-beginners] Nested folds Hello Pietro, Il 13 dicembre 2020 alle 10:39 Pietro Grandinetti ha scritto: > Hello, > I have a piece of code to represents Sentences, Paragraphs and the Content of an article. I added functions to count the words, code below. My questions: > > […] > > I also have two more practical questions on the following two functions: > > makeSentence :: String -> Sentence > makeSentence x = x::Sentence You can omit the `:: Sentence` part, since it is specified in the signature above. You can omit the whole function itself to be fair, Sentence is a type synonym! > sentCharCount :: Sentence -> Int > sentCharCount x = length $ filter (/= ' ') x You can write this point-free like this sentCharCount :: Sentence -> Int sentCharCount = length . filter (/= ' ') In this example you can regard `$` as «evaluate everything on the right before anything else», so length $ filter (/= ' ') ^^^^^^ ^^^^^^^^^^^^^^^ | | | | | +-- this has type :: [Char] -> [Char] | +-- length does not work on `[Char] -> [Char]` `.` instead is appropriate λ> :t (.) (.) :: (b -> c) -> (a -> b) -> a -> c Does this clear your doubts? —F _______________________________________________ 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 fa-ml at ariis.it Sun Dec 13 22:47:42 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Sun, 13 Dec 2020 23:47:42 +0100 Subject: [Haskell-beginners] Nested folds In-Reply-To: References: <20201213172503.GA22875@extensa> Message-ID: <20201213224742.GB22522@extensa> Il 13 dicembre 2020 alle 19:04 Pietro Grandinetti ha scritto: > Yes, that helped. However, I believe I shouldn't remove the `makeSentence`. > A user of the module is not supposed to know what a `Sentence` is, hence I > must provide a function such as `makeSentence`. But they will know, a type synonym is just a way to make signatures prettier/more informative, a program like this foo :: String foo = "foo" k = sentCharCount foo will _not_ be refused by the compiler. IF and when — in the future — you decide to use newtype/data then you will get a compiler error (and in turn would need a constructor with signature `:: String -> Sentence`. > Do you have any feedback on my questions 1,2 and 3? The functions are clearly written, there is some duplication because of the type synonyms (i.e. `parWordCount` and `contWordCount` are the same function). Do not worry about it now and revisit the exercise once you start using `newtype` and `data` + typeclasses —F From m.douglas.mcilroy at dartmouth.edu Mon Dec 14 17:14:53 2020 From: m.douglas.mcilroy at dartmouth.edu (M Douglas McIlroy) Date: Mon, 14 Dec 2020 12:14:53 -0500 Subject: [Haskell-beginners] 1=2 Message-ID: ghc and ghci 8.6.5 accept 1=2 at top level. It seems to have no effect. What does it mean? From amindfv at mailbox.org Tue Dec 15 01:05:05 2020 From: amindfv at mailbox.org (amindfv at mailbox.org) Date: Mon, 14 Dec 2020 20:05:05 -0500 Subject: [Haskell-beginners] 1=2 In-Reply-To: References: Message-ID: <20201215010505.GA18292@painter.painter> It's the same in do-blocks: main :: IO () main = do let 3 = 2 + 2 putStrLn "Oh fiddlesticks" On Mon, Dec 14, 2020 at 12:14:53PM -0500, M Douglas McIlroy wrote: > ghc and ghci 8.6.5 accept 1=2 at top level. It seems to have no effect. > What does it mean? > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners From fa-ml at ariis.it Tue Dec 15 01:29:12 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Tue, 15 Dec 2020 02:29:12 +0100 Subject: [Haskell-beginners] 1=2 In-Reply-To: <20201215010505.GA18292@painter.painter> References: <20201215010505.GA18292@painter.painter> Message-ID: <20201215012912.GA24885@extensa> Il 14 dicembre 2020 alle 20:05 amindfv at mailbox.org ha scritto: > It's the same in do-blocks: > > main :: IO () > main = do > let 3 = 2 + 2 > putStrLn "Oh fiddlesticks" What happens exactly when I type this? λ> "prova" = "foo" λ> 'c' = 'd' λ> 'c' 'c' >From the Report I read: lexp → let decls in exp decls → { decl1 ; … ; decln } (n ≥ 0) ⁝ decl → (funlhs | pat) rhs ⁝ Am I correct in saying `pat rhs` is the rule being used here? I do not understand how/when it comes useful in a let —F From hallgren at chalmers.se Tue Dec 15 14:45:01 2020 From: hallgren at chalmers.se (Thomas Hallgren) Date: Tue, 15 Dec 2020 15:45:01 +0100 Subject: [Haskell-beginners] 1=2 In-Reply-To: <20201215012912.GA24885@extensa> References: <20201215010505.GA18292@painter.painter> <20201215012912.GA24885@extensa> Message-ID: On 2020-12-14 18:14, M Douglas McIlroy wrote: > ghc and ghci 8.6.5 accept 1=2 at top level. It seems to have no effect. On 2020-12-15 02:29, Francesco Ariis wrote: > Il 14 dicembre 2020 alle 20:05 amindfv at mailbox.org ha scritto: >> It's the same in do-blocks: >> >> main :: IO () >> main = do >> let 3 = 2 + 2 >> putStrLn "Oh fiddlesticks" > > What happens exactly when I type this? > > λ> "prova" = "foo" > λ> 'c' = 'd' > λ> 'c' > 'c' These are examples of pattern bindings, but since they don't bind any variables, they are not very useful. As examples of more useful pattern bindings, consider > (xs,ys) = splitAt 3 [1..8] > [1,x,y] = [1..3] These are both examples where the value of the expression on the rhs matches the pattern on the lhs, so you can obtain the values of the variables bound by the pattern: > xs [1,2,3] > ys [4,5,6,7,8] > x 2 > y 3 If the value of the expression on the rhs doesn't match the pattern on the lhs, you get an error, but because of lazy evaluation the value of the rhs is not computed and matched against the pattern until you use one of the variables in the pattern: > [1,z,2] = [1..3] > z *** Exception: :7:1-16: Irrefutable pattern failed for pattern [1, z, 2] This means that when the pattern does not contain any variables, the value of the rhs is never computed and matched against the pattern, so even if the value does not match the pattern, there is no error message: > [] = [1..3] > [_,_,_] = [] > True = False > 1 = 2 If you turn on -Wunused-pattern-binds, you get a warning for pattern bindings like these: > :set -Wunused-pattern-binds > True=False :2:1: warning: [-Wunused-pattern-binds] This pattern-binding binds no variables: True = False Best regards, Thomas H From fa-ml at ariis.it Tue Dec 15 23:29:08 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Wed, 16 Dec 2020 00:29:08 +0100 Subject: [Haskell-beginners] 1=2 In-Reply-To: References: <20201215010505.GA18292@painter.painter> <20201215012912.GA24885@extensa> Message-ID: <20201215232908.GA22944@extensa> Il 15 dicembre 2020 alle 15:45 Thomas Hallgren ha scritto: > These are examples of pattern bindings, but since they don't bind any variables, > they are not very useful. > […] Very instructive, many thanks From leduin.cuenca at yachaytech.edu.ec Thu Dec 17 15:58:02 2020 From: leduin.cuenca at yachaytech.edu.ec (=?UTF-8?Q?Leduin_Jos=C3=A9_Cuenca_Macas?=) Date: Thu, 17 Dec 2020 10:58:02 -0500 Subject: [Haskell-beginners] bayes-monad package Message-ID: Dear all, I want to know if there exists a free access project that uses the bayes-monad package. The purpose is to use this project as an end-course task. Kind regards. *Leduin José Cuenca Macas* *Student | Estudiante* Tel. (+593) 991 618 273 -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Thu Dec 17 16:20:38 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Thu, 17 Dec 2020 17:20:38 +0100 Subject: [Haskell-beginners] bayes-monad package In-Reply-To: References: Message-ID: <20201217162037.GA6741@extensa> Hello Leduin, Il 17 dicembre 2020 alle 10:58 Leduin José Cuenca Macas ha scritto: > I want to know if there exists a free access project that uses the > bayes-monad package. The purpose is to use this project as an end-course > task. according to Reverse Dependencies [1], porcupine-core [2] uses it —F [1] https://packdeps.haskellers.com/reverse/monad-bayes [2] https://hackage.haskell.org/package/porcupine-core From borgauf at gmail.com Fri Dec 18 18:30:54 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Fri, 18 Dec 2020 12:30:54 -0600 Subject: [Haskell-beginners] map type explanation Message-ID: I'm looking at this ghci> :type map map :: (a -> b) -> [a] -> [b] and wondering what the (a -> b) part is about. map takes a function and applies it to an incoming list. Good. Understood. I'm guessing that the whole Haskell type declaration idea is based on currying, and I do understand how the (a -> b) part "takes" an incoming list, [a] and produces the [b] output. Also, I don't understand a and b very well either. Typically, a is just a generic variable, then b is another generic variable not necessarily the same as a. But how are they being used in this type declaration? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From toad3k at gmail.com Fri Dec 18 18:42:22 2020 From: toad3k at gmail.com (David McBride) Date: Fri, 18 Dec 2020 13:42:22 -0500 Subject: [Haskell-beginners] map type explanation In-Reply-To: References: Message-ID: They are not parameters, they are the types of the parameters. In this case a can really be anything, Int, Char, whatever, so long as the function takes a single argument of that type and the list that is given has elements of that same type. It is the same for b, it doesn't matter what b ends up being, so long as when you call that function the function's return value is compatible with the element type of the list that you intended to return from the entire statement. You can mess with it yourself in ghci to see how type inference works. >:t show :show :: Show a => a -> String >:t map show map show :: Show a => [a] -> [String] > :t flip map [1::Int] > flip map [1::Int] :: (Int -> b) -> [b] On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff wrote: > I'm looking at this > > ghci> :type map > map :: (a -> b) -> [a] -> [b] > > and wondering what the (a -> b) part is about. map takes a function and > applies it to an incoming list. Good. Understood. I'm guessing that the > whole Haskell type declaration idea is based on currying, and I do > understand how the (a -> b) part "takes" an incoming list, [a] and > produces the [b] output. Also, I don't understand a and b very well > either. Typically, a is just a generic variable, then b is another > generic variable not necessarily the same as a. But how are they being > used in this type declaration? > > LB > _______________________________________________ > 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 borgauf at gmail.com Fri Dec 18 22:01:01 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Fri, 18 Dec 2020 16:01:01 -0600 Subject: [Haskell-beginners] map type explanation In-Reply-To: References: Message-ID: Thank you, but why in map :: (a -> b) -> [a] -> [b] are there parentheses around a -> b ? In general, what is the currying aspect of this? On Fri, Dec 18, 2020 at 12:43 PM David McBride wrote: > They are not parameters, they are the types of the parameters. > > In this case a can really be anything, Int, Char, whatever, so long as the > function takes a single argument of that type and the list that is given > has elements of that same type. > It is the same for b, it doesn't matter what b ends up being, so long as > when you call that function the function's return value is compatible with > the element type of the list that you intended to return from the entire > statement. > > You can mess with it yourself in ghci to see how type inference works. > > >:t show > :show :: Show a => a -> String > >:t map show > map show :: Show a => [a] -> [String] > > :t flip map [1::Int] > > flip map [1::Int] :: (Int -> b) -> [b] > > > On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff > wrote: > >> I'm looking at this >> >> ghci> :type map >> map :: (a -> b) -> [a] -> [b] >> >> and wondering what the (a -> b) part is about. map takes a function and >> applies it to an incoming list. Good. Understood. I'm guessing that the >> whole Haskell type declaration idea is based on currying, and I do >> understand how the (a -> b) part "takes" an incoming list, [a] and >> produces the [b] output. Also, I don't understand a and b very well >> either. Typically, a is just a generic variable, then b is another >> generic variable not necessarily the same as a. But how are they being >> used in this type declaration? >> >> LB >> _______________________________________________ >> 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 utprimum at gmail.com Fri Dec 18 22:08:56 2020 From: utprimum at gmail.com (Ut Primum) Date: Fri, 18 Dec 2020 23:08:56 +0100 Subject: [Haskell-beginners] map type explanation In-Reply-To: References: Message-ID: Hi, a -> b is the type of a function taking arguments of a generic type (we call it a) and returning results of another type, that we call b. So (a -> b ) -> [a] -> [b] Means that you have a first argument that is a function (a-> b), a second argument that is a list of elements of the same type of the function input, and that the returned element is a list of things of the type of the output of the function. Cheers, Ut Il ven 18 dic 2020, 23:02 Lawrence Bottorff ha scritto: > Thank you, but why in > > map :: (a -> b) -> [a] -> [b] > > are there parentheses around a -> b ? In general, what is the currying > aspect of this? > > > On Fri, Dec 18, 2020 at 12:43 PM David McBride wrote: > >> They are not parameters, they are the types of the parameters. >> >> In this case a can really be anything, Int, Char, whatever, so long as >> the function takes a single argument of that type and the list that is >> given has elements of that same type. >> It is the same for b, it doesn't matter what b ends up being, so long as >> when you call that function the function's return value is compatible with >> the element type of the list that you intended to return from the entire >> statement. >> >> You can mess with it yourself in ghci to see how type inference works. >> >> >:t show >> :show :: Show a => a -> String >> >:t map show >> map show :: Show a => [a] -> [String] >> > :t flip map [1::Int] >> > flip map [1::Int] :: (Int -> b) -> [b] >> >> >> On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff >> wrote: >> >>> I'm looking at this >>> >>> ghci> :type map >>> map :: (a -> b) -> [a] -> [b] >>> >>> and wondering what the (a -> b) part is about. map takes a function and >>> applies it to an incoming list. Good. Understood. I'm guessing that the >>> whole Haskell type declaration idea is based on currying, and I do >>> understand how the (a -> b) part "takes" an incoming list, [a] and >>> produces the [b] output. Also, I don't understand a and b very well >>> either. Typically, a is just a generic variable, then b is another >>> generic variable not necessarily the same as a. But how are they being >>> used in this type declaration? >>> >>> LB >>> _______________________________________________ >>> 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 borgauf at gmail.com Fri Dec 18 22:55:30 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Fri, 18 Dec 2020 16:55:30 -0600 Subject: [Haskell-beginners] map type explanation In-Reply-To: References: Message-ID: Why is it not just a -> b -> [a] -> [b] again, why the parentheses? On Fri, Dec 18, 2020 at 4:10 PM Ut Primum wrote: > Hi, > > a -> b is the type of a function taking arguments of a generic type (we > call it a) and returning results of another type, that we call b. > > So > (a -> b ) -> [a] -> [b] > Means that you have a first argument that is a function (a-> b), a second > argument that is a list of elements of the same type of the function input, > and that the returned element is a list of things of the type of the output > of the function. > > Cheers, > Ut > > Il ven 18 dic 2020, 23:02 Lawrence Bottorff ha > scritto: > >> Thank you, but why in >> >> map :: (a -> b) -> [a] -> [b] >> >> are there parentheses around a -> b ? In general, what is the currying >> aspect of this? >> >> >> On Fri, Dec 18, 2020 at 12:43 PM David McBride wrote: >> >>> They are not parameters, they are the types of the parameters. >>> >>> In this case a can really be anything, Int, Char, whatever, so long as >>> the function takes a single argument of that type and the list that is >>> given has elements of that same type. >>> It is the same for b, it doesn't matter what b ends up being, so long as >>> when you call that function the function's return value is compatible with >>> the element type of the list that you intended to return from the entire >>> statement. >>> >>> You can mess with it yourself in ghci to see how type inference works. >>> >>> >:t show >>> :show :: Show a => a -> String >>> >:t map show >>> map show :: Show a => [a] -> [String] >>> > :t flip map [1::Int] >>> > flip map [1::Int] :: (Int -> b) -> [b] >>> >>> >>> On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff >>> wrote: >>> >>>> I'm looking at this >>>> >>>> ghci> :type map >>>> map :: (a -> b) -> [a] -> [b] >>>> >>>> and wondering what the (a -> b) part is about. map takes a function >>>> and applies it to an incoming list. Good. Understood. I'm guessing that the >>>> whole Haskell type declaration idea is based on currying, and I do >>>> understand how the (a -> b) part "takes" an incoming list, [a] and >>>> produces the [b] output. Also, I don't understand a and b very well >>>> either. Typically, a is just a generic variable, then b is another >>>> generic variable not necessarily the same as a. But how are they being >>>> used in this type declaration? >>>> >>>> LB >>>> _______________________________________________ >>>> 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 brubar.cs at gmail.com Fri Dec 18 23:19:41 2020 From: brubar.cs at gmail.com (Bruno Barbier) Date: Sat, 19 Dec 2020 00:19:41 +0100 Subject: [Haskell-beginners] map type explanation In-Reply-To: References: Message-ID: <5fdd38de.1c69fb81.3d91b.8f23@mx.google.com> Hi Lawrence, Lawrence Bottorff writes: > Why is it not just > > a -> b -> [a] -> [b] > > again, why the parentheses? In Haskell, (->) is a binary operator and is right associative. If you write: a -> b -> [a] -> [b] it implicitly means: a -> (b -> ([a] -> [b])) So here, you need explicit parenthesis: (a -> b) -> [a] -> [b] to mean: (a -> b) -> ([a] -> [b]) It's more about parsing binary operators than about types. Does it help ? Bruno > On Fri, Dec 18, 2020 at 4:10 PM Ut Primum wrote: > >> Hi, >> >> a -> b is the type of a function taking arguments of a generic type (we >> call it a) and returning results of another type, that we call b. >> >> So >> (a -> b ) -> [a] -> [b] >> Means that you have a first argument that is a function (a-> b), a second >> argument that is a list of elements of the same type of the function input, >> and that the returned element is a list of things of the type of the output >> of the function. >> >> Cheers, >> Ut >> >> Il ven 18 dic 2020, 23:02 Lawrence Bottorff ha >> scritto: >> >>> Thank you, but why in >>> >>> map :: (a -> b) -> [a] -> [b] >>> >>> are there parentheses around a -> b ? In general, what is the currying >>> aspect of this? >>> >>> >>> On Fri, Dec 18, 2020 at 12:43 PM David McBride wrote: >>> >>>> They are not parameters, they are the types of the parameters. >>>> >>>> In this case a can really be anything, Int, Char, whatever, so long as >>>> the function takes a single argument of that type and the list that is >>>> given has elements of that same type. >>>> It is the same for b, it doesn't matter what b ends up being, so long as >>>> when you call that function the function's return value is compatible with >>>> the element type of the list that you intended to return from the entire >>>> statement. >>>> >>>> You can mess with it yourself in ghci to see how type inference works. >>>> >>>> >:t show >>>> :show :: Show a => a -> String >>>> >:t map show >>>> map show :: Show a => [a] -> [String] >>>> > :t flip map [1::Int] >>>> > flip map [1::Int] :: (Int -> b) -> [b] >>>> >>>> >>>> On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff >>>> wrote: >>>> >>>>> I'm looking at this >>>>> >>>>> ghci> :type map >>>>> map :: (a -> b) -> [a] -> [b] >>>>> >>>>> and wondering what the (a -> b) part is about. map takes a function >>>>> and applies it to an incoming list. Good. Understood. I'm guessing that the >>>>> whole Haskell type declaration idea is based on currying, and I do >>>>> understand how the (a -> b) part "takes" an incoming list, [a] and >>>>> produces the [b] output. Also, I don't understand a and b very well >>>>> either. Typically, a is just a generic variable, then b is another >>>>> generic variable not necessarily the same as a. But how are they being >>>>> used in this type declaration? >>>>> >>>>> LB >>>>> _______________________________________________ >>>>> 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 From borgauf at gmail.com Sat Dec 19 03:36:22 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Fri, 18 Dec 2020 21:36:22 -0600 Subject: [Haskell-beginners] map type explanation In-Reply-To: <5fdd38de.1c69fb81.3d91b.8f23@mx.google.com> References: <5fdd38de.1c69fb81.3d91b.8f23@mx.google.com> Message-ID: So in effect a -> b -> [a] -> [b] wants to be, would be a -> (b -> ([a] -> [b])) without the parens (which is a natural result of lambda calculus, perhaps?) -- which is not what is meant by map. But underlying a Haskell type declaration is currying, is it not? At the type declaration level, it's all currying, correct? Conceptually, I understand how the a -> b "event" needs to be a "package" to apply to the list [a]. The map function commandeers the target function (which alone by itself does some a -> b evaluation) to be a new object that is then applied to each member of list [a]. Good. So (a -> b) then is a notation that signifies this "package-ness". Does anyone have examples of other "packaging" where a function doing some a -> b is changed to (a -> b) ? On Fri, Dec 18, 2020 at 5:18 PM Bruno Barbier wrote: > > Hi Lawrence, > > Lawrence Bottorff writes: > > > Why is it not just > > > > a -> b -> [a] -> [b] > > > > again, why the parentheses? > > In Haskell, (->) is a binary operator and is right associative. If you > write: > > a -> b -> [a] -> [b] > > it implicitly means: > > a -> (b -> ([a] -> [b])) > > So here, you need explicit parenthesis: > > (a -> b) -> [a] -> [b] > > to mean: > (a -> b) -> ([a] -> [b]) > > It's more about parsing binary operators than about types. > > Does it help ? > > Bruno > > > On Fri, Dec 18, 2020 at 4:10 PM Ut Primum wrote: > > > >> Hi, > >> > >> a -> b is the type of a function taking arguments of a generic type (we > >> call it a) and returning results of another type, that we call b. > >> > >> So > >> (a -> b ) -> [a] -> [b] > >> Means that you have a first argument that is a function (a-> b), a > second > >> argument that is a list of elements of the same type of the function > input, > >> and that the returned element is a list of things of the type of the > output > >> of the function. > >> > >> Cheers, > >> Ut > >> > >> Il ven 18 dic 2020, 23:02 Lawrence Bottorff ha > >> scritto: > >> > >>> Thank you, but why in > >>> > >>> map :: (a -> b) -> [a] -> [b] > >>> > >>> are there parentheses around a -> b ? In general, what is the currying > >>> aspect of this? > >>> > >>> > >>> On Fri, Dec 18, 2020 at 12:43 PM David McBride > wrote: > >>> > >>>> They are not parameters, they are the types of the parameters. > >>>> > >>>> In this case a can really be anything, Int, Char, whatever, so long as > >>>> the function takes a single argument of that type and the list that is > >>>> given has elements of that same type. > >>>> It is the same for b, it doesn't matter what b ends up being, so long > as > >>>> when you call that function the function's return value is compatible > with > >>>> the element type of the list that you intended to return from the > entire > >>>> statement. > >>>> > >>>> You can mess with it yourself in ghci to see how type inference works. > >>>> > >>>> >:t show > >>>> :show :: Show a => a -> String > >>>> >:t map show > >>>> map show :: Show a => [a] -> [String] > >>>> > :t flip map [1::Int] > >>>> > flip map [1::Int] :: (Int -> b) -> [b] > >>>> > >>>> > >>>> On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff > >>>> wrote: > >>>> > >>>>> I'm looking at this > >>>>> > >>>>> ghci> :type map > >>>>> map :: (a -> b) -> [a] -> [b] > >>>>> > >>>>> and wondering what the (a -> b) part is about. map takes a function > >>>>> and applies it to an incoming list. Good. Understood. I'm guessing > that the > >>>>> whole Haskell type declaration idea is based on currying, and I do > >>>>> understand how the (a -> b) part "takes" an incoming list, [a] and > >>>>> produces the [b] output. Also, I don't understand a and b very well > >>>>> either. Typically, a is just a generic variable, then b is another > >>>>> generic variable not necessarily the same as a. But how are they > being > >>>>> used in this type declaration? > >>>>> > >>>>> LB > >>>>> _______________________________________________ > >>>>> 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 jays at panix.com Sat Dec 19 05:44:32 2020 From: jays at panix.com (Jay Sulzberger) Date: Sat, 19 Dec 2020 05:44:32 +0000 () Subject: [Haskell-beginners] map type explanation In-Reply-To: References: <5fdd38de.1c69fb81.3d91b.8f23@mx.google.com> Message-ID: On Fri, 18 Dec 2020, Lawrence Bottorff wrote: > So in effect > > a -> b -> [a] -> [b] > > wants to be, would be > > a -> (b -> ([a] -> [b])) One difficulty in learning New Crazy Type Theory is that, by tradition, parentheses are suppressed so thoroughly that a beginner sometimes finds it hard to correctly parse the surface notation. Let us suppose we have a thing called "a". Another thing is called "b". a and b are, for the moment, just things. a and b are things of the same sort: they are both 'types'. In type theory, like in group theory, or ring theory, we have various algebras, with operations. In ring theory we ring elements, and operations: +, -, 0, 1, *. A particular ring, call the ring, say "Example" is given by the following data: 1. An underlying set, call this set Substrate_of_Example. 2. A specified element of Substrate_of_Example, the 0. 3. A specified element of Substrate_of_Example, the 1. 4. A specified everywhere defined single valued function, the +: S_E x S_E -> S_E 5. A specified everywhere defined single valued function, the *: S_E x S_E -> S_E 6. 4. A specified everywhere defined single valued function, the -: S_E -> S_E + and * take two inputs and have one output. - takes one input and has one output. By the definition of the concept "ring", the ring substrate S_E and the two constants, 0 and 1, and the three operations, +, *, and -, must satisfy certain laws. If case these laws are satisfied, we say that the data give us a uniquely defined instance of the concept ring. The sub-field of mathematics Ring Theory studies such things, that is, rings. Similarly Type Theory studies "type systems". The definition of a type system is not as tightly defined as the concept of a ring, but again, at least in the case of the Haskell_Type_System, we have these things: 1. An underlying set, call this set Substrate_of_Haskell_Type_System. This set is the set of types. For convenience we write "T" for "Substrate_of_Haskell_Type_System". 2. An everywhere defined single valued function, the hom operator =>: T x T -> T (We have written "=>" rather than "->" to the left of the ":" above to avoid confusion with the "->" in the above line.) 3. An everywhere defined single valued function, the list operator []: T -> T. (Note [] is not the list operator of, say, Common Lisp, or Scheme, or Haskell. [] operates on types, not on, ah, things which are not types, but rather have types. Oi.) A particular type system such as HTS is given by the above data, and the system is a type system, because just as for rings, certain laws are required to be obeyed. (Usually a type system has more operations than the above two.) Let us suppose we have before us the ring of integers Z. Here is an expression in the language of rings, which language applies to Z, because Z is a ring: (((1 + 1) * (0 + 1)) + ((- 1) * (1 + 1))) The notation is un-ambiguous. We know what it means, and we can calculate the value of the expression by applying the operations of the ring Z. Now similarly, we have expressions in the HTS. Here is one expression: ((Int -> Str) -> ([Int] -> [Str])) The above expression is fully parenthesized, and, thus we know what type it evaluates to. Here is another expression: (Int -> (Str -> ([Int] -> [Str]))) This expression too is fully parenthesized, and, thus we know what type it evaluates to. These two types specified by the two different expressions turn out not to be the same type. That is, the two expressions evaluate to different types. The concept of "currying" has come up. Part of my difficulty in learning a little bit of New Crazy Type Theory is that New Crazy Type Theorists have syntactic conventions which permit them to, often, reduce the number of parentheses in expressions. For example, one convention specifies that the string "a -> b -> c" should be translated to the fully parenthesized (a -> (b -> c)) and not to the different expression ((a -> b) -> c) The two expressions are different, and in general they evaluate to different types. And you are right: this convention has somewhat to do with currying. We say no more about currying, except that, to define "currying" a third operation on types is required: the product of types: xx: T x T -> T (Again, we write "xx" so that the operation on the left of ":" is not confused with the "x" on the right. Oi.) I speak now as a beginner. There is a phrase which, when I was an even more tenderly ignorant beginner than I am now, always confused me: Such and such operation is binary and right-associative. My delicate beginner's sensibilities were outraged. No! The operation might indeed be binary, but "right-associative" refers to the system of notation(s) for the operation(s), not to the operation. Of course, the above occasions for confusion are just the first and most simple, on the way to "hello world" in Haskell. I remain, as ever, your fellow student of history and probability, Jay Sulzberger PS. Likely there are errors in above. > > without the parens (which is a natural result of lambda calculus, perhaps?) > -- which is not what is meant by map. But underlying a Haskell type > declaration is currying, is it not? At the type declaration level, it's all > currying, correct? > > Conceptually, I understand how the a -> b "event" needs to be a "package" > to apply to the list [a]. The map function commandeers the target function > (which alone by itself does some a -> b evaluation) to be a new object that > is then applied to each member of list [a]. Good. So (a -> b) then is a > notation that signifies this "package-ness". > > Does anyone have examples of other "packaging" where a function doing some a > -> b is changed to (a -> b) ? > > On Fri, Dec 18, 2020 at 5:18 PM Bruno Barbier wrote: > >> >> Hi Lawrence, >> >> Lawrence Bottorff writes: >> >>> Why is it not just >>> >>> a -> b -> [a] -> [b] >>> >>> again, why the parentheses? >> >> In Haskell, (->) is a binary operator and is right associative. If you >> write: >> >> a -> b -> [a] -> [b] >> >> it implicitly means: >> >> a -> (b -> ([a] -> [b])) >> >> So here, you need explicit parenthesis: >> >> (a -> b) -> [a] -> [b] >> >> to mean: >> (a -> b) -> ([a] -> [b]) >> >> It's more about parsing binary operators than about types. >> >> Does it help ? >> >> Bruno >> >>> On Fri, Dec 18, 2020 at 4:10 PM Ut Primum wrote: >>> >>>> Hi, >>>> >>>> a -> b is the type of a function taking arguments of a generic type (we >>>> call it a) and returning results of another type, that we call b. >>>> >>>> So >>>> (a -> b ) -> [a] -> [b] >>>> Means that you have a first argument that is a function (a-> b), a >> second >>>> argument that is a list of elements of the same type of the function >> input, >>>> and that the returned element is a list of things of the type of the >> output >>>> of the function. >>>> >>>> Cheers, >>>> Ut >>>> >>>> Il ven 18 dic 2020, 23:02 Lawrence Bottorff ha >>>> scritto: >>>> >>>>> Thank you, but why in >>>>> >>>>> map :: (a -> b) -> [a] -> [b] >>>>> >>>>> are there parentheses around a -> b ? In general, what is the currying >>>>> aspect of this? >>>>> >>>>> >>>>> On Fri, Dec 18, 2020 at 12:43 PM David McBride >> wrote: >>>>> >>>>>> They are not parameters, they are the types of the parameters. >>>>>> >>>>>> In this case a can really be anything, Int, Char, whatever, so long as >>>>>> the function takes a single argument of that type and the list that is >>>>>> given has elements of that same type. >>>>>> It is the same for b, it doesn't matter what b ends up being, so long >> as >>>>>> when you call that function the function's return value is compatible >> with >>>>>> the element type of the list that you intended to return from the >> entire >>>>>> statement. >>>>>> >>>>>> You can mess with it yourself in ghci to see how type inference works. >>>>>> >>>>>>> :t show >>>>>> :show :: Show a => a -> String >>>>>>> :t map show >>>>>> map show :: Show a => [a] -> [String] >>>>>>> :t flip map [1::Int] >>>>>>> flip map [1::Int] :: (Int -> b) -> [b] >>>>>> >>>>>> >>>>>> On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff >>>>>> wrote: >>>>>> >>>>>>> I'm looking at this >>>>>>> >>>>>>> ghci> :type map >>>>>>> map :: (a -> b) -> [a] -> [b] >>>>>>> >>>>>>> and wondering what the (a -> b) part is about. map takes a function >>>>>>> and applies it to an incoming list. Good. Understood. I'm guessing >> that the >>>>>>> whole Haskell type declaration idea is based on currying, and I do >>>>>>> understand how the (a -> b) part "takes" an incoming list, [a] and >>>>>>> produces the [b] output. Also, I don't understand a and b very well >>>>>>> either. Typically, a is just a generic variable, then b is another >>>>>>> generic variable not necessarily the same as a. But how are they >> being >>>>>>> used in this type declaration? >>>>>>> >>>>>>> LB >>>>>>> _______________________________________________ >>>>>>> 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 >> > From dj112358 at outlook.com Sat Dec 19 11:00:34 2020 From: dj112358 at outlook.com (David James) Date: Sat, 19 Dec 2020 11:00:34 +0000 Subject: [Haskell-beginners] map type explanation In-Reply-To: References: <5fdd38de.1c69fb81.3d91b.8f23@mx.google.com>, Message-ID: Hello - some additional comments: 1. You should probably read this, if you haven’t already. 1. You can think of the declaration fmap :: (a -> b) -> [a] -> [b] as meaning: fmap takes two arguments: 1st arg of type (a -> b) (i.e. a function, which takes one argument (of type a) and returns a result (of type b)). 2nd arg of type [a] and returns: a result of type [b] An example of a function that can be passed as the first argument would be Data.Char.ord :: Char -> Int If we pass this to map, we bind the type a to Char and the type b to Int. Then the second argument must be of type [Char], and the result will be of type [Int]. E.g. map Data.Char.ord ['F', 'r', 'e', 'd'] gives [70,114,101,100] 1. Haskell allows “currying”. Which means all functions can be “partially applied”. For example, we can apply map to only one argument. E.g. map Data.Char.ord is partially applied, and has type [Char] -> [Int] You can see this by typing :t map Data.Char.ord (If you just type in map Data.Char.ord you will get an error, same as if you just typed in Data.Char.ord Haskell, reasonably, doesn’t know how to print a function) In fact, all function applications are curried, so even when you do map Data.Char.ord ['F', 'r', 'e', 'd'] It actually applies the 1st arg to get a function of type [Char] -> [Int], to which it then applies the second arg to get the final value, which it prints. You could write it as this: (map Data.Char.ord) ['F', 'r', 'e', 'd'] i.e. function application is left-associative. If you don’t put in the brackets to explicitly state differently, you effectively get brackets to the left. This is the same as e.g. 7 – 4 – 1 meaning (7 – 4) – 1 which equals 2. It does not mean 7 – (4 – 1) which equals 4. If you want the latter, you need to explicitly write the brackets. You could of course write map (Data.Char.ord ['F', 'r', 'e', 'd']) This is syntactically valid, but would attempt to apply Data.Char.ord to the list of characters, which would give a type error. (And a second type error for attempting to apply map to the result of Data.Char.ord. 1. In type declarations function application is right-associative, so a -> b -> [a] -> [b] means a -> (b -> ([a] -> [b])) which represents a function of one argument (of type a), which returns a result of type (b -> ([a] -> [b])). I’m not sure it would be possible to write such a function, but it would certainly not be the same as map. If you want the brackets in a different place (and we do), then we need to put them explicitly, i.e. (a -> b) -> ([a] -> [b]) Or, we could you the right-associative default to omit the second pair: (a -> b) -> [a] -> [b] 1. Note that the associativity is simply a matter of syntax. The Haskell definition could have said you always need to put the brackets. Then 7 – 4 – 1 would be a syntax error, you’d need to put either (7 – 4) – 1 or 7 – (4 – 1). However, many people find typing without brackets helpful most of the time. (Though I must admit that I often “over-bracket” my code, either because I’m not sure of the associativity of different operators, or because I want to make the code more explicitly clear). Haskell has defined function application to be left-associative because of currying, as described above. Even though map Data.Char.ord ['F', 'r', 'e', 'd'] looks like applying two arguments, it really does (map Data.Char.ord) first. Similarly, Haskell has defined functions in type declarations to be right-associative for the same reason. The function consumes the first arg first, so in (a -> b) -> [a] -> [b] after consuming the (a -> b), you’re left with a function of type ([a] -> [b]). Sorry, that ended up quite a bit longer than I expected, but I hope it helps and apologies if I’ve made any errors/etc. David. From: Lawrence Bottorff Sent: 19 December 2020 03:37 To: Bruno Barbier Cc: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell Subject: Re: [Haskell-beginners] map type explanation So in effect a -> b -> [a] -> [b] wants to be, would be a -> (b -> ([a] -> [b])) without the parens (which is a natural result of lambda calculus, perhaps?) -- which is not what is meant by map. But underlying a Haskell type declaration is currying, is it not? At the type declaration level, it's all currying, correct? Conceptually, I understand how the a -> b "event" needs to be a "package" to apply to the list [a]. The map function commandeers the target function (which alone by itself does some a -> b evaluation) to be a new object that is then applied to each member of list [a]. Good. So (a -> b) then is a notation that signifies this "package-ness". Does anyone have examples of other "packaging" where a function doing some a -> b is changed to (a -> b) ? On Fri, Dec 18, 2020 at 5:18 PM Bruno Barbier > wrote: Hi Lawrence, Lawrence Bottorff > writes: > Why is it not just > > a -> b -> [a] -> [b] > > again, why the parentheses? In Haskell, (->) is a binary operator and is right associative. If you write: a -> b -> [a] -> [b] it implicitly means: a -> (b -> ([a] -> [b])) So here, you need explicit parenthesis: (a -> b) -> [a] -> [b] to mean: (a -> b) -> ([a] -> [b]) It's more about parsing binary operators than about types. Does it help ? Bruno > On Fri, Dec 18, 2020 at 4:10 PM Ut Primum > wrote: > >> Hi, >> >> a -> b is the type of a function taking arguments of a generic type (we >> call it a) and returning results of another type, that we call b. >> >> So >> (a -> b ) -> [a] -> [b] >> Means that you have a first argument that is a function (a-> b), a second >> argument that is a list of elements of the same type of the function input, >> and that the returned element is a list of things of the type of the output >> of the function. >> >> Cheers, >> Ut >> >> Il ven 18 dic 2020, 23:02 Lawrence Bottorff > ha >> scritto: >> >>> Thank you, but why in >>> >>> map :: (a -> b) -> [a] -> [b] >>> >>> are there parentheses around a -> b ? In general, what is the currying >>> aspect of this? >>> >>> >>> On Fri, Dec 18, 2020 at 12:43 PM David McBride > wrote: >>> >>>> They are not parameters, they are the types of the parameters. >>>> >>>> In this case a can really be anything, Int, Char, whatever, so long as >>>> the function takes a single argument of that type and the list that is >>>> given has elements of that same type. >>>> It is the same for b, it doesn't matter what b ends up being, so long as >>>> when you call that function the function's return value is compatible with >>>> the element type of the list that you intended to return from the entire >>>> statement. >>>> >>>> You can mess with it yourself in ghci to see how type inference works. >>>> >>>> >:t show >>>> :show :: Show a => a -> String >>>> >:t map show >>>> map show :: Show a => [a] -> [String] >>>> > :t flip map [1::Int] >>>> > flip map [1::Int] :: (Int -> b) -> [b] >>>> >>>> >>>> On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff > >>>> wrote: >>>> >>>>> I'm looking at this >>>>> >>>>> ghci> :type map >>>>> map :: (a -> b) -> [a] -> [b] >>>>> >>>>> and wondering what the (a -> b) part is about. map takes a function >>>>> and applies it to an incoming list. Good. Understood. I'm guessing that the >>>>> whole Haskell type declaration idea is based on currying, and I do >>>>> understand how the (a -> b) part "takes" an incoming list, [a] and >>>>> produces the [b] output. Also, I don't understand a and b very well >>>>> either. Typically, a is just a generic variable, then b is another >>>>> generic variable not necessarily the same as a. But how are they being >>>>> used in this type declaration? >>>>> >>>>> LB >>>>> _______________________________________________ >>>>> 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 joshuatfriedlander at gmail.com Sat Dec 19 18:31:49 2020 From: joshuatfriedlander at gmail.com (Josh Friedlander) Date: Sat, 19 Dec 2020 20:31:49 +0200 Subject: [Haskell-beginners] map type explanation In-Reply-To: References: <5fdd38de.1c69fb81.3d91b.8f23@mx.google.com> Message-ID: I'm a real beginner, but IIUC might the misunderstanding here be that OP was assuming that since all *functions* in Haskell take only one argument - and multiple-argument functions just hide this by currying - the same must apply to *types*; whereas in fact types *may* take multiple arguments? On Sat, 19 Dec 2020, 13:02 David James, wrote: > Hello - some additional comments: > > > > 1. You should probably read this > , if you haven’t > already. > > > > 1. You can think of the declaration > > fmap :: (a -> b) -> [a] -> [b] > > as meaning: fmap takes two arguments: > > 1st arg of type (a -> b) (i.e. a function, which takes one argument (of > type a) and returns a result (of type b)). > > 2nd arg of type [a] > > and returns: > > a result of type [b] > > > > An example of a function that can be passed as the first argument would be > > Data.Char.ord :: Char -> Int > > If we pass this to map, we bind the type a to Char and the type b to Int. > Then the second argument must be of type [Char], and the result will be > of type [Int]. E.g. > > map Data.Char.ord ['F', 'r', 'e', 'd'] > > gives > > [70,114,101,100] > > > > 1. Haskell allows “currying”. Which means all functions can be > “partially applied”. For example, we can apply map to only one > argument. E.g. > > map Data.Char.ord > > is partially applied, and has type > > [Char] -> [Int] > > You can see this by typing > > :t map Data.Char.ord > > > > (If you just type in > > map Data.Char.ord > > you will get an error, same as if you just typed in > > Data.Char.ord > > Haskell, reasonably, doesn’t know how to print a function) > > > > In fact, all function applications are curried, so even when you do > > map Data.Char.ord ['F', 'r', 'e', 'd'] > > It actually applies the 1st arg to get a function of type [Char] -> [Int], > to which it then applies the second arg to get the final value, which it > prints. You could write it as this: > > (map Data.Char.ord) ['F', 'r', 'e', 'd'] > > > > i.e. function application is left-associative. If you don’t put in the > brackets to explicitly state differently, you effectively get brackets to > the left. This is the same as e.g. > > 7 – 4 – 1 > > meaning > > (7 – 4) – 1 > > which equals 2. It does not mean > > 7 – (4 – 1) > > which equals 4. If you want the latter, you need to > explicitly write the brackets. > > > > You could of course write > > map (Data.Char.ord ['F', 'r', 'e', 'd']) > > This is syntactically valid, but would attempt to apply Data.Char.ord to > the list of characters, which would give a type error. (And a second type > error for attempting to apply map to the result of Data.Char.ord. > > > > 1. In type declarations function application is right-associative, so > > a -> b -> [a] -> [b] > > means > > a -> (b -> ([a] -> [b])) > > which represents a function of one argument (of type a), which returns a > result of type (b -> ([a] -> [b])). I’m not sure it would be possible to > write such a function, but it would certainly not be the same as map. > > > > If you want the brackets in a different place (and we do), then we need to > put them explicitly, i.e. > > (a -> b) -> ([a] -> [b]) > > Or, we could you the right-associative default to omit the > second pair: > > (a -> b) -> [a] -> [b] > > > > 1. Note that the associativity is simply a matter of syntax. The > Haskell definition could have said you always need to put the brackets. > Then 7 – 4 – 1 would be a syntax error, you’d need to put either (7 – 4) – > 1 or 7 – (4 – 1). However, many people find typing without brackets helpful > most of the time. (Though I must admit that I often “over-bracket” my code, > either because I’m not sure of the associativity of different operators, or > because I want to make the code more explicitly clear). > > > > Haskell has defined function application to be left-associative because of > currying, as described above. Even though > > map Data.Char.ord ['F', 'r', 'e', 'd'] > > looks like applying two arguments, it really does (map Data.Char.ord) > first. > > > > Similarly, Haskell has defined functions in type declarations to be > right-associative for the same reason. The function consumes the first arg > first, so in > > (a -> b) -> [a] -> [b] > > after consuming the (a -> b), you’re left with a function of type ([a] -> > [b]). > > > > Sorry, that ended up quite a bit longer than I expected, but I hope it > helps and apologies if I’ve made any errors/etc. > > > > David. > > > > *From: *Lawrence Bottorff > *Sent: *19 December 2020 03:37 > *To: *Bruno Barbier > *Cc: *The Haskell-Beginners Mailing List - Discussion of primarily > beginner-level topics related to Haskell > *Subject: *Re: [Haskell-beginners] map type explanation > > > > So in effect > > > > a -> b -> [a] -> [b] > > > > wants to be, would be > > > > a -> (b -> ([a] -> [b])) > > > > without the parens (which is a natural result of lambda calculus, > perhaps?) -- which is not what is meant by map. But underlying a Haskell > type declaration is currying, is it not? At the type declaration level, > it's all currying, correct? > > > > Conceptually, I understand how the a -> b "event" needs to be a "package" > to apply to the list [a]. The map function commandeers the target > function (which alone by itself does some a -> b evaluation) to be a new > object that is then applied to each member of list [a]. Good. So (a -> b) > then is a notation that signifies this "package-ness". > > > > Does anyone have examples of other "packaging" where a function doing some a > -> b is changed to (a -> b) ? > > > > On Fri, Dec 18, 2020 at 5:18 PM Bruno Barbier wrote: > > > Hi Lawrence, > > Lawrence Bottorff writes: > > > Why is it not just > > > > a -> b -> [a] -> [b] > > > > again, why the parentheses? > > In Haskell, (->) is a binary operator and is right associative. If you > write: > > a -> b -> [a] -> [b] > > it implicitly means: > > a -> (b -> ([a] -> [b])) > > So here, you need explicit parenthesis: > > (a -> b) -> [a] -> [b] > > to mean: > (a -> b) -> ([a] -> [b]) > > It's more about parsing binary operators than about types. > > Does it help ? > > Bruno > > > On Fri, Dec 18, 2020 at 4:10 PM Ut Primum wrote: > > > >> Hi, > >> > >> a -> b is the type of a function taking arguments of a generic type (we > >> call it a) and returning results of another type, that we call b. > >> > >> So > >> (a -> b ) -> [a] -> [b] > >> Means that you have a first argument that is a function (a-> b), a > second > >> argument that is a list of elements of the same type of the function > input, > >> and that the returned element is a list of things of the type of the > output > >> of the function. > >> > >> Cheers, > >> Ut > >> > >> Il ven 18 dic 2020, 23:02 Lawrence Bottorff ha > >> scritto: > >> > >>> Thank you, but why in > >>> > >>> map :: (a -> b) -> [a] -> [b] > >>> > >>> are there parentheses around a -> b ? In general, what is the currying > >>> aspect of this? > >>> > >>> > >>> On Fri, Dec 18, 2020 at 12:43 PM David McBride > wrote: > >>> > >>>> They are not parameters, they are the types of the parameters. > >>>> > >>>> In this case a can really be anything, Int, Char, whatever, so long as > >>>> the function takes a single argument of that type and the list that is > >>>> given has elements of that same type. > >>>> It is the same for b, it doesn't matter what b ends up being, so long > as > >>>> when you call that function the function's return value is compatible > with > >>>> the element type of the list that you intended to return from the > entire > >>>> statement. > >>>> > >>>> You can mess with it yourself in ghci to see how type inference works. > >>>> > >>>> >:t show > >>>> :show :: Show a => a -> String > >>>> >:t map show > >>>> map show :: Show a => [a] -> [String] > >>>> > :t flip map [1::Int] > >>>> > flip map [1::Int] :: (Int -> b) -> [b] > >>>> > >>>> > >>>> On Fri, Dec 18, 2020 at 1:31 PM Lawrence Bottorff > >>>> wrote: > >>>> > >>>>> I'm looking at this > >>>>> > >>>>> ghci> :type map > >>>>> map :: (a -> b) -> [a] -> [b] > >>>>> > >>>>> and wondering what the (a -> b) part is about. map takes a function > >>>>> and applies it to an incoming list. Good. Understood. I'm guessing > that the > >>>>> whole Haskell type declaration idea is based on currying, and I do > >>>>> understand how the (a -> b) part "takes" an incoming list, [a] and > >>>>> produces the [b] output. Also, I don't understand a and b very well > >>>>> either. Typically, a is just a generic variable, then b is another > >>>>> generic variable not necessarily the same as a. But how are they > being > >>>>> used in this type declaration? > >>>>> > >>>>> LB > >>>>> _______________________________________________ > >>>>> 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 coot at coot.me Sun Dec 20 19:43:24 2020 From: coot at coot.me (coot at coot.me) Date: Sun, 20 Dec 2020 19:43:24 +0000 Subject: [Haskell-beginners] map type explanation In-Reply-To: References: Message-ID: Hi, The `(a -> b)` in `map :: (a -> b) -> [a] -> [b]` is a type of function from a type `a` to a type `b`.   Haskell, by default, is using implicit quantification, however using `ScopedTypeVariables` extension you could write `map :: forall a b. (a -> b) -> [a] -> [b]` to make it explicit.  This way you see that both `a` and `b` are introduced by `forall`.  In particular, you can substitute any types, e.g. if you substitute `a` with `Char` and `b` with `Int`, you'll get `map :: (Char -> Int) -> [Char] -> [Int]`.  If you enable `TypeApplication` extension you can do that in `ghci`:  `:t map @Char @Int`  You can read the type of `map` as follows: given a function `f` from type `a` to some type `b`, `map f :: [a] -> [b]`, i.e. `map f` is a function from list of `a` to list of `b`'s. Being able to write functions like `map`, is called parametric polymorphism. Using such  polymorphism you guarantee that the implentation of `map` cannot do any thing with `a`'s and `b`'s, as there's no knowledge about what they are, beside the recepe how to transform `a`'s into `b` given by `f`.  This limits what `map f` can do to a list of `a`'s. Best regards, Marcin Szamotulski ‐‐‐‐‐‐‐ Original Message ‐‐‐‐‐‐‐ On Friday, December 18th, 2020 at 19:30, Lawrence Bottorff wrote: > I'm looking at this > > ghci> :type map > > map :: (a -> b) -> [a] -> [b] > > and wondering what the (a -> b) part is about. map takes a function and applies it to an incoming list. Good. Understood. I'm guessing that the whole Haskell type declaration idea is based on currying, and I do understand how the (a -> b) part "takes" an incoming list, [a] and produces the [b] output. Also, I don't understand a and b very well either. Typically, a is just a generic variable, then b is another generic variable not necessarily the same as a. But how are they being used in this type declaration? > > LB -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 509 bytes Desc: OpenPGP digital signature URL: From maxim.frolov.07 at gmail.com Mon Dec 21 16:00:51 2020 From: maxim.frolov.07 at gmail.com (Maxim Frolov) Date: Mon, 21 Dec 2020 16:00:51 +0000 Subject: [Haskell-beginners] Problem with minimax with alpha beta pruning In-Reply-To: <15ab33b5-d777-488a-8f59-06bc12ee39ea@Spark> References: <15ab33b5-d777-488a-8f59-06bc12ee39ea@Spark> Message-ID: <1da56b08-a73f-407e-881f-6de8c82df5ca@Spark> Hi All, I am new to Haskell and got stuck while experimenting with minimax algorithm (tic-tac-toe game). Just for learning I am trying to avoid external modules and use only the standard Prelude library. Here is the code snippet: type Pos = (Int,Int) -- Players are O (minimizing) and X (maximizing), B is for the draw (blank), I and J are used for -INF and +INF respectively data Player = I | O | B | X | J     deriving (Eq, Ord, Show) type Grid = [(Pos,Player)] data Tree a = Node a [Tree a]     deriving Show minimax :: Player -> Player -> Tree Grid -> Tree (Grid, Player) minimax _ _ (Node g [])  | wins X g = Node (g,X) []  | wins O g = Node (g,O) []  | otherwise = Node (g,B) [] minimax a b (Node g ts)  | turn g == X =    let ts' = [minimax alpha b t | t <- ts, alpha < b]        ps = [p | Node (_,p) _ <- ts']        alpha = maximum (a:ps)    in Node (g, alpha) ts'  | turn g == O =    let ts' = [minimax a beta t | t <- ts, a < beta]        ps = [p | Node (_,p) _ <- ts']        beta = minimum (b:ps)    in Node (g, beta) ts' The function call is like: minimax I J tree It looks like I got a recursion loop. Could someone advise how to approach the problem? Thank you, Max -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Tue Dec 22 05:59:57 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Mon, 21 Dec 2020 23:59:57 -0600 Subject: [Haskell-beginners] Lambda expression currying Message-ID: Here's something from *Learn You... * Lambdas are normally surrounded by parentheses unless we mean for them to extend all the way to the right. Here's something interesting: due to the way functions are curried by default, these two are equivalent: addThree :: (Num a) => a -> a -> a -> a addThree x y z = x + y + z addThree :: (Num a) => a -> a -> a -> a addThree = \x -> \y -> \z -> x + y + z If we define a function like this, it's obvious why the type declaration is what it is. There are three ->'s in both the type declaration and the equation. But of course, the first way to write functions is far more readable, the second one is pretty much a gimmick to illustrate currying. So with the lambda version how exactly is the currying taking place? I understand something like this doubleDouble x = (\x -> x*2) (2 * x) So with beta reduction we have (2*x)*2, then plug in the argument. And with this overwrite x = (\x -> (\x -> (\x -> x) 4) 3) 2 which gives (\x -> (\x -> 4) 3) 2 (\x -> 4) 2 4 But how is the beta reduction happening with addThree? BTW, I flunked lambda calculus in Kindergarten. LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Tue Dec 22 06:54:46 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Tue, 22 Dec 2020 07:54:46 +0100 Subject: [Haskell-beginners] Lambda expression currying In-Reply-To: References: Message-ID: <20201222065446.GA20111@extensa> Hello Lawrence, Il 21 dicembre 2020 alle 23:59 Lawrence Bottorff ha scritto: > addThree :: (Num a) => a -> a -> a -> a > addThree = \x -> \y -> \z -> x + y + z > […] > > But how is the beta reduction happening with addThree? Should be: addThree = (\x -> \y -> \z -> x + y + z) 1 2 3 = (\y -> \z -> 1 + y + z) 2 3 beta = (\z -> 1 + 2 + z) 3 beta = 1 + 2 + 3 beta = … Does that make sense? —F From ky3 at atamo.com Tue Dec 22 08:27:11 2020 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Tue, 22 Dec 2020 15:27:11 +0700 Subject: [Haskell-beginners] Problem with minimax with alpha beta pruning In-Reply-To: <1da56b08-a73f-407e-881f-6de8c82df5ca@Spark> References: <15ab33b5-d777-488a-8f59-06bc12ee39ea@Spark> <1da56b08-a73f-407e-881f-6de8c82df5ca@Spark> Message-ID: Hi Maxim, The scope of this question falls outside this beginners list, which tends toward questions about haskell syntax (see other active thread). You will typically find more response on the haskell-cafe list, which you might want to resend your query to. On Mon, Dec 21, 2020 at 11:01 PM Maxim Frolov wrote: > Hi All, > > I am new to Haskell and got stuck while experimenting with minimax > algorithm (tic-tac-toe game). Just for learning I am trying to avoid > external modules and use only the standard Prelude library. > > Here is the code snippet: > > type Pos = (Int,Int) > -- Players are O (minimizing) and X (maximizing), B is for the draw > (blank), I and J are used for -INF and +INF respectively > data Player = I | O | B | X | J > deriving (Eq, Ord, Show) > type Grid = [(Pos,Player)] > data Tree a = Node a [Tree a] > deriving Show > > minimax :: Player -> Player -> Tree Grid -> Tree (Grid, Player) > minimax _ _ (Node g []) > | wins X g = Node (g,X) [] > | wins O g = Node (g,O) [] > | otherwise = Node (g,B) [] > minimax a b (Node g ts) > | turn g == X = > let ts' = [minimax alpha b t | t <- ts, alpha < b] > ps = [p | Node (_,p) _ <- ts'] > alpha = maximum (a:ps) > in Node (g, alpha) ts' > | turn g == O = > let ts' = [minimax a beta t | t <- ts, a < beta] > ps = [p | Node (_,p) _ <- ts'] > beta = minimum (b:ps) > in Node (g, beta) ts' > > > The function call is like: > > minimax I J tree > > > It looks like I got a recursion loop. Could someone advise how to approach > the problem? > > Thank you, > Max > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -- -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From maxim.frolov.07 at gmail.com Tue Dec 22 13:18:56 2020 From: maxim.frolov.07 at gmail.com (Maxim Frolov) Date: Tue, 22 Dec 2020 13:18:56 +0000 Subject: [Haskell-beginners] Problem with minimax with alpha beta pruning In-Reply-To: References: <15ab33b5-d777-488a-8f59-06bc12ee39ea@Spark> <1da56b08-a73f-407e-881f-6de8c82df5ca@Spark> Message-ID: <7fb37eab-89cd-4559-9c92-5dcb68c7f20b@Spark> Got it. Thank you Kim-Ee! On 22 Dec 2020, 08:28 +0000, Kim-Ee Yeoh , wrote: > Hi Maxim, > > The scope of this question falls outside this beginners list, which tends toward questions about haskell syntax (see other active thread). > > You will typically find more response on the haskell-cafe list, which you might want to resend your query to. > > > On Mon, Dec 21, 2020 at 11:01 PM Maxim Frolov wrote: > > > Hi All, > > > > > > I am new to Haskell and got stuck while experimenting with minimax algorithm (tic-tac-toe game). Just for learning I am trying to avoid external modules and use only the standard Prelude library. > > > > > > Here is the code snippet: > > > > > > type Pos = (Int,Int) > > > -- Players are O (minimizing) and X (maximizing), B is for the draw (blank), I and J are used for -INF and +INF respectively > > > data Player = I | O | B | X | J > > >     deriving (Eq, Ord, Show) > > > type Grid = [(Pos,Player)] > > > data Tree a = Node a [Tree a] > > >     deriving Show > > > > > > minimax :: Player -> Player -> Tree Grid -> Tree (Grid, Player) > > > minimax _ _ (Node g []) > > >  | wins X g = Node (g,X) [] > > >  | wins O g = Node (g,O) [] > > >  | otherwise = Node (g,B) [] > > > minimax a b (Node g ts) > > >  | turn g == X = > > >    let ts' = [minimax alpha b t | t <- ts, alpha < b] > > >        ps = [p | Node (_,p) _ <- ts'] > > >        alpha = maximum (a:ps) > > >    in Node (g, alpha) ts' > > >  | turn g == O = > > >    let ts' = [minimax a beta t | t <- ts, a < beta] > > >        ps = [p | Node (_,p) _ <- ts'] > > >        beta = minimum (b:ps) > > >    in Node (g, beta) ts' > > > > > > > > > The function call is like: > > > > > > minimax I J tree > > > > > > > > > It looks like I got a recursion loop. Could someone advise how to approach the problem? > > > > > > Thank you, > > > Max > > > > > > > > > _______________________________________________ > > > Beginners mailing list > > > Beginners at haskell.org > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -- > -- Kim-Ee > _______________________________________________ > 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 borgauf at gmail.com Tue Dec 22 16:00:22 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Tue, 22 Dec 2020 10:00:22 -0600 Subject: [Haskell-beginners] Lambda expression currying In-Reply-To: <20201222065446.GA20111@extensa> References: <20201222065446.GA20111@extensa> Message-ID: Thanks, that's clearer now. On Tue, Dec 22, 2020 at 12:55 AM Francesco Ariis wrote: > Hello Lawrence, > > Il 21 dicembre 2020 alle 23:59 Lawrence Bottorff ha scritto: > > addThree :: (Num a) => a -> a -> a -> a > > addThree = \x -> \y -> \z -> x + y + z > > […] > > > > But how is the beta reduction happening with addThree? > > Should be: > > addThree = (\x -> \y -> \z -> x + y + z) 1 2 3 > = (\y -> \z -> 1 + y + z) 2 3 beta > = (\z -> 1 + 2 + z) 3 beta > = 1 + 2 + 3 beta > = … > > Does that make sense? > —F > _______________________________________________ > 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 borgauf at gmail.com Tue Dec 22 17:48:02 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Tue, 22 Dec 2020 11:48:02 -0600 Subject: [Haskell-beginners] Another currying and lambda question Message-ID: In *Learn You... *I'm seeing this flipA :: (a -> b -> c) -> b -> a -> c flipA f x y = f y x and this flipB :: (a -> b -> c) -> b -> a -> c flipB f = \x y -> f y x What is it specifically about currying that makes flipA possible? Also, with flipB, could someone explain the beta reduction? It looks like f is not being acted on, just passed along, Would it look more like this in lambda calculus? (\x \y -> f y x) then (\x \y -> f y x) g a b gives g b a ? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Tue Dec 22 17:59:21 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Tue, 22 Dec 2020 18:59:21 +0100 Subject: [Haskell-beginners] Another currying and lambda question In-Reply-To: References: Message-ID: <20201222175921.GA3626@extensa> Il 22 dicembre 2020 alle 11:48 Lawrence Bottorff ha scritto: > flipA :: (a -> b -> c) -> b -> a -> c > flipA f x y = f y x > > What is it specifically about currying that makes flipA possible? I do not see how currying is involved here! Maybe when you pass a function to an higher order one? > flipB :: (a -> b -> c) -> b -> a -> c > flipB f = \x y -> f y x > > Also, with flipB, could someone explain the beta reduction? It looks > like f is not being acted on, just passed along, Would it look more > like this in lambda calculus? Indeed `f` is not being acted on (i.e. it is «outside» of the lambda) (λx. λy. f y x) b a (λy. f y b) a beta f a b beta fully expressed with lambdas would be: (λf. λx. λy. f y x) g b a From borgauf at gmail.com Tue Dec 22 21:15:42 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Tue, 22 Dec 2020 15:15:42 -0600 Subject: [Haskell-beginners] Another currying and lambda question In-Reply-To: <20201222175921.GA3626@extensa> References: <20201222175921.GA3626@extensa> Message-ID: Thanks again! On Tue, Dec 22, 2020 at 11:59 AM Francesco Ariis wrote: > Il 22 dicembre 2020 alle 11:48 Lawrence Bottorff ha scritto: > > flipA :: (a -> b -> c) -> b -> a -> c > > flipA f x y = f y x > > > > What is it specifically about currying that makes flipA possible? > > I do not see how currying is involved here! Maybe when you pass > a function to an higher order one? > > > flipB :: (a -> b -> c) -> b -> a -> c > > flipB f = \x y -> f y x > > > > Also, with flipB, could someone explain the beta reduction? It looks > > like f is not being acted on, just passed along, Would it look more > > like this in lambda calculus? > > Indeed `f` is not being acted on (i.e. it is «outside» of the lambda) > > (λx. λy. f y x) b a > (λy. f y b) a beta > f a b beta > > fully expressed with lambdas would be: > > (λf. λx. λy. f y x) g b a > > _______________________________________________ > 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 borgauf at gmail.com Thu Dec 24 03:12:08 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Wed, 23 Dec 2020 21:12:08 -0600 Subject: [Haskell-beginners] Confusion over currying, , lambda, and closures Message-ID: I have these three versions of addition addA x y = x + y addB x = \y -> x + y addC = \x -> \y -> x + y and all three add two arguments just fine > addA 2 3 5 > addB 2 3 5 > addC 2 3 5 but I can't see how addB and addC are actually accomplishing this. addA is currying, which I don't fully follow. addC I understand beta reduction-wise (\x -> \y -> x + y) 2 3 (\y -> 2 + y) 3 (2 + 3) 5 but I don't understand addB and what steps are happening currying/beta reduction-wise. Can someone break down the steps with addA and addB? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Thu Dec 24 04:02:17 2020 From: bob at redivi.com (Bob Ippolito) Date: Wed, 23 Dec 2020 20:02:17 -0800 Subject: [Haskell-beginners] Confusion over currying, , lambda, and closures In-Reply-To: References: Message-ID: The steps and semantics are the same, the only meaningful difference is syntax. These two definitions are indistinguishable: f x = y f = \x -> y In basically the same way that these two expressions are: (+) 1 2 1 + 2 In Haskell there are many cases where a more convenient but equivalent syntax exists to express certain terms. This is referred to as syntax sugar. On Wed, Dec 23, 2020 at 19:12 Lawrence Bottorff wrote: > I have these three versions of addition > > addA x y = x + y > addB x = \y -> x + y > addC = \x -> \y -> x + y > > and all three add two arguments just fine > > > addA 2 3 > 5 > > addB 2 3 > 5 > > addC 2 3 > 5 > > but I can't see how addB and addC are actually accomplishing this. addA is > currying, which I don't fully follow. addC I understand beta reduction-wise > > (\x -> \y -> x + y) 2 3 > (\y -> 2 + y) 3 > (2 + 3) > 5 > > but I don't understand addB and what steps are happening currying/beta > reduction-wise. Can someone break down the steps with addA and addB? > > LB > > > _______________________________________________ > 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 fa-ml at ariis.it Thu Dec 24 04:37:22 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Thu, 24 Dec 2020 05:37:22 +0100 Subject: [Haskell-beginners] Confusion over currying, , lambda, and closures In-Reply-To: References: Message-ID: <20201224043722.GB911@extensa> Il 23 dicembre 2020 alle 21:12 Lawrence Bottorff ha scritto: > I have these three versions of addition > > addA x y = x + y > addB x = \y -> x + y > addC = \x -> \y -> x + y > > […] > > I can't see how addB and addC are actually accomplishing this. addA is > currying, which I don't fully follow. Parameters on the left-hand side of a function definition can always be expressed as a lambda, by «plucking» them from the rightmost one addA x y = x + y addA x = \y -> x + y addA = \x -> \y -> x + y -- those three are equal! Intuitively you can say that first we are binding the patterns in the function definition and then the one left in the lambda right-hand side (if any). So: add 3 5 addA x = \y -> x + y 3 5 \y -> 3 + y 5 3 + 5 I suspect what the book is trying to teach you is that you can partially apply a function and pass it around merrily: map (addA 3) [1, 2, 3] So by writing `addA 3` we obtain: addA :: Int -> Int -> Int addA :: Int -> (Int -> Int) -- can also be written like this -- since `(->)` is associates to -- the right add3 :: Int -> Int -- applying addA to 3 another function with one parameter less. Once everything is applied, you will get your result! From frederic-emmanuel.picca at synchrotron-soleil.fr Thu Dec 24 06:48:51 2020 From: frederic-emmanuel.picca at synchrotron-soleil.fr (PICCA Frederic-Emmanuel) Date: Thu, 24 Dec 2020 06:48:51 +0000 Subject: [Haskell-beginners] mconcat Message-ID: Hello, I have a monoid and I would like to know if there is a way to do the concatenation in parallele ? the mappend method takes time for my type. thanks for you help. Frederic From jays at panix.com Thu Dec 24 07:15:25 2020 From: jays at panix.com (Jay Sulzberger) Date: Thu, 24 Dec 2020 07:15:25 +0000 () Subject: [Haskell-beginners] Confusion over currying, , lambda, and closures In-Reply-To: References: Message-ID: On Wed, 23 Dec 2020, Lawrence Bottorff wrote: > I have these three versions of addition > > addA x y = x + y > addB x = \y -> x + y > addC = \x -> \y -> x + y > > and all three add two arguments just fine > >> addA 2 3 > 5 >> addB 2 3 > 5 >> addC 2 3 > 5 > > but I can't see how addB and addC are actually accomplishing this. addA is > currying, which I don't fully follow. addC I understand beta reduction-wise > > (\x -> \y -> x + y) 2 3 > (\y -> 2 + y) 3 > (2 + 3) > 5 > > but I don't understand addB and what steps are happening currying/beta > reduction-wise. Can someone break down the steps with addA and addB? > > LB Dear Lawrence Bottorf, your questions are delightful! Heaven forwarding, I will respond more fully and clearly. The questions you ask strike at the heart of the issue: Why is Haskell so hard to learn? I offer no decent answer here, but I give below a transcript of an incoherent session with ghci on panix3.panix.com, panix3% ghci --version The Glorious Glasgow Haskell Compilation System, version 7.8.4 panix3% uname -a NetBSD panix3.panix.com 9.0 NetBSD 9.0 (PANIX-XEN-USER) #1: Sun May 3 21:15:18 EDT 2020 root at juggler.panix.com:/misc/obj64/misc/devel/netbsd/9.0/src/sys/arch/amd64/compile/PANIX-XEN-USER amd64 panix3% Below is the whole transcript of the session. Note two things: 1. I do not know ghci. 2. I failed to ask the ':t" questions in the right order, for a good training video. But I hope the transcript is helpful. oo--JS. bash-5.0$ ghci GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Prelude> let addA x y = x + y Prelude> addA :6:1: No instance for (Show (a0 -> a0 -> a0)) arising from a use of `print' In a stmt of an interactive GHCi command: print it Prelude> print addA :7:1: No instance for (Show (a0 -> a0 -> a0)) arising from a use of `print' In the expression: print addA In an equation for `it': it = print addA :7:7: No instance for (Num a0) arising from a use of `addA' The type variable `a0' is ambiguous Note: there are several potential instances: instance Num Double -- Defined in `GHC.Float' instance Num Float -- Defined in `GHC.Float' instance Integral a => Num (GHC.Real.Ratio a) -- Defined in `GHC.Real' ...plus three others In the first argument of `print', namely `addA' In the expression: print addA In an equation for `it': it = print addA Prelude> let addA x y = x + y Prelude> print it :9:7: Not in scope: `it' Perhaps you meant `id' (imported from Prelude) Prelude> addA :10:1: No instance for (Show (a0 -> a0 -> a0)) arising from a use of `print' In a stmt of an interactive GHCi command: print it Prelude> addA 7 :11:1: No instance for (Show (a0 -> a0)) arising from a use of `print' In a stmt of an interactive GHCi command: print it Prelude> addA 7 5 12 Prelude> (addA 7) :13:1: No instance for (Show (a0 -> a0)) arising from a use of `print' In a stmt of an interactive GHCi command: print it Prelude> :t (addA 7) (addA 7) :: Num a => a -> a Prelude> :t addA addA :: Num a => a -> a -> a Prelude> :t addA 7 addA 7 :: Num a => a -> a Prelude> :t addA 7 5 addA 7 5 :: Num a => a Prelude> let addB x = \y -> x + y Prelude> :t addB addB :: Num a => a -> a -> a Prelude> :t addB 7 addB 7 :: Num a => a -> a Prelude> :t (addB 7) (addB 7) :: Num a => a -> a Prelude> :t addB 7 5 addB 7 5 :: Num a => a Prelude> let addC = \x -> \y -> x + y Prelude> :t addC addC :: Num a => a -> a -> a Prelude> :t (addC) (addC) :: Num a => a -> a -> a Prelude> :t addC 7 addC 7 :: Num a => a -> a Prelude> :t (addC 7) (addC 7) :: Num a => a -> a Prelude> :t addC 7 5 addC 7 5 :: Num a => a Prelude> addC 7 5 12 Prelude> (addC 7 5) 12 Prelude> (exit) :31:2: Not in scope: `exit' Prelude> Leaving GHCi. bash-5.0$ From joel.neely at gmail.com Thu Dec 24 12:12:08 2020 From: joel.neely at gmail.com (Joel Neely) Date: Thu, 24 Dec 2020 06:12:08 -0600 Subject: [Haskell-beginners] Confusion over currying, , lambda, and closures In-Reply-To: References: Message-ID: Hi, Lawrence, Would it help you to think of addB as a function that takes its argument x and returns a function/lambda that adds x to the argument to which that returned function is applied? Best wishes, -jn- On Wed, Dec 23, 2020 at 9:12 PM Lawrence Bottorff wrote: > I have these three versions of addition > > addA x y = x + y > addB x = \y -> x + y > addC = \x -> \y -> x + y > > and all three add two arguments just fine > > > addA 2 3 > 5 > > addB 2 3 > 5 > > addC 2 3 > 5 > > but I can't see how addB and addC are actually accomplishing this. addA is > currying, which I don't fully follow. addC I understand beta reduction-wise > > (\x -> \y -> x + y) 2 3 > (\y -> 2 + y) 3 > (2 + 3) > 5 > > but I don't understand addB and what steps are happening currying/beta > reduction-wise. Can someone break down the steps with addA and addB? > > LB > > > _______________________________________________ > 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 borgauf at gmail.com Tue Dec 29 21:43:46 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Tue, 29 Dec 2020 15:43:46 -0600 Subject: [Haskell-beginners] OOP exercise with closures Message-ID: First, thanks for all the help you've offered. Often enough, it's so much that it takes me time to sift through all the good stuff. Thanks again. Okay, I'm in Lesson 10 of *Get Programming with Haskell * and we're creating an OOP-like world with closures. The first step is a cup object with one attribute, its ounce size. Here's a "constructor" cup :: t1 -> (t1 -> t2) -> t2 cup flOz = \message -> message flOz so this returns upon use > myCup = cup 6 myCup which has "internally" a lambda function (\message -> message) 6 waiting, correct? Now a "method" getOz aCup = aCup (\foz -> foz) creates a closure on the lambda function (\foz -> foz) . So upon calling > getOz myCup 6 I'm guessing myCup (\foz -> foz) was evaluated, but I don't understand how the 6 that went in as the bound variable in the constructor came out again with getOz. As I understand it, the cup constructor creates a closure around the given bound argument flOz -- which is confusing because I thought closures "carried" free variables, not bound variables. Perhaps the getOz lambda function (\foz -> foz) replaces completely the (\message -> message) lambda function? So the constructor could have been written cup flOz = (\message -> message) flOz In any case I'm shaky on how A) cup 6 sets up/stores the 6 in the creation of myCup and then how getOz pops it out again. LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Tue Dec 29 22:06:54 2020 From: fa-ml at ariis.it (Francesco Ariis) Date: Tue, 29 Dec 2020 23:06:54 +0100 Subject: [Haskell-beginners] OOP exercise with closures In-Reply-To: References: Message-ID: <20201229220654.GA10168@extensa> Il 29 dicembre 2020 alle 15:43 Lawrence Bottorff ha scritto: > Okay, I'm in Lesson 10 of *Get Programming with Haskell * and we're > creating an OOP-like world with closures. The first step is a cup object > with one attribute, its ounce size. Here's a "constructor" > > cup :: t1 -> (t1 -> t2) -> t2 > cup flOz = \message -> message flOz > > so this returns upon use > > > myCup = cup 6 > > myCup which has "internally" a lambda function > > (\message -> message) 6 > > waiting, correct? Not exactly. `myCup` is a function with takes another function as input λ> :t myCup myCup :: (Integer -> t2) -> t2 and the body looks like this \f -> f 6 `\f -> f 6` is different from `(\f -> f) 6`! > Now a "method" > > getOz aCup = aCup (\foz -> foz) > > creates a closure on the lambda function (\foz -> foz) . So upon calling > > > getOz myCup > 6 > > I'm guessing myCup (\foz -> foz) was evaluated, but I don't understand how > the 6 that went in as the bound variable in the constructor came out again > with getOz. To recap, `myCup` expands to: myCup cup 6 \message -> message 6 Now, applying `getOz` to it… getOz myCup myCup (\foz -> foz) (\message -> message 6) (\foz -> foz) (\foz -> foz) 6 6 From borgauf at gmail.com Wed Dec 30 03:12:29 2020 From: borgauf at gmail.com (Lawrence Bottorff) Date: Tue, 29 Dec 2020 21:12:29 -0600 Subject: [Haskell-beginners] OOP exercise with closures In-Reply-To: <20201229220654.GA10168@extensa> References: <20201229220654.GA10168@extensa> Message-ID: Thanks! Since I studied lambda calc a bit I understand the steps (\message -> message 6) (\foz -> foz) (\foz -> foz) 6 6 But this is so bizarre! To have a "constructor" that creates an instance, which is then really a holder of a lambda calculation is a mind-bender. On Tue, Dec 29, 2020 at 4:07 PM Francesco Ariis wrote: > Il 29 dicembre 2020 alle 15:43 Lawrence Bottorff ha scritto: > > Okay, I'm in Lesson 10 of *Get Programming with Haskell * and we're > > creating an OOP-like world with closures. The first step is a cup object > > with one attribute, its ounce size. Here's a "constructor" > > > > cup :: t1 -> (t1 -> t2) -> t2 > > cup flOz = \message -> message flOz > > > > so this returns upon use > > > > > myCup = cup 6 > > > > myCup which has "internally" a lambda function > > > > (\message -> message) 6 > > > > waiting, correct? > > Not exactly. `myCup` is a function with takes another function as input > > λ> :t myCup > myCup :: (Integer -> t2) -> t2 > > and the body looks like this > > \f -> f 6 > > `\f -> f 6` is different from `(\f -> f) 6`! > > > > Now a "method" > > > > getOz aCup = aCup (\foz -> foz) > > > > creates a closure on the lambda function (\foz -> foz) . So upon calling > > > > > getOz myCup > > 6 > > > > I'm guessing myCup (\foz -> foz) was evaluated, but I don't understand > how > > the 6 that went in as the bound variable in the constructor came out > again > > with getOz. > > To recap, `myCup` expands to: > > myCup > cup 6 > \message -> message 6 > > Now, applying `getOz` to it… > > getOz myCup > myCup (\foz -> foz) > (\message -> message 6) (\foz -> foz) > (\foz -> foz) 6 > 6 > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: