The JSON data is in the following format
{
"Genesis": {
"1": {
"1": "In the beginning..." ,
"2": "..."
},
"2": { ... }
},
"Exodus": { ... },
...
}
In JSON, keys aren't ordered and must be strings.
The goal is to parse the JSON file, order everything correctly (which means parsing the keys into integers), and produce an array that looks like this:
[
("Genesis", 1, 1, "In the beginning..")
("Genesis", 1, 2, "")
]
The data structure can be a tuple or some new type.
(ns versify.core
(:require [cheshire.core :refer :all])
(:gen-class))
(def book-order ["Genesis", "Exodus", "Leviticus", "Numbers", "Deuteronomy",
"Joshua", "Judges", "Ruth", "1 Samuel", "2 Samuel", "1 Kings", "2 Kings",
"1 Chronicles", "2 Chronicles", "Ezra", "Nehemiah", "Esther", "Job",
"Psalms", "Proverbs", "Ecclesiastes", "Song of Solomon", "Isaiah",
"Jeremiah", "Lamentations", "Ezekiel", "Daniel", "Hosea", "Joel", "Amos",
"Obadiah", "Jonah", "Micah", "Nahum", "Habakkuk", "Zephaniah", "Haggai",
"Zechariah", "Malachi", "Matthew", "Mark", "Luke", "John", "Acts",
"Romans", "1 Corinthians", "2 Corinthians", "Galatians", "Ephesians",
"Philippians", "Colossians", "1 Thessalonians", "2 Thessalonians",
"1 Timothy", "2 Timothy", "Titus", "Philemon", "Hebrews", "James",
"1 Peter", "2 Peter", "1 John", "2 John", "3 John", "Jude", "Revelation"])
(defn intify [m]
(apply assoc (sorted-map)
(mapcat
(fn [[k v]]
[(read-string k), v]) m)))
(defn get-books [bible]
(map (fn [book] [book, (bible book)]) book-order))
(defn get-chapters [books]
(mapcat (fn [[k v]]
(let [i (intify v)]
(map (fn [[n c]] [k, n, c]) i))) books))
(defn get-verses [verses]
(mapcat (fn [[b c d]]
(let [i (intify d)]
(map (fn [[v t]] [b, c, v, t]) i))) verses))
(def parse (comp get-verses get-chapters get-books))
(defn -main
[& args]
(let [bible (parse-string (slurp "ESV.json"))]
(first (parse bible))))
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Prelude hiding (lookup)
import Data.Aeson (decode, FromJSON)
import Data.Maybe (fromMaybe)
import Data.Aeson.Types
import Control.Applicative ((<$>))
import qualified Data.ByteString.Lazy.Char8 as BS
import Data.Map (Map, toList, fromList, lookup)
bookOrder = ["Genesis", "Exodus", "Leviticus", "Numbers", "Deuteronomy",
"Joshua", "Judges", "Ruth", "1 Samuel", "2 Samuel", "1 Kings", "2 Kings",
"1 Chronicles", "2 Chronicles", "Ezra", "Nehemiah", "Esther", "Job",
"Psalms", "Proverbs", "Ecclesiastes", "Song of Solomon", "Isaiah",
"Jeremiah", "Lamentations", "Ezekiel", "Daniel", "Hosea", "Joel", "Amos",
"Obadiah", "Jonah", "Micah", "Nahum", "Habakkuk", "Zephaniah", "Haggai",
"Zechariah", "Malachi", "Matthew", "Mark", "Luke", "John", "Acts",
"Romans", "1 Corinthians", "2 Corinthians", "Galatians", "Ephesians",
"Philippians", "Colossians", "1 Thessalonians", "2 Thessalonians",
"1 Timothy", "2 Timothy", "Titus", "Philemon", "Hebrews", "James",
"1 Peter", "2 Peter", "1 John", "2 John", "3 John", "Jude", "Revelation"]
type Verse = String
newtype Chapter = Chapter (Map String Verse) deriving (Show, Eq, Ord)
newtype Book = Book (Map String Chapter) deriving (Show, Eq, Ord)
newtype Bible = Bible (Map String Book) deriving (Show, Eq, Ord)
newtype OrderedChapter = OrderedChapter (Map Int Verse) deriving (Show, Eq, Ord)
newtype OrderedBook = OrderedBook (Map Int OrderedChapter) deriving (Show, Eq, Ord)
newtype OrderedBible = OrderedBible (Map String OrderedBook) deriving (Show, Eq, Ord)
instance FromJSON Chapter where
parseJSON val = Chapter <$> parseJSON val
instance FromJSON Book where
parseJSON val = Book <$> parseJSON val
instance FromJSON Bible where
parseJSON val = Bible <$> parseJSON val
getBooks :: OrderedBible -> [(String, OrderedBook)]
getBooks (OrderedBible b) = map (f b) bookOrder
where f b k = (k, (x k b))
x k b = case (lookup k b) of
Just b -> b
Nothing -> error "fail"
getChapters :: [(String, OrderedBook)] -> [(String, Int, OrderedChapter)]
getChapters books = concatMap f books
where f (bookName, (OrderedBook b)) = map (g bookName) (toList b)
g bookName (chapterNumber, chapter) = (bookName, chapterNumber, chapter)
getVerses :: [(String, Int, OrderedChapter)] -> [FlatVerse]
getVerses chapters = concatMap f chapters
where f (bookName, chapterNumber, (OrderedChapter chapter)) = map (g bookName chapterNumber) (toList chapter)
g bookName chapterNumber (verseNumber, verse) = FlatVerse {
text = verse,
book = bookName,
chapter = chapterNumber,
verse = verseNumber}
flattenBible :: OrderedBible -> [FlatVerse]
flattenBible = (getVerses . getChapters . getBooks)
data FlatVerse = FlatVerse { text :: String
, book :: String
, chapter :: Int
, verse :: Int
} deriving (Show)
formatVerse :: FlatVerse -> String
formatVerse v = "\"" ++ (text v) ++ "\" - " ++ (book v) ++ " "
++ show (chapter v) ++ ":" ++ show (book v)
loadBible :: BS.ByteString -> Bible
loadBible x = do
let y = decode x :: Maybe Bible
case y of
Just b -> b
Nothing -> error "mle"
getOrderedBible :: Bible -> OrderedBible
getOrderedBible (Bible bible) = OrderedBible (fromList (c bible))
where c bible = map (g bible) bookOrder
g bible key = (key, (getOrderedBook book)) where
book = case lookup key bible of
Just b -> b
Nothing -> error "fail"
getOrderedBook :: Book -> OrderedBook
getOrderedBook (Book b) = OrderedBook (fromList (map f (toList b)))
where f (num, chapter) = (read num :: Int, (getOrderedChapter chapter))
getOrderedChapter :: Chapter -> OrderedChapter
getOrderedChapter (Chapter c) = OrderedChapter (fromList (map f (toList c)))
where f (num, verse) = (read num :: Int, verse)
main = do
putStrLn "hey"
bible <- BS.readFile "ESV.json"
let b = getOrderedBible (loadBible bible)
f = flattenBible b
putStrLn $ show $ length f
putStrLn $ show $ formatVerse (head f)
Beyond "just give me some tuples", these two programs are not equivalent and the "Haskell vs Clojure" title might be perceived as hyperbolic.
One key thing to point out is that the Haskell program accounts for failure scenarios while the Clojure code does not. This is characteristic of programming styles in both languages. Both will have the same observationally equivalent result when they work properly but when the Clojure code fails it may not be immediately obvious why.
If there is truly no such possibility of a failure condition in this scenario, why bother choosing this as an example of Haskell and Clojure in contrast? Why pick any two languages to compare at all? That's golf. Golf is boring.
@douglasrocha: Not necessarily.
Map.lookup
is not "the same" asget
(which is secretly hiding in(bible book)
inget-book
).Map.lookup
returns an instance of the typeMaybe a
wherea
is some type (e.g.Integer
,String
, etc.). The value you get will either beJust aValue
orNothing
.get
on the other hand, only ever returns either an instance ofObject
ornil
. In other words the values you get fromMap.lookup
can be in different sets while the values you can fromget
are always from one set.