Last active
December 14, 2015 16:38
-
-
Save kakkun61/5116110 to your computer and use it in GitHub Desktop.
すごい Haskell 読書会 in 大阪 #6
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE TypeOperators #-} | |
{-# LANGUAGE MultiParamTypeClasses #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{- | |
問題:コロンをつかってみよう | |
data k :> v = k :> v deriving (Eq, Show) | |
data k :=> v = Nil | |
| (k :> v) :+ (k :=> v) | |
deriving (Eq, Show) | |
class a :->! b where | |
(->!) :: a -> b -> b | |
k:>v はペア、 k:=> v は簡単なkey-value store(Map)です | |
a:->!b は、b型の値の中から、a型の値でラベルされたような何かを取り除ける型クラスとしましょう | |
ようはdeleteです | |
Mapとしての空判定、空集合値、挿入、検索、削除などを実装して | |
instance (Eq k) => k :->! (k :=> v) where | |
にしてみてください | |
http://lingr.com/room/sugoih/archives/2013/03/08#message-14231968 | |
-} | |
data k :> v = k :> v deriving (Eq, Show) | |
data k :=> v = Nil | |
| (k :> v) :+ (k :=> v) | |
deriving (Eq, Show) | |
class a :->! b where | |
(->!) :: a -> b -> b | |
instance (Eq k) => k :->! (k :=> v) where | |
a ->! Nil = Nil | |
a ->! (s@(k :> v) :+ m) | |
| a == k = m | |
| otherwise = s :+ (a ->! m) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
data Akari a = Waai a (Akari a) | Daisuki | |
data H oo gle = H oo oo oo oo oo gle | |
data Ha y oo = Ha y oo oo oo oo oo | |
data O b = OOOO|OOOOOO|O|OO | |
data Hom r a = Hom (r -> a) | |
data State s a = State (s -> (a, s)) | |
data Just a = Nothing | Maybe (Maybe a) | |
-- 以上の型を Functor 型クラスのインスタンスにせよ by cojna | |
-- http://lingr.com/room/sugoih/archives/2013/03/08#message-14231876 | |
instance Functor Akari where | |
fmap f (Waai a b) = Waai (f a) (fmap f b) | |
fmap _ Daisuki = Daisuki | |
instance Functor (H oo) where | |
fmap f (H o1 o2 o3 o4 o5 o6) = H o1 o2 o3 o4 o5 (f o6) | |
instance Functor (Ha y) where | |
fmap f (Ha y o1 o2 o3 o4 o5) = Ha y (f o1) (f o2) (f o3) (f o4) (f o5) | |
instance Functor O where | |
fmap _ OOOO = OOOO | |
fmap _ OOOOOO = OOOOOO | |
fmap _ O = O | |
fmap _ OO = OO | |
instance Functor (Hom r) where | |
fmap f (Hom g) = Hom (f . g) | |
instance Functor (State s) where | |
fmap f (State g) = | |
State (\s -> case g s of (a, s') -> (f a, s')) | |
instance Functor Just where | |
fmap _ Nothing = Nothing | |
fmap f (Maybe a) = Maybe (fmap a) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment