前回 に続いてのパート2 です。
前回作成したエクセルデータを読み込むコードをモジュールにした上で、ボディ行を Computer 型に変換するところまで実装します。
Computer 型の実装をはじめるまえに、既存のコードをモジュールにします。
最初に stack new rw-xlsx でプロジェクトを作成した段階でモジュール用のファイル src/Lib.hs が既に用意されています。 ここに 現在の app/Main.hs の内容を移します。
src/Lib.hs:
{-# LANGUAGE OverloadedStrings #-}
module Lib (toRows, toRowCount, Row) where
import Codec.Xlsx (toXlsx, Xlsx, CellValue, ixSheet, ixCell, cellValue)
import Control.Lens
import qualified Data.Text as T
type SheetName = T.Text
type RowAndCol = (Int,Int)
toMaybeCellValue :: Xlsx -> SheetName -> RowAndCol -> Maybe CellValue
toMaybeCellValue xlsx sheetName rowAndCol = xlsx ^? ixSheet sheetName . ixCell rowAndCol . cellValue . _Just
type Row = [Maybe CellValue]
type RowIndex = Int
type ColCount = Int
toRow :: Xlsx -> SheetName -> RowIndex -> ColCount -> Row
toRow xlsx sheetName rowIndex colCount = map (\rowAndCol -> toMaybeCellValue xlsx sheetName rowAndCol) rowAndCols
where rowAndCols = map (\colIndex -> (rowIndex,colIndex)) $ take colCount [1..]
toRows :: Xlsx -> SheetName -> [RowIndex] -> [Row]
toRows xlsx sheetName rowIndexs = map (\rowIndex -> toRowXlsxSheetName rowIndex (toColCount xlsx sheetName)) rowIndexs
where toRowXlsxSheetName = toRow xlsx sheetName
toRowCount' :: Xlsx -> SheetName -> Int -> Int
toRowCount' xlsx sheetName rowIndex
| isNothing = rowIndex-1
| otherwise = toRowCount' xlsx sheetName (rowIndex+1)
where isNothing = (toMaybeCellValue xlsx sheetName (rowIndex, 1)) == Nothing
toRowCount :: Xlsx -> SheetName -> Int
toRowCount xlsx sheetName = toRowCount' xlsx sheetName 1
toColCount' :: Xlsx -> SheetName -> Int -> Int
toColCount' xlsx sheetName colIndex
| isNothing = colIndex-1
| otherwise = toColCount' xlsx sheetName (colIndex+1)
where isNothing = (toMaybeCellValue xlsx sheetName (1, colIndex)) == Nothing
toColCount :: Xlsx -> SheetName -> Int
toColCount xlsx sheetName = toColCount' xlsx sheetName 1
前回 完成させた app/Main.hs のコードをほぼそのまま src/Lib.hs にコピーしただけです。 ただし、いくつか修正しました。
まず Code.Xlsx のインポート宣言:
元のコード:
import Codec.Xlsx hiding (toRows)
変更後:
import Codec.Xlsx (toXlsx, Xlsx, CellValue, ixSheet, ixCell, cellValue)
もともとは、Codec.Xlsx で用意されているものを全部インポート (toRows を除いて) していましたが、使用しているものだけに制限しました。
あとはモジュールの宣言と公開する関数の指定です。
module Lib (toRows, toRowCount, Row) where
モジュールはこれで完成です。
次に app/Main.hs を修正します:
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Lib
import Codec.Xlsx (toXlsx, CellValue, CellValue(CellText,CellDouble))
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
main :: IO ()
main = do
bs <- L.readFile "computers.xlsx"
let
xlsx = toXlsx bs
sheetName = "Sheet1"
rowCount = toRowCount xlsx sheetName
rowIndexes = take rowCount [1..]
rows = toRows xlsx sheetName rowIndexes
putStrLn $ show rows
モジュールにした部分を削除し main 関数のみを残しました。
import 部分は今後必要になるものを含めて記述しています。
エクセルデータから読み込んだ行を Computer 型に変換して処理したい。 まず Computer 型を作成。
type Name = Maybe CellValue
type OS = Maybe CellValue
type Price = Maybe CellValue
data Computer = Computer Name OS Price deriving Show
次に Row から Computer を生成する関数を作成:
toComputer :: Row -> Computer
toComputer row = Computer (row !! 0) (row !! 1) (row !! 2)
本来は 1行目の列見出しを見て Name, OS, Price, を決めたいのですが、 ここでは row の一番目が Name、 二番目が OS、三番目が Price と決め打ちしています。
それでは ボディ行(見出し行以外の行) を Computer リストに変換します。
この部分を:
rowIndexes = take rowCount [1..]
rows = toRows xlsx sheetName rowIndexes
これに変更:
bodyRowIndexes = take (rowCount-1) [2..]
bodyRows = toRows xlsx sheetName bodyRowIndexes
computers = map (\row -> toComputer row) $ toRows xlsx sheetName bodyRowIndexes
つまり、ボディ行部分の行番号のリストを作成して、それを toRows で bodyRows :: [Row] に変換、 最後に toComputer を使って row を computer に変換です。
main 関数全体では次のようになります。
main :: IO ()
main = do
bs <- L.readFile "computers.xlsx"
let
xlsx = toXlsx bs
sheetName = "Sheet1"
rowCount = toRowCount xlsx sheetName
bodyRowIndexes = take (rowCount-1) [2..]
bodyRows = toRows xlsx sheetName bodyRowIndexes
computers = map (\row -> toComputer row) $ toRows xlsx sheetName bodyRowIndexes
putStrLn $ show computers
実行してみます。
$ stack run
[Computer (Just (CellText "macbook air")) (Just (CellText "macOS")) (Just (CellDouble 98000.0)),Computer (Just (CellText "macbook pro")) (Just (CellText "macOS")) (Just (CellDouble 128000.0)),Computer (Just (CellText "surface")) (Just (CellText "windows")) (Just (CellDouble 148000.0))]
意図通り作動しましたが、Computerの出力が読み辛いですね。 ここを調整します。 つまり、Computer を Show 型クラスのインスタンスにして show したときの出力を変更します。
instance Show Computer where
show c = foldl1 (\a b -> a ++ "/" ++ b) [(toName c), (toOS c), (toPrice c)]
where
toValue :: CellValue -> String
toValue (CellText v) = T.unpack v
toValue (CellDouble v) = show v
toName (Computer v _ _) = toValue $ maybe (CellText "") id v
toOS (Computer _ v _) = toValue $ maybe (CellText "") id v
toPrice (Computer _ _ v) = toValue $ maybe (CellDouble 0) id v
Computer 型の deriving Show は削除しておく.
再度実行:
$ stack run
[macbook air/macOS/98000.0,macbook pro/macOS/128000.0,surface/windows/148000.0]
表示がコンパクトになりました。
ここまでのコード app/Main.hs :
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Lib
import Codec.Xlsx (toXlsx, CellValue, CellValue(CellText,CellDouble))
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
type Name = Maybe CellValue
type OS = Maybe CellValue
type Price = Maybe CellValue
data Computer = Computer Name OS Price
instance Show Computer where
show c = foldl1 (\a b -> a ++ "/" ++ b) [(toName c), (toOS c), (toPrice c)]
where
toValue :: CellValue -> String
toValue (CellText v) = T.unpack v
toValue (CellDouble v) = show v
toName (Computer v _ _) = toValue $ maybe (CellText "") id v
toOS (Computer _ v _) = toValue $ maybe (CellText "") id v
toPrice (Computer _ _ v) = toValue $ maybe (CellDouble 0) id v
toComputer :: Row -> Computer
toComputer row = Computer (row !! 0) (row !! 1) (row !! 2)
main :: IO ()
main = do
bs <- L.readFile "computers.xlsx"
let
xlsx = toXlsx bs
sheetName = "Sheet1"
rowCount = toRowCount xlsx sheetName
bodyRowIndexes = take (rowCount-1) [2..]
bodyRows = toRows xlsx sheetName bodyRowIndexes
computers = map (\row -> toComputer row) $ toRows xlsx sheetName bodyRowIndexes
putStrLn $ show computers
所定のコンピュータのみを取り出す関数:
findComputersByOS :: OS -> [Computer] -> [Computer]
findComputersByOS os computers = filter (\c -> (toOS c)==os) computers
where toOS (Computer _ v _) = v
macOS のコンピュータのみ取り出す関数:
findMacOSComputers :: [Computer] -> [Computer]
findMacOSComputers = findComputersByOS (Just $ CellText "macOS")
実行:
$ stack run
[macbook air/macOS/98000.0,macbook pro/macOS/128000.0]
うまく、macOS のコンピュータのみを取り出すことができました。
あとは、Computer リストをエクセルデータに変換する必要があります。 この書き出し処理は パート3 に続きます。
ここまでの app/Main.hs をまとめます。
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Lib
import Codec.Xlsx (toXlsx, CellValue, CellValue(CellText,CellDouble))
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
type Name = Maybe CellValue
type OS = Maybe CellValue
type Price = Maybe CellValue
data Computer = Computer Name OS Price
instance Show Computer where
show c = foldl1 (\a b -> a ++ "/" ++ b) [(toName c), (toOS c), (toPrice c)]
where
toValue :: CellValue -> String
toValue (CellText v) = T.unpack v
toValue (CellDouble v) = show v
toName (Computer v _ _) = toValue $ maybe (CellText "") id v
toOS (Computer _ v _) = toValue $ maybe (CellText "") id v
toPrice (Computer _ _ v) = toValue $ maybe (CellDouble 0) id v
toComputer :: Row -> Computer
toComputer row = Computer (row !! 0) (row !! 1) (row !! 2)
findComputersByOS :: OS -> [Computer] -> [Computer]
findComputersByOS os computers = filter (\c -> (toOS c)==os) computers
where toOS (Computer _ v _) = v
findMacOSComputers :: [Computer] -> [Computer]
findMacOSComputers = findComputersByOS (Just $ CellText "macOS")
main :: IO ()
main = do
bs <- L.readFile "computers.xlsx"
let
xlsx = toXlsx bs
sheetName = "Sheet1"
rowCount = toRowCount xlsx sheetName
bodyRowIndexes = take (rowCount-1) [2..]
bodyRows = toRows xlsx sheetName bodyRowIndexes
computers = map (\row -> toComputer row) $ toRows xlsx sheetName bodyRowIndexes
macOSComputers = findMacOSComputers computers
putStrLn $ show macOSComputers
以上です。