Created
June 20, 2017 17:53
-
-
Save cocreature/f08cef567027f3aae1602bec313baa17 to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE OverloadedStrings #-} | |
{-# LANGUAGE NoImplicitPrelude #-} | |
import Protolude hiding (for) | |
import GHC.Base (String) | |
import Pipes | |
import qualified Pipes.Prelude as P | |
import Pipes.Safe (MonadSafe, runSafeT) | |
import qualified Pipes.Safe.Prelude as PSP | |
import qualified Pipes.ByteString as PB | |
import Pipes.Text.IO (fromHandle) | |
import Pipes.Parse | |
import qualified Pipes.Attoparsec as PA | |
import qualified Data.Attoparsec.ByteString.Char8 as AB | |
import Data.Hashable | |
import qualified Data.IntMap as IM | |
import Data.Vector (Vector) | |
import qualified Data.Vector as Vector | |
data AccountLine = AccountLine { | |
_accountId2 :: !ByteString, | |
_accountName2 :: !ByteString, | |
_accountContractId :: !ByteString, | |
_accountCPCode :: !Word32 | |
} deriving (Show) | |
type MapCPCodetoAccountIdIdx = IntMap Int | |
data Accounts = Accounts { | |
_accountIds :: !(Vector ByteString), | |
_xxx :: !(IntMap Int), | |
_accountCPcodes :: !MapCPCodetoAccountIdIdx | |
} deriving (Show) | |
parseAccount :: AB.Parser AccountLine | |
parseAccount = AccountLine <$> | |
getSubfield <* delim <*> | |
getSubfield <* delim <*> | |
getSubfield <* delim <*> | |
AB.decimal | |
where getSubfield = AB.takeTill (== '|') | |
delim = AB.char '|' | |
parseAccountLine :: AB.Parser AccountLine | |
parseAccountLine = AccountLine <$> | |
getSubfield <* delim <*> | |
getSubfield <* delim <*> | |
getSubfield <* delim <*> | |
AB.decimal <* AB.endOfLine | |
where getSubfield = AB.takeTill (== '|') | |
delim = AB.char '|' | |
parseLine :: (Monad m) => Parser ByteString m (Maybe (Either PA.ParsingError AccountLine)) | |
parseLine = PA.parse parseAccountLine | |
a = Accounts Vector.empty IM.empty IM.empty | |
x :: Accounts -> AccountLine -> Accounts | |
x (Accounts ids a2i cps) (AccountLine aid an cid cp) = | |
case IM.lookup (hash aid) a2i of | |
Nothing -> | |
Accounts | |
(Vector.snoc ids (toS aid)) | |
(IM.insert (hash aid) (length ids) a2i) | |
(IM.insert (fromIntegral cp) (length ids) cps) | |
Just idx -> Accounts ids a2i (IM.insert (fromIntegral cp) idx cps) | |
z = foldAll x a identity | |
readByteStringFile :: (MonadSafe m) => FilePath -> Producer' ByteString m () | |
readByteStringFile file = PSP.withFile file ReadMode PB.fromHandle | |
-- how do i combine z and parseLine ? | |
main :: IO () | |
main = do | |
let accountLines :: MonadSafe m => Producer AccountLine m (Either (PA.ParsingError, Producer ByteString m ()) ()) | |
accountLines = PA.parsed parseAccountLine (readByteStringFile "/tmp/blah2") | |
x <- runSafeT $ runEffect $ Pipes.Parse.evalStateT z $ accountLines | |
print x |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment