Skip to content

Latest commit

 

History

History
3195 lines (2641 loc) · 66.3 KB

20210907223510-haskell.org

File metadata and controls

3195 lines (2641 loc) · 66.3 KB

Haskell

:header-args+: :results output :wrap

概要

Haskellは純粋関数型Programming Language。

Memo

QuickCheck

QuickCheckというテストライブラリがある。型に基づくプロパティテスト、というもののよう。

【基礎】ランダムテスト (QuickCheck)

stack

stackはHaskellの開発ツール。

REPL

対話実行環境を立ち上げる。

ghci
>> :load -- ファイル読み込み
>> :reload -- 再読込。org-babelがおかしくなったときに使える
>> :quit -- ghci終了

プロンプトをセット。

:set prompt "GHCi> "

前置引数

(+) 2 2

マイナス演算子

2 + (- 1)

:infoコマンド

infixl が演算子の優先順位。

:info (+)
:info (*)

定数

pi

代入

let e = exp 1
(e ** pi) - pi

リスト

["foo", "bar", "baz"]

列挙表記

[1..10]
[1.0,1.25..2.0]

リスト結合

[3,1,3] ++ [3,7]

cons

1 : [2, 3]

型情報

⚠babelで実行すると実行されなくなるので、GHCIだけで試すこと。

Prelude> :set +t
Prelude> 'c'
'c'
it :: Char

Prelude> :unset +t

型エラー

1.2 % 3.4

:type

:type 1
:type "abc"
:type it

いくつかの数値型関数

succ 6
pred 9
sin (pi / 2)
truncate pi
round 3.4

:? コマンド

:?

型推論

式の後ろに書く::と型の組み合わせのことを 型シグネチャ という。

:type 'a'
'a' :: Char
[1, 2, 3] :: Int

関数適用

odd 3
odd 6
compare 3 3
compare 3 2
(compare 2 3) == LT
compare 2 3 == LT
compare (sqrt 3) (sqrt 6)

合成データ型: リスト

合成データ型は他のデータ型から構成する。よく使う合成データ型はリスト(可変長)とタプル(固定長)。

リスト型は 多相的 である。多相型を書く場合には 型変数 を使う。 head :: [a] -> a は「どんな型の値を含むかはわからないが、その型の値のリストは作れる」と言っている。

:type head
head [1,2,3,4]
head ['a','b','c']
tail [1,2,3,4]
tail [True,False]
-- 評価結果のBoolがリンクで解釈されてエクスポート時にエラーになるので再評価しない。
:type [[True],[False,False]]

異なる型ではエラー。

:type [1, 'a']

合成データ型: タプル

リストと違ってタプルは型が異なっていてもOK。

(1964, "Labyrinths")
()
:type (True, "hello")
:type (4, ['a', 'm'], (16, True))

タプルの型は数/位置/その位置に含まれる要素の型、で表す。 含まれている要素の型や数が異なれば別の型。

:type (False, 'a')
:type ('a', False)
:type (False, 'a')

関数

take 2 [1,2,3,4,5]
drop 3 [1,2,3,4,5]

fst(1,'a') と空白なしで書くと、引数2つに見えるが、違うことに注意。 単一のペアへの関数の適用である。

fst (1,'a')
snd (1,'a')

関数の型

:type lines
lines "the quick\nbrown for\njumps"

副作用がある関数で結果の型は IO ではじまる。

:type readFile

関数定義

Haskellのコードの中では、記号 = は「〜を意味する」ということ。左辺の名前は右辺の式であると定義される。 変数は式に名前をつける手段。

命令形言語を使ってきたのなら、変数は、異なる辞典で、異なる値を格納し得るメモリの番地(またはそれに類するもの)を特定する方法と考えるのが自然かもしれません。命令形言語では、いつでも変数の値を変更することが可能です。したがって、その変数のメモリ番地を確認するたびに違う結果になりえます。 変数に対する、この2つの概念には決定的な違いがあります。Haskellでは、式にいったん束縛した変数は、いつでも元の式に置き換えても良いのです。変数の値は変わらないからです。命令形言語はこの置き換え可能性を保持していません。

add a b = a + b
add 1 2
drop 2 "foobar"
drop 4 "foobar"
drop 4 [1, 2]
drop 0 [1, 2]
drop 7 []
drop (-2) "foo"

myDrop関数

インデントによって既存の定義が継続する。 org-babelでは1行ごとで新しいセッションになってしまうよう。 :{}: を使って複数行評価されるようにする。

変数名 xsx の複数形という意味。

式指向のためelseが必須(elseに入ったとき結果や型がないという事態になるため)。

:{
  myDrop n xs = if n <= 0 || null xs
                then xs
                else myDrop (n - 1) (tail xs)
:}

myDrop 2 "foobar"
myDrop 4 "foobar"
myDrop 4 [1, 2]
myDrop 0 [1, 2]
myDrop 7 []
myDrop(-2) "foo"

論理演算子。

:type null
:type (||)

遅延評価

正格評価: 関数を適用する前に関数への引数を評価する。 非正格評価(遅延評価): 評価せず、値が必要になったとき計算する「プロミス」を作る。未評価の式を追跡するのに使うレコードを サンク という。式の結果が使われないなら、値は計算されない。

isOdd n = mod n 2 == 1
isOdd 3
print (myDrop 2 "abcd")

:type 2 <= 0 || null "abcd"
null "abcd"

型変数

last [1,2,3]
last "baz"
:type last

この a が型変数。 型シグネチャに型変数を持つときには引数のいくつかはどのような型にでもなれることを示している。→ 多相的である。

多相関数

:type fst
:type take

これは実際にはこういうこと↓。

take :: Int -> ([a] -> [a])

純粋性

:type not

型定義

↓ BookInfoを 型構成子 という。 続く Bookは 値構成子 という。 Int, String, [String]は 構成要素 という。

:{
data BookInfo = Book Int String [String]
                deriving (Show)
:}

同じ構造を持っていても、2つの型を区別する。型構成子と値構成子の名前が違うから。

:{
data MagazineInfo = Magazine Int String [String]
                    deriving (Show)
:}
:info BookInfo

myInfo = Book 9780135072455 "Algebra of Programming" ["Richard Bird", "Oege de Moor"]
myInfo
:type myInfo
:type Book

型シノニム

型シノニムはコードを読みやすくするだけのもの。

type CustomerID = Int
type ReviewBody = String
data BetterReview = BetterReview BookInfo CustomerID ReviewBody
data Bool = False | True
type CardHolder = String
type CardNumber = String
type Address = [String]

:{
data BillingInfo = CreditCard CardNumber CardHolder Address
                   | CashOnDelivery
                   | Invoice CustomerID
                     deriving (Show)
:}
:info BillingInfo
:type CreditCard
CreditCard "2901650221064486" "Thomas Gradgrind"  ["Dickens", "England"]
:type it
:type Invoice
Invoice 2222

タプルと代数データ型

Book 2 "The Wealth of Networks" ["Yochai Benkler"]
(2, "The Wealth of Networks", ["Yochai Benkler"])

↓構造的に同一なので同じ型。

a = ("Porpoise", "Gray")
b = ("Table", "Oak")

↓別の名前なので別の型。

data Cetacean = Cetacean String String
data Furniture = Furniture String String

c = Cetacean "Porpoise" "Gray"
d = Furniture "Table" "Oak"

座標。

:{
-- x, yの座標
data Cartesian2D = Cartesian2D Double Double
                   deriving (Eq, Show)

-- 偏角と長さ
data Polar2D = Polar2D Double Double
               deriving (Eq, Show)
:}

== 演算子は引数が同じ型でないといけないのでエラー。

Cartesian2D (sqrt 2) (sqrt 2) == Polar2D (pi / 4) 2

タプルの場合判断しようがないのでチェックが効かない。

(1, 2) == (1, 2)
  • 複合型をコードの中で広く使う場合には data 宣言を使う
  • 規模が小さく、局所的にしか使わない場合はタプルでいい

他の言語との類似

struct book_info {
  int id;
  char *name;
  char **authors;
};
:{
data BookInfo = Book Int String [String]
                  deriving (Show)
:}

列挙型

C言語ではこう書く。

enum roygbiv {
  red,
  orange,
  yellow,
  green,
  blue,
  indigo,
  violet,
};
:{
data Roygbiv = Red
             | Orange
             | Yellow
             | Green
             | Blue
             | Indigo
             | Violet
               deriving (Eq, Show)
:}
:type Yellow
:type Red
Red == Yellow
Green == Green

haskellのenumは型が厳密。

take 3 "foobar"
take Red "foobar"

union

代数データ型が複数の選択肢を持つ場合はC言語の union と同じ。

type Vector = (Double, Double)
:{
data Shape = Circle Vector Double
           | Poly [Vector]
:}
:info Shape

パターンマッチ

↓2つの関数というわけではない。 同一関数の異なる入力パターンに対する振る舞いを定義している。

myNot True = False
myNot False = True
sumList (x:xs) = x + sumList xs
sumList [] = 0

sum [1,2]

タプルのパターンマッチ。

complicated (True, a, x:xs, 5) = (a, xs)
complicated (True, 1, [1,2,3], 5)

ぴったり一致しないと成功しない。 すべてのパターンマッチが失敗すると実行時エラー。

complicated (False, 1, [1,2,3], 5)

Exception: <interactive>:6422:1-40: Non-exhaustive patterns in function complicated

BookInfo型の場合。 パターンマッチをセット。

bookID (Book id title authors) = id
bookTitle (Book id title authors) = title
bookAuthors (Book id title authors) = authors

アクセスできる。

bookID (Book 3 "Probability Theory" ["E.T.H. Jaynes"])
bookTitle (Book 3 "Probability Theory" ["E.T.H. Jaynes"])
bookAuthors (Book 3 "Probability Theory" ["E.T.H. Jaynes"])

構成子に基づいて、アクセサ関数の型を推論できる。

:type bookID
:type bookTitle
:type bookAuthors

ワイルドカード

この類のコードをボイラープレートという。

nicerID (Book id _ _ ) = id
nicerTitle (Book _ title _) = title
nicerAuthors (Book _ _ authors) = authors
goodExample (x:xs) = x + goodExample xs
goodExample _ = 0
goodExample []
goodExample [1, 2]

レコード構文

:{
  data Customer = Customer {
     customerID :: CustomerID
   , customerName :: String
   , customerAddress :: Address
     } deriving (Show)
:}
:type customerID
:{
customer2 = Customer {
    customerID = 271828
  , customerAddress = ["1048576 Disk Drive",
                      "Milpitas, CA 95134",
                      "USA"]
  , customerName = "Jane Q. Citizen"
  }
:}
customer2
cities

レコード構文によって使えるアクセサ関数は、通常のHaskellの関数。

:type customerName
customerName customer2

パラメータ化された型

独自に定義する型も多相型にできる。型宣言に型変数を導入する。

↓この変数は型変数。

:{
data Maybe a = Just a
             | Nothing
:}
:info Maybe

これによって任意の型上の Maybe 型を使える。

someBool = Just True
:type someBool
someString = Just "something"
:type someString
:type Just "Invisible bike"
wrapped = Just (Just "wrapped")
:type wrapped

再帰型

リスト型は再帰型。定義に自身が含まれる。

:{
data List a = Cons a (List a)
            | Nil
              deriving (Show)
:}

確かめる。

Nil
Cons 0 Nil
Cons 1 it
Cons 2 it
Cons 3 it

二分木。

:{
data Tree a = Node a (Tree a) (Tree a)
            | Empty
              deriving (Show)
:}

本と違ってなぜかエラーになる。

fromList (x:xs) = Cons x (fromList xs)
fromList [] = Nil
fromList "durian"
fromList [Just True, Nothing, Just False]

Javaの例(クラス定義)。

class Tree<A>
{
    A value;
    Tree<A> left;
    Tree<B> right;

    public Tree(A v, Tree<A> l, Tree<A> r)
    {
        value = v;
        left = l;
        right = r;
    }
}

葉を構成する関数。

class Example
{
    static Tree<String> simpleTree()
    {
        return new Tree<String>(
                                "parent",
                                new Tree<String>("left leaf", null, null),
                                new Tree<String>("right leaf", null, null));
    }
}
:{
simpleTree = Node "parent" (Node "left child" Empty Empty)
                           (Node "right child" Empty Empty)
:}
:type simpleTree

エラー報告表示

listの要素が1つのときはエラー表示を出す。

:{
mySecond :: [a] -> a
mySecond xs = if null (tail xs)
              then error ("list too short")
              else head (tail xs)
:}
mySecond "xi"
mySecond [2, 3]
mySecond [2]

ちゃんとエラーメッセージが出ている。

エラーの可能性, Maybe

:{
safeSecond :: [a] -> Maybe a
safeSecond [] = Nothing
safeSecond xs = if null (tail xs)
                then Nothing
                else Just (head (tail xs))
:}
safeSecond [1,2] -- なぜかできない。

パターンマッチを使って改善。

tidySecond :: [a] -> Maybe a

tidySecond (_:x:_) = Just x
tidySecond _       = Nothing

シャドウ

内側の x が外側の x を隠す。

:{
bar = let x = 1
      in ((let x = "foo" in x), x)
:}
bar

where節

:{
lend2 amount balance = if amount < reserve * 0.5
                       then Just newBalance
                       else Nothing
      where reserve  = 100
            newBalance = balance - amount
:}
:{
pluralise :: String -> [Int] -> [String]
pluralise word counts = map plural counts
    where plural 0 = "no " ++ word ++ "s"
          plural 1 = "one " ++ word
          plural n = show n ++ " " ++ word ++ "s"
:}
pluralise "car" [0]
pluralise "car" [1]
pluralise "car" [2]

case式

:{
fromMaybe defval wrapped =
  case wrapped of
    Nothing -> defval
    Just value -> value
:}
:{
  data Fruit = Apple | Orange
  betterFruit f = case f of
                  "apple" -> Apple
                  "orange" -> Orange
:}

lend関数を書き直す。

:{
lend3 amount balance
     | amount <= 0            = Nothing
     | amount > reserve * 0.5 = Nothing
     | otherwise              = Just newBalance
    where reserve    = 100
          newBalance = balance - amount
:}

myDrop関数を書き直す。 元コード。

:{
myDrop n xs = if n <= 0 || null xs
              then xs
              else myDrop (n - 1) (tail xs)
 :}
myDrop 2 "abcd"
:{
niceDrop n xs | n <= 0 = xs
niceDrop _ []          = []
niceDrop n (_:xs)      = niceDrop (n - 1) xs
:}
niceDrop 2 "abcd"

テキスト行分割

:type lines
lines "line 1\nline 2"
lines "foo\n\nbar\n"
break odd [2,4,5,6,8]
:module +Data.Char
break isUpper "isUpper"
:{
  a `plus` b = a + b
  data a `Pair` b = a `Pair` b
             deriving (Show)
  foo = Pair 1 2
  bar = True `Pair` "quux"
:}
1 `plus` 2
plus 1 2
Pair "a" "a"
"a" `Pair` "a"

リストの処理

:type length
length []
length [1,2,3]
null []
head [1,2]
tail "foo"
last "bar"

連結関数。

:type (++)
"foo" ++ "bar"
[] ++ [1,2,3]
[1] ++ []

concat 連結して1つのリストにする。

:type concat
concat [[1,2,3], [4,5,6]]
concat [[[1,2],[3]], [[4],[5],[6]]]
concat (concat [[1,2],[3]], [[4],[5],[6]])

reverse 逆順にする。

:type reverse
reverse "foo"

便利な条件判定、 allany

:type all
all odd [1,3,5]
all odd [3,1,4]
all odd []
:type any
any even [3,1,4]
any even []

部分リスト。

:type take
take 3 "foobar"
take 2 [1]
:type drop
drop 3 "xyzzy"
drop 1 []

splitAt インデックスで分割したリストのペアを返す。

:type splitAt
splitAt 3 "foobar"

span 条件に合うもの、以外でリストを返す。

:type span
span even [2,4,6,7,9,10,11]
:type break
break even [1,3,5,6,8,9,10]

elem 値がリスト中に存在するか示す。

:type elem
2 `elem` [5,3,2,1,1]
2 `notElem` [5,3,2,1,1]

filter 条件に合うリストを返す。

:type filter
 filter odd [2,4,1,3,6,8,5,7]

isPrefixOf 部分リストがより大きなリストの中にあるか調べる。

:module +Data.List
:type isPrefixOf
"foo" `isPrefixOf` "foobar"
[1,2] `isPrefixOf` []

zip 2つのリストをペアのリストにする。

:type zip
zip [12,72,93] "zippity"

zipWith 2つのリストのペアごとに関数を適用する。

:type zipWith
zipWith (+) [1,2,3] [4,5,6]

可変長引数はHaskellの型システムのうえでは難しい。 複数のリストを閉じ合わせるには zip3zip7` を使う。

リストのいけてる扱い方

haskellにおいてはほかの言語と同じように、扱えない部分がある。 length はリスト全体を辿らないといけないが、無限リストである可能性がある。

:{
  mySmartExample xs = if not (null xs)
                      then head xs
                      else 'Z'
  myOtherExample (x:_) = x
  myOtherExample [] = 'Z'
:}
mySmartExample "head"
mySmartExample []

部分関数

正当な入力の部分集合の値に対してのみ値を返す関数のことを部分関数という。 入力の全定義域に対して正しい結果を返す関数のことを全関数という。

文字列専用の関数

lines "foo\nbar"
unlines ["foo", "bar"]

words は入力文字を任意の空白で区切る。

words "the \r quick \t brown\n\n\nfox"
unwords ["jumps", "over", "the", "lazy", "dog"]

ループ

Haskellには、 for ループ、 while ループはない。

C言語の例。 こんなふうにはできないので末尾再帰を使う。

int as_int(char *str)
{
  int acc;
  for (acc = 0; isdigit(*str); str++) {
    acc = acc * 10 + (*str - '0');
  }

  return acc;
}

配列の中のすべての要素を2乗する。

void square(double *out, const double *in, size_t length)
{
  for (size_t i = 0; i < length; i++) {
    out[i] = in[i] * in[i];
  }
}
:{
 square :: [Double] -> [Double]
 square (x:xs) = x*x : square xs
 square []     = []
:}
square [1,2]
square []

大文字化。

:{
upperCase :: String -> String

upperCase (x:xs) = toUpper x : upperCase xs
upperCase []     = []
:}
upperCase "hello"

map は関数を引数としてとり、リストのすべての要素に適用する。

upperCase2 xs = map toUpper xs
upperCase2 "hello"

map を書き直してみる。

:{
  myMap :: (a -> b) -> [a] -> [b]
  myMap f (x:xs) = f x : myMap f xs
  myMap _ _      = []
:}
  upperCase3 xs = myMap toUpper xs
  upperCase3 "hello"

フィルター

:{
oddList :: [Int] -> [Int]

oddList (x:xs) | odd x = x : oddList xs
               | otherwise = oddList xs
oddList _                  = []
:}
oddList [1,2,3,4,5,6,7,8,9,10]

helper は末尾再帰の関数で、蓄積変数 acc を使ってリストのその時点での部分和を保持する。

:{
mySum xs = helper 0 xs
  where helper acc (x:xs) = helper (acc + x) xs
        helper acc _      = acc
:}
mySum [1,2,3,4]

畳み込み

畳み込み: リストのすべての要素に何かを行い、蓄積変数を更新していって、終わったところで蓄積変数を返す。

:{
foldl :: (a -> b -> a) -> a -> [b] -> a

foldl step zero (x:xs) = foldl step (step zero x) xs
foldl _    zero []     = zero
:}
:{
niceSum :: [Integer] -> Integer
niceSum xs = foldl (+) 0 xs
:}
niceSum [1,2,3,4,5]

問題を2つに単純化することで、すっきり書けるようになった。 蓄積値の初期値をどうするかと、蓄積変数の更新。

明示的再帰は綿密に読む必要があり、わかりづらい。 畳み込みを使えば再帰を理解しやすい。

右側からの畳み込み。

foldr :: (a -> b -> b) -> b -> [a] -> b
foldr step zero (x:xs) = step x (foldr step zero xs)
foldr _    zero []     = 0

:{
myFilter p xs = foldr step [] xs
  where step x ys | p x = x : ys
                  | otherwise = ys
:}
myFilter (+) [1,2]

無名関数

普通に書く例。

:{
isInAny needle haystack = any inSequence haystack
    where inSequence s = needle `isInfixOf` s
:}

無名関数を使う例。

isInAny2 needle haystack = any (\s -> needle `isInfixOf` s) haystack

->の意味…左側の型を引数に取り、右側の型の値を返す関数。

Haskellにおいては、 すべての関数は1つしか引数を取らない 。 1つ渡すと型シグネチャから1つ削られたことがわかる。

:type dropWhile
:type dropWhile isSpace
map (dropWhile isSpace) [" a", "f", "    e"]
:type zip3
zip3 "foo" "bar" "quux"
:type zip3 "foo"
let zip3foo = zip3 "foo"
:type zip3foo
zip3foo "aaa" "bbb"

関数が受け入れ可能な数よりも少ない数の引数を渡すことを関数の部分適用という(カリー化)。

isInAny3 needle haystack = any (isInfixOf needle) haystack

カリー化の例。 使う前。

niceSum :: [Integer] -> Integer
niceSum xs = foldl (+) 0 xs

完全に適用せずに、省略できる。

niceSum :: [Integer] -> Integer
niceSum = foldl (+) 0

:type (`elem` ['a'..'z'])

引数が小文字アルファベットか調べる関数になる。

(`elem` ['a'..'z']) 'a'
(`elem` [1..9]) 1
(`elem` [1..9]) 10

all と組み合わせる。簡潔にリスト全体か判定する関数になった。

all (`elem` ['a'..'z']) "Frobozz"

inInAny3 の改良版。

isInAny4 needle haystack = any (needle `isInfixOf`) haystack
:type isInAny4

アズパターン

:m +Data.List
tail "foobar"
tail (tail "foobar")
tails "foobar"
tails []

空でない接尾辞が欲しくなったとする。

xs@(_:xs') はアズパターンという。 変数 xs を、 @ 記号の右辺とマッチした値に束縛する、という意味。

:{
sufixes :: [a] -> [[a]]
sufixes xs@(_:xs') = xs : sufixes xs'
sufixes _          = []
:}
sufixes "foo"

アズパターンはデータをコピーする代わりに共有する(xs を再利用している)。 メモリの割り当てを回避するのでパフォーマンスが良い。

合成

init 関数はリストの最期の要素を除いた残りを返す。

init [1,2,3]

init tails を合成する。

suffix2 xs = init (tails xs)
suffix2 [1,2,3]

ある関数を適用してから、その結果に別の関数をしている。このパターンを関数にできる。

:{
compose :: (b -> c) -> (a -> b) -> a -> c
compose f g x = f (g x)
suffixes3 xs = compose init tails xs
:}
suffixes3 [1,2,3]

勝手にカリー化するので変数は外せる。

suffixes4 = compose init tails
suffixes4 [1,2,3]

連結はよくあることなので、 . 演算子として使える。

suffixes5 = init . tails
suffixes5 [1,2,3]

通常の演算子のひとつ。

:type (.)

単語の先頭が大文字か。

:type isUpper . head
isUpper 'W'
:type filter (isUpper . head)

関数合成の例。

words を使う。

:type words
words "#define DLT_CHAOS     5"

tail を使う。

:type tail
tail ["#define","DLT_CHAOS","5"]

合成する。

:type tail . words
(tail . words) "#define DLT_CHAOS           5"

head を使う。

:type head . tail . words
(head . tail . words) "#define DLT_CHAOS     5"

優先順位…ライブラリ関数の合成 > 畳み込み > 末尾再帰。

スペースリーク

遅延評価しない式のことを 正格な式 という。 seq は正格化する。

:{
foldl' _ zero []    = zero
foldl' step zero (x:xs) =
    let new = step zero x
    in new `seq` foldl' step new xs
:}

seq は値を評価する方法としての存在価値しかない。

:type seq
foldl' (+) 1 (2:[])

これは↓のように展開される。

:{
let new = 1 + 2
in new `seq` foldl' (+) new []
:}

一度↓のように展開する。

fold' (+) 3 []

seq によってサンクがない。

型クラス

同値性検査をしたい。

色の場合。

:{
data Color = Red | Green | Blue
colorEq :: Color -> Color -> Bool
colorEq Red Red = True
colorEq Green Green = True
colorEq Blue Blue = True
colorEq _ _ = False
:}

stringの場合。

stringEq :: [Char] -> [Char] -> Bool
stringEq [] [] = True
stringEq (x:xs) (y:ys) = x == y && stringEq xs ys
stringEq _ _ = False

つまり…型ごとに別の名前の関数を使って比較しなければならない。 すべて == で比較できると便利(ジェネリック関数)。 型クラスは実際に与えられたデータの型ごとに実装を持ち得る関数の集合によって定義するもの。

型クラスを定義する。 BasicEq という型クラスを定義する。 インスタンスの型は a

:{
class BasicEq a where
    isEqual :: a -> a -> Bool
:}
:type isEqual

→ あらゆる型 a に対して、 aBasicEq のインスタンスである限り、 isEqual は型 a のパラメータを2つ取り、 Bool を返す。

:{
instance BasicEq Bool where
    isEqual True  True  = True
    isEqual False False = True
    isEqual _     _     = False
:}
:{
class BasicEq2 a where
    isEqual2    :: a -> a -> Bool
    isNotEqual2 :: a -> a -> Bool
:}

notを追加する。

:{
class BasicEq3 a where
      isEqual3 :: a -> a -> Bool
      -- isEqual3 x y = not (isNotEqual3 x y)

      isNotEqual3 :: a -> a -> Bool
      -- isNotEqual3 x y = not (isEqual3 x y)
:}

組み込みの Eq 型を見る。

class Eq a where
    (==), (/=) :: a -> a -> Bool

    -- 最低限の完全な定義は(==) か (/=) のどちらか
    x /= y     = not (x == y)
    x == y     = not (x /= y)

型クラスのインスタンス宣言

Color型だけでなく、BasicEq3のインスタンスとして宣言したあらゆる型に対して isEqual3 が使える。

instance BasicEq3 Color where
    isEqual3 Red   Red   = True
    isEqual3 Green Green = True
    isEqual3 Blue  Blue  = True
    isEqual3 _     _     = False

show 1
show [1,2,3]
show (1,2)
putStrLn (show 1)
putStrLn (show [1,2,3])
show "Hello!"
putStrLn (show "Hello!")
show ['H', 'i']
show "Hi, \"Jane\""
putStrLn (show "Hi, \"Jane\"")

自分で定義した型に対して Show インスタンスを定義する。

instance Show Color where
    show Red   = "Red"
    show Green = "Green"
    show Blue  = "Blue"

エラーが出てうまくいかない…。

:{
main = do
    putStrLn "Please enter a Double:"
    inpStr <- getLine
    let inpDouble = (read inpStr)::Double
    putStrLn ("Twice " ++ show inpDouble ++ " is " ++ show (inpDouble * 2))
:}
read "5"

型の a は、それぞれのReadのインスタンスのこと。

:type (read "5")

実際に呼ばれる特定の関数はreadの返り値から期待される型で決まる。

(read "5")::Integer
(read "5")::Double
:{
instance Read Color where
   readsPrec _ value =
       -- ペアは文字列と欲しい返り値
       tryParse [("Red", Red), ("Green", Green), ("Blue", Blue)]
       where tryParse [] = []
             tryParse ((attempt, result):xs) =
                 if (take (length attempt) value) == attempt
                    then [(result, drop (length attempt) value)]
                    else tryParse xs
:}

なぜかstack overflowでできない。

(read "Red")::Color
(read "Green")::Color
(read "Blue")::Color
(read "[Red]")::Color
(read "[Red,Red,Blue]")::Color

シリアライズ

let d1 = [Just 5, Nothing, Nothing, Just 8, Just 9]::[Maybe Int]
:type show
:type show d1
putStrLn (show d1)

ファイルに書き込み。

writeFile "test" (show d1)

再度読み込み。 d2 に明示的に型を与えるのがポイント。

input <- readFile "test"
let d2 = (read input) ::[Maybe Int]
print d1
print d2
d1 == d2

showにほかの引数を与えてみる。

putStrLn $ show [("hi", 1), ("there", 3)]
putStrLn $ show [[1, 2, 3], [4, 0, 1], [], [503]]
putStrLn $ show [Left 5, Right "there", Left 0, Right "nine"]
putStrLn $ show [Left 0, Right [1, 2, 3], Left 5, Right []]

数値型

強力な数値型がある。 Haskellの演算子は関数にすぎない。 演算子を関数とみなす場合には括弧で囲む。

:{
data Color = Red | Green | Blue
       deriving (Read, Show, Eq, Ord)
:}
show Red
(read "Red")::Color
(read "[Red,Red,Blue]")::[Color]
(read "[Red, Red, Blue]")::[Color]
Red == Red
Red == Blue
Data.List.sort [Blue,Green,Blue,Red]
Red < Blue

型が参照している型が、やはりその型クラスのインスタンスであると宣言しないといけない。

CannotShow が Show のインスタンスではないので、エラー。

:{
data CannotShow = CannotShow
data CannotDeriveShow = CannotDeriveShow CannotShow
                        deriving (Show)
:}
:{
data OK = OK
instance Show OK where
    show _ = "OK"
data ThisWorks = ThisWorks OK
                 deriving (Show)
:}

Haskell では異なる型の値を含むリストはサポートされてないので、JSONオブジェクトを直接表現できない。 代わりにデータ構成子でそれぞれの値を含む必要がある。

type JSONError = String

class JSON a where
    toJValue :: a -> JValue
    fromJValue :: JValue -> Either JSONError a

instance JSON JValue where
    toJValue = id
    fromJValue = Right

よりよいエラー文。

data Maybe a = Nothing
             | Just a
               deriving (Eq, Ord, Read, Show)

data Either a b = Left a
                | Right b
                  deriving (Eq, Ord, Read, Show)
instance JSON Bool where
    toJValue = JBool
    fromJValue (JBool b) = Right b
    fromJValue _ = Left "not a JSON boolean"

特殊なコメントで制限回避。プラグマというコンパイラ指令。

{-# LANGUAGE TypeSynonymInstances #-}

型クラスとインスタンス

新しいインスタンスはどこででも追加できる。型クラスを定義したモジュール内のみに限定されてない。 型クラスは開世界仮説に基づいている。

doubleToJValue :: (Double -> a) -> JValue -> Either JSONError a
doubleToJValue f (JNumber v) = Right (f v)
doubleToJValue _ _ = Left "not a JSON number"

instance JSON Int where
    toJValue = JNumber . realToFrac
    fromJValue = doubleToJValue round

instance JSON Integer where
    toJValue = JNumber . realToFrac
    fromJValue = doubleToJValue round

instance JSON Double where
    toJValue = JNumber
    fromJValue = doubleToJValue id

インスタンスの重複。 リストをJSONの配列に変換する例。

instance (JSON a) => JSON [a] where
    toJValue = undefined
    fromJValue = undefined
instance (JSON a) => JSON [(String, a)] where
    toJValue = undefined
    fromJValue = undefined
{-# LANGUAGE FlexibleInstances #-}
class Borked a where
    bork :: a -> String

instance Borked Int where
    bork = show

instance Borked (Int, Int) where
    bork (a, b) = bork a ++ ", " ++ bork b

instance (Borked a, Borked b) => Borked (a, b) where
    bork (a, b) = ">>" ++ bork a ++ " " ++ bork b ++ "<<"

GHC は保守的で、使える可能性のあるインスタンスは1つだけであるべきとする。 なのでbork を使おうとするとエラーになる。

型クラスに関する制約の緩和

Tasks

org-babelでhaskellを実行できなくなる

:set +t を評価すると使えなくなる。

xmpfilterのHaskell版を探す or 作る

なければ簡易版で作る。 いちいちロード、コンパイルは学習に不便。既存のがあるはずだが、調べ方がわからない。

org-babel でよさそう。

<2021-10-20 Wed>

100

200

<2021-10-13 Wed> 160pまで到達。

300

400

500

600

700

Reference

わかりやすそうな入門。

haskellの畳み込みのすぐれたチュートリアル。

Haskellの仕様書。

haskellのjsonプリティプリンタライブラリの設計。

IOの説明。

Haskellのブラウザローグライクゲーム。

Haskellのモナドの解説。

Archives

すごいHaskellたのしく学ぼう [100%]

何か作る的なテーマがないので読むのがつらい。 参考になりそうなパッケージを探したけど、ピンとくるものがない。 いくつかパッケージをbuildしてみたが、依存パッケージで動かない。どうするかな。

よくわからん。

30%

40%

50%

<2021-09-25 Sat>

60%

<2021-09-25 Sat>

70%

<2021-09-26 Sun>

80%

<2021-09-26 Sun>

90%

<2021-09-28 Tue>

100%

<2021-09-28 Tue>