#ifdef TRUST
{-# LANGUAGE Trustworthy #-}
#endif

{-|
    This module exposes collections of words in a best guess of the current
    language on the computer the application is running on.

    For UNIX-based systems, including MacOS, this list is taken either
    @/usr/share/dict/words@ or @/usr/dict/words@, whichever is the first
    that exists.  If neither path exists, then the list is taken from a
    built-in collection of English language words.

    Better localization would be nice for platforms that do not have words
    files.
-}
module Language.Words (allWords, allStringWords) where

import           Data.Text (Text)
import qualified Data.Text         as T
import qualified Data.Text.Lazy    as LT
import qualified Data.Text.Lazy.IO as LT

import           System.Directory
import           System.IO
import           System.IO.Unsafe

import           Paths_words

{-# NOINLINE allWords #-}
allWords :: [Text]
allWords = unsafePerformIO wordsIO

{-# NOINLINE allStringWords #-}
allStringWords :: [String]
allStringWords = unsafePerformIO stringWordsIO

wordsIO :: IO [Text]
wordsIO = withWordsFile $
    fmap (dropWhile T.null . map (T.concat . LT.toChunks) . LT.lines)
    . LT.hGetContents

stringWordsIO :: IO [String]
stringWordsIO = withWordsFile $ fmap (dropWhile null . lines) . hGetContents

withWordsFile k = do
    f <- findWordsFile
    h <- openFile f ReadMode
    k h

findWordsFile = do
    files <- getWordsFiles
    lookForWords files

getWordsFiles = do
    builtin <- getDataFileName "words"
    return [ "/usr/share/dict/words", "/usr/dict/words", builtin ]

lookForWords (f:fs) = do
    success <- doesFileExist f
    if success then return f else lookForWords fs
lookForWords [] = error "words: Can't find words file; even tried built-in!"