Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Tagged types (Nikita Fufaev)
   2. Re:  Tagged types (PICCA Frederic-Emmanuel)


----------------------------------------------------------------------

Message: 1
Date: Fri, 12 Oct 2018 00:35:06 +0300
From: Nikita Fufaev <kittto...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Tagged types
Message-ID:
        <CAHo=-3a8ecaru0tuzfed3etlbg2p-v3iz+wyc8lwtfefcuh...@mail.gmail.com>
Content-Type: text/plain; charset="UTF-8"

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
<frederic-emmanuel.pi...@synchrotron-soleil.fr> wrote:
> 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


------------------------------

Message: 2
Date: Fri, 12 Oct 2018 12:35:54 +0000
From: PICCA Frederic-Emmanuel
        <frederic-emmanuel.pi...@synchrotron-soleil.fr>
To: "The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell" <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Tagged types
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53015b33d...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="us-ascii"

I endup with this solution, whcih is for me quite elegant. Maybe this could be 
generalize with the singleton package.

mkSomeDataCollection :: DataCollection a b -> SomeDataCollection
mkSomeDataCollection c = withSCollectType $ \s -> 
                                       withSCollectSourceFormat $ \f ->
                                         SomeDataCollection s f (coerce c)
    where
      withSCollectType :: (forall c. SCollectType c -> SomeDataCollection) -> 
SomeDataCollection
      withSCollectType cont = if "ref-" `isPrefixOf` imagePrefix c
                              then cont SCaracterization
                              else cont SCollect

      withSCollectSourceFormat :: (forall c .SCollectSourceFormat c -> 
SomeDataCollection) -> SomeDataCollection
      withSCollectSourceFormat cont = case imageSuffix c of
                                        (Just "cbf") -> cont SCbf
                                        (Just "h5") -> cont SHdf5
                                        (Just _) -> cont SCbf
                                        Nothing -> cont SCbf


I can not use singleton since I decided to stick to Debian stable/unstable

Cheers and thanks a lot for the help.

Frederic

------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 124, Issue 8
*****************************************

Reply via email to