Skip to content
Snippets Groups Projects
select.hs 983 B
Newer Older
#!/usr/bin/env -S runhaskell --ghc-arg="-Wall" --ghc-arg="-i lib"
{-# LANGUAGE ExplicitNamespaces, OverloadedStrings #-}
module Main where

import Control.Monad.Except (ExceptT(..), runExceptT)
import Data.Map ((!?))
import Data.Maybe (catMaybes)
import Data.Vector (Vector, toList)
import GEODE.Metadata (Entry, Has(..), PrimaryKey, type(@), indexBy, readNamedTsv, tsvFile)
import System.Environment (getArgs)
import System.Exit (die)
import System.Script (syntax)

getMeta :: Vector PrimaryKey -> Vector (PrimaryKey @ Entry) -> [(PrimaryKey @ Entry)]
getMeta coords meta = catMaybes ((indexed !?) <$> toList coords)
  where
    indexed = indexBy get meta

main :: IO ()
main = getArgs >>= run
  where
    run [keys, input, output] =
      runExceptT ( getMeta
                    <$> ExceptT (readNamedTsv keys)
                    <*> ExceptT (readNamedTsv input) )
      >>= either die (tsvFile output)
    run _ = syntax "PRIMARY_KEY.tsv INPUT_METADATA.tsv OUTPUT_METADATA.tsv"