Friday, December 29, 2017

November 2017 1HaskellADay 1Liner problem and solutions

  • November 5th, 2017: f :: Map Int [a] -> [b] - > [(Int, b)]
    for, e.g.: f mapping bs
    length bs == length (concat (Map.elems mapping))
    define f
    • Andreas Källberg @Anka213 Using parallel list comprehensions:
      f mp bs = [ (k,b) | (k,as) <-assocs mp, a <- as | b <- bs]
    • Steve Trout @strout f = zip . foldMapWithKey (fmap . const)

Thursday, November 30, 2017

November 2017 1HaskellADay problems and solutions

Saturday, November 4, 2017

October 2017 1Liner 1HaskellADay problems and solutions

  • October 20th, 2017:
    You have a list of numbers: [1,2,3,4]
    You have a list of the same length of number fns: [succ, id, id, succ]
    You want: [2,2,3,5]
    •  🇪🇺 Cλément D  🌈  🐇 @clementd zipWith (flip ($)) ?
      •  he adds: `zipWith (flip id)` is a bit shorter tho
    • Simon Courtenage @SCourtenage zipWith ($) [succ,id,id,succ] [1,2,3,4]
    • lukasz @lukaszklekot getZipList $ ZipList [succ, id, id, succ] <*> ZipList [1, 2, 3, 4]
    • Alexey Radkov @sheshanaag (map (uncurry ($)) .) . zip
  • October 5th, 2017: "reverse the sequencing"
    You have [[(1,2),(1,3),(1,7)],[(9,2)],[(11,3)]]
    You want [(1,[2,3,7]),(9,[2]),(11,[3])]
    • bazzargh @bazzargh map ((,) <$> head.(map fst) <*> (map snd))
    • bazzargh @bazzargh map ((first head).unzip)
    • Chris Martin @chris__martin \x -> [(a, b : fmap snd xs) | Just ((a, b) :| xs) <- fmap="" li="" nonempty="" x="">
    • Simon Courtenage @SCourtenage fmap (\x -> (fst . head $ x, fmap snd x))
      • Denis Stoyanov  🐜 @xgrommx Your solution nice) but u can do it with point free style like
        • fmap(fst.head &&& fmap snd)
    • Denis Stoyanov  🐜 @xgrommx My solution is ugly, but I wanna to solve it with traverse)
      • fmap(first head . traverse (first (:[])))
    • Andreas Källberg @Anka213 map$fst.head&&&map snd
    • Scott Fleischma‏ @scottfleischman
      traverse
        $ _1
          (\case
              [y] -> Just y
              _ -> Nothing
          . nub
          )
        . unzip
        :: [[(Int, Int)]] -> Maybe [(Int, [Int])]
    • Scott Fleischman @scottfleischman
      let
    •  sing [] = Left "Too few"
       sing [x] = Right x
       sing (_ : _) = Left "Too many"
       valid = sing . nub
       go = _1 valid . unzip
      in traverse go
    • matt @themattchan map ((head *** id ) . unzip)
  • October 3rd, 2017:
    you have [(1,[2,3,4]),(10,[5,6,7])]
    you want [(1,2),(1,3),(1,4),(10,5),(10,6),(10,7)]

    or, generally: [(a,[b])] -> [(a,b)]

    Go!

    • bazzargh @bazzargh (uncurry (zip . repeat) =<<)
    • Bruno @Brun0Cad (=<<) sequence
    • Denis Stoyanov  🐜 @xgrommx fmap (uncurry (liftA2(,) . (:[])))
      • Darren G @Kludgy I like that this doesn't unnecessarily implicate the sequentiality of bind.
    • Darren G @Kludgy Funny this same product came up at work last week.
      concatMap $ \(a,bs) -> fmap (\b -> (a,b)) bs

Tuesday, October 31, 2017

October 2017 1HaskellADay problems and solutions

Tuesday, October 3, 2017

September 2017 1HaskellADay 1Liner problems and solutions

  • September 26th, 2017:
    art2RawNames art = Raw (artId art) <$> (Map.lookup "Person" $ metadata art)
    curry away the 'art' var. ref: Y2017.M09.D26.Exercise 
  • September 19th, 2017:  The #1Liner to follow (next tweet) is a question based off a code snippet from Y2017.M09.D18.Solution. What is a better/more elegant definition?
    fmap (wordStrength . wc) (BL.readFile filename) >>= \dict ->
    return (Map.insert filename dict m)
    Reformulate. Curry the dict-ref.

Saturday, September 30, 2017

September 2017 1HaskellADay problems and solutions

Tuesday, September 19, 2017

August 2017 1HaskellADay 1Liners Problems and Solutions

  • August 1st, 2017:
  • f :: (Maybe a, b) -> Maybe (a, b) Define points-free.
  • August 1st, 2017:
    Given f above and f a and f b are mutually exclusive in Maybe monad, define
    g :: Maybe (a, b) -> Maybe (a, b) -> (Maybe a, b)
    points free
  • August 1st, 2017:
    Now, let's define the dual of f
    f' :: Maybe (a, b) -> (Maybe a, b)
    points free

Friday, September 1, 2017

August 2017 1HaskellADay problems and solutions

Tuesday, August 1, 2017

July 2017 1HaskellADay 1Liner

  • July 7th, 2017:
    In LU-decomposition of matrices you have square P-matrix:
    [[1,0..],
     [0,2,0..],
     [0,0,3,0..],
    ...]
    For matrices of n² size
    Code that
    • ∃! David Turner @DaveCTurner
      • matrix n = let td = take n . drop 1 in td [td $ replicate i 0 ++ [i] ++ repeat 0 | i <- [0..]]

Monday, July 31, 2017

July 2017 1HaskellADay Problems and Solutions

Friday, July 7, 2017

June 2017 1HaskellADay 1Liners

  • June 17th, 2017:
    f :: (a, [a]) -> [a] -> [a]
    f (c, w1) w2 = c:w1 ++ w2

    Define f points-free
    • bazzargh @bazzargh (++).uncurry(:)
      • Felt there must be a nicer way to exploit symmetry of mappend.uncurry(mappend.pure) but can't find it

Monday, July 3, 2017

June 2017 1HaskellADay Problems and Solutions

Friday, June 16, 2017

May 2017 1Liners 1HaskellADay

  • May 10th, 2017:
    Define (^) :: (a -> a) -> Int -> (a -> a)
    The 'power'-function where f ^ 3 = f . f . f
    • Conor McBride @pigworker flip ((ala Endo foldMap .) . replicate)

Wednesday, June 7, 2017

May 2017 1HaskellADay problems and solutions