Skip to content

Instantly share code, notes, and snippets.

@cocreature
Created May 25, 2015 08:50
Show Gist options
  • Save cocreature/0d0940e94b63c978bc41 to your computer and use it in GitHub Desktop.
Save cocreature/0d0940e94b63c978bc41 to your computer and use it in GitHub Desktop.
Frames with multiple custom columns
{-# LANGUAGE ConstraintKinds, DataKinds, FlexibleContexts, GADTs,
OverloadedStrings, PatternSynonyms, QuasiQuotes,
ScopedTypeVariables, TemplateHaskell, TypeOperators,
ViewPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
module Data where
import Control.Lens
import Data.Readable
import qualified Data.Text as T
import Frames
import Frames.CSV
import Pipes
import qualified Pipes.Prelude as P
import Types
tableTypes'
rowGen {rowTypeName = "Answer"
,columnUniverse = $(colQ ''MyColumns)}
"data/raw-anon-v1-0.csv"
answerStream :: Producer Answer IO ()
answerStream = readTableOpt answerParser "data/raw-anon-v1-0.csv"
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
module Types where
import Data.Typeable
import Data.Text
import Frames
import Data.Readable
import Control.Monad
import Frames.InCore
import qualified Data.Vector as V
newtype NumericalAnswer = NumericalAnswer (Maybe Int) deriving (Show,Read,Eq,Ord,Typeable)
newtype SkillLevel = SkillLevel (Maybe Text) deriving (Show,Read,Eq,Ord,Typeable)
instance Readable NumericalAnswer where
fromText t
| t == "0" = return $ NumericalAnswer $ Just 0
| t == "1" = return $ NumericalAnswer $ Just 1
| t == "2" = return $ NumericalAnswer $ Just 2
| t == "3" = return $ NumericalAnswer $ Just 3
| t == "4" = return $ NumericalAnswer $ Just 4
| t == "\"\"" || t == "Don't know" = return $ NumericalAnswer Nothing
| otherwise = mzero
instance Readable SkillLevel where
fromText t
| t `elem` ["none","beginner","learning","competent","expert"] = return $ SkillLevel (Just t)
| t == "\"\"" = return $ SkillLevel Nothing
| otherwise = mzero
type instance VectorFor NumericalAnswer = V.Vector
type instance VectorFor SkillLevel = V.Vector
type MyColumns = SkillLevel ': NumericalAnswer ': CommonColumns
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment