Skip to content

Instantly share code, notes, and snippets.

@jsoo1
Last active March 8, 2022 05:34
Show Gist options
  • Save jsoo1/b292ec35691acb37b72b775d2f5f55c1 to your computer and use it in GitHub Desktop.
Save jsoo1/b292ec35691acb37b72b775d2f5f55c1 to your computer and use it in GitHub Desktop.
applying functions to a value
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DerivingStrategies #-}
module ApplyingFunctions where
import System.IO
import Data.Foldable
import Control.Applicative
import Control.Monad
type Apply = forall a b. a -> [a -> b] -> [b]
-- Using direct recursion
applyR :: Apply
applyR x [] = []
applyR x (f:fs) = f x : applyR x fs
-- Using foldr
applyF :: Apply
applyF x fs = foldr (\f ys -> f x : ys) [] fs
-- Using map
applyM :: Apply
applyM x fs = map ($ x) fs
-- Using list comprehensions
applyL :: Apply
applyL x fs = [f x|f <- fs]
example1 :: [String]
example1 = applyL "hello, world"
[ (\s -> s ++ "!!")
, (\s -> s ++ "?")
, (\s -> s ++ ".")
, reverse
-- Won't compile.
-- All functions in this list :: String -> String
-- length :: String -> Int
-- , length
]
example2 :: [Int -> Bool]
example2 = applyM 42
[ (\fortyTwo x -> fortyTwo == x)
, (\fortyTwo x -> fortyTwo < x)
, (\fortyTwo x -> fortyTwo + 10 < x ^ 2)
]
data State = On | Off
deriving stock Show
example3 :: String -> [Maybe State]
example3 x = applyF x
[ (\s -> if s == "on" then Just On else Nothing)
, (\s -> if s == "off" then Just Off else Nothing)
, (\_ -> Nothing)
]
example4 :: [IO ()]
example4 = applyR "hello, world!"
[ (\s -> withBinaryFile "/dev/null" WriteMode
(\devNull -> hPutStrLn devNull s))
, putStrLn
, (\s -> do
resp <- getLine
when (resp == s) (putStrLn "you guessed right!")
)
]
example5 :: IO ()
example5 = sequence_ example4
example6 :: Maybe State
example6 = foldl' (<|>) empty (example3 "off")
example7 :: Maybe State
example7 = foldl' (<|>) empty (example3 "junk")
example8 :: [Bool]
example8 = [x | x <- applyM 50 example2, x]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment