Fork me on GitHub
#other-languages
<
2018-07-25
>
borkdude19:07:50

Is anyone here by any chance doing the exercises from HaskellBook? I need a hint on assignment S from chapter 21

ddellacosta19:07:29

I don’t know much about that book but can you paste the problem in here? Or, go to #haskell on freenode…

borkdude19:07:28

@ddellacosta I need to write a Traversable instance for data S n a = S (n a) a deriving (Eq, Show). This is the code I have:

{-# LANGUAGE FlexibleContexts #-}

module TraversableS where

import Test.QuickCheck hiding (Success, Failure)
import Test.QuickCheck.Checkers
import Test.QuickCheck.Classes
import Data.Monoid

data S n a = S (n a) a deriving (Eq, Show)

instance ( Functor n
         , Arbitrary (n a)
         , Arbitrary a )
         => Arbitrary (S n a) where
  arbitrary =
    S <$> arbitrary <*> arbitrary

instance ( Applicative n
         , Testable (n Property)
         , EqProp a )
  => EqProp (S n a) where
  (S x y) =-= (S p q) =
    (property $ (=-=) <$> x <*> p)
    .&. (y =-= q)

instance (Functor n) => Functor (S n) where
  fmap f (S fa a) = S foo (f a) where
    foo = (fmap f fa) -- we must do this to keep it of the type S (n b) b

instance (Foldable n) => Foldable (S n) where
  foldMap f (S fa a) = foo <> f a where
    foo = foldMap f fa

instance (Traversable n)
  => Traversable (S n) where
  traverse f (S fa a) = s where
    x = traverse f fa
    y = f a
    s = S <$> x <*> y

mainS = -- why you not work?
  let trigger :: (S [] (Int, Int, [Int]))
      trigger = undefined
  in quickBatch (traversable trigger)
But the output:
traversable:
  fmap:    *** Failed! Falsifiable (after 12 tests and 2 shrinks):
<function>
S [-11,8,-7,-9,-5,3,1,11,2,-10,6] (-8)
LHS
1
  foldMap: +++ OK, passed 500 tests. 

borkdude19:07:06

Some of the code was already given in the book, but not the Foldable and Traversable instances

ddellacosta19:07:23

just include DeriveFoldable and DeriveTraversable? 😛

ddellacosta19:07:07

seriously, not sure exactly what it’s testing so not sure I can help, but let me stare at it a bit

borkdude19:07:30

I’m afk for 15 minutes

ddellacosta19:07:33

and maybe someone else who is better at Haskell will show up too

ddellacosta20:07:59

@borkdude so is S [-11,8,-7,-9,-5,3,1,11,2,-10,6] (-8) an instance of S n a, where a is Int and n is [] (a list)?

ddellacosta20:07:26

if I’m reading the types correctly, it seems like the foldMap instance is treating the semigroup for n a and a as the same thing

ddellacosta20:07:37

but if it’s type-checking that suggests I’m confused

borkdude20:07:12

@ddellacosta that’s correct, n is [] and a is Int

borkdude20:07:38

@ddellacosta hmm, it does type-check, but let me check this

borkdude20:07:01

it also law-checks

ddellacosta20:07:16

no I’m sorry, I was confused

ddellacosta20:07:41

so yeah your Foldable seems pretty alright

borkdude20:07:45

yeah, foo is of type m and so is f a

ddellacosta20:07:53

so what about the traverse then…are you sure you want an S n a return value? like if you have a (S n a) and n is Applicative, maybe that needs to be n (S n b) (where b is the output of your a -> f b)? nevermind, was misreading

ddellacosta20:07:08

but again, if it’s type-checking I may be confused

ddellacosta20:07:23

I’m just comparing your code to the type sig for traverse

ddellacosta20:07:05

…and hoping my questions maybe trigger you realizing something, even if I’m offbase

borkdude20:07:22

the type here is (a -> f b) -> S n a -> f (S n b)

borkdude20:07:15

so for example:

-- example = S (Just "http://...") "http://..."
-- get :: String -> IO Resp
-- fmap get example :: S (Just (IO resp)) (IO resp)
-- but we want: IO (S (Just resp) resp)

borkdude20:07:21

this is very confusing

ddellacosta20:07:24

(thinking/reading)

ddellacosta20:07:29

yeah this is a tough one, lots of moving parts

ddellacosta20:07:19

shoot @borkdude I have to go, I’m sorry, if I can get back on and help more I will--you may have more luck posting this in #haskell on IRC though, I bet with the level of folks there someone will immediately point out the issue

borkdude20:07:36

Example:

type Resp = String
get ::  String -> IO Resp
get s = pure "<html></html>"
example = S (Just "http://") "http://"
test1 :: S Maybe (IO Resp)
test1 = fmap get example
test2 :: IO (S Maybe Resp) 
test2 = traverse get example -- S (Just "<html></html>") "<html></html>"

ddellacosta20:07:20

wait so with that example, that’s showing you how it does work now? (except the return value of the last one is in IO I guess, assuming you dumped that out in ghci)

ddellacosta20:07:50

yeah it does, just tried it, okay

ddellacosta20:07:46

damn I can’t see what’s wrong with it, for example just tried this too:

λ> traverse (\n -> [n+1]) (S [1,2,3] 1)
[S [2,3,4] 2]
λ>

ddellacosta20:07:05

okay actually going away now

borkdude20:07:26

thanks. The full code is here in this gist. I’ll start asking others as well: https://gist.github.com/borkdude/3d7eebe5fd2f7ac1fdca73a8cceb608e

borkdude21:07:03

@ddellacosta mystery solved, the EqProp instance from the book was wrong