Skip to content

Instantly share code, notes, and snippets.

@vasalf
Created March 5, 2020 13:51
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save vasalf/17b9316c24b6ebc579f1405ce7f454cd to your computer and use it in GitHub Desktop.
Save vasalf/17b9316c24b6ebc579f1405ce7f454cd to your computer and use it in GitHub Desktop.
module Lib where
import Control.Monad (replicateM)
someFunc :: IO ()
someFunc = undefined
a, b, m :: Int
a = 179
b = 239
m = 1791791791
-- rand :: Int -> (Int, Int)
-- rand n = let t = (a * n + b) `mod` m
-- in (t, t)
f :: String -> Bool
f s = True
f' :: String -> (Int -> (Int, Bool))
f' s = \x -> (x, True)
newtype Rand a = Rand { runRand :: Int -> (Int, a) }
newtype State s a = State { runState :: s -> (s, a) }
f'' :: String -> Rand Bool
f'' s = Rand $ f' s
rand :: Rand Int
rand = Rand $ \x -> let t = (a * x + b) `mod` m in (t, t)
-- fmap' :: (a -> b) -> Rand a -> Rand b
-- fmap' f (Rand g) = Rand $ \x -> let (y, z) = runRand g x in (y, f z)
instance Functor Rand where
fmap f g = Rand $ \x -> let (y, z) = runRand g x in (y, f z)
evenRand :: Rand Int
evenRand = ((*) 2) <$> rand
pure' :: a -> Rand a
pure' x = Rand $ \y -> (y, x)
f''' :: Rand (String -> Bool)
f''' = pure' f
-- Rand (a -> b) === Int -> (Int, a -> b)
ap' :: Rand (a -> b) -> Rand a -> Rand b
ap' (Rand f) (Rand x) =
Rand $ \n -> let (n', f') = f n
(n'', x') = x n'
in (n'', f' x')
instance Applicative Rand where
pure = pure'
(<*>) = ap'
randPair :: Rand (Int, Int)
randPair = ((,) <$> rand) <*> rand
bind :: Rand a -> (a -> Rand b) -> Rand b
bind (Rand x) f = Rand $ \n -> let (n', x') = x n
(n'', f') = runRand (f x') n'
in (n'', f')
instance Monad Rand where
(>>=) = bind
randPair' :: Rand (Int, Int)
randPair' = rand
>>= (\x -> rand
>>= (\y -> pure (x, y)))
randPair'' :: Rand (Int, Int)
randPair'' = do
x <- rand
y <- ((+) x) <$> rand
rand
pure (x, y)
replicateM' :: Applicative m => Int -> m a -> m [a]
replicateM' 0 _ = pure []
replicateM' n x = (:) <$> x <*> replicateM' (n - 1) x
ap'' :: Monad m => m (a -> b) -> m a -> m b
ap'' f x = do
f' <- f
x' <- x
return $ f' x'
val :: Maybe Int
val = do
x <- Just 179
y <- Just 239
return $ x + y
Nothing
data Maybe' a = Nothing' | Just' a
data Either' a b = Left' a | Right' b
x :: Either Int String
x = Left 0
y :: Either Int String
y = Right "abacaba"
ints :: [(Int, Int)]
ints = [(x, y) | x <- [1..10],
y <- [1..10]]
ints' = do
x <- [1..10]
y <- [1..10]
return $ (x, y)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment