<div dir="ltr"><div class="gmail_default" style="font-family:tahoma,sans-serif"><img src="cid:ii_15ad03fc08552907" alt="Inline image 1" width="562" height="205"><br></div><div class="gmail_default" style="font-family:tahoma,sans-serif">"Problem Opening Wizard"</div><div class="gmail_default" style="font-family:tahoma,sans-serif"><br></div><div class="gmail_default" style="font-family:tahoma,sans-serif">I've Eclipse "<span style="font-family:'.sf ns text';font-size:11px">Version: Neon.2 Release (4.6.2) </span><span style="font-family:'.sf ns text';font-size:11px">Build id: 20161208-0600</span>" installed on macOS El Capitan 10.11.6. </div><div class="gmail_default" style="font-family:tahoma,sans-serif"><br></div><div class="gmail_default" style="font-family:tahoma,sans-serif">​"<span style="font-family:'.sf ns text';font-size:11px">The selected wizard could not be started.</span></div>
<p style="margin:0px;text-indent:1.1px;font-size:11px;line-height:normal;font-family:'.sf ns text'">Plug-in net.sf.eclipsefp.haskell.ui was unable to load class net.sf.eclipsefp.haskell.ui.wizards.NewHaskellProjectWizard.</p>
<div class="gmail_default" style="font-family:tahoma,sans-serif"><span style="font-family:'.sf ns text';font-size:11px;text-indent:1.1px">An error occurred while automatically activating bundle net.sf.eclipsefp.haskell.ui (482).</span>"​</div><div class="gmail_default" style="font-family:tahoma,sans-serif"><br></div><div class="gmail_default" style="font-family:tahoma,sans-serif">Albert. </div><div class="gmail_default" style="font-family:tahoma,sans-serif"><br></div><div class="gmail_default" style="font-family:tahoma,sans-serif">Anyone has the same problem and solved it? </div><div class="gmail_default" style="font-family:tahoma,sans-serif"><br></div><div class="gmail_default" style="font-family:tahoma,sans-serif">Thanks. </div><div class="gmail_default" style="font-family:tahoma,sans-serif"><br></div></div><div class="gmail_extra"><br><div class="gmail_quote">On Thu, Feb 23, 2017 at 1:10 AM,  <span dir="ltr"><<a href="mailto:beginners-request@haskell.org" target="_blank">beginners-request@haskell.org</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Send Beginners mailing list submissions to<br>
        <a href="mailto:beginners@haskell.org">beginners@haskell.org</a><br>
<br>
To subscribe or unsubscribe via the World Wide Web, visit<br>
        <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/beginners</a><br>
or, via email, send a message with subject or body 'help' to<br>
        <a href="mailto:beginners-request@haskell.org">beginners-request@haskell.org</a><br>
<br>
You can reach the person managing the list at<br>
        <a href="mailto:beginners-owner@haskell.org">beginners-owner@haskell.org</a><br>
<br>
When replying, please edit your Subject line so it is more specific<br>
than "Re: Contents of Beginners digest..."<br>
<br>
<br>
Today's Topics:<br>
<br>
   1. Re:  Type error when using splitOn function. (Francesco Ariis)<br>
   2. Re:  Type error when using splitOn function. (S. H. Aegis)<br>
   3.  How to link two Types (PICCA Frederic-Emmanuel)<br>
   4. Re:  How to link two Types (David McBride)<br>
   5. Re:  How to link two Types (PICCA Frederic-Emmanuel)<br>
   6. Re:  How to link two Types (David McBride)<br>
<br>
<br>
------------------------------<wbr>------------------------------<wbr>----------<br>
<br>
Message: 1<br>
Date: Wed, 22 Feb 2017 14:31:16 +0100<br>
From: Francesco Ariis <<a href="mailto:fa-ml@ariis.it">fa-ml@ariis.it</a>><br>
To: <a href="mailto:beginners@haskell.org">beginners@haskell.org</a><br>
Subject: Re: [Haskell-beginners] Type error when using splitOn<br>
        function.<br>
Message-ID: <20170222133116.GA14860@casa.<wbr>casa><br>
Content-Type: text/plain; charset=us-ascii<br>
<br>
On Wed, Feb 22, 2017 at 09:02:22PM +0900, S. H. Aegis wrote:<br>
> Thank you so much.<br>
><br>
> --makeRxDxList :: Functor f => f Text -> f [Text]<br>
> Above signature comes from ghci using command :t<br>
> My intention is<br>
> makeRxDxList :: Text -> [[Text]]<br>
> but, I got error, and try several times and below codes pass a complier.<br>
> makeRxDxList rowRxDx = fmap (\x -> splitOn (pack ",") x) rowRxDx  -- This<br>
> code pass a compile.<br>
> and then, I run ghci, type :t, and got below signature.<br>
> makeRxDxList :: Functor f => f Text -> f [Text]<br>
><br>
> Your kind answer says, I cannot help using fmap. right? ^^;<br>
> Thanks again.<br>
<br>
Then this:<br>
<br>
    makeRxDxList :: Text -> [[Text]]<br>
    makeRxDxList rowRxDx = fmap f (lines rowRxDx)<br>
                -- you imported Prelude hiding map, so we will use fmap<br>
        where<br>
              f :: Text -> [Text]<br>
              f x = splitOn (pack ",") x<br>
<br>
should do (at least it typechecks).<br>
<br>
GHC errors may not have the prettiest formatting ever, but they are<br>
very useful, the most important bits being line & column of the offending<br>
expression plus the "expected this but got that" part; get acquainted<br>
with them!<br>
<br>
<br>
<br>
------------------------------<br>
<br>
Message: 2<br>
Date: Wed, 22 Feb 2017 22:41:10 +0900<br>
From: "S. H. Aegis" <<a href="mailto:shaegis@gmail.com">shaegis@gmail.com</a>><br>
To: The Haskell-Beginners Mailing List - Discussion of primarily<br>
        beginner-level topics related to Haskell <<a href="mailto:beginners@haskell.org">beginners@haskell.org</a>><br>
Subject: Re: [Haskell-beginners] Type error when using splitOn<br>
        function.<br>
Message-ID:<br>
        <<a href="mailto:CAJp-NqxZ5gAqQT8-Swd%2BPE-ys_PVSAJo1c74%2BB-UuFabJr_F4w@mail.gmail.com">CAJp-NqxZ5gAqQT8-Swd+PE-ys_<wbr>PVSAJo1c74+B-UuFabJr_F4w@mail.<wbr>gmail.com</a>><br>
Content-Type: text/plain; charset="utf-8"<br>
<br>
It works !!! (^O^)<br>
Thank you so much.<br>
<br>
Have a nice day~!<br>
<br>
2017-02-22 22:31 GMT+09:00 Francesco Ariis <<a href="mailto:fa-ml@ariis.it">fa-ml@ariis.it</a>>:<br>
<br>
> On Wed, Feb 22, 2017 at 09:02:22PM +0900, S. H. Aegis wrote:<br>
> > Thank you so much.<br>
> ><br>
> > --makeRxDxList :: Functor f => f Text -> f [Text]<br>
> > Above signature comes from ghci using command :t<br>
> > My intention is<br>
> > makeRxDxList :: Text -> [[Text]]<br>
> > but, I got error, and try several times and below codes pass a complier.<br>
> > makeRxDxList rowRxDx = fmap (\x -> splitOn (pack ",") x) rowRxDx  -- This<br>
> > code pass a compile.<br>
> > and then, I run ghci, type :t, and got below signature.<br>
> > makeRxDxList :: Functor f => f Text -> f [Text]<br>
> ><br>
> > Your kind answer says, I cannot help using fmap. right? ^^;<br>
> > Thanks again.<br>
><br>
> Then this:<br>
><br>
>     makeRxDxList :: Text -> [[Text]]<br>
>     makeRxDxList rowRxDx = fmap f (lines rowRxDx)<br>
>                 -- you imported Prelude hiding map, so we will use fmap<br>
>         where<br>
>               f :: Text -> [Text]<br>
>               f x = splitOn (pack ",") x<br>
><br>
> should do (at least it typechecks).<br>
><br>
> GHC errors may not have the prettiest formatting ever, but they are<br>
> very useful, the most important bits being line & column of the offending<br>
> expression plus the "expected this but got that" part; get acquainted<br>
> with them!<br>
><br>
> ______________________________<wbr>_________________<br>
> Beginners mailing list<br>
> <a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/beginners</a><br>
><br>
<br>
<br>
<br>
--<br>
Sok Ha, CHANG<br>
Dr. Chang's Clinic. #203. 503-23. AmSa-Dong, GangDong-Gu, Seoul.<br>
Tel: +82-2-442-7585<br>
-------------- next part --------------<br>
An HTML attachment was scrubbed...<br>
URL: <<a href="http://mail.haskell.org/pipermail/beginners/attachments/20170222/0d194b9d/attachment-0001.html" rel="noreferrer" target="_blank">http://mail.haskell.org/<wbr>pipermail/beginners/<wbr>attachments/20170222/0d194b9d/<wbr>attachment-0001.html</a>><br>
<br>
------------------------------<br>
<br>
Message: 3<br>
Date: Wed, 22 Feb 2017 15:27:39 +0000<br>
From: PICCA Frederic-Emmanuel<br>
        <<a href="mailto:frederic-emmanuel.picca@synchrotron-soleil.fr">frederic-emmanuel.picca@<wbr>synchrotron-soleil.fr</a>><br>
To: "<a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a>" <<a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a>><br>
Subject: [Haskell-beginners] How to link two Types<br>
Message-ID:<br>
        <<a href="mailto:A2A20EC3B8560D408356CAC2FC148E53BB34799C@SUN-DAG3.synchrotron-soleil.fr">A2A20EC3B8560D408356CAC2FC148<wbr>E53BB34799C@SUN-DAG3.<wbr>synchrotron-soleil.fr</a>><br>
<br>
Content-Type: text/plain; charset="us-ascii"<br>
<br>
Hello, I wrote this code<br>
<br>
data DataFrameH5 a<br>
    = DataFrameH5<br>
      (Nxs a) -- Nexus file<br>
      (DataSource H5) -- gamma<br>
      (DataSource H5) -- delta<br>
      (DataSource H5) -- wavelength<br>
      PoniGenerator -- ponie generator<br>
<br>
class Frame t a where<br>
  len :: t -> IO (Maybe Int)<br>
  row :: t -> Int -> MaybeT IO (DifTomoFrame a DIM1)<br>
<br>
instance Frame (DataFrameH5 DataFrameH5Path) DataFrameH5Path where<br>
  len (DataFrameH5 _ _ (DataSourceH5 _ d) _ _) = lenH5Dataspace d<br>
<br>
  row d@(DataFrameH5 nxs' g d' w ponigen) idx = do<br>
    n <- lift $ len d<br>
    let eof = fromJust n - 1 == idx<br>
    let mu = 0.0<br>
    let komega = 0.0<br>
    let kappa = 0.0<br>
    let kphi = 0.0<br>
    gamma <- g `atIndex'` (ix1 0)<br>
    delta <- d' `atIndex'` (ix1 idx)<br>
    wavelength <- w `atIndex'` (ix1 0)<br>
    let source = Source (head wavelength *~ nano meter)<br>
    let positions = concat [mu, komega, kappa, kphi, gamma, delta]<br>
    -- print positions<br>
    let geometry =  Geometry K6c source positions Nothing<br>
    let detector = ZeroD<br>
    m <- lift $ geometryDetectorRotationGet geometry detector<br>
    poniext <- lift $ ponigen (MyMatrix HklB m) idx<br>
    return $ DifTomoFrame { difTomoFrameNxs = nxs'<br>
                          , difTomoFrameIdx = idx<br>
                          , difTomoFrameEOF = eof<br>
                          , difTomoFrameGeometry = geometry<br>
                          , difTomoFramePoniExt = poniext<br>
                          }<br>
<br>
has you can see my t type contains also the a reference to the a one<br>
So when I create the instance, I need to write two times the DataFrameH5Path<br>
<br>
I would like to know how to write the same class with only<br>
<br>
class Frame t where<br>
  len :: t -> IO (Maybe Int)<br>
  row :: t -> Int -> MaybeT IO (DifTomoFrame <extract type a from type t> DIM1)<br>
<br>
thanks for your help<br>
<br>
Frederic<br>
<br>
<br>
------------------------------<br>
<br>
Message: 4<br>
Date: Wed, 22 Feb 2017 10:59:38 -0500<br>
From: David McBride <<a href="mailto:toad3k@gmail.com">toad3k@gmail.com</a>><br>
To: The Haskell-Beginners Mailing List - Discussion of primarily<br>
        beginner-level topics related to Haskell <<a href="mailto:beginners@haskell.org">beginners@haskell.org</a>><br>
Subject: Re: [Haskell-beginners] How to link two Types<br>
Message-ID:<br>
        <<a href="mailto:CAN%2BTr42Bu7nENuGLkBuU9q4Jrdzd-3qoA%2BG-b%2BAWh-N-MQzDsw@mail.gmail.com">CAN+<wbr>Tr42Bu7nENuGLkBuU9q4Jrdzd-<wbr>3qoA+G-b+AWh-N-MQzDsw@mail.<wbr>gmail.com</a>><br>
Content-Type: text/plain; charset=UTF-8<br>
<br>
Maybe TypeFamilies would work for you?  I can only give you a<br>
barebones outline of what it might look like.<br>
<br>
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-}<br>
import Control.Monad.Trans.Maybe<br>
<br>
data DataFrameH5 a = DataFrameH5<br>
data DataFrameH5Path = DataFrameH5Path<br>
<br>
class Frame t where<br>
  type Key t<br>
  len :: t -> IO (Maybe Int)<br>
  row :: t -> Int -> MaybeT IO (Key t)<br>
<br>
instance Frame (DataFrameH5 a) where<br>
  type Key (DataFrameH5 a) = a<br>
  len DataFrameH5 = return . Just $ undefined<br>
  row DataFrameH5 idx = MaybeT $ do<br>
    return undefined<br>
<br>
On Wed, Feb 22, 2017 at 10:27 AM, PICCA Frederic-Emmanuel<br>
<<a href="mailto:frederic-emmanuel.picca@synchrotron-soleil.fr">frederic-emmanuel.picca@<wbr>synchrotron-soleil.fr</a>> wrote:<br>
> Hello, I wrote this code<br>
><br>
> data DataFrameH5 a<br>
>     = DataFrameH5<br>
>       (Nxs a) -- Nexus file<br>
>       (DataSource H5) -- gamma<br>
>       (DataSource H5) -- delta<br>
>       (DataSource H5) -- wavelength<br>
>       PoniGenerator -- ponie generator<br>
><br>
> class Frame t a where<br>
>   len :: t -> IO (Maybe Int)<br>
>   row :: t -> Int -> MaybeT IO (DifTomoFrame a DIM1)<br>
><br>
> instance Frame (DataFrameH5 DataFrameH5Path) DataFrameH5Path where<br>
>   len (DataFrameH5 _ _ (DataSourceH5 _ d) _ _) = lenH5Dataspace d<br>
><br>
>   row d@(DataFrameH5 nxs' g d' w ponigen) idx = do<br>
>     n <- lift $ len d<br>
>     let eof = fromJust n - 1 == idx<br>
>     let mu = 0.0<br>
>     let komega = 0.0<br>
>     let kappa = 0.0<br>
>     let kphi = 0.0<br>
>     gamma <- g `atIndex'` (ix1 0)<br>
>     delta <- d' `atIndex'` (ix1 idx)<br>
>     wavelength <- w `atIndex'` (ix1 0)<br>
>     let source = Source (head wavelength *~ nano meter)<br>
>     let positions = concat [mu, komega, kappa, kphi, gamma, delta]<br>
>     -- print positions<br>
>     let geometry =  Geometry K6c source positions Nothing<br>
>     let detector = ZeroD<br>
>     m <- lift $ geometryDetectorRotationGet geometry detector<br>
>     poniext <- lift $ ponigen (MyMatrix HklB m) idx<br>
>     return $ DifTomoFrame { difTomoFrameNxs = nxs'<br>
>                           , difTomoFrameIdx = idx<br>
>                           , difTomoFrameEOF = eof<br>
>                           , difTomoFrameGeometry = geometry<br>
>                           , difTomoFramePoniExt = poniext<br>
>                           }<br>
><br>
> has you can see my t type contains also the a reference to the a one<br>
> So when I create the instance, I need to write two times the DataFrameH5Path<br>
><br>
> I would like to know how to write the same class with only<br>
><br>
> class Frame t where<br>
>   len :: t -> IO (Maybe Int)<br>
>   row :: t -> Int -> MaybeT IO (DifTomoFrame <extract type a from type t> DIM1)<br>
><br>
> thanks for your help<br>
><br>
> Frederic<br>
> ______________________________<wbr>_________________<br>
> Beginners mailing list<br>
> <a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/beginners</a><br>
<br>
<br>
------------------------------<br>
<br>
Message: 5<br>
Date: Wed, 22 Feb 2017 16:19:41 +0000<br>
From: PICCA Frederic-Emmanuel<br>
        <<a href="mailto:frederic-emmanuel.picca@synchrotron-soleil.fr">frederic-emmanuel.picca@<wbr>synchrotron-soleil.fr</a>><br>
To: "The Haskell-Beginners Mailing List - Discussion of primarily<br>
        beginner-level topics related to Haskell" <<a href="mailto:beginners@haskell.org">beginners@haskell.org</a>><br>
Subject: Re: [Haskell-beginners] How to link two Types<br>
Message-ID:<br>
        <<a href="mailto:A2A20EC3B8560D408356CAC2FC148E53BB3489ED@SUN-DAG3.synchrotron-soleil.fr">A2A20EC3B8560D408356CAC2FC148<wbr>E53BB3489ED@SUN-DAG3.<wbr>synchrotron-soleil.fr</a>><br>
<br>
Content-Type: text/plain; charset="us-ascii"<br>
<br>
Hello thanks, I will investigate, but I like this solution.<br>
I can ad more type to a type family right ?<br>
<br>
<br>
Is it possible with this type family to be able to link in the other way ?<br>
<br>
a -> t<br>
<br>
Cheers<br>
<br>
Fred<br>
<br>
------------------------------<br>
<br>
Message: 6<br>
Date: Wed, 22 Feb 2017 11:29:16 -0500<br>
From: David McBride <<a href="mailto:toad3k@gmail.com">toad3k@gmail.com</a>><br>
To: The Haskell-Beginners Mailing List - Discussion of primarily<br>
        beginner-level topics related to Haskell <<a href="mailto:beginners@haskell.org">beginners@haskell.org</a>><br>
Subject: Re: [Haskell-beginners] How to link two Types<br>
Message-ID:<br>
        <CAN+Tr43H_Z9ckhW+f6GqeBXf_O=<wbr>LX=<a href="mailto:AvQYgzCh7gx7Qyxeb4dg@mail.gmail.com">AvQYgzCh7gx7Qyxeb4dg@mail.<wbr>gmail.com</a>><br>
Content-Type: text/plain; charset=UTF-8<br>
<br>
It is hard to tell from your code what you intend, but it works<br>
however you want it to, so long as it type checks.<br>
<br>
class Frame a where<br>
  type Whatever a<br>
  len :: Whatever a -> IO (Maybe Int)<br>
  row :: Whatever a -> MaybeT IO (DifTomoFrame a DIM1)<br>
<br>
instance Frame DataFrameH5Path  where<br>
  type Whatever DataFrameH5Path = DataFrameH5<br>
  len = undefined -- :: DataFrameH5 -> IO (Maybe Int)<br>
  row = undefined -- :: DataFrameH5 -> Int -> MaybeT (DifTomoFrame<br>
DataFrameH5Path DIM1)<br>
<br>
<br>
<br>
On Wed, Feb 22, 2017 at 11:19 AM, PICCA Frederic-Emmanuel<br>
<<a href="mailto:frederic-emmanuel.picca@synchrotron-soleil.fr">frederic-emmanuel.picca@<wbr>synchrotron-soleil.fr</a>> wrote:<br>
> Hello thanks, I will investigate, but I like this solution.<br>
> I can ad more type to a type family right ?<br>
><br>
><br>
> Is it possible with this type family to be able to link in the other way ?<br>
><br>
> a -> t<br>
><br>
> Cheers<br>
><br>
> Fred<br>
> ______________________________<wbr>_________________<br>
> Beginners mailing list<br>
> <a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/beginners</a><br>
<br>
<br>
------------------------------<br>
<br>
Subject: Digest Footer<br>
<br>
______________________________<wbr>_________________<br>
Beginners mailing list<br>
<a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/beginners</a><br>
<br>
<br>
------------------------------<br>
<br>
End of Beginners Digest, Vol 104, Issue 16<br>
******************************<wbr>************<br>
</blockquote></div><br></div>