
return (if "ref-" `isPrefixOf` imagePrefix col
then
cont SCaracterization
else
cont SCollect)
where
cont :: forall coc. SCaracterizationOrCollect coc -> SomeDataCollection
cont sing = case imageSuffix col of
(Just "cbf") -> SomeDataCollection sing SCbf (coerce col)
(Just "h5") -> SomeDataCollection sing SHdf5 (coerce col)
(Just _) -> SomeDataCollection sing SCbf (coerce col)
Nothing -> SomeDataCollection sing SCbf (coerce col)
You could also get rid of SomeDataCollection in a similar way:
data DataCollection a b = DataCollection (SCaracterizationOrCollect a)
(SSuffix b) String
parseFileName :: forall c. String -> (forall a b. DataCollection a b -> c) -> c
parseFileName col cont = (if "ref-" `isPrefixOf` imagePrefix col
then
cont2 SCaracterization
else
cont2 SCollect)
where cont2 :: forall coc. SCaracterizationOrCollect coc -> c
cont2 sing = case imageSuffix col of
(Just "cbf") -> cont $ DataCollection sing SCbf (coerce col)
(Just "h5") -> cont $ DataCollection sing SHdf5 (coerce col)
(Just _) -> cont $ DataCollection sing SCbf (coerce col)
Nothing -> cont $ DataCollection sing SCbf (coerce col)
In general, when you want to type some expression that can be of
different types depending on values, you can turn it into a function
that takes polymorphic continuation as an argument.
If you plan to have many tags on DataCollection and many functions
that return DataCollections of different types where some tags depend
on argument values and some tags are staticlly known, this style is
probably easier.
If you are willing to use singletons package, there is another way to do this:
{-# Language TemplateHaskell, KindSignatures, TypeFamilies, DataKinds,
ScopedTypeVariables #-}
import Data.Coerce
import Data.Singletons.TH
import Data.List
$(singletons [d|
data Suffix = Cbf | Hdf5
data CaracterizationOrCollect = Caracterization | Collect
|])
data SomeDataCollection where
SomeDataCollection :: SCaracterizationOrCollect a -> SSuffix b ->
DataCollection a b -> SomeDataCollection
newtype DataCollection (a::CaracterizationOrCollect) (b::Suffix) = DC String
someFunc :: String -> IO SomeDataCollection
someFunc col = return $ withSomeSing (if "ref-" `isPrefixOf` imagePrefix col
then
Caracterization
else
Collect)
(\sing -> case imageSuffix col of
(Just "cbf") ->
SomeDataCollection sing SCbf (coerce col)
(Just "h5") ->
SomeDataCollection sing SHdf5 (coerce col)
(Just _) ->
SomeDataCollection sing SCbf (coerce col)
Nothing -> SomeDataCollection
sing SCbf (coerce col))
Hopefully, when the hyped DependentTypes extension lands, this will
all be authomated and we won't need to explicitly use a single
singleton anymore.
On 11/10/2018, PICCA Frederic-Emmanuel
Hello, So I end-up for now with two singletons for my SomeDataCollection
So I red the Datacollection from an xml file (col) then I create the SomeDataCollection type depending on a bunch of values found in the Datacollection. like this.
return $ if "ref-" `isPrefixOf` imagePrefix col then case imageSuffix col of (Just "cbf") -> SomeDataCollection SCaracterization SCbf (coerce col) (Just "h5") -> SomeDataCollection SCaracterization SHdf5 (coerce col) (Just _) -> SomeDataCollection SCaracterization SCbf (coerce col) Nothing -> SomeDataCollection SCaracterization SCbf (coerce col) else case imageSuffix col of (Just "cbf") -> SomeDataCollection SCollect SCbf (coerce col) (Just "h5") -> SomeDataCollection SCollect SHdf5 (coerce col) (Just _) -> SomeDataCollection SCollect SCbf (coerce col) Nothing -> SomeDataCollection SCollect SCbf (coerce col)
Now I would like to do something like
let t = if "ref-" `isPrefixOf` imagePrefix col then SCaracterization else SCollect
and then
return SomeDatacollection t f (coerce col)
But If I try to do this I have an error like this
src/ISPyB/Soap.hs:119:37-44: error: • Couldn't match type ‘'Collect’ with ‘'Caracterization’ Expected type: SCollectType 'Caracterization Actual type: SCollectType 'Collect • In the expression: SCollect In the expression: if "ref-" `isPrefixOf` imagePrefix col then SCaracterization else SCollect In an equation for ‘t’: t = if "ref-" `isPrefixOf` imagePrefix col then SCaracterization else SCollect
how can I fix this and make the code better to read.
thanks
Fred _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Nikita Fufaev, +7 999 825-95-07