Created
July 22, 2018 00:03
-
-
Save kozross/02a24dd27e3c4e79932018bcc1ba9973 to your computer and use it in GitHub Desktop.
This file contains hidden or 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 DeriveGeneric #-} | |
{-# LANGUAGE DuplicateRecordFields #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
module Data.CRLF where | |
import GHC.Generics | |
import Control.Monad.Except | |
import Data.Binary | |
import Data.Bits | |
import qualified Control.Monad.State as S | |
import qualified Data.Text as T | |
data ColumnTypeError a = TooManyValues Int | TooFewValues | LoNotLessThanHi a a | RepeatedValue a | |
deriving (Eq, Show, Read) | |
data ColumnType a b = Categorical { missingVal :: Maybe b, | |
dict :: [(b, a)] } | | |
Discrete { missingValue :: Maybe b, | |
lo :: Maybe (b, a), | |
hi :: Maybe (b, a) } | | |
Continuous { missingValue :: Maybe b, | |
lo :: Maybe (b, a), | |
hi :: Maybe (b, a) } | |
deriving (Eq, Show, Read, Generic) | |
instance (Binary a, Binary b) => Binary (ColumnType a b) | |
mkCategorical :: (Eq a, FiniteBits b, Enum b, MonadError (ColumnTypeError a) m) => [a] -> m (ColumnType a b) | |
mkCategorical xs | |
| length xs < 3 = throwError TooFewValues | |
{- This case gives an error like this: | |
src/Data/CRLF.hs|56 col 21 error| error: • Could not deduce (FiniteBits b0) arising from a use of ‘finiteBitSize’ from the context: (Eq a, FiniteBits b, Enum b, MonadError (ColumnTypeError a) m) bound by the type signature for: mkCategorical :: forall a b (m :: * -> *). (Eq a, FiniteBits b, Enum b, MonadError (ColumnTypeError a) m) => [a] -> m (ColumnType a b) at /home/koz/documents/uni/research/papers/case-study/code/crlf/src/Data/CRLF.hs:53:1-108 The type variable ‘b0’ is ambiguous These potential instances exist: instance FiniteBits Int16 -- Defined in ‘GHC.Int’ instance FiniteBits Int32 -- Defined in ‘GHC.Int’ instance FiniteBits Int64 -- Defined in ‘GHC.Int’ ...plus 8 others ...plus two instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the second argument of ‘(^)’, namely ‘finiteBitSize (undefined :: b)’ In the second argument of ‘(>)’, namely ‘2 ^ finiteBitSize (undefined :: b)’ In the expression: length xs > 2 ^ finiteB | |
Why am I getting this? This is a copy/paste from a (much) larger file, so line numbers may not match up -} | |
| length xs > 2 ^ finiteBitSize (undefined :: b) = throwError (TooManyValues (length xs)) | |
| otherwise = case duplicated xs of | |
Just x -> throwError (RepeatedValue x) | |
Nothing -> return (Categorical Nothing (zip [zeroBits ..] xs)) | |
duplicated :: (Eq a) => [a] -> Maybe a | |
duplicated [] = Nothing | |
duplicated xs = S.evalState (foldM go Nothing xs) [] | |
where go res@(Just _) _ = return res | |
go Nothing x = do history <- S.get | |
if x `elem` history | |
then return (Just x) | |
else S.put (x : history) >> return Nothing |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment